Merge branch 'devel' into feature-ga
[unres.git] / source / unres / src_MD / src / md-diff / np / a
diff --git a/source/unres/src_MD/src/md-diff/np/a b/source/unres/src_MD/src/md-diff/np/a
deleted file mode 100644 (file)
index 83be36b..0000000
+++ /dev/null
@@ -1,664 +0,0 @@
-c------------------------------------------------------
-      double precision function HNose(ek,s,e,pi,Q,t_bath,dimen)
-      implicit none
-      double precision ek,s,e,pi,Q,t_bath,Rb
-      integer dimen
-      Rb=0.001986d0
-      HNose=ek+e+pi**2/(2*Q)+dimen*Rb*t_bath*log(s)
-c      print '(6f15.5,i5,a2,2f15.5)',ek,s,e,pi,Q,t_bath,dimen,"--",
-c     &      pi**2/(2*Q),dimen*Rb*t_bath*log(s)
-      return
-      end
-c-----------------------------------------------------------------
-      double precision function HNose_nh(eki,e)
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.MD'
-      HNose_nh=eki+e+dimen*Rb*t_bath*xlogs(1)+qmass(1)*vlogs(1)**2/2
-      do i=2,nnos
-        HNose_nh=HNose_nh+qmass(i)*vlogs(i)**2/2+Rb*t_bath*xlogs(i)
-      enddo
-c      write(4,'(5e15.5)') 
-c     &       vlogs(1),xlogs(1),HNose,eki,e
-      return
-      end
-c-----------------------------------------------------------------
-      SUBROUTINE NHCINT(akin,scale,wdti,wdti2,wdti4,wdti8)
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.MD'
-      double precision akin,gnkt,dt,aa,gkt,scale
-      double precision wdti(maxyosh),wdti2(maxyosh),
-     &                 wdti4(maxyosh),wdti8(maxyosh)
-      integer i,iresn,iyosh,inos,nnos1
-
-      dt=d_time
-      nnos1=nnos+1
-      GKT = Rb*t_bath
-      GNKT = dimen*GKT
-      akin=akin*2
-
-      
-C THIS ROUTINE DOES THE NOSE-HOOVER PART OF THE
-C INTEGRATION FROM t=0 TO t=DT/2
-C GET THE TOTAL KINETIC ENERGY
-      SCALE = 1.D0
-c      CALL GETKINP(MASS,VX,VY,VZ,AKIN)
-C UPDATE THE FORCES
-      GLOGS(1) = (AKIN - GNKT)/QMASS(1)
-C START THE MULTIPLE TIME STEP PROCEDURE
-      DO IRESN = 1,NRESN
-       DO IYOSH = 1,NYOSH
-C UPDATE THE THERMOSTAT VELOCITIES
-        VLOGS(NNOS) = VLOGS(NNOS) + GLOGS(NNOS)*WDTI4(IYOSH)
-        DO INOS = 1,NNOS-1
-         AA = EXP(-WDTI8(IYOSH)*VLOGS(NNOS1-INOS) )
-         VLOGS(NNOS-INOS) = VLOGS(NNOS-INOS)*AA*AA
-     &          + WDTI4(IYOSH)*GLOGS(NNOS-INOS)*AA
-        ENDDO
-C UPDATE THE PARTICLE VELOCITIES
-        AA = EXP(-WDTI2(IYOSH)*VLOGS(1) )
-        SCALE = SCALE*AA
-C UPDATE THE FORCES
-        GLOGS(1) = (SCALE*SCALE*AKIN - GNKT)/QMASS(1)
-C UPDATE THE THERMOSTAT POSITIONS
-        DO INOS = 1,NNOS
-         XLOGS(INOS) = XLOGS(INOS) + VLOGS(INOS)*WDTI2(IYOSH)
-        ENDDO
-C UPDATE THE THERMOSTAT VELOCITIES
-        DO INOS = 1,NNOS-1
-         AA = EXP(-WDTI8(IYOSH)*VLOGS(INOS+1) )
-         VLOGS(INOS) = VLOGS(INOS)*AA*AA
-     &      + WDTI4(IYOSH)*GLOGS(INOS)*AA
-         GLOGS(INOS+1) = (QMASS(INOS)*VLOGS(INOS)*VLOGS(INOS)
-     &      -GKT)/QMASS(INOS+1)
-        ENDDO
-        VLOGS(NNOS) = VLOGS(NNOS) + GLOGS(NNOS)*WDTI4(IYOSH)
-       ENDDO
-      ENDDO
-C UPDATE THE PARTICLE VELOCITIES
-c outside of this subroutine
-c      DO I = 1,N
-c       VX(I) = VX(I)*SCALE
-c       VY(I) = VY(I)*SCALE
-c       VZ(I) = VZ(I)*SCALE
-c      ENDDO
-      RETURN
-      END
-c-----------------------------------------------------------------
-      subroutine tnp1_respa_i_step1
-c Applying Nose-Poincare algorithm - step 1 to coordinates
-c JPSJ 70 75 (2001) S. Nose
-c
-c d_t is not updated here
-c
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-      double precision adt,adt2,tmp
-        
-      tmp=1+pi_np/(2*Q_np)*0.5*d_time
-      s12_np=s_np*tmp**2
-      pistar=pi_np/tmp
-      s12_dt=d_time/s12_np
-      d_time_s12=d_time*0.5*s12_np
-
-      do j=1,3
-        d_t_new(j,0)=d_t_old(j,0)+d_a_old(j,0)*d_time_s12
-        dc(j,0)=dc_old(j,0)+d_t_new(j,0)*s12_dt
-      enddo
-      do i=nnt,nct-1   
-        do j=1,3    
-          d_t_new(j,i)=d_t_old(j,i)+d_a_old(j,i)*d_time_s12
-          dc(j,i)=dc_old(j,i)+d_t_new(j,i)*s12_dt
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3    
-           d_t_new(j,inres)=d_t_old(j,inres)+d_a_old(j,inres)*d_time_s12
-           dc(j,inres)=dc_old(j,inres)+d_t_new(j,inres)*s12_dt
-          enddo
-        endif      
-      enddo 
-      return
-      end
-c---------------------------------------------------------------------
-      subroutine tnp1_respa_i_step2
-c  Step 2 of the velocity Verlet algorithm: update velocities
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-
-      double precision d_time_s12
-
-      do i=0,2*nres
-       do j=1,3
-        d_t(j,i)=d_t_new(j,i)
-       enddo
-      enddo
-
-      call kinetic(EK)
-      EK=EK/s12_np**2
-
-      d_time_s12=0.5d0*s12_np*d_time
-
-      do j=1,3
-        d_t(j,0)=d_t_new(j,0)+d_a(j,0)*d_time_s12
-      enddo
-      do i=nnt,nct-1
-        do j=1,3
-          d_t(j,i)=d_t_new(j,i)+d_a(j,i)*d_time_s12
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3
-            d_t(j,inres)=d_t_new(j,inres)+d_a(j,inres)*d_time_s12
-          enddo
-        endif
-      enddo 
-
-      pistar=pistar+(EK-0.5*(E_old+potE)
-     &       -dimen*Rb*t_bath*log(s12_np)+Csplit-dimen*Rb*t_bath)*d_time
-      tmp=1+pistar/(2*Q_np)*0.5*d_time
-      s_np=s12_np*tmp**2
-      pi_np=pistar/tmp
-
-      return
-      end
-c-------------------------------------------------------
-
-      subroutine tnp1_step1
-c Applying Nose-Poincare algorithm - step 1 to coordinates
-c JPSJ 70 75 (2001) S. Nose
-c
-c d_t is not updated here
-c
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-      double precision adt,adt2,tmp
-        
-      tmp=1+pi_np/(2*Q_np)*0.5*d_time
-      s12_np=s_np*tmp**2
-      pistar=pi_np/tmp
-      s12_dt=d_time/s12_np
-      d_time_s12=d_time*0.5*s12_np
-
-      do j=1,3
-        d_t_new(j,0)=d_t_old(j,0)+d_a_old(j,0)*d_time_s12
-        dc(j,0)=dc_old(j,0)+d_t_new(j,0)*s12_dt
-      enddo
-      do i=nnt,nct-1   
-        do j=1,3    
-          d_t_new(j,i)=d_t_old(j,i)+d_a_old(j,i)*d_time_s12
-          dc(j,i)=dc_old(j,i)+d_t_new(j,i)*s12_dt
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3    
-           d_t_new(j,inres)=d_t_old(j,inres)+d_a_old(j,inres)*d_time_s12
-           dc(j,inres)=dc_old(j,inres)+d_t_new(j,inres)*s12_dt
-          enddo
-        endif      
-      enddo 
-      return
-      end
-c---------------------------------------------------------------------
-      subroutine tnp1_step2
-c  Step 2 of the velocity Verlet algorithm: update velocities
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-
-      double precision d_time_s12
-
-      do i=0,2*nres
-       do j=1,3
-        d_t(j,i)=d_t_new(j,i)
-       enddo
-      enddo
-
-      call kinetic(EK)
-      EK=EK/s12_np**2
-
-      d_time_s12=0.5d0*s12_np*d_time
-
-      do j=1,3
-        d_t(j,0)=d_t_new(j,0)+d_a(j,0)*d_time_s12
-      enddo
-      do i=nnt,nct-1
-        do j=1,3
-          d_t(j,i)=d_t_new(j,i)+d_a(j,i)*d_time_s12
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3
-            d_t(j,inres)=d_t_new(j,inres)+d_a(j,inres)*d_time_s12
-          enddo
-        endif
-      enddo 
-
-cd      write(iout,*) 'pistar',pistar,EK,E_old,potE,s12_np
-      pistar=pistar+(EK-0.5*(E_old+potE)
-     &       -dimen*Rb*t_bath*log(s12_np)+H0-dimen*Rb*t_bath)*d_time
-      tmp=1+pistar/(2*Q_np)*0.5*d_time
-      s_np=s12_np*tmp**2
-      pi_np=pistar/tmp
-
-      return
-      end
-
-c-----------------------------------------------------------------
-      subroutine tnp_respa_i_step1
-c Applying Nose-Poincare algorithm - step 1 to coordinates
-c J.Comput.Phys. 151 114 (1999) S.D.Bond B.J.Leimkuhler B.B.Laird
-c
-c d_t is not updated here, it is destroyed
-c
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-      double precision C_np,d_time_s,tmp,d_time_ss
-
-      d_time_s=d_time*0.5*s_np        
-ct2      d_time_s=d_time*0.5*s12_np
-
-      do j=1,3
-        d_t_new(j,0)=d_t_old(j,0)+d_a_old(j,0)*d_time_s
-      enddo
-      do i=nnt,nct-1   
-        do j=1,3    
-          d_t_new(j,i)=d_t_old(j,i)+d_a_old(j,i)*d_time_s
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3    
-           d_t_new(j,inres)=d_t_old(j,inres)+d_a_old(j,inres)*d_time_s
-          enddo
-        endif      
-      enddo 
-
-      do i=0,2*nres
-       do j=1,3
-        d_t(j,i)=d_t_new(j,i)
-       enddo
-      enddo
-
-      call kinetic(EK)
-      EK=EK/s_np**2
-
-      C_np=0.5*d_time*(dimen*Rb*t_bath*(1.0+log(s_np))-EK+potE-Csplit)
-     &                     -pi_np
-
-      pistar=-2.0*C_np/(1.0+sqrt(1.0-C_np*d_time/Q_np))
-      tmp=0.5*d_time*pistar/Q_np
-      s12_np=s_np*(1.0+tmp)/(1.0-tmp)
-
-      d_time_ss=0.5*d_time*(1.0/s12_np+1.0/s_np)
-ct2      d_time_ss=d_time/s12_np
-c      d_time_ss=0.5*d_time*(1.0/sold_np+1.0/s_np) 
-
-      do j=1,3
-        dc(j,0)=dc_old(j,0)+d_t_new(j,0)*d_time_ss
-      enddo
-      do i=nnt,nct-1   
-        do j=1,3    
-          dc(j,i)=dc_old(j,i)+d_t_new(j,i)*d_time_ss
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3    
-           dc(j,inres)=dc_old(j,inres)+d_t_new(j,inres)*d_time_ss
-          enddo
-        endif      
-      enddo 
-
-      return
-      end
-c---------------------------------------------------------------------
-
-      subroutine tnp_respa_i_step2
-c  Step 2 of the velocity Verlet algorithm: update velocities
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-
-      double precision d_time_s
-
-      EK=EK*(s_np/s12_np)**2
-      HNose1=Hnose(EK,s12_np,potE,pistar,Q_np,t_bath,dimen)
-      pi_np=pistar+0.5*d_time*(2*EK-dimen*Rb*t_bath
-     &                              -HNose1+Csplit)         
-
-cr      print '(a,5f)','i_step2',EK,potE,HNose1,pi_np,E_long
-      d_time_s=d_time*0.5*s12_np
-c      d_time_s=d_time*0.5*s_np
-
-      do j=1,3
-        d_t(j,0)=d_t_new(j,0)+d_a(j,0)*d_time_s
-      enddo
-      do i=nnt,nct-1
-        do j=1,3
-          d_t(j,i)=d_t_new(j,i)+d_a(j,i)*d_time_s
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3
-            d_t(j,inres)=d_t_new(j,inres)+d_a(j,inres)*d_time_s
-          enddo
-        endif
-      enddo 
-
-      s_np=s12_np
-
-      return
-      end
-c-----------------------------------------------------------------
-      subroutine tnp_respa_step1
-c Applying Nose-Poincare algorithm - step 1 to vel for RESPA
-c J.Comput.Phys. 151 114 (1999) S.D.Bond B.J.Leimkuhler B.B.Laird
-c
-c d_t is not updated here, it is destroyed
-c
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-      double precision C_np,d_time_s,tmp,d_time_ss
-      double precision energia(0:n_ene)
-
-      d_time_s=d_time*0.5*s_np        
-
-      do j=1,3
-        d_t_old(j,0)=d_t_old(j,0)+d_a(j,0)*d_time_s
-      enddo
-      do i=nnt,nct-1   
-        do j=1,3    
-          d_t_old(j,i)=d_t_old(j,i)+d_a(j,i)*d_time_s
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3    
-           d_t_old(j,inres)=d_t_old(j,inres)+d_a(j,inres)*d_time_s
-          enddo
-        endif      
-      enddo 
-
-
-c      C_np=0.5*d_time*(dimen*Rb*t_bath*(1.0+log(s_np))-EK+potE-H0)
-c     &                     -pi_np
-c
-c      pistar=-2.0*C_np/(1.0+sqrt(1.0-C_np*d_time/Q_np))
-c      tmp=0.5*d_time*pistar/Q_np
-c      s12_np=s_np*(1.0+tmp)/(1.0-tmp)
-c      write(iout,*) 'tnp_respa_step1',s_np,s12_np,EK,potE,C_np,pistar,tmp
-
-ct1      pi_np=pistar
-c      sold_np=s_np
-c      s_np=s12_np
-
-c-------------------------------------
-c test of reviewer's comment
-       pi_np=pi_np-0.5*d_time*(E_long+Csplit-H0)
-cr       print '(a,3f)','1 pi_np,s_np',pi_np,s_np,E_long
-c-------------------------------------
-
-      return
-      end
-c---------------------------------------------------------------------
-      subroutine tnp_respa_step2
-c  Step 2 of the velocity Verlet algorithm: update velocities for RESPA
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-
-      double precision d_time_s
-
-ct1      s12_np=s_np
-ct2      pistar=pi_np
-
-ct      call kinetic(EK)
-ct      HNose1=Hnose(EK,s12_np,potE,pistar,Q_np,t_bath,dimen)
-ct      pi_np=pistar+0.5*d_time*(2*EK-dimen*Rb*t_bath)
-ct     &                              -0.5*d_time*(HNose1-H0)         
-
-c-------------------------------------
-c test of reviewer's comment
-      pi_np=pi_np-0.5*d_time*(E_long+Csplit-H0)
-cr      print '(a,3f)','2 pi_np,s_np',pi_np,s_np,E_long
-c-------------------------------------
-      d_time_s=d_time*0.5*s_np
-
-      do j=1,3
-        d_t_old(j,0)=d_t_old(j,0)+d_a(j,0)*d_time_s
-      enddo
-      do i=nnt,nct-1
-        do j=1,3
-          d_t_old(j,i)=d_t_old(j,i)+d_a(j,i)*d_time_s
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3
-            d_t_old(j,inres)=d_t_old(j,inres)+d_a(j,inres)*d_time_s
-          enddo
-        endif
-      enddo 
-
-cd      s_np=s12_np
-
-      return
-      end
-c---------------------------------------------------------------------
-      subroutine tnp_step1
-c Applying Nose-Poincare algorithm - step 1 to coordinates
-c J.Comput.Phys. 151 114 (1999) S.D.Bond B.J.Leimkuhler B.B.Laird
-c
-c d_t is not updated here, it is destroyed
-c
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-      double precision C_np,d_time_s,tmp,d_time_ss
-
-      d_time_s=d_time*0.5*s_np        
-
-      do j=1,3
-        d_t_new(j,0)=d_t_old(j,0)+d_a_old(j,0)*d_time_s
-      enddo
-      do i=nnt,nct-1   
-        do j=1,3    
-          d_t_new(j,i)=d_t_old(j,i)+d_a_old(j,i)*d_time_s
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3    
-           d_t_new(j,inres)=d_t_old(j,inres)+d_a_old(j,inres)*d_time_s
-          enddo
-        endif      
-      enddo 
-
-      do i=0,2*nres
-       do j=1,3
-        d_t(j,i)=d_t_new(j,i)
-       enddo
-      enddo
-
-      call kinetic(EK)
-      EK=EK/s_np**2
-
-      C_np=0.5*d_time*(dimen*Rb*t_bath*(1.0+log(s_np))-EK+potE-H0)
-     &                     -pi_np
-
-      pistar=-2.0*C_np/(1.0+sqrt(1.0-C_np*d_time/Q_np))
-      tmp=0.5*d_time*pistar/Q_np
-      s12_np=s_np*(1.0+tmp)/(1.0-tmp)
-c      write(iout,*) 'tnp_step1',s_np,s12_np,EK,potE,C_np,pistar,tmp
-
-      d_time_ss=0.5*d_time*(1.0/s12_np+1.0/s_np)
-
-      do j=1,3
-        dc(j,0)=dc_old(j,0)+d_t_new(j,0)*d_time_ss
-      enddo
-      do i=nnt,nct-1   
-        do j=1,3    
-          dc(j,i)=dc_old(j,i)+d_t_new(j,i)*d_time_ss
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3    
-           dc(j,inres)=dc_old(j,inres)+d_t_new(j,inres)*d_time_ss
-          enddo
-        endif      
-      enddo 
-
-      return
-      end
-c-----------------------------------------------------------------
-      subroutine tnp_step2
-c  Step 2 of the velocity Verlet algorithm: update velocities
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'
-      include 'COMMON.CONTROL'
-      include 'COMMON.VAR'
-      include 'COMMON.MD'
-      include 'COMMON.CHAIN'
-      include 'COMMON.DERIV'
-      include 'COMMON.GEO'
-      include 'COMMON.LOCAL'
-      include 'COMMON.INTERACT'
-      include 'COMMON.IOUNITS'
-      include 'COMMON.NAMES'
-
-      double precision d_time_s
-
-      EK=EK*(s_np/s12_np)**2
-      HNose1=Hnose(EK,s12_np,potE,pistar,Q_np,t_bath,dimen)
-      pi_np=pistar+0.5*d_time*(2*EK-dimen*Rb*t_bath)
-     &                              -0.5*d_time*(HNose1-H0)         
-
-cd      write(iout,'(a,4f)') 'mmm',EK,potE,HNose1,pi_np
-      d_time_s=d_time*0.5*s12_np
-
-      do j=1,3
-        d_t(j,0)=d_t_new(j,0)+d_a(j,0)*d_time_s
-      enddo
-      do i=nnt,nct-1
-        do j=1,3
-          d_t(j,i)=d_t_new(j,i)+d_a(j,i)*d_time_s
-        enddo
-      enddo
-      do i=nnt,nct
-        if (itype(i).ne.10) then
-          inres=i+nres
-          do j=1,3
-            d_t(j,inres)=d_t_new(j,inres)+d_a(j,inres)*d_time_s
-          enddo
-        endif
-      enddo 
-
-      s_np=s12_np
-
-      return
-      end