unres_package_Oct_2016 from emilial
[unres4.git] / source / unres / MREMD.f90
index f33432f..92a1178 100644 (file)
       integer(kind=2),dimension(:),allocatable :: ifirst !(maxprocs)
       integer(kind=2),dimension(:,:),allocatable :: nupa,&
        ndowna !(0:maxprocs/4,0:maxprocs)
-      real(kind=8),dimension(:,:),allocatable :: t_restart1 !(5,maxprocs)
+      real(kind=4),dimension(:,:),allocatable :: t_restart1 !(5,maxprocs)
       integer,dimension(:),allocatable :: iset_restart1 !(maxprocs)
 !      common /traj1cache/
-      real(kind=8),dimension(:),allocatable :: totT_cache,EK_cache,&
+      real(kind=4),dimension(:),allocatable :: totT_cache,EK_cache,&
        potE_cache,t_bath_cache,Uconst_cache !(max_cache_traj)
-      real(kind=8),dimension(:,:),allocatable :: qfrag_cache !(50,max_cache_traj)
-      real(kind=8),dimension(:,:),allocatable :: qpair_cache !(100,max_cache_traj)
-      real(kind=8),dimension(:,:),allocatable :: ugamma_cache,&
+      real(kind=4),dimension(:,:),allocatable :: qfrag_cache !(50,max_cache_traj)
+      real(kind=4),dimension(:,:),allocatable :: qpair_cache !(100,max_cache_traj)
+      real(kind=4),dimension(:,:),allocatable :: ugamma_cache,&
        utheta_cache,uscdiff_cache !(maxfrag_back,max_cache_traj)
-      real(kind=8),dimension(:,:,:),allocatable :: c_cache !(3,maxres2+2,max_cache_traj)
+      real(kind=4),dimension(:,:,:),allocatable :: c_cache !(3,maxres2+2,max_cache_traj)
       integer :: ntwx_cache,ii_write   !,max_cache_traj_use
       integer,dimension(:),allocatable :: iset_cache !(max_cache_traj)
 !-----------------------------------------------------------------------------
       nres2=2*nres
       time001=0.0d0
 
-write(iout,*) "jestesmy na poczatku MREMD"
       ntwx_cache=0
       time00=MPI_WTIME()
       time01=time00
@@ -121,7 +120,6 @@ write(iout,*) "jestesmy na poczatku MREMD"
        write (iout,*) "NREP=",nrep
       endif
 
