Adam's unres update
[unres.git] / source / unres / src-HCD-5D / energy_split-sep.F
1       subroutine etotal_long(energia)
2       implicit none
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       double precision time00
17       integer ierror,ierr
18 #endif
19       include 'COMMON.SETUP'
20       include 'COMMON.IOUNITS'
21       double precision energia(0:n_ene)
22       include 'COMMON.FFIELD'
23       include 'COMMON.DERIV'
24       include 'COMMON.INTERACT'
25       include 'COMMON.SBRIDGE'
26       include 'COMMON.CHAIN'
27       include 'COMMON.VAR'
28       include 'COMMON.LOCAL'
29       include 'COMMON.QRESTR'
30       include 'COMMON.MD'
31       include 'COMMON.CONTROL'
32       include 'COMMON.TIME1'
33       double precision evdw,evdw1,evdw2,evdw2_14,ees,eel_loc,
34      & eello_turn3,eello_turn4,edfadis,estr,ehpb,ebe,ethetacnstr,
35      & escloc,etors,edihcnstr,etors_d,esccor,ecorr,ecorr5,ecorr6,eturn6,
36      & eliptran,Eafmforce,Etube,
37      & esaxs_constr,ehomology_constr,edfator,edfanei,edfabet
38       integer i,n_corr,n_corr1
39 c      write(iout,'(a,i2)')'Calling etotal_long ipot=',ipot
40 #ifdef TIMING_ENE
41       double precision time01
42 #endif
43       if (modecalc.eq.12.or.modecalc.eq.14) then
44 #ifdef MPI
45 c        if (fg_rank.eq.0) call int_from_cart1(.false.)
46 #else
47         call int_from_cart1(.false.)
48 #endif
49       endif
50 #ifdef MPI      
51       edfadis=0.0d0
52       edfator=0.0d0
53       edfanei=0.0d0
54       edfabet=0.0d0
55       ehomology_constr=0.0d0
56       Uconst=0.0d0
57       Uconst_back=0.0d0
58 c      write(iout,*) "ETOTAL_LONG Processor",fg_rank,
59 c     & " absolute rank",myrank," nfgtasks",nfgtasks
60 c      call flush(iout)
61       if (nfgtasks.gt.1) then
62         time00=MPI_Wtime()
63 C FG slaves call the following matching MPI_Bcast in ERGASTULUM
64         if (fg_rank.eq.0) then
65           call MPI_Bcast(3,1,MPI_INTEGER,king,FG_COMM,IERROR)
66 c          write (iout,*) "Processor",myrank," BROADCAST iorder"
67 c          call flush(iout)
68 C FG master sets up the WEIGHTS_ array which will be broadcast to the 
69 C FG slaves as WEIGHTS array.
70           weights_(1)=wsc
71           weights_(2)=wscp
72           weights_(3)=welec
73           weights_(4)=wcorr
74           weights_(5)=wcorr5
75           weights_(6)=wcorr6
76           weights_(7)=wel_loc
77           weights_(8)=wturn3
78           weights_(9)=wturn4
79           weights_(10)=wturn6
80           weights_(11)=wang
81           weights_(12)=wscloc
82           weights_(13)=wtor
83           weights_(14)=wtor_d
84           weights_(15)=wstrain
85           weights_(16)=wvdwpp
86           weights_(17)=wbond
87           weights_(18)=scal14
88           weights_(21)=wsccor
89           weights_(22)=wliptran
90           weights_(25)=wtube
91           weights_(26)=wsaxs
92           weights_(28)=wdfa_dist
93           weights_(29)=wdfa_tor
94           weights_(30)=wdfa_nei
95           weights_(31)=wdfa_beta
96 C FG Master broadcasts the WEIGHTS_ array
97           call MPI_Bcast(weights_(1),n_ene,
98      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
99         else
100 C FG slaves receive the WEIGHTS array
101           call MPI_Bcast(weights(1),n_ene,
102      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
103           wsc=weights(1)
104           wscp=weights(2)
105           welec=weights(3)
106           wcorr=weights(4)
107           wcorr5=weights(5)
108           wcorr6=weights(6)
109           wel_loc=weights(7)
110           wturn3=weights(8)
111           wturn4=weights(9)
112           wturn6=weights(10)
113           wang=weights(11)
114           wscloc=weights(12)
115           wtor=weights(13)
116           wtor_d=weights(14)
117           wstrain=weights(15)
118           wvdwpp=weights(16)
119           wbond=weights(17)
120           scal14=weights(18)
121           wsccor=weights(21)
122           wliptran=weights(22)
123           wtube=weights(25)
124           wsaxs=weights(26)
125           wdfa_dist=weights(28)
126           wdfa_tor=weights(29)
127           wdfa_nei=weights(30)
128           wdfa_beta=weights(31)
129         endif
130         call MPI_Bcast(dc(1,1),6*nres,MPI_DOUBLE_PRECISION,
131      &    king,FG_COMM,IERR)
132          time_Bcast=time_Bcast+MPI_Wtime()-time00
133          time_Bcastw=time_Bcastw+MPI_Wtime()-time00
134 c        call chainbuild_cart
135 c        call int_from_cart1(.false.)
136       endif
137 c      write (iout,*) 'Processor',myrank,
138 c     &  ' calling etotal_short ipot=',ipot
139 c      call flush(iout)
140 c      print *,'Processor',myrank,' nnt=',nnt,' nct=',nct
141       if (nfgtasks.gt.1) then
142         call MPI_Bcast(itime_mat,1,MPI_INT,king,FG_COMM,IERROR)
143       endif
144       if (mod(itime_mat,imatupdate).eq.0) then
145 #ifdef TIMING_ENE
146         time01=MPI_Wtime()
147 #endif
148         call make_SCp_inter_list_RESPA
149         call make_SCSC_inter_list_RESPA
150         call make_pp_inter_list
151         call make_pp_vdw_inter_list_RESPA
152 #ifdef TIMING_ENE
153         time_list=time_list+MPI_Wtime()-time01
154 #endif
155       endif
156 #endif     
157 cd    print *,'nnt=',nnt,' nct=',nct
158 C
159 C Compute the side-chain and electrostatic interaction energy
160 C
161 #ifdef TIMING_ENE
162       time01=MPI_Wtime()
163 #endif
164       goto (101,102,103,104,105,106) ipot
165 C Lennard-Jones potential.
166   101 call elj_long(evdw)
167 cd    print '(a)','Exit ELJ'
168       goto 107
169 C Lennard-Jones-Kihara potential (shifted).
170   102 call eljk_long(evdw)
171       goto 107
172 C Berne-Pechukas potential (dilated LJ, angular dependence).
173   103 call ebp_long(evdw)
174       goto 107
175 C Gay-Berne potential (shifted LJ, angular dependence).
176   104 call egb_long(evdw)
177       goto 107
178 C Gay-Berne-Vorobjev potential (shifted LJ, angular dependence).
179   105 call egbv_long(evdw)
180       goto 107
181 C Soft-sphere potential
182   106 call e_softsphere(evdw)
183 C
184 C Calculate electrostatic (H-bonding) energy of the main chain.
185 C
186   107 continue
187 #ifdef TIMING_ENE
188       time_evdw_long=time_evdw_long+MPI_Wtime()-time01
189 #endif
190 #ifdef TIMING
191       time01=MPI_Wtime() 
192 #endif
193       call vec_and_deriv
194 #ifdef TIMING
195       time_vec=time_vec+MPI_Wtime()-time01
196 #endif
197 c      write (iout,*) "etotal_long: shield_mode",shield_mode
198 #ifdef TIMING_ENE
199       time01=MPI_Wtime()
200 #endif
201       if (shield_mode.eq.1) then
202        call set_shield_fac
203       else if  (shield_mode.eq.2) then
204        call set_shield_fac2
205       endif
206
207       if (ipot.lt.6) then
208 #ifdef SPLITELE
209          if (welec.gt.0d0.or.wvdwpp.gt.0d0.or.wel_loc.gt.0d0.or.
210      &       wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
211      &       .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
212      &       .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
213 #else
214          if (welec.gt.0d0.or.wel_loc.gt.0d0.or.
215      &       wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
216      &       .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
217      &       .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
218 #endif
219            call eelec_scale(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
220          else
221             ees=0
222             evdw1=0
223             eel_loc=0
224             eello_turn3=0
225             eello_turn4=0
226          endif
227       else
228 c        write (iout,*) "Soft-spheer ELEC potential"
229         call eelec_soft_sphere(ees,evdw1,eel_loc,eello_turn3,
230      &   eello_turn4)
231       endif
232 #ifdef TIMING_ENE
233       time_eelec_long=time_eelec_long+MPI_Wtime()-time01
234 #endif
235 C
236 C Calculate excluded-volume interaction energy between peptide groups
237 C and side chains.
238 C
239 #ifdef TIMING_ENE
240       time01=MPI_Wtime()
241 #endif
242       if (ipot.lt.6) then
243        if(wscp.gt.0d0) then
244         call escp_long(evdw2,evdw2_14)
245        else
246         evdw2=0
247         evdw2_14=0
248        endif
249       else
250         call escp_soft_sphere(evdw2,evdw2_14)
251       endif
252 #ifdef TIMING_ENE
253       time_escp_long=time_escp_long+MPI_Wtime()-time01
254 #endif
255 #ifdef FOURBODY
256
257 C 12/1/95 Multi-body terms
258 C
259       n_corr=0
260       n_corr1=0
261       if ((wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0 
262      &    .or. wturn6.gt.0.0d0) .and. ipot.lt.6) then
263          call multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,n_corr1)
264 c         write (2,*) 'n_corr=',n_corr,' n_corr1=',n_corr1,
265 c     &" ecorr",ecorr," ecorr5",ecorr5," ecorr6",ecorr6," eturn6",eturn6
266       else
267          ecorr=0.0d0
268          ecorr5=0.0d0
269          ecorr6=0.0d0
270          eturn6=0.0d0
271       endif
272       if ((wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) .and. ipot.lt.6) then
273          call multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
274       else
275          ecorr=0.0d0
276          ecorr5=0.0d0
277          ecorr6=0.0d0
278          eturn6=0.0d0
279       endif
280 #else
281          ecorr=0.0d0
282          ecorr5=0.0d0
283          ecorr6=0.0d0
284          eturn6=0.0d0
285 #endif
286
287 C If performing constraint dynamics, call the constraint energy
288 C  after the equilibration time
289       if(usampl.and.totT.gt.eq_time) then
290          call EconstrQ   
291          if (loc_qlike) then
292            call Econstr_back_qlike
293          else
294            call Econstr_back
295          endif
296       else
297          Uconst=0.0d0
298          Uconst_back=0.0d0
299       endif
300
301 C Sum the energies
302 C
303       do i=1,n_ene
304         energia(i)=0.0d0
305       enddo
306       energia(1)=evdw
307 #ifdef SCP14
308       energia(2)=evdw2-evdw2_14
309       energia(18)=evdw2_14
310 #else
311       energia(2)=evdw2
312       energia(18)=0.0d0
313 #endif
314 #ifdef SPLITELE
315       energia(3)=ees
316       energia(16)=evdw1
317 #else
318       energia(3)=ees+evdw1
319       energia(16)=0.0d0
320 #endif
321       energia(4)=ecorr
322       energia(5)=ecorr5
323       energia(6)=ecorr6
324       energia(7)=eel_loc
325       energia(8)=eello_turn3
326       energia(9)=eello_turn4
327       energia(10)=eturn6
328       energia(20)=Uconst+Uconst_back
329       energia(27)=ehomology_constr
330       energia(28)=edfadis
331       energia(29)=edfator
332       energia(30)=edfanei
333       energia(31)=edfabet
334       call sum_energy(energia,.true.)
335 c      write (iout,*) "Exit ETOTAL_LONG"
336 c      call flush(iout)
337       return
338       end
339 c------------------------------------------------------------------------------
340       subroutine etotal_short(energia)
341       implicit real*8 (a-h,o-z)
342       include 'DIMENSIONS'
343 c
344 c Compute the short-range fast-varying contributions to the energy
345 c
346 #ifndef ISNAN
347       external proc_proc
348 #ifdef WINPGI
349 cMS$ATTRIBUTES C ::  proc_proc
350 #endif
351 #endif
352 #ifdef MPI
353       include "mpif.h"
354       double precision weights_(n_ene)
355       double precision time00
356       integer ierror,ierr
357 #endif
358       include 'COMMON.SETUP'
359       include 'COMMON.IOUNITS'
360       double precision energia(0:n_ene)
361       include 'COMMON.FFIELD'
362       include 'COMMON.DERIV'
363       include 'COMMON.INTERACT'
364       include 'COMMON.SBRIDGE'
365       include 'COMMON.CHAIN'
366       include 'COMMON.VAR'
367       include 'COMMON.LOCAL'
368       include 'COMMON.CONTROL'
369       include 'COMMON.SAXS'
370       include 'COMMON.TORCNSTR'
371       include 'COMMON.TIME1'
372       double precision evdw,evdw1,evdw2,evdw2_14,ees,eel_loc,
373      & eello_turn3,eello_turn4,edfadis,estr,ehpb,ebe,ethetacnstr,
374      & escloc,etors,edihcnstr,etors_d,esccor,ecorr,ecorr5,ecorr6,eturn6,
375      & eliptran,Eafmforce,Etube,
376      & esaxs_constr,ehomology_constr,edfator,edfanei,edfabet
377       integer i,n_corr,n_corr1
378 #ifdef TIMING_ENE
379       double precision time01
380 #endif
381 c      write(iout,'(a,i2)')'Calling etotal_short ipot=',ipot
382 c      call flush(iout)
383       if (modecalc.eq.12.or.modecalc.eq.14) then
384 #ifdef MPI
385         if (fg_rank.eq.0) call int_from_cart1(.false.)
386 #else
387         call int_from_cart1(.false.)
388 #endif
389       endif
390 #ifdef MPI      
391 #ifndef DFA
392       edfadis=0.0d0
393       edfator=0.0d0
394       edfanei=0.0d0
395       edfabet=0.0d0
396 #endif
397       evdw=0.0d0
398       ees=0.0d0
399       evdw1=0.0d0
400       eel_loc=0.0d0
401       eello_turn3=0.0d0
402       eello_turn4=0.0d0
403       evdw2=0
404       evdw2_14=0
405       ecorr=0.0d0
406       ecorr5=0.0d0
407       ecorr6=0.0d0
408       eturn6=0.0d0
409 c      write(iout,*) "ETOTAL_SHORT Processor",fg_rank,
410 c     & " absolute rank",myrank," nfgtasks",nfgtasks
411 c      call flush(iout)
412       if (nfgtasks.gt.1) then
413         time00=MPI_Wtime()
414 C FG slaves call the following matching MPI_Bcast in ERGASTULUM
415         if (fg_rank.eq.0) then
416           call MPI_Bcast(2,1,MPI_INTEGER,king,FG_COMM,IERROR)
417 c          write (iout,*) "Processor",myrank," BROADCAST iorder"
418 c          call flush(iout)
419 C FG master sets up the WEIGHTS_ array which will be broadcast to the 
420 C FG slaves as WEIGHTS array.
421           weights_(1)=wsc
422           weights_(2)=wscp
423           weights_(3)=welec
424           weights_(4)=wcorr
425           weights_(5)=wcorr5
426           weights_(6)=wcorr6
427           weights_(7)=wel_loc
428           weights_(8)=wturn3
429           weights_(9)=wturn4
430           weights_(10)=wturn6
431           weights_(11)=wang
432           weights_(12)=wscloc
433           weights_(13)=wtor
434           weights_(14)=wtor_d
435           weights_(15)=wstrain
436           weights_(16)=wvdwpp
437           weights_(17)=wbond
438           weights_(18)=scal14
439           weights_(21)=wsccor
440           weights_(26)=wsaxs
441           weights_(29)=wdfa_tor
442           weights_(30)=wdfa_nei
443           weights_(31)=wdfa_beta
444 C FG Master broadcasts the WEIGHTS_ array
445           call MPI_Bcast(weights_(1),n_ene,
446      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
447         else
448 C FG slaves receive the WEIGHTS array
449           call MPI_Bcast(weights(1),n_ene,
450      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
451           wsc=weights(1)
452           wscp=weights(2)
453           welec=weights(3)
454           wcorr=weights(4)
455           wcorr5=weights(5)
456           wcorr6=weights(6)
457           wel_loc=weights(7)
458           wturn3=weights(8)
459           wturn4=weights(9)
460           wturn6=weights(10)
461           wang=weights(11)
462           wscloc=weights(12)
463           wtor=weights(13)
464           wtor_d=weights(14)
465           wstrain=weights(15)
466           wvdwpp=weights(16)
467           wbond=weights(17)
468           scal14=weights(18)
469           wsccor=weights(21)
470           wsaxs=weights(26)
471         endif
472 c        write (iout,*),"Processor",myrank," BROADCAST weights"
473         call MPI_Bcast(c(1,1),6*nres,MPI_DOUBLE_PRECISION,
474      &    king,FG_COMM,IERR)
475 c        write (iout,*) "Processor",myrank," BROADCAST c"
476         call MPI_Bcast(dc(1,1),6*nres,MPI_DOUBLE_PRECISION,
477      &    king,FG_COMM,IERR)
478 c        write (iout,*) "Processor",myrank," BROADCAST dc"
479         call MPI_Bcast(dc_norm(1,1),6*nres,MPI_DOUBLE_PRECISION,
480      &    king,FG_COMM,IERR)
481 c        write (iout,*) "Processor",myrank," BROADCAST dc_norm"
482         call MPI_Bcast(theta(1),nres,MPI_DOUBLE_PRECISION,
483      &    king,FG_COMM,IERR)
484 c        write (iout,*) "Processor",myrank," BROADCAST theta"
485         call MPI_Bcast(phi(1),nres,MPI_DOUBLE_PRECISION,
486      &    king,FG_COMM,IERR)
487 c        write (iout,*) "Processor",myrank," BROADCAST phi"
488         call MPI_Bcast(alph(1),nres,MPI_DOUBLE_PRECISION,
489      &    king,FG_COMM,IERR)
490 c        write (iout,*) "Processor",myrank," BROADCAST alph"
491         call MPI_Bcast(omeg(1),nres,MPI_DOUBLE_PRECISION,
492      &    king,FG_COMM,IERR)
493 c        write (iout,*) "Processor",myrank," BROADCAST omeg"
494         call MPI_Bcast(vbld(1),2*nres,MPI_DOUBLE_PRECISION,
495      &    king,FG_COMM,IERR)
496 c        write (iout,*) "Processor",myrank," BROADCAST vbld"
497         call MPI_Bcast(vbld_inv(1),2*nres,MPI_DOUBLE_PRECISION,
498      &    king,FG_COMM,IERR)
499          time_Bcast=time_Bcast+MPI_Wtime()-time00
500 c        write (iout,*) "Processor",myrank," BROADCAST vbld_inv"
501       endif
502 c      write (iout,*) 'Processor',myrank,
503 c     &  ' calling etotal_short ipot=',ipot
504 c      call flush(iout)
505 c      print *,'Processor',myrank,' nnt=',nnt,' nct=',nct
506 #endif     
507 c      call int_from_cart1(.false.)
508 C
509 C Compute the side-chain and electrostatic interaction energy
510 C
511 #ifdef TIMING_ENE
512       time01=MPI_Wtime()
513 #endif
514       goto (101,102,103,104,105,106) ipot
515 C Lennard-Jones potential.
516   101 call elj_short(evdw)
517 cd    print '(a)','Exit ELJ'
518       goto 107
519 C Lennard-Jones-Kihara potential (shifted).
520   102 call eljk_short(evdw)
521       goto 107
522 C Berne-Pechukas potential (dilated LJ, angular dependence).
523   103 call ebp_short(evdw)
524       goto 107
525 C Gay-Berne potential (shifted LJ, angular dependence).
526   104 call egb_short(evdw)
527       goto 107
528 C Gay-Berne-Vorobjev potential (shifted LJ, angular dependence).
529   105 call egbv_short(evdw)
530       goto 107
531 C Soft-sphere potential - already dealt with in the long-range part
532   106 evdw=0.0d0
533 c  106 call e_softsphere_short(evdw)
534 C
535 C Calculate electrostatic (H-bonding) energy of the main chain.
536 C
537   107 continue
538 #ifdef TIMING_ENE
539       time_evdw_short=time_evdw_short+MPI_Wtime()-time01
540 #endif
541 c
542 c Calculate the short-range part of Evdwpp
543 c
544 #ifdef TIMING_ENE
545       time01=MPI_Wtime()
546 #endif
547       call evdwpp_short(evdw1)
548 #ifdef TIMING_ENE
549       time_eelec_short=time_eelec_short+MPI_Wtime()-time01
550 #endif
551 c
552 c Calculate the short-range part of ESCp
553 c
554 #ifdef TIMING_ENE
555       time01=MPI_Wtime()
556 #endif
557       if (ipot.lt.6) then
558         call escp_short(evdw2,evdw2_14)
559       endif
560 #ifdef TIMING_ENE
561       time_escp_short=time_escp_short+MPI_Wtime()-time01
562 #endif
563 c
564 c Calculate the bond-stretching energy
565 c
566       call ebond(estr)
567
568 C Calculate the disulfide-bridge and other energy and the contributions
569 C from other distance constraints.
570       call edis(ehpb)
571 C
572 C Calculate the virtual-bond-angle energy.
573 C
574       if (wang.gt.0d0) then
575        if (tor_mode.eq.0) then
576          call ebend(ebe)
577        else
578 C ebend kcc is Kubo cumulant clustered rigorous attemp to derive the
579 C energy function
580          call ebend_kcc(ebe)
581        endif
582       else
583         ebe=0.0d0
584       endif
585       ethetacnstr=0.0d0
586       if (with_theta_constr) call etheta_constr(ethetacnstr)
587 C
588 C Calculate the SC local energy.
589 C
590 #ifdef TIMING
591       time01=MPI_Wtime() 
592 #endif
593       call vec_and_deriv
594 #ifdef TIMING
595       time_vec=time_vec+MPI_Wtime()-time01
596 #endif
597       call esc(escloc)
598 C
599 C Calculate the virtual-bond torsional energy.
600 C
601       if (wtor.gt.0.0d0) then
602          if (tor_mode.eq.0) then
603            call etor(etors)
604          else
605 C etor kcc is Kubo cumulant clustered rigorous attemp to derive the
606 C energy function
607            call etor_kcc(etors)
608          endif
609       else
610         etors=0.0d0
611       endif
612       edihcnstr=0.0d0
613 c Lipid transfer
614       if (wliptran.gt.0) then
615         call Eliptransfer(eliptran)
616       else
617         eliptran=0.0d0
618       endif
619       if (AFMlog.gt.0) then
620         call AFMforce(Eafmforce)
621       else if (selfguide.gt.0) then
622         call AFMvel(Eafmforce)
623       else 
624         Eafmforce=0.0d0
625       endif
626       if (TUBElog.eq.1) then
627 C      print *,"just before call"
628         call calctube(Etube)
629       elseif (TUBElog.eq.2) then
630         call calctube2(Etube)
631       else
632         Etube=0.0d0
633       endif
634
635       if (ndih_constr.gt.0) call etor_constr(edihcnstr)
636 c      print *,"Processor",myrank," computed Utor"
637 C
638 C 6/23/01 Calculate double-torsional energy
639 C
640       if ((wtor_d.gt.0.0d0).and.(tor_mode.eq.0)) then
641         call etor_d(etors_d)
642       else
643         etors_d=0
644       endif
645 c
646 c Homology restraints
647 c
648       if (constr_homology.ge.1) then
649         call e_modeller(ehomology_constr)
650       else
651         ehomology_constr=0.0d0
652       endif
653 #ifdef DFA
654 C     BARTEK for dfa test!
655       if (wdfa_dist.gt.0) then
656          call edfad(edfadis)
657       else
658          edfadis=0.0
659       endif
660 c      print*, 'edfad is finished!', edfadis
661       if (wdfa_tor.gt.0) then
662          call edfat(edfator)
663       else
664          edfator=0.0
665       endif
666 c      print*, 'edfat is finished!', edfator
667       if (wdfa_nei.gt.0) then
668          call edfan(edfanei)
669       else
670          edfanei=0.0
671       endif
672 c      print*, 'edfan is finished!', edfanei
673       if (wdfa_beta.gt.0) then
674          call edfab(edfabet)
675       else
676          edfabet=0.0
677       endif
678 c      print*, 'edfab is finished!', edfabet
679 #endif
680 C
681 C 21/5/07 Calculate local sicdechain correlation energy
682 C
683       if (wsccor.gt.0.0d0) then
684         call eback_sc_corr(esccor)
685       else
686         esccor=0.0d0
687       endif
688 c      write (iout,*) "nsaxs",nsaxs," saxs_mode",saxs_mode
689       if (nsaxs.gt.0 .and. saxs_mode.eq.0) then
690         call e_saxs(Esaxs_constr)
691 c        write (iout,*) "From Esaxs: Esaxs_constr",Esaxs_constr
692       else if (nsaxs.gt.0 .and. saxs_mode.gt.0) then
693         call e_saxsC(Esaxs_constr)
694 c        write (iout,*) "From EsaxsC: Esaxs_constr",Esaxs_constr
695       else
696         Esaxs_constr = 0.0d0
697       endif
698 C
699 C Put energy components into an array
700 C
701       do i=1,n_ene
702         energia(i)=0.0d0
703       enddo
704       energia(1)=evdw
705 #ifdef SCP14
706       energia(2)=evdw2-evdw2_14
707       energia(18)=evdw2_14
708 #else
709       energia(2)=evdw2
710       energia(18)=0.0d0
711 #endif
712 #ifdef SPLITELE
713       energia(3)=ees
714       energia(16)=evdw1
715 #else
716       energia(3)=ees+evdw1
717       energia(16)=0.0d0
718 #endif
719       energia(4)=ecorr
720       energia(5)=ecorr5
721       energia(6)=ecorr6
722       energia(7)=eel_loc
723       energia(8)=eello_turn3
724       energia(9)=eello_turn4
725       energia(10)=eturn6
726       energia(11)=ebe
727       energia(12)=escloc
728       energia(13)=etors
729       energia(14)=etors_d
730       energia(15)=ehpb
731       energia(17)=estr
732       energia(19)=edihcnstr
733       energia(21)=esccor
734       energia(22)=eliptran
735       energia(24)=ethetacnstr
736       energia(25)=Etube
737       energia(26)=Esaxs_constr
738       energia(27)=ehomology_constr
739       energia(28)=edfadis
740       energia(29)=edfator
741       energia(30)=edfanei
742       energia(31)=edfabet
743 c      write (iout,*) "ETOTAL_SHORT before SUM_ENERGY"
744 c      call flush(iout)
745       call sum_energy(energia,.true.)
746 c      write (iout,*) "Exit ETOTAL_SHORT"
747 c      call flush(iout)
748       return
749       end