working side-chain phosphate
[unres4.git] / source / unres / MREMD.f90
index 0630c7d..350ab52 100644 (file)
           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  
       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
 
          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()
       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)