changes for ees working (no split mode)
[unres4.git] / source / unres / minim.f90
index 66726f4..d556363 100644 (file)
@@ -3,11 +3,14 @@
       use io_units
       use names
       use math
+!      use MPI_data
       use geometry_data
       use energy_data
       use control_data
       use minim_data
       use geometry
+!      use csa_data
+!      use energy
       implicit none
 !-----------------------------------------------------------------------------
 !
 !
 !        ***  we did not.  try a longer step unless this was a newton
 !        ***  step.
-!
+
          v(radfac) = v(rdfcmx)
          gts = v(gtstep)
          if (v(fdif) .lt. (half/v(radfac) - one) * gts) &
 !  ***  carry out humsl (unconstrained minimization) iterations, using
 !  ***  hessian matrix provided by the caller.
 !
+!el      use control
       use control, only:stopx
 
 !  ***  parameter declarations  ***
 !     else
 !       not_done=.false.
 !     endif
+      write(iout,*) 'Warning calling chainbuild'
       call chainbuild
 
 !el---------------------
       endif
 #endif
       call var_to_geom_restr(n,x)
+      write(iout,*) 'Warning calling chainbuild'
       call chainbuild 
 !
 ! Evaluate the derivatives of virtual bond lengths and SC vectors in variables.
       icg=mod(nf,2)+1
       call var_to_geom_restr(n,x)
       call zerograd
+      write(iout,*) 'Warning calling chainbuild'
       call chainbuild
 !d    write (iout,*) 'ETOTAL called from FUNC'
       call etotal(energia)
       integer :: n,i,ij,ig,igall
       real(kind=8),dimension(6*nres) :: xx,x   !(maxvar) (maxvar=6*maxres)
 
+!el      allocate(varall(nvar)) allocated in alioc_ener_arrays
+
       do i=1,nvar
         varall(i)=x(i)
       enddo
 
       use MPI_data
       use energy, only: cartgrad,zerograd,etotal
+!      use MD_data
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 #ifdef MPI
           cur_omeg(i)=omeg(i)
         endif
       enddo
-
+      write(iout,*) 'Warning calling chainbuild'
       call chainbuild
       call egb1(evdw)
       call esc(escloc)
       wang=orig_w(11)
       wtor=orig_w(13)
       wtor_d=orig_w(14)
-
+      write(iout,*) 'Warning calling chainbuild'
       call chainbuild
       call etotal(energy_)
       etot=energy_(0)
       enddo
 !elmask_r=.false.
       IF (mask_r) THEN
-write(iout,*) "mask_r",mask_r,"petla if minimize_sc1"
        call x2xx(x,xx,nvar_restr)
        call sumsl(nvar_restr,d,xx,func_restr1,grad_restr1,&
                           iv,liv,lv,v,idum,rdum,fdum)      
        call xx2x(x,xx)
       ELSE
-write(iout,*) "mask_r",mask_r,"petla else minimize_sc1"
        call sumsl(nvar,d,x,func,gradient,iv,liv,lv,v,idum,rdum,fdum)      
       ENDIF
 !el---------------------
@@ -4717,6 +4725,7 @@ write(iout,*) "mask_r",mask_r,"petla else minimize_sc1"
 
       call var_to_geom_restr(n,x)
       call zerograd
+      write(iout,*) 'Warning calling chainbuild'
       call chainbuild
 !d    write (iout,*) 'ETOTAL called from FUNC'
       call egb1(evdw)
@@ -4763,6 +4772,7 @@ write(iout,*) "mask_r",mask_r,"petla else minimize_sc1"
       if (nf.eq.0) return
       goto 40
    30 call var_to_geom_restr(n,x)
+      write(iout,*) 'Warning calling chainbuild'
       call chainbuild 
 !
 ! Evaluate the derivatives of virtual bond lengths and SC vectors in variables.
@@ -4884,6 +4894,7 @@ write(iout,*) "mask_r",mask_r,"petla else minimize_sc1"
 !
       use calc_data
       use energy, only: sc_grad
+!      use control, only:stopx
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
 !      include 'COMMON.GEO'
@@ -5027,6 +5038,7 @@ write(iout,*) "mask_r",mask_r,"petla else minimize_sc1"
 !  ***  minimize general unconstrained objective function using   ***
 !  ***  analytic gradient and hessian approx. from secant update  ***
 !
+!      use control
       integer :: n, liv, lv
       integer :: iv(liv), uiparm(1)
       real(kind=8) :: d(n), x(n), v(lv), urparm(1)