working microcanonical
[unres4.git] / source / unres / unres.f90
index deb5713..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 
           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
 !-----------------------------------------------------------------------------