X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2FMREMD.f90;h=350ab5288fff529ca3568895ba623810967a2bf3;hb=8ca97b16fe25b7053f258263899ba030572cc58f;hp=0630c7dec76949b325d688804125beb756b02aef;hpb=d9408016c2011e3dade935da06f883a2665bb73b;p=unres4.git diff --git a/source/unres/MREMD.f90 b/source/unres/MREMD.f90 index 0630c7d..350ab52 100644 --- a/source/unres/MREMD.f90 +++ b/source/unres/MREMD.f90 @@ -347,11 +347,15 @@ if(me.eq.king.or..not.out1file) & write(iout,*) me,"iset=",iset,"t_bath=",t_bath endif -! - stdfp=dsqrt(2*Rb*t_bath/d_time) +! + do i=1,5 + stdfp(i)=dsqrt(2*Rb*t_bath/d_time) + enddo + do j=1,5 do i=1,ntyp - stdfsc(i)=dsqrt(2*Rb*t_bath/d_time) + stdfsc(i,j)=dsqrt(2*Rb*t_bath/d_time) enddo + enddo ! print *,'irep',me,t_bath if (.not.rest) then @@ -383,10 +387,12 @@ if (rest) then if (me.eq.king .or. .not. out1file) & write (iout,'(a60,f10.5)') "REMD restart Temperature:",t_bath - stdfp=dsqrt(2*Rb*t_bath/d_time) + do j=1,5 + stdfp(j)=dsqrt(2*Rb*t_bath/d_time) do i=1,ntyp - stdfsc(i)=dsqrt(2*Rb*t_bath/d_time) + stdfsc(i,j)=dsqrt(2*Rb*t_bath/d_time) enddo + enddo call rescale_weights(t_bath) endif @@ -1251,11 +1257,12 @@ call rescale_weights(t_bath) !o write (iout,*) "Processor",me, !o & " rescaling weights with temperature",t_bath - - stdfp=dsqrt(2*Rb*t_bath/d_time) + do j=1,5 + stdfp(j)=dsqrt(2*Rb*t_bath/d_time) do i=1,ntyp - stdfsc(i)=dsqrt(2*Rb*t_bath/d_time) + stdfsc(i,j)=dsqrt(2*Rb*t_bath/d_time) enddo + enddo !de write(iout,*) 'REMD after',me,t_bath time08=MPI_WTIME() @@ -1997,7 +2004,7 @@ subroutine alloc_MREMD_arrays ! if(.not.allocated(mset)) allocate(mset(max0(nset,1))) - if(.not.allocated(stdfsc)) allocate(stdfsc(ntyp1)) !(ntyp1)) + if(.not.allocated(stdfsc)) allocate(stdfsc(ntyp1,5)) !(ntyp1)) ! commom.remd ! common /remdcommon/ in io: read_REMDpar ! real(kind=8),dimension(:),allocatable :: remd_t !(maxprocs)