X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2FMREMD.F90;h=37c772052894c92c3cace6e7e22607a2384b3dc3;hb=bc23440fbe68672d430f71f22f46b11265f003db;hp=9914d9babd0afa1532ac2190f403c99e23ed82d2;hpb=2a2cf0a81468098903fcb64cad0d3f5cd3f6a77f;p=unres4.git diff --git a/source/unres/MREMD.F90 b/source/unres/MREMD.F90 index 9914d9b..37c7720 100644 --- a/source/unres/MREMD.F90 +++ b/source/unres/MREMD.F90 @@ -85,7 +85,7 @@ real(kind=8) :: remd_t_bath(Nprocs) !(maxprocs) integer :: iremd_iset(Nprocs) !(maxprocs) - integer(kind=2) :: i_index(Nprocs,Nprocs,Nprocs,Nprocs) + integer(kind=2) :: i_index(Nprocs,Nprocs/2,Nprocs/10,Nprocs/10) ! (maxprocs/4,maxprocs/20,maxprocs/200,maxprocs/200) real(kind=8) :: remd_ene(0:n_ene+4,Nprocs) !(0:n_ene+4,maxprocs) integer :: iremd_acc(Nprocs),iremd_tot(Nprocs) !(maxprocs) @@ -94,7 +94,7 @@ !el external ilen character(len=50) :: tytul !el common /gucio/ cm - integer :: itime +! integer :: itime !old integer nup(0:maxprocs),ndown(0:maxprocs) integer :: rep2i(0:Nprocs),ireqi(Nprocs) !(maxprocs) integer :: icache_all(Nprocs) !(maxprocs) @@ -107,8 +107,8 @@ econstr_temp_iex integer :: k,il,il1,i,j,nharp,ii,ierr,itime_master,irr,iex,& i_set_temp,itmp,i_temp,i_mult,i_iset,i_mset,i_dir,i_temp1,& - i_mult1,i_iset1,i_mset1,ierror - integer,dimension(4,nres/3) :: iharp !(4,nres/3)(4,maxres/3) + i_mult1,i_iset1,i_mset1,ierror,itime,mnum + integer,dimension(4,nres) :: iharp !(4,nres/3)(4,maxres/3) !deb imin_itime_old=0 integer :: nres2 !el WRITE(iout,*) "JUST AFTER CALL" @@ -360,7 +360,17 @@ stdfsc(i,j)=dsqrt(2*Rb*t_bath/d_time) enddo enddo - + if (lang.gt.0 .and. .not.surfarea) then + do i=nnt,nct-1 + mnum=(molnum(i)) + stdforcp(i)=stdfp(mnum)*dsqrt(gamp(mnum)) + enddo + do i=nnt,nct + mnum=molnum(i) + if (itype(i,mnum).ne.ntyp1) stdforcsc(i)=stdfsc(iabs(itype(i,mnum)),mnum)& + *dsqrt(gamsc(iabs(itype(i,mnum)),mnum)) + enddo + endif ! print *,'irep',me,t_bath if (.not.rest) then if (me.eq.king .or. .not. out1file) & @@ -397,6 +407,19 @@ stdfsc(i,j)=dsqrt(2*Rb*t_bath/d_time) enddo enddo + if (lang.gt.0 .and. .not.surfarea) then + do i=nnt,nct-1 + mnum=(molnum(i)) + stdforcp(i)=stdfp(mnum)*dsqrt(gamp(mnum)) +! write(iout,*) "stdforcp=",stdforcp(i),itype(i,mnum),i + enddo + do i=nnt,nct + mnum=molnum(i) + if (itype(i,mnum).ne.ntyp1) stdforcsc(i)=stdfsc(iabs(itype(i,mnum)),mnum)& + *dsqrt(gamsc(iabs(itype(i,mnum)),mnum)) +! write(iout,*) "stdforcsc=",stdforcsc(i),itype(i,mnum),i + enddo + endif call rescale_weights(t_bath) endif @@ -457,10 +480,12 @@ tt0=tcpu() #endif itime=0 + itime_mat=itime end_of_run=.false. do while(.not.end_of_run) itime=itime+1 + itime_mat=itime if(itime.eq.n_timestep.and.me.eq.king) end_of_run=.true. if(mremdsync.and.itime.eq.n_timestep) end_of_run=.true. rstcount=rstcount+1 @@ -543,6 +568,7 @@ stop #endif endif + itime_mat=itime if(ntwe.ne.0) then if (mod(itime,ntwe).eq.0) then call statout(itime) @@ -613,7 +639,7 @@ ugamma_cache(i,ntwx_cache)=ugamma(i) uscdiff_cache(i,ntwx_cache)=uscdiff(i) enddo -! call returnbox + call returnbox do i=1,nres*2 do j=1,3 c_cache(j,i,ntwx_cache)=c(j,i) @@ -744,19 +770,26 @@ synflag=.true. if (me.eq.king .or. .not. out1file) & write(iout,*) 'REMD synchro at1',itime,ntwx_cache,Nprocs,nodes -!!!!!! TRIAL OF MINIM SYNC - if (me.eq.king) then - do i=1,nodes-1 - call mpi_isend(itime,1,MPI_INTEGER,i,101, & - CG_COMM, ireqi(i), ierr) -!d write(iout,*) 'REMD synchro with',i -!d call flush(iout) - enddo - call mpi_waitall(nodes-1,ireqi,statusi,ierr) - call mpi_barrier(CG_COMM, ierr) - time01=MPI_WTIME() - endif -!!!!!!!!!!!!!!!!! +!!!!!!! TRIAL OF MINIM SYNC +! if (me.eq.king) then +! do i=1,nodes-1 +! call mpi_isend(itime,1,MPI_INTEGER,i,101, & +! CG_COMM, ireqi(i), ierr) +!!d write(iout,*) 'REMD synchro with',i +!!d call flush(iout) +! enddo +! call mpi_waitall(nodes-1,ireqi,statusi,ierr) +! call mpi_barrier(CG_COMM, ierr) +! time01=MPI_WTIME() +! endif +!!!!!!!!!!!!!!!! +! if (me.ne.king) then +! call mpi_recv(itime_master, 1, MPI_INTEGER,& +! 0,101,CG_COMM, status, ierr) +! call mpi_barrier(CG_COMM, ierr) +!deb if (out1file.or.traj1file) then +! +! endif write(iout,*) icache_all if(traj1file) then write(iout,*) "before mpi_gather ntwx_cache" @@ -1286,6 +1319,19 @@ stdfsc(i,j)=dsqrt(2*Rb*t_bath/d_time) enddo enddo +!c Compute the standard deviations of stochastic forces for Langevin dynamics +!c if the friction coefficients do not depend on surface area + if (lang.gt.0 .and. .not.surfarea) then + do i=nnt,nct-1 + mnum=(molnum(i)) + stdforcp(i)=stdfp(mnum)*dsqrt(gamp(mnum)) + enddo + do i=nnt,nct + mnum=molnum(i) + if (itype(i,mnum).ne.ntyp1) stdforcsc(i)=stdfsc(iabs(itype(i,mnum)),mnum)& + *dsqrt(gamsc(iabs(itype(i,mnum)),mnum)) + enddo + endif !de write(iout,*) 'REMD after',me,t_bath time08=MPI_WTIME()