correction in returnbox
[unres4.git] / source / unres / MD.f90
index 1af6b18..32e48f8 100644 (file)
       real(kind=8),dimension(:,:),allocatable :: ginvfric !(2*nres,2*nres) !maxres2=2*maxres
 !-----------------------------------------------------------------------------
 !      common /przechowalnia/ subroutine: setup_fricmat
-!el      real(kind=8),dimension(:,:),allocatable :: fcopy !(2*nres,2*nres)
+      real(kind=8),dimension(:,:),allocatable :: fcopy !(2*nres,2*nres)
 !-----------------------------------------------------------------------------
 !
 !
       real(kind=8) :: tt0,scalfac
       integer :: nres2
       nres2=2*nres
+      print *, "ENTER MD"
 !
 #ifdef MPI
+      print *,"MY tmpdir",tmpdir,ilen(tmpdir)
       if (ilen(tmpdir).gt.0) &
         call copy_to_tmp(pref_orig(:ilen(pref_orig))//"_" &
               //liczba(:ilen(liczba))//'.rst')
 #else
       tt0 = tcpu()
 #endif
+       print *,"just befor setup matix",nres
 ! Determine the inverse of the inertia matrix.
       call setup_MD_matrices
 ! Initialize MD
+      print *,"AFTER SETUP MATRICES"
       call init_MD
+      print *,"AFTER INIT MD"
+
 #ifdef MPI
       t_MDsetup = MPI_Wtime()-tt0
 #else
         stop
 #endif
       else if (lang.eq.1 .or. lang.eq.4) then
+        print *,"before setup_fricmat"
         call setup_fricmat
+        print *,"after setup_fricmat"
       endif
 #ifdef MPI
       t_langsetup=MPI_Wtime()-tt0
 #endif
         endif
         if (ntwe.ne.0) then
-         if (mod(itime,ntwe).eq.0) call statout(itime)
+         if (mod(itime,ntwe).eq.0) then
+            call statout(itime)
+            call returnbox
+         endif
 #ifdef VOUT
         do j=1,3
           v_work(j)=d_t(j,0)
 #endif
         endif
         if (mod(itime,ntwx).eq.0) then
+          call returnbox
           write (tytul,'("time",f8.2)') totT
           if(mdpdb) then
              call hairpin(.true.,nharp,iharp)
       logical :: lprn = .false.
       real(kind=8) :: dtdi !el ,gamvec(2*nres)
 !el      real(kind=8),dimension(2*nres,2*nres) :: ginvfric,fcopy
-      real(kind=8),dimension(2*nres,2*nres) :: fcopy
+!      real(kind=8),allocatable,dimension(:,:) :: fcopy
 !el      real(kind=8),dimension(2*nres*(2*nres+1)/2) :: Ghalf   !(mmaxres2) (mmaxres2=(maxres2*(maxres2+1)/2))
 !el      common /syfek/ gamvec
       real(kind=8) :: work(8*2*nres)
       integer :: iwork(2*nres)
 !el      common /przechowalnia/ ginvfric,Ghalf,fcopy
       integer :: ii,iti,k,l,nzero,nres2,nres6,ierr,mnum
+      nres2=2*nres
+      nres6=6*nres
 #ifdef MPI
+      if(.not.allocated(fricmat)) allocate(fricmat(nres2,nres2))
+       if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2)) !maxres2=2*maxres
       if (fg_rank.ne.king) goto 10
 #endif
-      nres2=2*nres
-      nres6=6*nres
+!      nres2=2*nres
+!      nres6=6*nres
 
       if(.not.allocated(gamvec)) allocate(gamvec(nres2)) !(MAXRES2)
       if(.not.allocated(ginvfric)) allocate(ginvfric(nres2,nres2)) !maxres2=2*maxres
-!el      if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2)) !maxres2=2*maxres
+       if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2)) !maxres2=2*maxres
 !el      allocate(fcopy(nres2,nres2)) !maxres2=2*maxres
       if(.not.allocated(Ghalf)) allocate(Ghalf(nres2*(nres2+1)/2)) !maxres2=2*maxres
 
-!el      if(.not.allocated(fricmat)) allocate(fricmat(nres2,nres2))
+      if(.not.allocated(fricmat)) allocate(fricmat(nres2,nres2))
 !  Zeroing out fricmat
       do i=1,dimen
         do j=1,dimen
       allocate(flag_stoch(0:maxflag_stoch)) !(0:maxflag_stoch)
 #endif
 
-!el      if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2))
+      if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2))
 !----------------------
 ! commom.hairpin in CSA module
 !----------------------