-write(iout,*) "jestesmy na poczatku MREMD"
       synflag=.false.
       if (ilen(tmpdir).gt.0 .and. (me.eq.king)) then
         call copy_to_tmp(pref_orig(:ilen(pref_orig))//"_mremd.rst")
@@ -831,6 +829,7 @@ write(iout,*) "jestesmy na poczatku MREMD"
                remd_t_bath(i)=remd_ene(n_ene+1,i)
                iremd_iset(i)=remd_ene(n_ene+2,i)
             enddo
+#ifdef DEBUG
             if(lmuca) then
 !o             write(iout,*) 'REMD exchange temp,ene,elow,ehigh'
              do i=1,nodes
@@ -844,6 +843,7 @@ write(iout,*) "jestesmy na poczatku MREMD"
                 write(iout,'(6f12.5)') (remd_ene(j,i),j=1,n_ene)
               enddo
             endif
+#endif
 !-------------------------------------           
            IF(.not.usampl) THEN
             write (iout,*) "Enter exchnge, remd_m",remd_m(1),&
@@ -857,7 +857,9 @@ write(iout,*) "jestesmy na poczatku MREMD"
 
              do ii=1,nodes-1
 
+#ifdef DEBUG
               write (iout,*) "i",i," nupa(0,i)",int(nupa(0,i))
+#endif
              if(i.gt.0.and.nupa(0,i).gt.0) then
               iex=i
 !              if (i.eq.1 .and. int(nupa(0,i)).eq.1) then
@@ -1216,6 +1218,12 @@ write(iout,*) "jestesmy na poczatku MREMD"
          time06=MPI_WTIME()
 !d         write (iout,*) "Before scatter"
 !d         call flush(iout)
+#ifdef DEBUG
+         if (me.eq.king) then
+           write (iout,*) "t_bath before scatter",remd_t_bath
+           call flush(iout)
+         endif
+#endif
          call mpi_scatter(remd_t_bath,1,mpi_double_precision,&
                  t_bath,1,mpi_double_precision,king,&
                  CG_COMM,ierr) 
@@ -1251,7 +1259,15 @@ write(iout,*) "jestesmy na poczatku MREMD"
 !de         write(iout,*) 'REMD after',me,t_bath
            time08=MPI_WTIME()
            if (me.eq.king .or. .not. out1file) then
-            write(iout,*) 'REMD exchange time=',time08-time00
+            write(iout,*) 'REMD exchange time 8-0=',time08-time00
+            write(iout,*) 'REMD exchange time 8-7=',time08-time07
+            write(iout,*) 'REMD exchange time 7-6=',time07-time06
+            write(iout,*) 'REMD exchange time 6-5=',time06-time05
+            write(iout,*) 'REMD exchange time 5-4=',time05-time04
+            write(iout,*) 'REMD exchange time 4-3=',time04-time03
+            write(iout,*) 'REMD exchange time 3-2=',time03-time02
+            write(iout,*) 'REMD exchange time 2-1=',time02-time01
+            write(iout,*) 'REMD exchange time 1-0=',time01-time00
             call flush(iout)
            endif
         endif
@@ -1291,9 +1307,9 @@ write(iout,*) "jestesmy na poczatku MREMD"
        '  End of MD calculation  '
       endif
 !el  common /przechowalnia/
-      deallocate(d_restart1)
-      deallocate(d_restart2)
-      deallocate(p_c)
+!      deallocate(d_restart1)
+!      deallocate(d_restart2)
+!      deallocate(p_c)
 !el--------------
       return
       end subroutine MREMD
@@ -1517,13 +1533,22 @@ write(iout,*) "jestesmy na poczatku MREMD"
       if(me.eq.king) call xdrfopen(ixdrf,cartname, "a", iret)
 #endif
       do ii=1,ii_write
+!       write (iout,*) "before gather write1traj: from node",ii
+!       call flush(iout)
+!       write (iout,*) totT_cache(ii),EK_cache(ii),potE_cache(ii),t_bath_cache(ii),Uconst_cache(ii)
+!       call flush(iout)
        t5_restart1(1)=totT_cache(ii)
        t5_restart1(2)=EK_cache(ii)
        t5_restart1(3)=potE_cache(ii)
        t5_restart1(4)=t_bath_cache(ii)
        t5_restart1(5)=Uconst_cache(ii)
+!       write (iout,*) "before gather write1traj: from node",ii,t5_restart1(1),t5_restart1(3),t5_restart1(5),t5_restart1(4)
+       call flush(iout)
        call mpi_gather(t5_restart1,5,mpi_real,&
             t_restart1,5,mpi_real,king,CG_COMM,ierr)
+!       do il=1,nodes
+!       write (iout,*) "after gather write1traj: from node",il,t_restart1(1,il),t_restart1(3,il),t_restart1(5,il),t_restart1(4,il)
+!       enddo
 
        call mpi_gather(iset_cache(ii),1,mpi_integer,&
             iset_restart1,1,mpi_integer,king,CG_COMM,ierr)
@@ -1627,6 +1652,7 @@ write(iout,*) "jestesmy na poczatku MREMD"
           call xdrffloat(ixdrf, real(t_restart1(3,il)), iret)
           call xdrffloat(ixdrf, real(t_restart1(5,il)), iret)
           call xdrffloat(ixdrf, real(t_restart1(4,il)), iret)
+!          write (iout,*) "write1traj: from node",ii,t_restart1(1,il),t_restart1(3,il),t_restart1(5,il),t_restart1(4,il)
           call xdrfint(ixdrf, nss, iret) 
           do j=1,nss
            if (dyn_ss) then