update
[unres.git] / source / unres / src_MD-M / unres.F
index 0039fcc..da6249d 100644 (file)
@@ -56,8 +56,9 @@ c      call memmon_print_usage()
       if (me.eq.king) call cinfo
 C Read force field parameters and job setup data
       call readrtns
-      call flush(iout)
 C
+      write (iout,*) "After readrtns"
+      call cartprint
       if (me.eq.king .or. .not. out1file) then
        write (iout,'(2a/)') 
      & text_mode_calc(modecalc)(:ilen(text_mode_calc(modecalc))),
@@ -83,6 +84,8 @@ C Fine-grain slaves just do energy and gradient components.
       else
 #endif
       if (modecalc.eq.0) then
+        write (iout,*) "Calling exec_eeval_or_minim"
+        call cartprint
         call exec_eeval_or_minim
       else if (modecalc.eq.1) then
         call exec_regularize
@@ -103,7 +106,12 @@ C Fine-grain slaves just do energy and gradient components.
       else if (modecalc.eq.12) then
         call exec_MD
       else if (modecalc.eq.14) then
+#ifdef MPI
         call exec_MREMD
+#else
+        write (iout,*) "Need a parallel version to run MREMD."
+        stop
+#endif
       else
         write (iout,'(a)') 'This calculation type is not supported',
      &   ModeCalc
@@ -132,13 +140,20 @@ c--------------------------------------------------------------------------
       include 'COMMON.SETUP'
       include 'COMMON.CONTROL'
       include 'COMMON.IOUNITS'
-      if (me.eq.king .or. .not. out1file)
-     &   write (iout,*) "Calling chainbuild"
+c      if (me.eq.king .or. .not. out1file) then
+c        write (iout,*) "Calling chainbuild"
+c        call flush(iout)
+c      endif
       call chainbuild
+c      if (me.eq.king .or. .not. out1file) then
+c        write (iout,*) "Calling MD"
+c        call flush(iout)
+c      endif
       call MD
       return
       end
 c---------------------------------------------------------------------------
+#ifdef MPI
       subroutine exec_MREMD
       include 'DIMENSIONS'
 #ifdef MPI
@@ -163,6 +178,7 @@ c---------------------------------------------------------------------------
       endif
       return
       end
+#endif
 c---------------------------------------------------------------------------
       subroutine exec_eeval_or_minim
       implicit real*8 (a-h,o-z)
@@ -189,9 +205,20 @@ c---------------------------------------------------------------------------
       double precision energy(0:n_ene)
       double precision energy_long(0:n_ene),energy_short(0:n_ene)
       double precision varia(maxvar)
-      if (indpdb.eq.0) call chainbuild
+      if (indpdb.eq.0)     call chainbuild
+      if (indpdb.ne.0) then
+      dc(1,0)=c(1,1)
+      dc(2,0)=c(2,1)
+      dc(3,0)=c(3,1)
+      endif
+#ifdef MPI
       time00=MPI_Wtime()
+#else
+      time00=tcpu()
+#endif
+      write (iout,*) "Energy evaluation/minimization"
       call chainbuild_cart
+c      print *,'dc',dc(1,0),dc(2,0),dc(3,0)
       if (split_ene) then
        print *,"Processor",myrank," after chainbuild"
        icall=1
@@ -203,20 +230,30 @@ c---------------------------------------------------------------------------
        call enerprint(energy_short(0))
        do i=0,n_ene
          energy(i)=energy_long(i)+energy_short(i)
-         write (iout,*) i,energy_long(i),energy_short(i),energy(i)
+c         write (iout,*) i,energy_long(i),energy_short(i),energy(i)
        enddo
        write (iout,*) "Printing long+short range energy"
        call enerprint(energy(0))
       endif
+      write(iout,*)"before etotal"
+      call flush(iout)
       call etotal(energy(0))
+      write(iout,*)"after etotal"
+      call flush(iout)
+#ifdef MPI
       time_ene=MPI_Wtime()-time00
+#else 
+      time_ene=tcpu()-time00
+#endif
       write (iout,*) "Time for energy evaluation",time_ene
       print *,"after etotal"
       etota = energy(0)
       etot =etota
       call enerprint(energy(0))
       call hairpin(.true.,nharp,iharp)
+        print *,'after hairpin'
       call secondary2(.true.)
+        print *,'after secondary'
       if (minim) then
 crc overlap test
         if (overlapsc) then 
