added source code
[unres.git] / source / unres / src_MD / src / md-diff / mts / md.f
1       subroutine MD
2 c------------------------------------------------
3 c  The driver for molecular dynamics subroutines
4 c------------------------------------------------
5       implicit real*8 (a-h,o-z)
6       include 'DIMENSIONS'
7 #ifdef MPI
8       include "mpif.h"
9       integer IERROR,ERRCODE
10 #endif
11       include 'COMMON.SETUP'
12       include 'COMMON.CONTROL'
13       include 'COMMON.VAR'
14       include 'COMMON.MD'
15 #ifndef LANG0
16       include 'COMMON.LANGEVIN'
17 #else
18       include 'COMMON.LANGEVIN.lang0'
19 #endif
20       include 'COMMON.CHAIN'
21       include 'COMMON.DERIV'
22       include 'COMMON.GEO'
23       include 'COMMON.LOCAL'
24       include 'COMMON.INTERACT'
25       include 'COMMON.IOUNITS'
26       include 'COMMON.NAMES'
27       include 'COMMON.TIME1'
28       double precision cm(3),L(3),vcm(3)
29 #ifdef VOUT
30       double precision v_work(maxres6),v_transf(maxres6)
31 #endif
32       integer ilen,rstcount
33       external ilen
34       character*50 tytul
35       common /gucio/ cm
36       integer itime
37 c
38 #ifdef MPI
39       if (ilen(tmpdir).gt.0)
40      &  call copy_to_tmp(pref_orig(:ilen(pref_orig))//"_"
41      &        //liczba(:ilen(liczba))//'.rst')
42 #else
43       if (ilen(tmpdir).gt.0)
44      &  call copy_to_tmp(pref_orig(:ilen(pref_orig))//"_"//'.rst')
45 #endif
46       t_MDsetup=0.0d0
47       t_langsetup=0.0d0
48       t_MD=0.0d0
49       t_enegrad=0.0d0
50       t_sdsetup=0.0d0
51       write (iout,'(20(1h=),a20,20(1h=))') "MD calculation started"
52 #ifdef MPI
53       tt0=MPI_Wtime()
54 #else
55       tt0 = tcpu()
56 #endif
57 c Determine the inverse of the inertia matrix.
58       call setup_MD_matrices
59 c Initialize MD
60       call init_MD
61 #ifdef MPI
62       t_MDsetup = MPI_Wtime()-tt0
63 #else
64       t_MDsetup = tcpu()-tt0
65 #endif
66       rstcount=0 
67 c   Entering the MD loop       
68 #ifdef MPI
69       tt0 = MPI_Wtime()
70 #else
71       tt0 = tcpu()
72 #endif
73       if (lang.eq.2 .or. lang.eq.3) then
74 #ifndef   LANG0
75         call setup_fricmat
76         if (lang.eq.2) then
77           call sd_verlet_p_setup        
78         else
79           call sd_verlet_ciccotti_setup
80         endif
81         do i=1,dimen
82           do j=1,dimen
83             pfric0_mat(i,j,0)=pfric_mat(i,j)
84             afric0_mat(i,j,0)=afric_mat(i,j)
85             vfric0_mat(i,j,0)=vfric_mat(i,j)
86             prand0_mat(i,j,0)=prand_mat(i,j)
87             vrand0_mat1(i,j,0)=vrand_mat1(i,j)
88             vrand0_mat2(i,j,0)=vrand_mat2(i,j)
89           enddo
90         enddo
91         flag_stoch(0)=.true.
92         do i=1,maxflag_stoch
93           flag_stoch(i)=.false.
94         enddo  
95 #else
96         write (iout,*) 
97      &   "LANG=2 or 3 NOT SUPPORTED. Recompile without -DLANG0"
98 #ifdef MPI
99         call MPI_Abort(MPI_COMM_WORLD,IERROR,ERRCODE)
100 #endif
101         stop
102 #endif
103       else if (lang.eq.1 .or. lang.eq.4) then
104         call setup_fricmat
105       endif
106 #ifdef MPI
107       t_langsetup=MPI_Wtime()-tt0
108       tt0=MPI_Wtime()
109 #else
110       t_langsetup=tcpu()-tt0
111       tt0=tcpu()
112 #endif
113       do itime=1,n_timestep
114         rstcount=rstcount+1
115         if (lang.gt.0 .and. surfarea .and. 
116      &      mod(itime,reset_fricmat).eq.0) then
117           if (lang.eq.2 .or. lang.eq.3) then
118 #ifndef LANG0
119             call setup_fricmat
120             if (lang.eq.2) then
121               call sd_verlet_p_setup
122             else
123               call sd_verlet_ciccotti_setup
124             endif
125             do i=1,dimen
126               do j=1,dimen
127                 pfric0_mat(i,j,0)=pfric_mat(i,j)
128                 afric0_mat(i,j,0)=afric_mat(i,j)
129                 vfric0_mat(i,j,0)=vfric_mat(i,j)
130                 prand0_mat(i,j,0)=prand_mat(i,j)
131                 vrand0_mat1(i,j,0)=vrand_mat1(i,j)
132                 vrand0_mat2(i,j,0)=vrand_mat2(i,j)
133               enddo
134             enddo
135             flag_stoch(0)=.true.
136             do i=1,maxflag_stoch
137               flag_stoch(i)=.false.
138             enddo   
139 #endif
140           else if (lang.eq.1 .or. lang.eq.4) then
141             call setup_fricmat
142           endif
143           write (iout,'(a,i10)') 
144      &      "Friction matrix reset based on surface area, itime",itime
145         endif
146         if (reset_vel .and. tbf .and. lang.eq.0 
147      &      .and. mod(itime,count_reset_vel).eq.0) then
148           call random_vel
149           write(iout,'(a,f20.2)') 
150      &     "Velocities reset to random values, time",totT       
151           do i=0,2*nres
152             do j=1,3
153               d_t_old(j,i)=d_t(j,i)
154             enddo
155           enddo
156         endif
157         if (reset_moment .and. mod(itime,count_reset_moment).eq.0) then
158           call inertia_tensor  
159           call vcm_vel(vcm)
160           do j=1,3
161              d_t(j,0)=d_t(j,0)-vcm(j)
162           enddo
163           call kinetic(EK)
164           kinetic_T=2.0d0/(dimen3*Rb)*EK
165           scalfac=dsqrt(T_bath/kinetic_T)
166           write(iout,'(a,f20.2)') "Momenta zeroed out, time",totT       
167           do i=0,2*nres
168             do j=1,3
169               d_t_old(j,i)=scalfac*d_t(j,i)
170             enddo
171           enddo
172         endif  
173         if (lang.ne.4) then
174           if (RESPA) then
175 c Time-reversible RESPA algorithm 
176 c (Tuckerman et al., J. Chem. Phys., 97, 1990, 1992)
177             call RESPA_step(itime)
178           else
179 c Variable time step algorithm.
180             call velverlet_step(itime)
181           endif
182         else
183 #ifdef BROWN
184           call brown_step(itime)
185 #else
186           print *,"Brown dynamics not here!"
187 #ifdef MPI
188           call MPI_Abort(MPI_COMM_WORLD,IERROR,ERRCODE)
189 #endif
190           stop
191 #endif
192         endif
193         if (ntwe.ne.0) then
194          if (mod(itime,ntwe).eq.0) call statout(itime)
195 #ifdef VOUT
196         do j=1,3
197           v_work(j)=d_t(j,0)
198         enddo
199         ind=3
200         do i=nnt,nct-1
201           do j=1,3
202             ind=ind+1
203             v_work(ind)=d_t(j,i)
204           enddo
205         enddo
206         do i=nnt,nct
207           if (itype(i).ne.10) then
208             do j=1,3
209               ind=ind+1
210               v_work(ind)=d_t(j,i+nres)
211             enddo
212           endif
213         enddo
214
215         write (66,'(80f10.5)') 
216      &    ((d_t(j,i),j=1,3),i=0,nres-1),((d_t(j,i+nres),j=1,3),i=1,nres)
217         do i=1,ind
218           v_transf(i)=0.0d0
219           do j=1,ind
220             v_transf(i)=v_transf(i)+gvec(j,i)*v_work(j)
221           enddo
222            v_transf(i)= v_transf(i)*dsqrt(geigen(i))
223         enddo
224         write (67,'(80f10.5)') (v_transf(i),i=1,ind)
225 #endif
226         endif
227         if (mod(itime,ntwx).eq.0) then
228           write (tytul,'("time",f8.2)') totT
229           if(mdpdb) then
230              call pdbout(potE,tytul,ipdb)
231           else 
232              call cartout(totT)
233           endif
234         endif
235         if (rstcount.eq.1000.or.itime.eq.n_timestep) then
236            open(irest2,file=rest2name,status='unknown')
237            write(irest2,*) totT,EK,potE,totE,t_bath
238            do i=1,2*nres
239             write (irest2,'(3e15.5)') (d_t(j,i),j=1,3)
240            enddo
241            do i=1,2*nres
242             write (irest2,'(3e15.5)') (dc(j,i),j=1,3)
243            enddo
244           close(irest2)
245           rstcount=0
246         endif 
247       enddo
248 #ifdef MPI
249       t_MD=MPI_Wtime()-tt0
250 #else
251       t_MD=tcpu()-tt0
252 #endif
253       write (iout,'(//35(1h=),a10,35(1h=)/10(/a40,1pe15.5))') 
254      &  '  Timing  ',
255      & 'MD calculations setup:',t_MDsetup,
256      & 'Energy & gradient evaluation:',t_enegrad,
257      & 'Stochastic MD setup:',t_langsetup,
258      & 'Stochastic MD step setup:',t_sdsetup,
259      & 'MD steps:',t_MD
260       write (iout,'(/28(1h=),a25,27(1h=))') 
261      & '  End of MD calculation  '
262 #ifdef TIMING_ENE
263       write (iout,*) "time for etotal",t_etotal," elong",t_elong,
264      &  " eshort",t_eshort
265       write (iout,*) "time_fric",time_fric," time_stoch",time_stoch,
266      & " time_fricmatmult",time_fricmatmult," time_fsample ",
267      & time_fsample
268 #endif
269       return
270       end