43f9baa871d4912b6b4f86c5ec27c6930a350ea7
[unres.git] / source / unres / src_MD-M / energy_split-sep.F
1       subroutine etotal_long(energia)
2       implicit real*8 (a-h,o-z)
3       include 'DIMENSIONS'
4 c
5 c Compute the long-range slow-varying contributions to the energy
6 c
7 #ifndef ISNAN
8       external proc_proc
9 #ifdef WINPGI
10 cMS$ATTRIBUTES C ::  proc_proc
11 #endif
12 #endif
13 #ifdef MPI
14       include "mpif.h"
15       double precision weights_(n_ene)
16 #endif
17       include 'COMMON.SETUP'
18       include 'COMMON.IOUNITS'
19       double precision energia(0:n_ene)
20       include 'COMMON.FFIELD'
21       include 'COMMON.DERIV'
22       include 'COMMON.INTERACT'
23       include 'COMMON.SBRIDGE'
24       include 'COMMON.CHAIN'
25       include 'COMMON.VAR'
26       include 'COMMON.LOCAL'
27       include 'COMMON.MD'
28       include 'COMMON.CONTROL'
29 c      write(iout,'(a,i2)')'Calling etotal_long ipot=',ipot
30       if (modecalc.eq.12.or.modecalc.eq.14) then
31 #ifdef MPI
32 c        if (fg_rank.eq.0) call int_from_cart1(.false.)
33 #else
34         call int_from_cart1(.false.)
35 #endif
36       endif
37 #ifdef MPI      
38 c      write(iout,*) "ETOTAL_LONG Processor",fg_rank,
39 c     & " absolute rank",myrank," nfgtasks",nfgtasks
40       call flush(iout)
41       if (nfgtasks.gt.1) then
42         time00=MPI_Wtime()
43 C FG slaves call the following matching MPI_Bcast in ERGASTULUM
44         if (fg_rank.eq.0) then
45           call MPI_Bcast(3,1,MPI_INTEGER,king,FG_COMM,IERROR)
46 c          write (iout,*) "Processor",myrank," BROADCAST iorder"
47 c          call flush(iout)
48 C FG master sets up the WEIGHTS_ array which will be broadcast to the 
49 C FG slaves as WEIGHTS array.
50           weights_(1)=wsc
51           weights_(2)=wscp
52           weights_(3)=welec
53           weights_(4)=wcorr
54           weights_(5)=wcorr5
55           weights_(6)=wcorr6
56           weights_(7)=wel_loc
57           weights_(8)=wturn3
58           weights_(9)=wturn4
59           weights_(10)=wturn6
60           weights_(11)=wang
61           weights_(12)=wscloc
62           weights_(13)=wtor
63           weights_(14)=wtor_d
64           weights_(15)=wstrain
65           weights_(16)=wvdwpp
66           weights_(17)=wbond
67           weights_(18)=scal14
68           weights_(21)=wsccor
69 C FG Master broadcasts the WEIGHTS_ array
70           call MPI_Bcast(weights_(1),n_ene,
71      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
72         else
73 C FG slaves receive the WEIGHTS array
74           call MPI_Bcast(weights(1),n_ene,
75      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
76           wsc=weights(1)
77           wscp=weights(2)
78           welec=weights(3)
79           wcorr=weights(4)
80           wcorr5=weights(5)
81           wcorr6=weights(6)
82           wel_loc=weights(7)
83           wturn3=weights(8)
84           wturn4=weights(9)
85           wturn6=weights(10)
86           wang=weights(11)
87           wscloc=weights(12)
88           wtor=weights(13)
89           wtor_d=weights(14)
90           wstrain=weights(15)
91           wvdwpp=weights(16)
92           wbond=weights(17)
93           scal14=weights(18)
94           wsccor=weights(21)
95         endif
96         call MPI_Bcast(dc(1,1),6*nres,MPI_DOUBLE_PRECISION,
97      &    king,FG_COMM,IERR)
98          time_Bcast=time_Bcast+MPI_Wtime()-time00
99          time_Bcastw=time_Bcastw+MPI_Wtime()-time00
100 c        call chainbuild_cart
101 c        call int_from_cart1(.false.)
102       endif
103 c      write (iout,*) 'Processor',myrank,
104 c     &  ' calling etotal_short ipot=',ipot
105 c      call flush(iout)
106 c      print *,'Processor',myrank,' nnt=',nnt,' nct=',nct
107 #endif     
108 cd    print *,'nnt=',nnt,' nct=',nct
109 C
110 C Compute the side-chain and electrostatic interaction energy
111 C
112       goto (101,102,103,104,105,106) ipot
113 C Lennard-Jones potential.
114   101 call elj_long(evdw)
115 cd    print '(a)','Exit ELJ'
116       goto 107
117 C Lennard-Jones-Kihara potential (shifted).
118   102 call eljk_long(evdw)
119       goto 107
120 C Berne-Pechukas potential (dilated LJ, angular dependence).
121   103 call ebp_long(evdw)
122       goto 107
123 C Gay-Berne potential (shifted LJ, angular dependence).
124   104 call egb_long(evdw)
125       goto 107
126 C Gay-Berne-Vorobjev potential (shifted LJ, angular dependence).
127   105 call egbv_long(evdw)
128       goto 107
129 C Soft-sphere potential
130   106 call e_softsphere(evdw)
131 C
132 C Calculate electrostatic (H-bonding) energy of the main chain.
133 C
134   107 continue
135       call vec_and_deriv
136       if (shield_mode.gt.0) then
137        call set_shield_fac
138       endif
139
140       if (ipot.lt.6) then
141 #ifdef SPLITELE
142          if (welec.gt.0d0.or.wvdwpp.gt.0d0.or.wel_loc.gt.0d0.or.
143      &       wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
144      &       .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
145      &       .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
146 #else
147          if (welec.gt.0d0.or.wel_loc.gt.0d0.or.
148      &       wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
149      &       .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
150      &       .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
151 #endif
152            call eelec_scale(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
153          else
154             ees=0
155             evdw1=0
156             eel_loc=0
157             eello_turn3=0
158             eello_turn4=0
159          endif
160       else
161 c        write (iout,*) "Soft-spheer ELEC potential"
162         call eelec_soft_sphere(ees,evdw1,eel_loc,eello_turn3,
163      &   eello_turn4)
164       endif
165 C
166 C Calculate excluded-volume interaction energy between peptide groups
167 C and side chains.
168 C
169       if (ipot.lt.6) then
170        if(wscp.gt.0d0) then
171         call escp_long(evdw2,evdw2_14)
172        else
173         evdw2=0
174         evdw2_14=0
175        endif
176       else
177         call escp_soft_sphere(evdw2,evdw2_14)
178       endif
179
180 C 12/1/95 Multi-body terms
181 C
182       n_corr=0
183       n_corr1=0
184       if ((wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0 
185      &    .or. wturn6.gt.0.0d0) .and. ipot.lt.6) then
186          call multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,n_corr1)
187 c         write (2,*) 'n_corr=',n_corr,' n_corr1=',n_corr1,
188 c     &" ecorr",ecorr," ecorr5",ecorr5," ecorr6",ecorr6," eturn6",eturn6
189       else
190          ecorr=0.0d0
191          ecorr5=0.0d0
192          ecorr6=0.0d0
193          eturn6=0.0d0
194       endif
195       if ((wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) .and. ipot.lt.6) then
196          call multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
197       endif
198
199 C If performing constraint dynamics, call the constraint energy
200 C  after the equilibration time
201       if(usampl.and.totT.gt.eq_time) then
202          call EconstrQ   
203          call Econstr_back
204       else
205          Uconst=0.0d0
206          Uconst_back=0.0d0
207       endif
208
209 C Sum the energies
210 C
211       do i=1,n_ene
212         energia(i)=0.0d0
213       enddo
214       energia(1)=evdw
215 #ifdef SCP14
216       energia(2)=evdw2-evdw2_14
217       energia(18)=evdw2_14
218 #else
219       energia(2)=evdw2
220       energia(18)=0.0d0
221 #endif
222 #ifdef SPLITELE
223       energia(3)=ees
224       energia(16)=evdw1
225 #else
226       energia(3)=ees+evdw1
227       energia(16)=0.0d0
228 #endif
229       energia(4)=ecorr
230       energia(5)=ecorr5
231       energia(6)=ecorr6
232       energia(7)=eel_loc
233       energia(8)=eello_turn3
234       energia(9)=eello_turn4
235       energia(10)=eturn6
236       energia(20)=Uconst+Uconst_back
237       call sum_energy(energia,.true.)
238 c      write (iout,*) "Exit ETOTAL_LONG"
239       call flush(iout)
240       return
241       end
242 c------------------------------------------------------------------------------
243       subroutine etotal_short(energia)
244       implicit real*8 (a-h,o-z)
245       include 'DIMENSIONS'
246 c
247 c Compute the short-range fast-varying contributions to the energy
248 c
249 #ifndef ISNAN
250       external proc_proc
251 #ifdef WINPGI
252 cMS$ATTRIBUTES C ::  proc_proc
253 #endif
254 #endif
255 #ifdef MPI
256       include "mpif.h"
257       double precision weights_(n_ene)
258 #endif
259       include 'COMMON.SETUP'
260       include 'COMMON.IOUNITS'
261       double precision energia(0:n_ene)
262       include 'COMMON.FFIELD'
263       include 'COMMON.DERIV'
264       include 'COMMON.INTERACT'
265       include 'COMMON.SBRIDGE'
266       include 'COMMON.CHAIN'
267       include 'COMMON.VAR'
268       include 'COMMON.LOCAL'
269       include 'COMMON.CONTROL'
270
271 c      write(iout,'(a,i2)')'Calling etotal_short ipot=',ipot
272 c      call flush(iout)
273       if (modecalc.eq.12.or.modecalc.eq.14) then
274 #ifdef MPI
275         if (fg_rank.eq.0) call int_from_cart1(.false.)
276 #else
277         call int_from_cart1(.false.)
278 #endif
279       endif
280 #ifdef MPI      
281 c      write(iout,*) "ETOTAL_SHORT Processor",fg_rank,
282 c     & " absolute rank",myrank," nfgtasks",nfgtasks
283 c      call flush(iout)
284       if (nfgtasks.gt.1) then
285         time00=MPI_Wtime()
286 C FG slaves call the following matching MPI_Bcast in ERGASTULUM
287         if (fg_rank.eq.0) then
288           call MPI_Bcast(2,1,MPI_INTEGER,king,FG_COMM,IERROR)
289 c          write (iout,*) "Processor",myrank," BROADCAST iorder"
290 c          call flush(iout)
291 C FG master sets up the WEIGHTS_ array which will be broadcast to the 
292 C FG slaves as WEIGHTS array.
293           weights_(1)=wsc
294           weights_(2)=wscp
295           weights_(3)=welec
296           weights_(4)=wcorr
297           weights_(5)=wcorr5
298           weights_(6)=wcorr6
299           weights_(7)=wel_loc
300           weights_(8)=wturn3
301           weights_(9)=wturn4
302           weights_(10)=wturn6
303           weights_(11)=wang
304           weights_(12)=wscloc
305           weights_(13)=wtor
306           weights_(14)=wtor_d
307           weights_(15)=wstrain
308           weights_(16)=wvdwpp
309           weights_(17)=wbond
310           weights_(18)=scal14
311           weights_(21)=wsccor
312 C FG Master broadcasts the WEIGHTS_ array
313           call MPI_Bcast(weights_(1),n_ene,
314      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
315         else
316 C FG slaves receive the WEIGHTS array
317           call MPI_Bcast(weights(1),n_ene,
318      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
319           wsc=weights(1)
320           wscp=weights(2)
321           welec=weights(3)
322           wcorr=weights(4)
323           wcorr5=weights(5)
324           wcorr6=weights(6)
325           wel_loc=weights(7)
326           wturn3=weights(8)
327           wturn4=weights(9)
328           wturn6=weights(10)
329           wang=weights(11)
330           wscloc=weights(12)
331           wtor=weights(13)
332           wtor_d=weights(14)
333           wstrain=weights(15)
334           wvdwpp=weights(16)
335           wbond=weights(17)
336           scal14=weights(18)
337           wsccor=weights(21)
338         endif
339 c        write (iout,*),"Processor",myrank," BROADCAST weights"
340         call MPI_Bcast(c(1,1),maxres6,MPI_DOUBLE_PRECISION,
341      &    king,FG_COMM,IERR)
342 c        write (iout,*) "Processor",myrank," BROADCAST c"
343         call MPI_Bcast(dc(1,1),maxres6,MPI_DOUBLE_PRECISION,
344      &    king,FG_COMM,IERR)
345 c        write (iout,*) "Processor",myrank," BROADCAST dc"
346         call MPI_Bcast(dc_norm(1,1),maxres6,MPI_DOUBLE_PRECISION,
347      &    king,FG_COMM,IERR)
348 c        write (iout,*) "Processor",myrank," BROADCAST dc_norm"
349         call MPI_Bcast(theta(1),nres,MPI_DOUBLE_PRECISION,
350      &    king,FG_COMM,IERR)
351 c        write (iout,*) "Processor",myrank," BROADCAST theta"
352         call MPI_Bcast(phi(1),nres,MPI_DOUBLE_PRECISION,
353      &    king,FG_COMM,IERR)
354 c        write (iout,*) "Processor",myrank," BROADCAST phi"
355         call MPI_Bcast(alph(1),nres,MPI_DOUBLE_PRECISION,
356      &    king,FG_COMM,IERR)
357 c        write (iout,*) "Processor",myrank," BROADCAST alph"
358         call MPI_Bcast(omeg(1),nres,MPI_DOUBLE_PRECISION,
359      &    king,FG_COMM,IERR)
360 c        write (iout,*) "Processor",myrank," BROADCAST omeg"
361         call MPI_Bcast(vbld(1),2*nres,MPI_DOUBLE_PRECISION,
362      &    king,FG_COMM,IERR)
363 c        write (iout,*) "Processor",myrank," BROADCAST vbld"
364         call MPI_Bcast(vbld_inv(1),2*nres,MPI_DOUBLE_PRECISION,
365      &    king,FG_COMM,IERR)
366          time_Bcast=time_Bcast+MPI_Wtime()-time00
367 c        write (iout,*) "Processor",myrank," BROADCAST vbld_inv"
368       endif
369 c      write (iout,*) 'Processor',myrank,
370 c     &  ' calling etotal_short ipot=',ipot
371 c      call flush(iout)
372 c      print *,'Processor',myrank,' nnt=',nnt,' nct=',nct
373 #endif     
374 c      call int_from_cart1(.false.)
375 C
376 C Compute the side-chain and electrostatic interaction energy
377 C
378       goto (101,102,103,104,105,106) ipot
379 C Lennard-Jones potential.
380   101 call elj_short(evdw)
381 cd    print '(a)','Exit ELJ'
382       goto 107
383 C Lennard-Jones-Kihara potential (shifted).
384   102 call eljk_short(evdw)
385       goto 107
386 C Berne-Pechukas potential (dilated LJ, angular dependence).
387   103 call ebp_short(evdw)
388       goto 107
389 C Gay-Berne potential (shifted LJ, angular dependence).
390   104 call egb_short(evdw)
391       goto 107
392 C Gay-Berne-Vorobjev potential (shifted LJ, angular dependence).
393   105 call egbv_short(evdw)
394       goto 107
395 C Soft-sphere potential - already dealt with in the long-range part
396   106 evdw=0.0d0
397 c  106 call e_softsphere_short(evdw)
398 C
399 C Calculate electrostatic (H-bonding) energy of the main chain.
400 C
401   107 continue
402       call vec_and_deriv
403       if (shield_mode.gt.0) then
404        call set_shield_fac
405       endif
406
407       if (ipot.lt.6) then
408 #ifdef SPLITELE
409          if (welec.gt.0d0.or.wvdwpp.gt.0d0.or.wel_loc.gt.0d0.or.
410      &       wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
411      &       .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
412      &       .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
413 #else
414          if (welec.gt.0d0.or.wel_loc.gt.0d0.or.
415      &       wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
416      &       .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
417      &       .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
418 #endif
419            call eelec_scale(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
420          else
421             ees=0
422             evdw1=0
423             eel_loc=0
424             eello_turn3=0
425             eello_turn4=0
426          endif
427       else
428 c        write (iout,*) "Soft-spheer ELEC potential"
429         call eelec_soft_sphere(ees,evdw1,eel_loc,eello_turn3,
430      &   eello_turn4)
431       endif
432
433 c
434 c Calculate the short-range part of Evdwpp
435 c
436       call evdwpp_short(evdw1)
437 c
438 c Calculate the short-range part of ESCp
439 c
440       if (ipot.lt.6) then
441         call escp_short(evdw2,evdw2_14)
442       endif
443 c
444 c Calculate the bond-stretching energy
445 c
446       call ebond(estr)
447
448 C Calculate the disulfide-bridge and other energy and the contributions
449 C from other distance constraints.
450       call edis(ehpb)
451 C
452 C Calculate the virtual-bond-angle energy.
453 C
454       call ebend(ebe,ethetcnstr)
455 C
456 C Calculate the SC local energy.
457 C
458       call vec_and_deriv
459       call esc(escloc)
460 C
461 C Calculate the virtual-bond torsional energy.
462 C
463       call etor(etors,edihcnstr)
464 C
465 C 6/23/01 Calculate double-torsional energy
466 C
467       call etor_d(etors_d)
468 C
469 C 21/5/07 Calculate local sicdechain correlation energy
470 C
471       if (wsccor.gt.0.0d0) then
472         call eback_sc_corr(esccor)
473       else
474         esccor=0.0d0
475       endif
476 C
477 C Put energy components into an array
478 C
479       do i=1,n_ene
480         energia(i)=0.0d0
481       enddo
482       energia(1)=evdw
483 #ifdef SCP14
484       energia(2)=evdw2-evdw2_14
485       energia(18)=evdw2_14
486 #else
487       energia(2)=evdw2
488       energia(18)=0.0d0
489 #endif
490 #ifdef SPLITELE
491       energia(3)=ees
492       energia(16)=evdw1
493 #else
494       energia(3)=ees+evdw1
495       energia(16)=0.0d0
496 #endif
497       energia(4)=ecorr
498       energia(5)=ecorr5
499       energia(6)=ecorr6
500       energia(7)=eel_loc
501       energia(8)=eello_turn3
502       energia(9)=eello_turn4
503
504       energia(11)=ebe
505       energia(12)=escloc
506       energia(13)=etors
507       energia(14)=etors_d
508       energia(15)=ehpb
509       energia(17)=estr
510       energia(19)=edihcnstr
511       energia(21)=esccor
512 c      write (iout,*) "ETOTAL_SHORT before SUM_ENERGY"
513       call flush(iout)
514       call sum_energy(energia,.true.)
515 c      write (iout,*) "Exit ETOTAL_SHORT"
516       call flush(iout)
517       return
518       end