working side-chain phosphate
[unres4.git] / source / unres / unres.f90
index 4216238..e84e1d0 100644 (file)
 #ifdef MPI
       include "mpif.h"
 #endif
+      print *,'Start MD'
       call alloc_MD_arrays
-      if (me.eq.king .or. .not. out1file) &
-         write (iout,*) "Calling chainbuild"
-      call chainbuild
+!      if (me.eq.king .or. .not. out1file) &
+!         write (iout,*) "Calling chainbuild"
+!      call chainbuild
       call MD
       return
       end subroutine exec_MD
       call alloc_MD_arrays
       call alloc_MREMD_arrays
 
-      if (me.eq.king .or. .not. out1file) &
-         write (iout,*) "Calling chainbuild"
-      call chainbuild
+!     if (me.eq.king .or. .not. out1file) &
+!         write (iout,*) "Calling chainbuild"
+!      call chainbuild
       if (me.eq.king .or. .not. out1file) &
          write (iout,*) "Calling REMD"
       if (remd_mlist) then 
 
       integer :: j,k
       call alloc_compare_arrays
-      if (indpdb.eq.0) call chainbuild
+      if (indpdb.eq.0) then 
+      call chainbuild
+      write(iout,*) 'Warning: Calling chainbuild'
+      endif
 #ifdef MPI
       time00=MPI_Wtime()
 #endif
         else 
           if (indpdb.ne.0) then 
             call bond_regular
+            write(iout,*) 'Warning: Calling chainbuild'
             call chainbuild
           endif
           call geom_to_var(nvar,varia)
           write (iout,'(a,i20)') '# of energy evaluations:',nfun+1
           write (iout,'(a,f16.3)')'# of energy evaluations/sec:',evals
       else
-        print *,'refstr=',refstr
+        print *,'refstr=',refstr,frac,frac_nn,co
         if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
+        print *,"after rms_nac_ncc"
         call briefout(0,etot)
       endif
       if (outpdb) call pdbout(etot,titel(:32),ipdb)
       if (outmol2) call mol2out(etot,titel(:32))
-!elwrite(iout,*) "after exec_eeval_or_minim"
+      write(iout,*) "after exec_eeval_or_minim"
       return
       end subroutine exec_eeval_or_minim
 !-----------------------------------------------------------------------------
             read (intin,'(i5)',end=1100,err=1100) iconf
             call read_angles(intin,*11)
             call geom_to_var(nvar,varia)
+            write(iout,*) 'Warning: Calling chainbuild'
             call chainbuild
           endif
           write (iout,'(a,i7)') 'Conformation #',iconf
             read (intin,'(i5)',end=11,err=11) iconf
             call read_angles(intin,*11)
             call geom_to_var(nvar,varia)
+            write(iout,*) 'Warning: Calling chainbuild'
             call chainbuild
           endif
           write (iout,'(a,i7)') 'Conformation #',iconf
 !         print *,'result received from worker ',man,' sending now'
 
           call var_to_geom(nvar,varia)
+          write(iout,*) 'Warning: Calling chainbuild'
           call chainbuild
           call etotal(energy_)
           iconf=ind(2)
             read (intin,'(i5)',end=1101,err=1101) iconf
             call read_angles(intin,*11)
             call geom_to_var(nvar,varia)
+            write(iout,*) 'Warning: Calling chainbuild'
             call chainbuild
           endif
           n=n+1
                      CG_COMM,muster,ierr)
 
         call var_to_geom(nvar,varia)
+        write(iout,*) 'Warning: Calling chainbuild'
         call chainbuild
         call etotal(energy_)
         iconf=ind(2)
             read (intin,'(i5)',end=11,err=11) iconf
             call read_angles(intin,*11)
             call geom_to_var(nvar,varia)
+            write(iout,*) 'Warning: Calling chainbuild'
             call chainbuild
           endif
         write (iout,'(a,i7)') 'Conformation #',iconf
 !        if (itype(i).ne.10) 
 !     &      vbld(i+nres)=vbld(i+nres)+ran_number(-0.001d0,0.001d0)
 !      enddo
-      if (indpdb.eq.0) call chainbuild
+      if (indpdb.eq.0) then 
+        write(iout,*) 'Warning: Calling chainbuild'
+        call chainbuild
+      endif
 !      do i=0,nres
 !        do j=1,3
 !          dc(j,i)=dc(j,i)+ran_number(-0.2d0,0.2d0)
       logical :: debug
 
       call alloc_compare_arrays
+      write(iout,*) 'Warning: Calling chainbuild'
       call chainbuild
       call etotal(energy_)
       call enerprint(energy_)