@@ -232,7 +269,11 @@ crc overlap test
 
         if (dccart) then
           print *, 'Calling MINIM_DC'
+#ifdef MPI
           time1=MPI_WTIME()
+#else
+          time1=tcpu()
+#endif
           call minim_dc(etot,iretcode,nfun)
         else
           if (indpdb.ne.0) then 
@@ -241,15 +282,25 @@ crc overlap test
           endif
           call geom_to_var(nvar,varia)
           print *,'Calling MINIMIZE.'
+#ifdef MPI
           time1=MPI_WTIME()
+#else
+          time1=tcpu()
+#endif
           call minimize(etot,varia,iretcode,nfun)
         endif
         print *,'SUMSL return code is',iretcode,' eval ',nfun
+#ifdef MPI
         evals=nfun/(MPI_WTIME()-time1)
+#else
+        evals=nfun/(tcpu()-time1)
+#endif
         print *,'# eval/s',evals
         print *,'refstr=',refstr
-        call hairpin(.true.,nharp,iharp)
+        call hairpin(.false.,nharp,iharp)
+        print *,'after hairpin'
         call secondary2(.true.)
+        print *,'after secondary'
         call etotal(energy(0))
         etot = energy(0)
         call enerprint(energy(0))
@@ -611,7 +662,7 @@ c Broadcast the order to compute internal coordinates to the slaves.
       endif
       do while (.not. eof)
           if (read_cart) then
-            read (intin,'(e15.10,e15.5)',end=1100,err=1100) time,ene
+            read (intin,'(e15.10,e15.5)',end=11,err=11) time,ene
             call read_x(intin,*11)
 #ifdef MPI
 c Broadcast the order to compute internal coordinates to the slaves.
@@ -620,7 +671,7 @@ c Broadcast the order to compute internal coordinates to the slaves.
 #endif
             call int_from_cart1(.false.)
           else
-            read (intin,'(i5)',end=1100,err=1100) iconf
+            read (intin,'(i5)',end=11,err=11) iconf
             call read_angles(intin,*11)
             call geom_to_var(nvar,varia)
             call chainbuild
@@ -671,6 +722,7 @@ c---------------------------------------------------------------------------
       include 'COMMON.SBRIDGE'
       common /srutu/ icall
       double precision energy(0:max_ene)
+c      print *,"A TU?"
 c      do i=2,nres
 c        vbld(i)=vbld(i)+ran_number(-0.1d0,0.1d0)
 c        if (itype(i).ne.10) 
@@ -692,21 +744,53 @@ c      enddo
 c      do j=1,3
 c        dc(j,0)=ran_number(-0.2d0,0.2d0)
 c      enddo
+#ifdef UMB
       usampl=.true.
+      scale_umb=.false.
+      adaptive=.true.
       totT=1.d0
       eq_time=0.0d0
       call read_fragments
+      iset=1
+      nperm=1
+      print *, "AFTER read fragments"
+           write (iout,*) "iset",iset
+           if (loc_qlike) then
+           write(iout,*) "fragment, weights, q0:"
+           do i=1,nfrag_back
+            write(iout,'(2i5,3(f8.1,f8.2))') ifrag_back(1,i,iset),
+     &         ifrag_back(2,i,iset),
+     &         wfrag_back(1,i,iset),qin_back(1,i,iset),
+     &         wfrag_back(2,i,iset),qin_back(2,i,iset),
+     &         wfrag_back(3,i,iset),qin_back(3,i,iset)
+           enddo
+           else
+           write(iout,*) "fragment, weights:"
+           do i=1,nfrag_back
+            write(iout,'(2i5,3f8.1)') ifrag_back(1,i,iset),
+     &         ifrag_back(2,i,iset),wfrag_back(1,i,iset),
+     &         wfrag_back(2,i,iset),wfrag_back(3,i,iset)
+           enddo
+           endif
+      call read_REMDpar
+      call PMFread
+      call rescale_weights(t_bath)
       call chainbuild_cart
+      print *,"chainbuild_cart"
       call cartprint
+      print *,"After cartprint"
       call intout
       icall=1
+      print *,"before ETOT"
       call etotal(energy(0))
       etot = energy(0)
       call enerprint(energy(0))
       write (iout,*) "Uconst",Uconst," Uconst_back",uconst_back
       print *,'icheckgrad=',icheckgrad
+#endif
       goto (10,20,30) icheckgrad
   10  call check_ecartint
+      call check_ecartint
       return
   20  call check_cartgrad
       return