Poprawiony SCR_MD-M i dzialajacy
[unres.git] / source / unres / src_MD-M / energy_p_new_barrier.F
1       subroutine etotal(energia)
2       implicit real*8 (a-h,o-z)
3       include 'DIMENSIONS'
4 #ifndef ISNAN
5       external proc_proc
6 #ifdef WINPGI
7 cMS$ATTRIBUTES C ::  proc_proc
8 #endif
9 #endif
10 #ifdef MPI
11       include "mpif.h"
12       double precision weights_(n_ene)
13 #endif
14       include 'COMMON.SETUP'
15       include 'COMMON.IOUNITS'
16       double precision energia(0:n_ene)
17       include 'COMMON.LOCAL'
18       include 'COMMON.FFIELD'
19       include 'COMMON.DERIV'
20       include 'COMMON.INTERACT'
21       include 'COMMON.SBRIDGE'
22       include 'COMMON.CHAIN'
23       include 'COMMON.VAR'
24       include 'COMMON.MD'
25       include 'COMMON.CONTROL'
26       include 'COMMON.TIME1'
27 #ifdef MPI      
28 c      print*,"ETOTAL Processor",fg_rank," absolute rank",myrank,
29 c     & " nfgtasks",nfgtasks
30       if (nfgtasks.gt.1) then
31         time00=MPI_Wtime()
32 C FG slaves call the following matching MPI_Bcast in ERGASTULUM
33         if (fg_rank.eq.0) then
34           call MPI_Bcast(0,1,MPI_INTEGER,king,FG_COMM,IERROR)
35 c          print *,"Processor",myrank," BROADCAST iorder"
36 C FG master sets up the WEIGHTS_ array which will be broadcast to the 
37 C FG slaves as WEIGHTS array.
38           weights_(1)=wsc
39           weights_(2)=wscp
40           weights_(3)=welec
41           weights_(4)=wcorr
42           weights_(5)=wcorr5
43           weights_(6)=wcorr6
44           weights_(7)=wel_loc
45           weights_(8)=wturn3
46           weights_(9)=wturn4
47           weights_(10)=wturn6
48           weights_(11)=wang
49           weights_(12)=wscloc
50           weights_(13)=wtor
51           weights_(14)=wtor_d
52           weights_(15)=wstrain
53           weights_(16)=wvdwpp
54           weights_(17)=wbond
55           weights_(18)=scal14
56           weights_(21)=wsccor
57 C FG Master broadcasts the WEIGHTS_ array
58           call MPI_Bcast(weights_(1),n_ene,
59      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
60         else
61 C FG slaves receive the WEIGHTS array
62           call MPI_Bcast(weights(1),n_ene,
63      &        MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
64           wsc=weights(1)
65           wscp=weights(2)
66           welec=weights(3)
67           wcorr=weights(4)
68           wcorr5=weights(5)
69           wcorr6=weights(6)
70           wel_loc=weights(7)
71           wturn3=weights(8)
72           wturn4=weights(9)
73           wturn6=weights(10)
74           wang=weights(11)
75           wscloc=weights(12)
76           wtor=weights(13)
77           wtor_d=weights(14)
78           wstrain=weights(15)
79           wvdwpp=weights(16)
80           wbond=weights(17)
81           scal14=weights(18)
82           wsccor=weights(21)
83         endif
84         time_Bcast=time_Bcast+MPI_Wtime()-time00
85         time_Bcastw=time_Bcastw+MPI_Wtime()-time00
86 c        call chainbuild_cart
87       endif
88 c      print *,'Processor',myrank,' calling etotal ipot=',ipot
89 c      print *,'Processor',myrank,' nnt=',nnt,' nct=',nct
90 #else
91 c      if (modecalc.eq.12.or.modecalc.eq.14) then
92 c        call int_from_cart1(.false.)
93 c      endif
94 #endif     
95 #ifdef TIMING
96       time00=MPI_Wtime()
97 #endif
98
99 C Compute the side-chain and electrostatic interaction energy
100 C
101       goto (101,102,103,104,105,106) ipot
102 C Lennard-Jones potential.
103   101 call elj(evdw)
104 cd    print '(a)','Exit ELJ'
105       goto 107
106 C Lennard-Jones-Kihara potential (shifted).
107   102 call eljk(evdw)
108       goto 107
109 C Berne-Pechukas potential (dilated LJ, angular dependence).
110   103 call ebp(evdw)
111       goto 107
112 C Gay-Berne potential (shifted LJ, angular dependence).
113   104 call egb(evdw)
114       goto 107
115 C Gay-Berne-Vorobjev potential (shifted LJ, angular dependence).
116   105 call egbv(evdw)
117       goto 107
118 C Soft-sphere potential
119   106 call e_softsphere(evdw)
120 C
121 C Calculate electrostatic (H-bonding) energy of the main chain.
122 C
123   107 continue
124 c      print *,"Processor",myrank," computed USCSC"
125 #ifdef TIMING
126       time01=MPI_Wtime() 
127 #endif
128       call vec_and_deriv
129 #ifdef TIMING
130       time_vec=time_vec+MPI_Wtime()-time01
131 #endif
132 c      print *,"Processor",myrank," left VEC_AND_DERIV"
133       if (ipot.lt.6) then
134 #ifdef SPLITELE
135          if (welec.gt.0d0.or.wvdwpp.gt.0d0.or.wel_loc.gt.0d0.or.
136      &       wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
137      &       .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
138      &       .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
139 #else
140          if (welec.gt.0d0.or.wel_loc.gt.0d0.or.
141      &       wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
142      &       .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0 
143      &       .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
144 #endif
145             call eelec(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
146          else
147             ees=0.0d0
148             evdw1=0.0d0
149             eel_loc=0.0d0
150             eello_turn3=0.0d0
151             eello_turn4=0.0d0
152          endif
153       else
154 c        write (iout,*) "Soft-spheer ELEC potential"
155         call eelec_soft_sphere(ees,evdw1,eel_loc,eello_turn3,
156      &   eello_turn4)
157       endif
158 c      print *,"Processor",myrank," computed UELEC"
159 C
160 C Calculate excluded-volume interaction energy between peptide groups
161 C and side chains.
162 C
163       if (ipot.lt.6) then
164        if(wscp.gt.0d0) then
165         call escp(evdw2,evdw2_14)
166        else
167         evdw2=0
168         evdw2_14=0
169        endif
170       else
171 c        write (iout,*) "Soft-sphere SCP potential"
172         call escp_soft_sphere(evdw2,evdw2_14)
173       endif
174 c
175 c Calculate the bond-stretching energy
176 c
177       call ebond(estr)
178
179 C Calculate the disulfide-bridge and other energy and the contributions
180 C from other distance constraints.
181 cd    print *,'Calling EHPB'
182       call edis(ehpb)
183 cd    print *,'EHPB exitted succesfully.'
184 C
185 C Calculate the virtual-bond-angle energy.
186 C
187       if (wang.gt.0d0) then
188         call ebend(ebe)
189       else
190         ebe=0
191       endif
192 c      print *,"Processor",myrank," computed UB"
193 C
194 C Calculate the SC local energy.
195 C
196       call esc(escloc)
197 c      print *,"Processor",myrank," computed USC"
198 C
199 C Calculate the virtual-bond torsional energy.
200 C
201 cd    print *,'nterm=',nterm
202       if (wtor.gt.0) then
203        call etor(etors,edihcnstr)
204       else
205        etors=0
206        edihcnstr=0
207       endif
208 c      print *,"Processor",myrank," computed Utor"
209 C
210 C 6/23/01 Calculate double-torsional energy
211 C
212       if (wtor_d.gt.0) then
213        call etor_d(etors_d)
214       else
215        etors_d=0
216       endif
217 c      print *,"Processor",myrank," computed Utord"
218 C
219 C 21/5/07 Calculate local sicdechain correlation energy
220 C
221       if (wsccor.gt.0.0d0) then
222         call eback_sc_corr(esccor)
223       else
224         esccor=0.0d0
225       endif
226 c      print *,"Processor",myrank," computed Usccorr"
227
228 C 12/1/95 Multi-body terms
229 C
230       n_corr=0
231       n_corr1=0
232       if ((wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0 
233      &    .or. wturn6.gt.0.0d0) .and. ipot.lt.6) then
234          call multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,n_corr1)
235 cd         write(2,*)'multibody_eello n_corr=',n_corr,' n_corr1=',n_corr1,
236 cd     &" ecorr",ecorr," ecorr5",ecorr5," ecorr6",ecorr6," eturn6",eturn6
237       else
238          ecorr=0.0d0
239          ecorr5=0.0d0
240          ecorr6=0.0d0
241          eturn6=0.0d0
242       endif
243       if ((wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) .and. ipot.lt.6) then
244          call multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
245 cd         write (iout,*) "multibody_hb ecorr",ecorr
246       endif
247 c      print *,"Processor",myrank," computed Ucorr"
248
249 C If performing constraint dynamics, call the constraint energy
250 C  after the equilibration time
251       if(usampl.and.totT.gt.eq_time) then
252          call EconstrQ   
253          call Econstr_back
254       else
255          Uconst=0.0d0
256          Uconst_back=0.0d0
257       endif
258 #ifdef TIMING
259       time_enecalc=time_enecalc+MPI_Wtime()-time00
260 #endif
261 c      print *,"Processor",myrank," computed Uconstr"
262 #ifdef TIMING
263       time00=MPI_Wtime()
264 #endif
265 c
266 C Sum the energies
267 C
268       energia(1)=evdw
269 #ifdef SCP14
270       energia(2)=evdw2-evdw2_14
271       energia(18)=evdw2_14
272 #else
273       energia(2)=evdw2
274       energia(18)=0.0d0
275 #endif
276 #ifdef SPLITELE
277       energia(3)=ees
278       energia(16)=evdw1
279 #else
280       energia(3)=ees+evdw1
281       energia(16)=0.0d0
282 #endif
283       energia(4)=ecorr
284       energia(5)=ecorr5
285       energia(6)=ecorr6
286       energia(7)=eel_loc
287       energia(8)=eello_turn3
288       energia(9)=eello_turn4
289       energia(10)=eturn6
290       energia(11)=ebe
291       energia(12)=escloc
292       energia(13)=etors
293       energia(14)=etors_d
294       energia(15)=ehpb
295       energia(19)=edihcnstr
296       energia(17)=estr
297       energia(20)=Uconst+Uconst_back
298       energia(21)=esccor
299 c      print *," Processor",myrank," calls SUM_ENERGY"
300       call sum_energy(energia,.true.)
301 c      print *," Processor",myrank," left SUM_ENERGY"
302 #ifdef TIMING
303       time_sumene=time_sumene+MPI_Wtime()-time00
304 #endif
305       return
306       end
307 c-------------------------------------------------------------------------------
308       subroutine sum_energy(energia,reduce)
309       implicit real*8 (a-h,o-z)
310       include 'DIMENSIONS'
311 #ifndef ISNAN
312       external proc_proc
313 #ifdef WINPGI
314 cMS$ATTRIBUTES C ::  proc_proc
315 #endif
316 #endif
317 #ifdef MPI
318       include "mpif.h"
319 #endif
320       include 'COMMON.SETUP'
321       include 'COMMON.IOUNITS'
322       double precision energia(0:n_ene),enebuff(0:n_ene+1)
323       include 'COMMON.FFIELD'
324       include 'COMMON.DERIV'
325       include 'COMMON.INTERACT'
326       include 'COMMON.SBRIDGE'
327       include 'COMMON.CHAIN'
328       include 'COMMON.VAR'
329       include 'COMMON.CONTROL'
330       include 'COMMON.TIME1'
331       logical reduce
332 #ifdef MPI
333       if (nfgtasks.gt.1 .and. reduce) then
334 #ifdef DEBUG
335         write (iout,*) "energies before REDUCE"
336         call enerprint(energia)
337         call flush(iout)
338 #endif
339         do i=0,n_ene
340           enebuff(i)=energia(i)
341         enddo
342         time00=MPI_Wtime()
343         call MPI_Barrier(FG_COMM,IERR)
344         time_barrier_e=time_barrier_e+MPI_Wtime()-time00
345         time00=MPI_Wtime()
346         call MPI_Reduce(enebuff(0),energia(0),n_ene+1,
347      &    MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
348 #ifdef DEBUG
349         write (iout,*) "energies after REDUCE"
350         call enerprint(energia)
351         call flush(iout)
352 #endif
353         time_Reduce=time_Reduce+MPI_Wtime()-time00
354       endif
355       if (fg_rank.eq.0) then
356 #endif
357       evdw=energia(1)
358 #ifdef SCP14
359       evdw2=energia(2)+energia(18)
360       evdw2_14=energia(18)
361 #else
362       evdw2=energia(2)
363 #endif
364 #ifdef SPLITELE
365       ees=energia(3)
366       evdw1=energia(16)
367 #else
368       ees=energia(3)
369       evdw1=0.0d0
370 #endif
371       ecorr=energia(4)
372       ecorr5=energia(5)
373       ecorr6=energia(6)
374       eel_loc=energia(7)
375       eello_turn3=energia(8)
376       eello_turn4=energia(9)
377       eturn6=energia(10)
378       ebe=energia(11)
379       escloc=energia(12)
380       etors=energia(13)
381       etors_d=energia(14)
382       ehpb=energia(15)
383       edihcnstr=energia(19)
384       estr=energia(17)
385       Uconst=energia(20)
386       esccor=energia(21)
387 #ifdef SPLITELE
388       etot=wsc*evdw+wscp*evdw2+welec*ees+wvdwpp*evdw1
389      & +wang*ebe+wtor*etors+wscloc*escloc
390      & +wstrain*ehpb+nss*ebr+wcorr*ecorr+wcorr5*ecorr5
391      & +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3
392      & +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d
393      & +wbond*estr+Uconst+wsccor*esccor
394 #else
395       etot=wsc*evdw+wscp*evdw2+welec*(ees+evdw1)
396      & +wang*ebe+wtor*etors+wscloc*escloc
397      & +wstrain*ehpb+nss*ebr+wcorr*ecorr+wcorr5*ecorr5
398      & +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3
399      & +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d
400      & +wbond*estr+Uconst+wsccor*esccor
401 #endif
402       energia(0)=etot
403 c detecting NaNQ
404 #ifdef ISNAN
405 #ifdef AIX
406       if (isnan(etot).ne.0) energia(0)=1.0d+99
407 #else
408       if (isnan(etot)) energia(0)=1.0d+99
409 #endif
410 #else
411       i=0
412 #ifdef WINPGI
413       idumm=proc_proc(etot,i)
414 #else
415       call proc_proc(etot,i)
416 #endif
417       if(i.eq.1)energia(0)=1.0d+99
418 #endif
419 #ifdef MPI
420       endif
421 #endif
422       return
423       end
424 c-------------------------------------------------------------------------------
425       subroutine sum_gradient
426       implicit real*8 (a-h,o-z)
427       include 'DIMENSIONS'
428 #ifndef ISNAN
429       external proc_proc
430 #ifdef WINPGI
431 cMS$ATTRIBUTES C ::  proc_proc
432 #endif
433 #endif
434 #ifdef MPI
435       include 'mpif.h'
436       double precision gradbufc(3,maxres),gradbufx(3,maxres),
437      &  glocbuf(4*maxres),gradbufc_sum(3,maxres),gloc_scbuf(3,maxres)
438 #endif
439       include 'COMMON.SETUP'
440       include 'COMMON.IOUNITS'
441       include 'COMMON.FFIELD'
442       include 'COMMON.DERIV'
443       include 'COMMON.INTERACT'
444       include 'COMMON.SBRIDGE'
445       include 'COMMON.CHAIN'
446       include 'COMMON.VAR'
447       include 'COMMON.CONTROL'
448       include 'COMMON.TIME1'
449       include 'COMMON.MAXGRAD'
450       include 'COMMON.SCCOR'
451 #ifdef TIMING
452       time01=MPI_Wtime()
453 #endif
454 #ifdef DEBUG
455       write (iout,*) "sum_gradient gvdwc, gvdwx"
456       do i=1,nres
457         write (iout,'(i3,3f10.5,5x,3f10.5,5x,f10.5)') 
458      &   i,(gvdwx(j,i),j=1,3),(gvdwc(j,i),j=1,3)
459       enddo
460       call flush(iout)
461 #endif
462 #ifdef MPI
463 C FG slaves call the following matching MPI_Bcast in ERGASTULUM
464         if (nfgtasks.gt.1 .and. fg_rank.eq.0) 
465      &    call MPI_Bcast(1,1,MPI_INTEGER,king,FG_COMM,IERROR)
466 #endif
467 C
468 C 9/29/08 AL Transform parts of gradients in site coordinates to the gradient
469 C            in virtual-bond-vector coordinates
470 C
471 #ifdef DEBUG
472 c      write (iout,*) "gel_loc gel_loc_long and gel_loc_loc"
473 c      do i=1,nres-1
474 c        write (iout,'(i5,3f10.5,2x,3f10.5,2x,f10.5)') 
475 c     &   i,(gel_loc(j,i),j=1,3),(gel_loc_long(j,i),j=1,3),gel_loc_loc(i)
476 c      enddo
477 c      write (iout,*) "gel_loc_tur3 gel_loc_turn4"
478 c      do i=1,nres-1
479 c        write (iout,'(i5,3f10.5,2x,f10.5)') 
480 c     &  i,(gcorr4_turn(j,i),j=1,3),gel_loc_turn4(i)
481 c      enddo
482       write (iout,*) "gradcorr5 gradcorr5_long gradcorr5_loc"
483       do i=1,nres
484         write (iout,'(i3,3f10.5,5x,3f10.5,5x,f10.5)') 
485      &   i,(gradcorr5(j,i),j=1,3),(gradcorr5_long(j,i),j=1,3),
486      &   g_corr5_loc(i)
487       enddo
488       call flush(iout)
489 #endif
490 #ifdef SPLITELE
491       do i=1,nct
492         do j=1,3
493           gradbufc(j,i)=wsc*gvdwc(j,i)+
494      &                wscp*(gvdwc_scp(j,i)+gvdwc_scpp(j,i))+
495      &                welec*gelc_long(j,i)+wvdwpp*gvdwpp(j,i)+
496      &                wel_loc*gel_loc_long(j,i)+
497      &                wcorr*gradcorr_long(j,i)+
498      &                wcorr5*gradcorr5_long(j,i)+
499      &                wcorr6*gradcorr6_long(j,i)+
500      &                wturn6*gcorr6_turn_long(j,i)+
501      &                wstrain*ghpbc(j,i)
502         enddo
503       enddo 
504 #else
505       do i=1,nct
506         do j=1,3
507           gradbufc(j,i)=wsc*gvdwc(j,i)+
508      &                wscp*(gvdwc_scp(j,i)+gvdwc_scpp(j,i))+
509      &                welec*gelc_long(j,i)+
510      &                wbond*gradb(j,i)+
511      &                wel_loc*gel_loc_long(j,i)+
512      &                wcorr*gradcorr_long(j,i)+
513      &                wcorr5*gradcorr5_long(j,i)+
514      &                wcorr6*gradcorr6_long(j,i)+
515      &                wturn6*gcorr6_turn_long(j,i)+
516      &                wstrain*ghpbc(j,i)
517         enddo
518       enddo 
519 #endif
520 #ifdef MPI
521       if (nfgtasks.gt.1) then
522       time00=MPI_Wtime()
523 #ifdef DEBUG
524       write (iout,*) "gradbufc before allreduce"
525       do i=1,nres
526         write (iout,'(i3,3f10.5)') i,(gradbufc(j,i),j=1,3)
527       enddo
528       call flush(iout)
529 #endif
530       do i=1,nres
531         do j=1,3
532           gradbufc_sum(j,i)=gradbufc(j,i)
533         enddo
534       enddo
535 c      call MPI_AllReduce(gradbufc(1,1),gradbufc_sum(1,1),3*nres,
536 c     &    MPI_DOUBLE_PRECISION,MPI_SUM,FG_COMM,IERR)
537 c      time_reduce=time_reduce+MPI_Wtime()-time00
538 #ifdef DEBUG
539 c      write (iout,*) "gradbufc_sum after allreduce"
540 c      do i=1,nres
541 c        write (iout,'(i3,3f10.5)') i,(gradbufc_sum(j,i),j=1,3)
542 c      enddo
543 c      call flush(iout)
544 #endif
545 #ifdef TIMING
546 c      time_allreduce=time_allreduce+MPI_Wtime()-time00
547 #endif
548       do i=nnt,nres
549         do k=1,3
550           gradbufc(k,i)=0.0d0
551         enddo
552       enddo
553 #ifdef DEBUG
554       write (iout,*) "igrad_start",igrad_start," igrad_end",igrad_end
555       write (iout,*) (i," jgrad_start",jgrad_start(i),
556      &                  " jgrad_end  ",jgrad_end(i),
557      &                  i=igrad_start,igrad_end)
558 #endif
559 c
560 c Obsolete and inefficient code; we can make the effort O(n) and, therefore,
561 c do not parallelize this part.
562 c
563 c      do i=igrad_start,igrad_end
564 c        do j=jgrad_start(i),jgrad_end(i)
565 c          do k=1,3
566 c            gradbufc(k,i)=gradbufc(k,i)+gradbufc_sum(k,j)
567 c          enddo
568 c        enddo
569 c      enddo
570       do j=1,3
571         gradbufc(j,nres-1)=gradbufc_sum(j,nres)
572       enddo
573       do i=nres-2,nnt,-1
574         do j=1,3
575           gradbufc(j,i)=gradbufc(j,i+1)+gradbufc_sum(j,i+1)
576         enddo
577       enddo
578 #ifdef DEBUG
579       write (iout,*) "gradbufc after summing"
580       do i=1,nres
581         write (iout,'(i3,3f10.5)') i,(gradbufc(j,i),j=1,3)
582       enddo
583       call flush(iout)
584 #endif
585       else
586 #endif
587 #ifdef DEBUG
588       write (iout,*) "gradbufc"
589       do i=1,nres
590         write (iout,'(i3,3f10.5)') i,(gradbufc(j,i),j=1,3)
591       enddo
592       call flush(iout)
593 #endif
594       do i=1,nres
595         do j=1,3
596           gradbufc_sum(j,i)=gradbufc(j,i)
597           gradbufc(j,i)=0.0d0
598         enddo
599       enddo
600       do j=1,3
601         gradbufc(j,nres-1)=gradbufc_sum(j,nres)
602       enddo
603       do i=nres-2,nnt,-1
604         do j=1,3
605           gradbufc(j,i)=gradbufc(j,i+1)+gradbufc_sum(j,i+1)
606         enddo
607       enddo
608 c      do i=nnt,nres-1
609 c        do k=1,3
610 c          gradbufc(k,i)=0.0d0
611 c        enddo
612 c        do j=i+1,nres
613 c          do k=1,3
614 c            gradbufc(k,i)=gradbufc(k,i)+gradbufc(k,j)
615 c          enddo
616 c        enddo
617 c      enddo
618 #ifdef DEBUG
619       write (iout,*) "gradbufc after summing"
620       do i=1,nres
621         write (iout,'(i3,3f10.5)') i,(gradbufc(j,i),j=1,3)
622       enddo
623       call flush(iout)
624 #endif
625 #ifdef MPI
626       endif
627 #endif
628       do k=1,3
629         gradbufc(k,nres)=0.0d0
630       enddo
631       do i=1,nct
632         do j=1,3
633 #ifdef SPLITELE
634           gradc(j,i,icg)=gradbufc(j,i)+welec*gelc(j,i)+
635      &                wel_loc*gel_loc(j,i)+
636      &                0.5d0*(wscp*gvdwc_scpp(j,i)+
637      &                welec*gelc_long(j,i)+wvdwpp*gvdwpp(j,i)+
638      &                wel_loc*gel_loc_long(j,i)+
639      &                wcorr*gradcorr_long(j,i)+
640      &                wcorr5*gradcorr5_long(j,i)+
641      &                wcorr6*gradcorr6_long(j,i)+
642      &                wturn6*gcorr6_turn_long(j,i))+
643      &                wbond*gradb(j,i)+
644      &                wcorr*gradcorr(j,i)+
645      &                wturn3*gcorr3_turn(j,i)+
646      &                wturn4*gcorr4_turn(j,i)+
647      &                wcorr5*gradcorr5(j,i)+
648      &                wcorr6*gradcorr6(j,i)+
649      &                wturn6*gcorr6_turn(j,i)+
650      &                wsccor*gsccorc(j,i)
651      &               +wscloc*gscloc(j,i)
652 #else
653           gradc(j,i,icg)=gradbufc(j,i)+welec*gelc(j,i)+
654      &                wel_loc*gel_loc(j,i)+
655      &                0.5d0*(wscp*gvdwc_scpp(j,i)+
656      &                welec*gelc_long(j,i)
657      &                wel_loc*gel_loc_long(j,i)+
658      &                wcorr*gcorr_long(j,i)+
659      &                wcorr5*gradcorr5_long(j,i)+
660      &                wcorr6*gradcorr6_long(j,i)+
661      &                wturn6*gcorr6_turn_long(j,i))+
662      &                wbond*gradb(j,i)+
663      &                wcorr*gradcorr(j,i)+
664      &                wturn3*gcorr3_turn(j,i)+
665      &                wturn4*gcorr4_turn(j,i)+
666      &                wcorr5*gradcorr5(j,i)+
667      &                wcorr6*gradcorr6(j,i)+
668      &                wturn6*gcorr6_turn(j,i)+
669      &                wsccor*gsccorc(j,i)
670      &               +wscloc*gscloc(j,i)
671 #endif
672           gradx(j,i,icg)=wsc*gvdwx(j,i)+wscp*gradx_scp(j,i)+
673      &                  wbond*gradbx(j,i)+
674      &                  wstrain*ghpbx(j,i)+wcorr*gradxorr(j,i)+
675      &                  wsccor*gsccorx(j,i)
676      &                 +wscloc*gsclocx(j,i)
677         enddo
678       enddo 
679 #ifdef DEBUG
680       write (iout,*) "gloc before adding corr"
681       do i=1,4*nres
682         write (iout,*) i,gloc(i,icg)
683       enddo
684 #endif
685       do i=1,nres-3
686         gloc(i,icg)=gloc(i,icg)+wcorr*gcorr_loc(i)
687      &   +wcorr5*g_corr5_loc(i)
688      &   +wcorr6*g_corr6_loc(i)
689      &   +wturn4*gel_loc_turn4(i)
690      &   +wturn3*gel_loc_turn3(i)
691      &   +wturn6*gel_loc_turn6(i)
692      &   +wel_loc*gel_loc_loc(i)
693       enddo
694 #ifdef DEBUG
695       write (iout,*) "gloc after adding corr"
696       do i=1,4*nres
697         write (iout,*) i,gloc(i,icg)
698       enddo
699 #endif
700 #ifdef MPI
701       if (nfgtasks.gt.1) then
702         do j=1,3
703           do i=1,nres
704             gradbufc(j,i)=gradc(j,i,icg)
705             gradbufx(j,i)=gradx(j,i,icg)
706           enddo
707         enddo
708         do i=1,4*nres
709           glocbuf(i)=gloc(i,icg)
710         enddo
711 #define DEBUG
712 #ifdef DEBUG
713       write (iout,*) "gloc_sc before reduce"
714       do i=1,nres
715        do j=1,1
716         write (iout,*) i,j,gloc_sc(j,i,icg)
717        enddo
718       enddo
719 #endif
720 #undef DEBUG
721         do i=1,nres
722          do j=1,3
723           gloc_scbuf(j,i)=gloc_sc(j,i,icg)
724          enddo
725         enddo
726         time00=MPI_Wtime()
727         call MPI_Barrier(FG_COMM,IERR)
728         time_barrier_g=time_barrier_g+MPI_Wtime()-time00
729         time00=MPI_Wtime()
730         call MPI_Reduce(gradbufc(1,1),gradc(1,1,icg),3*nres,
731      &    MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
732         call MPI_Reduce(gradbufx(1,1),gradx(1,1,icg),3*nres,
733      &    MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
734         call MPI_Reduce(glocbuf(1),gloc(1,icg),4*nres,
735      &    MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
736         time_reduce=time_reduce+MPI_Wtime()-time00
737         call MPI_Reduce(gloc_scbuf(1,1),gloc_sc(1,1,icg),3*nres,
738      &    MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
739         time_reduce=time_reduce+MPI_Wtime()-time00
740 #define DEBUG
741 #ifdef DEBUG
742       write (iout,*) "gloc_sc after reduce"
743       do i=1,nres
744        do j=1,1
745         write (iout,*) i,j,gloc_sc(j,i,icg)
746        enddo
747       enddo
748 #endif
749 #undef DEBUG
750 #ifdef DEBUG
751       write (iout,*) "gloc after reduce"
752       do i=1,4*nres
753         write (iout,*) i,gloc(i,icg)
754       enddo
755 #endif
756       endif
757 #endif
758       if (gnorm_check) then
759 c
760 c Compute the maximum elements of the gradient
761 c
762       gvdwc_max=0.0d0
763       gvdwc_scp_max=0.0d0
764       gelc_max=0.0d0
765       gvdwpp_max=0.0d0
766       gradb_max=0.0d0
767       ghpbc_max=0.0d0
768       gradcorr_max=0.0d0
769       gel_loc_max=0.0d0
770       gcorr3_turn_max=0.0d0
771       gcorr4_turn_max=0.0d0
772       gradcorr5_max=0.0d0
773       gradcorr6_max=0.0d0
774       gcorr6_turn_max=0.0d0
775       gsccorc_max=0.0d0
776       gscloc_max=0.0d0
777       gvdwx_max=0.0d0
778       gradx_scp_max=0.0d0
779       ghpbx_max=0.0d0
780       gradxorr_max=0.0d0
781       gsccorx_max=0.0d0
782       gsclocx_max=0.0d0
783       do i=1,nct
784         gvdwc_norm=dsqrt(scalar(gvdwc(1,i),gvdwc(1,i)))
785         if (gvdwc_norm.gt.gvdwc_max) gvdwc_max=gvdwc_norm
786         gvdwc_scp_norm=dsqrt(scalar(gvdwc_scp(1,i),gvdwc_scp(1,i)))
787         if (gvdwc_scp_norm.gt.gvdwc_scp_max) 
788      &   gvdwc_scp_max=gvdwc_scp_norm
789         gelc_norm=dsqrt(scalar(gelc(1,i),gelc(1,i)))
790         if (gelc_norm.gt.gelc_max) gelc_max=gelc_norm
791         gvdwpp_norm=dsqrt(scalar(gvdwpp(1,i),gvdwpp(1,i)))
792         if (gvdwpp_norm.gt.gvdwpp_max) gvdwpp_max=gvdwpp_norm
793         gradb_norm=dsqrt(scalar(gradb(1,i),gradb(1,i)))
794         if (gradb_norm.gt.gradb_max) gradb_max=gradb_norm
795         ghpbc_norm=dsqrt(scalar(ghpbc(1,i),ghpbc(1,i)))
796         if (ghpbc_norm.gt.ghpbc_max) ghpbc_max=ghpbc_norm
797         gradcorr_norm=dsqrt(scalar(gradcorr(1,i),gradcorr(1,i)))
798         if (gradcorr_norm.gt.gradcorr_max) gradcorr_max=gradcorr_norm
799         gel_loc_norm=dsqrt(scalar(gel_loc(1,i),gel_loc(1,i)))
800         if (gel_loc_norm.gt.gel_loc_max) gel_loc_max=gel_loc_norm
801         gcorr3_turn_norm=dsqrt(scalar(gcorr3_turn(1,i),
802      &    gcorr3_turn(1,i)))
803         if (gcorr3_turn_norm.gt.gcorr3_turn_max) 
804      &    gcorr3_turn_max=gcorr3_turn_norm
805         gcorr4_turn_norm=dsqrt(scalar(gcorr4_turn(1,i),
806      &    gcorr4_turn(1,i)))
807         if (gcorr4_turn_norm.gt.gcorr4_turn_max) 
808      &    gcorr4_turn_max=gcorr4_turn_norm
809         gradcorr5_norm=dsqrt(scalar(gradcorr5(1,i),gradcorr5(1,i)))
810         if (gradcorr5_norm.gt.gradcorr5_max) 
811      &    gradcorr5_max=gradcorr5_norm
812         gradcorr6_norm=dsqrt(scalar(gradcorr6(1,i),gradcorr6(1,i)))
813         if (gradcorr6_norm.gt.gradcorr6_max) gcorr6_max=gradcorr6_norm
814         gcorr6_turn_norm=dsqrt(scalar(gcorr6_turn(1,i),
815      &    gcorr6_turn(1,i)))
816         if (gcorr6_turn_norm.gt.gcorr6_turn_max) 
817      &    gcorr6_turn_max=gcorr6_turn_norm
818         gsccorr_norm=dsqrt(scalar(gsccorc(1,i),gsccorc(1,i)))
819         if (gsccorr_norm.gt.gsccorr_max) gsccorr_max=gsccorr_norm
820         gscloc_norm=dsqrt(scalar(gscloc(1,i),gscloc(1,i)))
821         if (gscloc_norm.gt.gscloc_max) gscloc_max=gscloc_norm
822         gvdwx_norm=dsqrt(scalar(gvdwx(1,i),gvdwx(1,i)))
823         if (gvdwx_norm.gt.gvdwx_max) gvdwx_max=gvdwx_norm
824         gradx_scp_norm=dsqrt(scalar(gradx_scp(1,i),gradx_scp(1,i)))
825         if (gradx_scp_norm.gt.gradx_scp_max) 
826      &    gradx_scp_max=gradx_scp_norm
827         ghpbx_norm=dsqrt(scalar(ghpbx(1,i),ghpbx(1,i)))
828         if (ghpbx_norm.gt.ghpbx_max) ghpbx_max=ghpbx_norm
829         gradxorr_norm=dsqrt(scalar(gradxorr(1,i),gradxorr(1,i)))
830         if (gradxorr_norm.gt.gradxorr_max) gradxorr_max=gradxorr_norm
831         gsccorrx_norm=dsqrt(scalar(gsccorx(1,i),gsccorx(1,i)))
832         if (gsccorrx_norm.gt.gsccorrx_max) gsccorrx_max=gsccorrx_norm
833         gsclocx_norm=dsqrt(scalar(gsclocx(1,i),gsclocx(1,i)))
834         if (gsclocx_norm.gt.gsclocx_max) gsclocx_max=gsclocx_norm
835       enddo 
836       if (gradout) then
837 #ifdef AIX
838         open(istat,file=statname,position="append")
839 #else
840         open(istat,file=statname,access="append")
841 #endif
842         write (istat,'(1h#,21f10.2)') gvdwc_max,gvdwc_scp_max,
843      &     gelc_max,gvdwpp_max,gradb_max,ghpbc_max,
844      &     gradcorr_max,gel_loc_max,gcorr3_turn_max,gcorr4_turn_max,
845      &     gradcorr5_max,gradcorr6_max,gcorr6_turn_max,gsccorc_max,
846      &     gscloc_max,gvdwx_max,gradx_scp_max,ghpbx_max,gradxorr_max,
847      &     gsccorx_max,gsclocx_max
848         close(istat)
849         if (gvdwc_max.gt.1.0d4) then
850           write (iout,*) "gvdwc gvdwx gradb gradbx"
851           do i=nnt,nct
852             write(iout,'(i5,4(3f10.2,5x))') i,(gvdwc(j,i),gvdwx(j,i),
853      &        gradb(j,i),gradbx(j,i),j=1,3)
854           enddo
855           call pdbout(0.0d0,'cipiszcze',iout)
856           call flush(iout)
857         endif
858       endif
859       endif
860 #ifdef DEBUG
861       write (iout,*) "gradc gradx gloc"
862       do i=1,nres
863         write (iout,'(i5,3f10.5,5x,3f10.5,5x,f10.5)') 
864      &   i,(gradc(j,i,icg),j=1,3),(gradx(j,i,icg),j=1,3),gloc(i,icg)
865       enddo 
866 #endif
867 #ifdef TIMING
868       time_sumgradient=time_sumgradient+MPI_Wtime()-time01
869 #endif
870       return
871       end
872 c-------------------------------------------------------------------------------
873       subroutine rescale_weights(t_bath)
874       implicit real*8 (a-h,o-z)
875       include 'DIMENSIONS'
876       include 'COMMON.IOUNITS'
877       include 'COMMON.FFIELD'
878       include 'COMMON.SBRIDGE'
879       double precision kfac /2.4d0/
880       double precision x,x2,x3,x4,x5,licznik /1.12692801104297249644/
881 c      facT=temp0/t_bath
882 c      facT=2*temp0/(t_bath+temp0)
883       if (rescale_mode.eq.0) then
884         facT=1.0d0
885         facT2=1.0d0
886         facT3=1.0d0
887         facT4=1.0d0
888         facT5=1.0d0
889       else if (rescale_mode.eq.1) then
890         facT=kfac/(kfac-1.0d0+t_bath/temp0)
891         facT2=kfac**2/(kfac**2-1.0d0+(t_bath/temp0)**2)
892         facT3=kfac**3/(kfac**3-1.0d0+(t_bath/temp0)**3)
893         facT4=kfac**4/(kfac**4-1.0d0+(t_bath/temp0)**4)
894         facT5=kfac**5/(kfac**5-1.0d0+(t_bath/temp0)**5)
895       else if (rescale_mode.eq.2) then
896         x=t_bath/temp0
897         x2=x*x
898         x3=x2*x
899         x4=x3*x
900         x5=x4*x
901         facT=licznik/dlog(dexp(x)+dexp(-x))
902         facT2=licznik/dlog(dexp(x2)+dexp(-x2))
903         facT3=licznik/dlog(dexp(x3)+dexp(-x3))
904         facT4=licznik/dlog(dexp(x4)+dexp(-x4))
905         facT5=licznik/dlog(dexp(x5)+dexp(-x5))
906       else
907         write (iout,*) "Wrong RESCALE_MODE",rescale_mode
908         write (*,*) "Wrong RESCALE_MODE",rescale_mode
909 #ifdef MPI
910        call MPI_Finalize(MPI_COMM_WORLD,IERROR)
911 #endif
912        stop 555
913       endif
914       welec=weights(3)*fact
915       wcorr=weights(4)*fact3
916       wcorr5=weights(5)*fact4
917       wcorr6=weights(6)*fact5
918       wel_loc=weights(7)*fact2
919       wturn3=weights(8)*fact2
920       wturn4=weights(9)*fact3
921       wturn6=weights(10)*fact5
922       wtor=weights(13)*fact
923       wtor_d=weights(14)*fact2
924       wsccor=weights(21)*fact
925
926       return
927       end
928 C------------------------------------------------------------------------
929       subroutine enerprint(energia)
930       implicit real*8 (a-h,o-z)
931       include 'DIMENSIONS'
932       include 'COMMON.IOUNITS'
933       include 'COMMON.FFIELD'
934       include 'COMMON.SBRIDGE'
935       include 'COMMON.MD'
936       double precision energia(0:n_ene)
937       etot=energia(0)
938       evdw=energia(1)
939       evdw2=energia(2)
940 #ifdef SCP14
941       evdw2=energia(2)+energia(18)
942 #else
943       evdw2=energia(2)
944 #endif
945       ees=energia(3)
946 #ifdef SPLITELE
947       evdw1=energia(16)
948 #endif
949       ecorr=energia(4)
950       ecorr5=energia(5)
951       ecorr6=energia(6)
952       eel_loc=energia(7)
953       eello_turn3=energia(8)
954       eello_turn4=energia(9)
955       eello_turn6=energia(10)
956       ebe=energia(11)
957       escloc=energia(12)
958       etors=energia(13)
959       etors_d=energia(14)
960       ehpb=energia(15)
961       edihcnstr=energia(19)
962       estr=energia(17)
963       Uconst=energia(20)
964       esccor=energia(21)
965 #ifdef SPLITELE
966       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,evdw1,wvdwpp,
967      &  estr,wbond,ebe,wang,
968      &  escloc,wscloc,etors,wtor,etors_d,wtor_d,ehpb,wstrain,
969      &  ecorr,wcorr,
970      &  ecorr5,wcorr5,ecorr6,wcorr6,eel_loc,wel_loc,eello_turn3,wturn3,
971      &  eello_turn4,wturn4,eello_turn6,wturn6,esccor,wsccor,
972      &  edihcnstr,ebr*nss,
973      &  Uconst,etot
974    10 format (/'Virtual-chain energies:'//
975      & 'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/
976      & 'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/
977      & 'EES=   ',1pE16.6,' WEIGHT=',1pD16.6,' (p-p)'/
978      & 'EVDWPP=',1pE16.6,' WEIGHT=',1pD16.6,' (p-p VDW)'/
979      & 'ESTR=  ',1pE16.6,' WEIGHT=',1pD16.6,' (stretching)'/
980      & 'EBE=   ',1pE16.6,' WEIGHT=',1pD16.6,' (bending)'/
981      & 'ESC=   ',1pE16.6,' WEIGHT=',1pD16.6,' (SC local)'/
982      & 'ETORS= ',1pE16.6,' WEIGHT=',1pD16.6,' (torsional)'/
983      & 'ETORSD=',1pE16.6,' WEIGHT=',1pD16.6,' (double torsional)'/
984      & 'EHBP=  ',1pE16.6,' WEIGHT=',1pD16.6,
985      & ' (SS bridges & dist. cnstr.)'/
986      & 'ECORR4=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
987      & 'ECORR5=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
988      & 'ECORR6=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
989      & 'EELLO= ',1pE16.6,' WEIGHT=',1pD16.6,' (electrostatic-local)'/
990      & 'ETURN3=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 3rd order)'/
991      & 'ETURN4=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 4th order)'/
992      & 'ETURN6=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 6th order)'/
993      & 'ESCCOR=',1pE16.6,' WEIGHT=',1pD16.6,' (backbone-rotamer corr)'/
994      & 'EDIHC= ',1pE16.6,' (dihedral angle constraints)'/
995      & 'ESS=   ',1pE16.6,' (disulfide-bridge intrinsic energy)'/
996      & 'UCONST= ',1pE16.6,' (Constraint energy)'/ 
997      & 'ETOT=  ',1pE16.6,' (total)')
998 #else
999       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,
1000      &  estr,wbond,ebe,wang,
1001      &  escloc,wscloc,etors,wtor,etors_d,wtor_d,ehpb,wstrain,
1002      &  ecorr,wcorr,
1003      &  ecorr5,wcorr5,ecorr6,wcorr6,eel_loc,wel_loc,eello_turn3,wturn3,
1004      &  eello_turn4,wturn4,eello_turn6,wturn6,esccor,wsccro,edihcnstr,
1005      &  ebr*nss,Uconst,etot
1006    10 format (/'Virtual-chain energies:'//
1007      & 'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/
1008      & 'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/
1009      & 'EES=   ',1pE16.6,' WEIGHT=',1pD16.6,' (p-p)'/
1010      & 'ESTR=  ',1pE16.6,' WEIGHT=',1pD16.6,' (stretching)'/
1011      & 'EBE=   ',1pE16.6,' WEIGHT=',1pD16.6,' (bending)'/
1012      & 'ESC=   ',1pE16.6,' WEIGHT=',1pD16.6,' (SC local)'/
1013      & 'ETORS= ',1pE16.6,' WEIGHT=',1pD16.6,' (torsional)'/
1014      & 'ETORSD=',1pE16.6,' WEIGHT=',1pD16.6,' (double torsional)'/
1015      & 'EHBP=  ',1pE16.6,' WEIGHT=',1pD16.6,
1016      & ' (SS bridges & dist. cnstr.)'/
1017      & 'ECORR4=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
1018      & 'ECORR5=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
1019      & 'ECORR6=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
1020      & 'EELLO= ',1pE16.6,' WEIGHT=',1pD16.6,' (electrostatic-local)'/
1021      & 'ETURN3=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 3rd order)'/
1022      & 'ETURN4=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 4th order)'/
1023      & 'ETURN6=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 6th order)'/
1024      & 'ESCCOR=',1pE16.6,' WEIGHT=',1pD16.6,' (backbone-rotamer corr)'/
1025      & 'EDIHC= ',1pE16.6,' (dihedral angle constraints)'/
1026      & 'ESS=   ',1pE16.6,' (disulfide-bridge intrinsic energy)'/
1027      & 'UCONST=',1pE16.6,' (Constraint energy)'/ 
1028      & 'ETOT=  ',1pE16.6,' (total)')
1029 #endif
1030       return
1031       end
1032 C-----------------------------------------------------------------------
1033       subroutine elj(evdw)
1034 C
1035 C This subroutine calculates the interaction energy of nonbonded side chains
1036 C assuming the LJ potential of interaction.
1037 C
1038       implicit real*8 (a-h,o-z)
1039       include 'DIMENSIONS'
1040       parameter (accur=1.0d-10)
1041       include 'COMMON.GEO'
1042       include 'COMMON.VAR'
1043       include 'COMMON.LOCAL'
1044       include 'COMMON.CHAIN'
1045       include 'COMMON.DERIV'
1046       include 'COMMON.INTERACT'
1047       include 'COMMON.TORSION'
1048       include 'COMMON.SBRIDGE'
1049       include 'COMMON.NAMES'
1050       include 'COMMON.IOUNITS'
1051       include 'COMMON.CONTACTS'
1052       dimension gg(3)
1053 c      write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
1054       evdw=0.0D0
1055       do i=iatsc_s,iatsc_e
1056         itypi=iabs(itype(i))
1057         if (itypi.eq.ntyp1) cycle
1058         itypi1=iabs(itype(i+1))
1059         xi=c(1,nres+i)
1060         yi=c(2,nres+i)
1061         zi=c(3,nres+i)
1062 C Change 12/1/95
1063         num_conti=0
1064 C
1065 C Calculate SC interaction energy.
1066 C
1067         do iint=1,nint_gr(i)
1068 cd        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
1069 cd   &                  'iend=',iend(i,iint)
1070           do j=istart(i,iint),iend(i,iint)
1071             itypj=iabs(itype(j)) 
1072             if (itypj.eq.ntyp1) cycle
1073             xj=c(1,nres+j)-xi
1074             yj=c(2,nres+j)-yi
1075             zj=c(3,nres+j)-zi
1076 C Change 12/1/95 to calculate four-body interactions
1077             rij=xj*xj+yj*yj+zj*zj
1078             rrij=1.0D0/rij
1079 c           write (iout,*)'i=',i,' j=',j,' itypi=',itypi,' itypj=',itypj
1080             eps0ij=eps(itypi,itypj)
1081             fac=rrij**expon2
1082             e1=fac*fac*aa(itypi,itypj)
1083             e2=fac*bb(itypi,itypj)
1084             evdwij=e1+e2
1085 cd          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
1086 cd          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
1087 cd          write (iout,'(2(a3,i3,2x),6(1pd12.4)/2(3(1pd12.4),5x)/)')
1088 cd   &        restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
1089 cd   &        bb(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,epsi,sigm,
1090 cd   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
1091             evdw=evdw+evdwij
1092
1093 C Calculate the components of the gradient in DC and X
1094 C
1095             fac=-rrij*(e1+evdwij)
1096             gg(1)=xj*fac
1097             gg(2)=yj*fac
1098             gg(3)=zj*fac
1099             do k=1,3
1100               gvdwx(k,i)=gvdwx(k,i)-gg(k)
1101               gvdwx(k,j)=gvdwx(k,j)+gg(k)
1102               gvdwc(k,i)=gvdwc(k,i)-gg(k)
1103               gvdwc(k,j)=gvdwc(k,j)+gg(k)
1104             enddo
1105 cgrad            do k=i,j-1
1106 cgrad              do l=1,3
1107 cgrad                gvdwc(l,k)=gvdwc(l,k)+gg(l)
1108 cgrad              enddo
1109 cgrad            enddo
1110 C
1111 C 12/1/95, revised on 5/20/97
1112 C
1113 C Calculate the contact function. The ith column of the array JCONT will 
1114 C contain the numbers of atoms that make contacts with the atom I (of numbers
1115 C greater than I). The arrays FACONT and GACONT will contain the values of
1116 C the contact function and its derivative.
1117 C
1118 C Uncomment next line, if the correlation interactions include EVDW explicitly.
1119 c           if (j.gt.i+1 .and. evdwij.le.0.0D0) then
1120 C Uncomment next line, if the correlation interactions are contact function only
1121             if (j.gt.i+1.and. eps0ij.gt.0.0D0) then
1122               rij=dsqrt(rij)
1123               sigij=sigma(itypi,itypj)
1124               r0ij=rs0(itypi,itypj)
1125 C
1126 C Check whether the SC's are not too far to make a contact.
1127 C
1128               rcut=1.5d0*r0ij
1129               call gcont(rij,rcut,1.0d0,0.2d0*rcut,fcont,fprimcont)
1130 C Add a new contact, if the SC's are close enough, but not too close (r<sigma).
1131 C
1132               if (fcont.gt.0.0D0) then
1133 C If the SC-SC distance if close to sigma, apply spline.
1134 cAdam           call gcont(-rij,-1.03d0*sigij,2.0d0*sigij,1.0d0,
1135 cAdam &             fcont1,fprimcont1)
1136 cAdam           fcont1=1.0d0-fcont1
1137 cAdam           if (fcont1.gt.0.0d0) then
1138 cAdam             fprimcont=fprimcont*fcont1+fcont*fprimcont1
1139 cAdam             fcont=fcont*fcont1
1140 cAdam           endif
1141 C Uncomment following 4 lines to have the geometric average of the epsilon0's
1142 cga             eps0ij=1.0d0/dsqrt(eps0ij)
1143 cga             do k=1,3
1144 cga               gg(k)=gg(k)*eps0ij
1145 cga             enddo
1146 cga             eps0ij=-evdwij*eps0ij
1147 C Uncomment for AL's type of SC correlation interactions.
1148 cadam           eps0ij=-evdwij
1149                 num_conti=num_conti+1
1150                 jcont(num_conti,i)=j
1151                 facont(num_conti,i)=fcont*eps0ij
1152                 fprimcont=eps0ij*fprimcont/rij
1153                 fcont=expon*fcont
1154 cAdam           gacont(1,num_conti,i)=-fprimcont*xj+fcont*gg(1)
1155 cAdam           gacont(2,num_conti,i)=-fprimcont*yj+fcont*gg(2)
1156 cAdam           gacont(3,num_conti,i)=-fprimcont*zj+fcont*gg(3)
1157 C Uncomment following 3 lines for Skolnick's type of SC correlation.
1158                 gacont(1,num_conti,i)=-fprimcont*xj
1159                 gacont(2,num_conti,i)=-fprimcont*yj
1160                 gacont(3,num_conti,i)=-fprimcont*zj
1161 cd              write (iout,'(2i5,2f10.5)') i,j,rij,facont(num_conti,i)
1162 cd              write (iout,'(2i3,3f10.5)') 
1163 cd   &           i,j,(gacont(kk,num_conti,i),kk=1,3)
1164               endif
1165             endif
1166           enddo      ! j
1167         enddo        ! iint
1168 C Change 12/1/95
1169         num_cont(i)=num_conti
1170       enddo          ! i
1171       do i=1,nct
1172         do j=1,3
1173           gvdwc(j,i)=expon*gvdwc(j,i)
1174           gvdwx(j,i)=expon*gvdwx(j,i)
1175         enddo
1176       enddo
1177 C******************************************************************************
1178 C
1179 C                              N O T E !!!
1180 C
1181 C To save time, the factor of EXPON has been extracted from ALL components
1182 C of GVDWC and GRADX. Remember to multiply them by this factor before further 
1183 C use!
1184 C
1185 C******************************************************************************
1186       return
1187       end
1188 C-----------------------------------------------------------------------------
1189       subroutine eljk(evdw)
1190 C
1191 C This subroutine calculates the interaction energy of nonbonded side chains
1192 C assuming the LJK potential of interaction.
1193 C
1194       implicit real*8 (a-h,o-z)
1195       include 'DIMENSIONS'
1196       include 'COMMON.GEO'
1197       include 'COMMON.VAR'
1198       include 'COMMON.LOCAL'
1199       include 'COMMON.CHAIN'
1200       include 'COMMON.DERIV'
1201       include 'COMMON.INTERACT'
1202       include 'COMMON.IOUNITS'
1203       include 'COMMON.NAMES'
1204       dimension gg(3)
1205       logical scheck
1206 c     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
1207       evdw=0.0D0
1208       do i=iatsc_s,iatsc_e
1209         itypi=iabs(itype(i))
1210         if (itypi.eq.ntyp1) cycle
1211         itypi1=iabs(itype(i+1))
1212         xi=c(1,nres+i)
1213         yi=c(2,nres+i)
1214         zi=c(3,nres+i)
1215 C
1216 C Calculate SC interaction energy.
1217 C
1218         do iint=1,nint_gr(i)
1219           do j=istart(i,iint),iend(i,iint)
1220             itypj=iabs(itype(j))
1221             if (itypj.eq.ntyp1) cycle
1222             xj=c(1,nres+j)-xi
1223             yj=c(2,nres+j)-yi
1224             zj=c(3,nres+j)-zi
1225             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
1226             fac_augm=rrij**expon
1227             e_augm=augm(itypi,itypj)*fac_augm
1228             r_inv_ij=dsqrt(rrij)
1229             rij=1.0D0/r_inv_ij 
1230             r_shift_inv=1.0D0/(rij+r0(itypi,itypj)-sigma(itypi,itypj))
1231             fac=r_shift_inv**expon
1232             e1=fac*fac*aa(itypi,itypj)
1233             e2=fac*bb(itypi,itypj)
1234             evdwij=e_augm+e1+e2
1235 cd          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
1236 cd          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
1237 cd          write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
1238 cd   &        restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
1239 cd   &        bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
1240 cd   &        sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
1241 cd   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
1242             evdw=evdw+evdwij
1243
1244 C Calculate the components of the gradient in DC and X
1245 C
1246             fac=-2.0D0*rrij*e_augm-r_inv_ij*r_shift_inv*(e1+e1+e2)
1247             gg(1)=xj*fac
1248             gg(2)=yj*fac
1249             gg(3)=zj*fac
1250             do k=1,3
1251               gvdwx(k,i)=gvdwx(k,i)-gg(k)
1252               gvdwx(k,j)=gvdwx(k,j)+gg(k)
1253               gvdwc(k,i)=gvdwc(k,i)-gg(k)
1254               gvdwc(k,j)=gvdwc(k,j)+gg(k)
1255             enddo
1256 cgrad            do k=i,j-1
1257 cgrad              do l=1,3
1258 cgrad                gvdwc(l,k)=gvdwc(l,k)+gg(l)
1259 cgrad              enddo
1260 cgrad            enddo
1261           enddo      ! j
1262         enddo        ! iint
1263       enddo          ! i
1264       do i=1,nct
1265         do j=1,3
1266           gvdwc(j,i)=expon*gvdwc(j,i)
1267           gvdwx(j,i)=expon*gvdwx(j,i)
1268         enddo
1269       enddo
1270       return
1271       end
1272 C-----------------------------------------------------------------------------
1273       subroutine ebp(evdw)
1274 C
1275 C This subroutine calculates the interaction energy of nonbonded side chains
1276 C assuming the Berne-Pechukas potential of interaction.
1277 C
1278       implicit real*8 (a-h,o-z)
1279       include 'DIMENSIONS'
1280       include 'COMMON.GEO'
1281       include 'COMMON.VAR'
1282       include 'COMMON.LOCAL'
1283       include 'COMMON.CHAIN'
1284       include 'COMMON.DERIV'
1285       include 'COMMON.NAMES'
1286       include 'COMMON.INTERACT'
1287       include 'COMMON.IOUNITS'
1288       include 'COMMON.CALC'
1289       common /srutu/ icall
1290 c     double precision rrsave(maxdim)
1291       logical lprn
1292       evdw=0.0D0
1293 c     print *,'Entering EBP nnt=',nnt,' nct=',nct,' expon=',expon
1294       evdw=0.0D0
1295 c     if (icall.eq.0) then
1296 c       lprn=.true.
1297 c     else
1298         lprn=.false.
1299 c     endif
1300       ind=0
1301       do i=iatsc_s,iatsc_e
1302         itypi=iabs(itype(i))
1303         if (itypi.eq.ntyp1) cycle
1304         itypi1=iabs(itype(i+1))
1305         xi=c(1,nres+i)
1306         yi=c(2,nres+i)
1307         zi=c(3,nres+i)
1308         dxi=dc_norm(1,nres+i)
1309         dyi=dc_norm(2,nres+i)
1310         dzi=dc_norm(3,nres+i)
1311 c        dsci_inv=dsc_inv(itypi)
1312         dsci_inv=vbld_inv(i+nres)
1313 C
1314 C Calculate SC interaction energy.
1315 C
1316         do iint=1,nint_gr(i)
1317           do j=istart(i,iint),iend(i,iint)
1318             ind=ind+1
1319             itypj=iabs(itype(j))
1320             if (itypj.eq.ntyp1) cycle
1321 c            dscj_inv=dsc_inv(itypj)
1322             dscj_inv=vbld_inv(j+nres)
1323             chi1=chi(itypi,itypj)
1324             chi2=chi(itypj,itypi)
1325             chi12=chi1*chi2
1326             chip1=chip(itypi)
1327             chip2=chip(itypj)
1328             chip12=chip1*chip2
1329             alf1=alp(itypi)
1330             alf2=alp(itypj)
1331             alf12=0.5D0*(alf1+alf2)
1332 C For diagnostics only!!!
1333 c           chi1=0.0D0
1334 c           chi2=0.0D0
1335 c           chi12=0.0D0
1336 c           chip1=0.0D0
1337 c           chip2=0.0D0
1338 c           chip12=0.0D0
1339 c           alf1=0.0D0
1340 c           alf2=0.0D0
1341 c           alf12=0.0D0
1342             xj=c(1,nres+j)-xi
1343             yj=c(2,nres+j)-yi
1344             zj=c(3,nres+j)-zi
1345             dxj=dc_norm(1,nres+j)
1346             dyj=dc_norm(2,nres+j)
1347             dzj=dc_norm(3,nres+j)
1348             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
1349 cd          if (icall.eq.0) then
1350 cd            rrsave(ind)=rrij
1351 cd          else
1352 cd            rrij=rrsave(ind)
1353 cd          endif
1354             rij=dsqrt(rrij)
1355 C Calculate the angle-dependent terms of energy & contributions to derivatives.
1356             call sc_angular
1357 C Calculate whole angle-dependent part of epsilon and contributions
1358 C to its derivatives
1359             fac=(rrij*sigsq)**expon2
1360             e1=fac*fac*aa(itypi,itypj)
1361             e2=fac*bb(itypi,itypj)
1362             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
1363             eps2der=evdwij*eps3rt
1364             eps3der=evdwij*eps2rt
1365             evdwij=evdwij*eps2rt*eps3rt
1366             evdw=evdw+evdwij
1367             if (lprn) then
1368             sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
1369             epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
1370 cd            write (iout,'(2(a3,i3,2x),15(0pf7.3))')
1371 cd     &        restyp(itypi),i,restyp(itypj),j,
1372 cd     &        epsi,sigm,chi1,chi2,chip1,chip2,
1373 cd     &        eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
1374 cd     &        om1,om2,om12,1.0D0/dsqrt(rrij),
1375 cd     &        evdwij
1376             endif
1377 C Calculate gradient components.
1378             e1=e1*eps1*eps2rt**2*eps3rt**2
1379             fac=-expon*(e1+evdwij)
1380             sigder=fac/sigsq
1381             fac=rrij*fac
1382 C Calculate radial part of the gradient
1383             gg(1)=xj*fac
1384             gg(2)=yj*fac
1385             gg(3)=zj*fac
1386 C Calculate the angular part of the gradient and sum add the contributions
1387 C to the appropriate components of the Cartesian gradient.
1388             call sc_grad
1389           enddo      ! j
1390         enddo        ! iint
1391       enddo          ! i
1392 c     stop
1393       return
1394       end
1395 C-----------------------------------------------------------------------------
1396       subroutine egb(evdw)
1397 C
1398 C This subroutine calculates the interaction energy of nonbonded side chains
1399 C assuming the Gay-Berne potential of interaction.
1400 C
1401       implicit real*8 (a-h,o-z)
1402       include 'DIMENSIONS'
1403       include 'COMMON.GEO'
1404       include 'COMMON.VAR'
1405       include 'COMMON.LOCAL'
1406       include 'COMMON.CHAIN'
1407       include 'COMMON.DERIV'
1408       include 'COMMON.NAMES'
1409       include 'COMMON.INTERACT'
1410       include 'COMMON.IOUNITS'
1411       include 'COMMON.CALC'
1412       include 'COMMON.CONTROL'
1413       logical lprn
1414       evdw=0.0D0
1415 ccccc      energy_dec=.false.
1416 c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
1417       evdw=0.0D0
1418       lprn=.false.
1419 c     if (icall.eq.0) lprn=.false.
1420       ind=0
1421       do i=iatsc_s,iatsc_e
1422         itypi=iabs(itype(i))
1423         if (itypi.eq.ntyp1) cycle
1424         itypi1=iabs(itype(i+1))
1425         xi=c(1,nres+i)
1426         yi=c(2,nres+i)
1427         zi=c(3,nres+i)
1428         dxi=dc_norm(1,nres+i)
1429         dyi=dc_norm(2,nres+i)
1430         dzi=dc_norm(3,nres+i)
1431 c        dsci_inv=dsc_inv(itypi)
1432         dsci_inv=vbld_inv(i+nres)
1433 c        write (iout,*) "i",i,dsc_inv(itypi),dsci_inv,1.0d0/vbld(i+nres)
1434 c        write (iout,*) "dcnori",dxi*dxi+dyi*dyi+dzi*dzi
1435 C
1436 C Calculate SC interaction energy.
1437 C
1438         do iint=1,nint_gr(i)
1439           do j=istart(i,iint),iend(i,iint)
1440             ind=ind+1
1441             itypj=iabs(itype(j))
1442             if (itypj.eq.ntyp1) cycle
1443 c            dscj_inv=dsc_inv(itypj)
1444             dscj_inv=vbld_inv(j+nres)
1445 c            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
1446 c     &       1.0d0/vbld(j+nres)
1447 c            write (iout,*) "i",i," j", j," itype",itype(i),itype(j)
1448             sig0ij=sigma(itypi,itypj)
1449             chi1=chi(itypi,itypj)
1450             chi2=chi(itypj,itypi)
1451             chi12=chi1*chi2
1452             chip1=chip(itypi)
1453             chip2=chip(itypj)
1454             chip12=chip1*chip2
1455             alf1=alp(itypi)
1456             alf2=alp(itypj)
1457             alf12=0.5D0*(alf1+alf2)
1458 C For diagnostics only!!!
1459 c           chi1=0.0D0
1460 c           chi2=0.0D0
1461 c           chi12=0.0D0
1462 c           chip1=0.0D0
1463 c           chip2=0.0D0
1464 c           chip12=0.0D0
1465 c           alf1=0.0D0
1466 c           alf2=0.0D0
1467 c           alf12=0.0D0
1468             xj=c(1,nres+j)-xi
1469             yj=c(2,nres+j)-yi
1470             zj=c(3,nres+j)-zi
1471             dxj=dc_norm(1,nres+j)
1472             dyj=dc_norm(2,nres+j)
1473             dzj=dc_norm(3,nres+j)
1474 c            write (iout,*) "dcnorj",dxi*dxi+dyi*dyi+dzi*dzi
1475 c            write (iout,*) "j",j," dc_norm",
1476 c     &       dc_norm(1,nres+j),dc_norm(2,nres+j),dc_norm(3,nres+j)
1477             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
1478             rij=dsqrt(rrij)
1479 C Calculate angle-dependent terms of energy and contributions to their
1480 C derivatives.
1481             call sc_angular
1482             sigsq=1.0D0/sigsq
1483             sig=sig0ij*dsqrt(sigsq)
1484             rij_shift=1.0D0/rij-sig+sig0ij
1485 c for diagnostics; uncomment
1486 c            rij_shift=1.2*sig0ij
1487 C I hate to put IF's in the loops, but here don't have another choice!!!!
1488             if (rij_shift.le.0.0D0) then
1489               evdw=1.0D20
1490 cd              write (iout,'(2(a3,i3,2x),17(0pf7.3))')
1491 cd     &        restyp(itypi),i,restyp(itypj),j,
1492 cd     &        rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq) 
1493               return
1494             endif
1495             sigder=-sig*sigsq
1496 c---------------------------------------------------------------
1497             rij_shift=1.0D0/rij_shift 
1498             fac=rij_shift**expon
1499             e1=fac*fac*aa(itypi,itypj)
1500             e2=fac*bb(itypi,itypj)
1501             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
1502             eps2der=evdwij*eps3rt
1503             eps3der=evdwij*eps2rt
1504 c            write (iout,*) "sigsq",sigsq," sig",sig," eps2rt",eps2rt,
1505 c     &        " eps3rt",eps3rt," eps1",eps1," e1",e1," e2",e2
1506             evdwij=evdwij*eps2rt*eps3rt
1507             evdw=evdw+evdwij
1508             if (lprn) then
1509             sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
1510             epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
1511             write (iout,'(2(a3,i3,2x),17(0pf7.3))')
1512      &        restyp(itypi),i,restyp(itypj),j,
1513      &        epsi,sigm,chi1,chi2,chip1,chip2,
1514      &        eps1,eps2rt**2,eps3rt**2,sig,sig0ij,
1515      &        om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,
1516      &        evdwij
1517             endif
1518
1519             if (energy_dec) write (iout,'(a6,2i5,0pf7.3)') 
1520      &                        'evdw',i,j,evdwij
1521
1522 C Calculate gradient components.
1523             e1=e1*eps1*eps2rt**2*eps3rt**2
1524             fac=-expon*(e1+evdwij)*rij_shift
1525             sigder=fac*sigder
1526             fac=rij*fac
1527 c            fac=0.0d0
1528 C Calculate the radial part of the gradient
1529             gg(1)=xj*fac
1530             gg(2)=yj*fac
1531             gg(3)=zj*fac
1532 C Calculate angular part of the gradient.
1533             call sc_grad
1534           enddo      ! j
1535         enddo        ! iint
1536       enddo          ! i
1537 c      write (iout,*) "Number of loop steps in EGB:",ind
1538 cccc      energy_dec=.false.
1539       return
1540       end
1541 C-----------------------------------------------------------------------------
1542       subroutine egbv(evdw)
1543 C
1544 C This subroutine calculates the interaction energy of nonbonded side chains
1545 C assuming the Gay-Berne-Vorobjev potential of interaction.
1546 C
1547       implicit real*8 (a-h,o-z)
1548       include 'DIMENSIONS'
1549       include 'COMMON.GEO'
1550       include 'COMMON.VAR'
1551       include 'COMMON.LOCAL'
1552       include 'COMMON.CHAIN'
1553       include 'COMMON.DERIV'
1554       include 'COMMON.NAMES'
1555       include 'COMMON.INTERACT'
1556       include 'COMMON.IOUNITS'
1557       include 'COMMON.CALC'
1558       common /srutu/ icall
1559       logical lprn
1560       evdw=0.0D0
1561 c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
1562       evdw=0.0D0
1563       lprn=.false.
1564 c     if (icall.eq.0) lprn=.true.
1565       ind=0
1566       do i=iatsc_s,iatsc_e
1567         itypi=iabs(itype(i))
1568         if (itypi.eq.ntyp1) cycle
1569         itypi1=iabs(itype(i+1))
1570         xi=c(1,nres+i)
1571         yi=c(2,nres+i)
1572         zi=c(3,nres+i)
1573         dxi=dc_norm(1,nres+i)
1574         dyi=dc_norm(2,nres+i)
1575         dzi=dc_norm(3,nres+i)
1576 c        dsci_inv=dsc_inv(itypi)
1577         dsci_inv=vbld_inv(i+nres)
1578 C
1579 C Calculate SC interaction energy.
1580 C
1581         do iint=1,nint_gr(i)
1582           do j=istart(i,iint),iend(i,iint)
1583             ind=ind+1
1584             itypj=iabs(itype(j))
1585             if (itypj.eq.ntyp1) cycle
1586 c            dscj_inv=dsc_inv(itypj)
1587             dscj_inv=vbld_inv(j+nres)
1588             sig0ij=sigma(itypi,itypj)
1589             r0ij=r0(itypi,itypj)
1590             chi1=chi(itypi,itypj)
1591             chi2=chi(itypj,itypi)
1592             chi12=chi1*chi2
1593             chip1=chip(itypi)
1594             chip2=chip(itypj)
1595             chip12=chip1*chip2
1596             alf1=alp(itypi)
1597             alf2=alp(itypj)
1598             alf12=0.5D0*(alf1+alf2)
1599 C For diagnostics only!!!
1600 c           chi1=0.0D0
1601 c           chi2=0.0D0
1602 c           chi12=0.0D0
1603 c           chip1=0.0D0
1604 c           chip2=0.0D0
1605 c           chip12=0.0D0
1606 c           alf1=0.0D0
1607 c           alf2=0.0D0
1608 c           alf12=0.0D0
1609             xj=c(1,nres+j)-xi
1610             yj=c(2,nres+j)-yi
1611             zj=c(3,nres+j)-zi
1612             dxj=dc_norm(1,nres+j)
1613             dyj=dc_norm(2,nres+j)
1614             dzj=dc_norm(3,nres+j)
1615             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
1616             rij=dsqrt(rrij)
1617 C Calculate angle-dependent terms of energy and contributions to their
1618 C derivatives.
1619             call sc_angular
1620             sigsq=1.0D0/sigsq
1621             sig=sig0ij*dsqrt(sigsq)
1622             rij_shift=1.0D0/rij-sig+r0ij
1623 C I hate to put IF's in the loops, but here don't have another choice!!!!
1624             if (rij_shift.le.0.0D0) then
1625               evdw=1.0D20
1626               return
1627             endif
1628             sigder=-sig*sigsq
1629 c---------------------------------------------------------------
1630             rij_shift=1.0D0/rij_shift 
1631             fac=rij_shift**expon
1632             e1=fac*fac*aa(itypi,itypj)
1633             e2=fac*bb(itypi,itypj)
1634             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
1635             eps2der=evdwij*eps3rt
1636             eps3der=evdwij*eps2rt
1637             fac_augm=rrij**expon
1638             e_augm=augm(itypi,itypj)*fac_augm
1639             evdwij=evdwij*eps2rt*eps3rt
1640             evdw=evdw+evdwij+e_augm
1641             if (lprn) then
1642             sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
1643             epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
1644             write (iout,'(2(a3,i3,2x),17(0pf7.3))')
1645      &        restyp(itypi),i,restyp(itypj),j,
1646      &        epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),
1647      &        chi1,chi2,chip1,chip2,
1648      &        eps1,eps2rt**2,eps3rt**2,
1649      &        om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,
1650      &        evdwij+e_augm
1651             endif
1652 C Calculate gradient components.
1653             e1=e1*eps1*eps2rt**2*eps3rt**2
1654             fac=-expon*(e1+evdwij)*rij_shift
1655             sigder=fac*sigder
1656             fac=rij*fac-2*expon*rrij*e_augm
1657 C Calculate the radial part of the gradient
1658             gg(1)=xj*fac
1659             gg(2)=yj*fac
1660             gg(3)=zj*fac
1661 C Calculate angular part of the gradient.
1662             call sc_grad
1663           enddo      ! j
1664         enddo        ! iint
1665       enddo          ! i
1666       end
1667 C-----------------------------------------------------------------------------
1668       subroutine sc_angular
1669 C Calculate eps1,eps2,eps3,sigma, and parts of their derivatives in om1,om2,
1670 C om12. Called by ebp, egb, and egbv.
1671       implicit none
1672       include 'COMMON.CALC'
1673       include 'COMMON.IOUNITS'
1674       erij(1)=xj*rij
1675       erij(2)=yj*rij
1676       erij(3)=zj*rij
1677       om1=dxi*erij(1)+dyi*erij(2)+dzi*erij(3)
1678       om2=dxj*erij(1)+dyj*erij(2)+dzj*erij(3)
1679       om12=dxi*dxj+dyi*dyj+dzi*dzj
1680       chiom12=chi12*om12
1681 C Calculate eps1(om12) and its derivative in om12
1682       faceps1=1.0D0-om12*chiom12
1683       faceps1_inv=1.0D0/faceps1
1684       eps1=dsqrt(faceps1_inv)
1685 C Following variable is eps1*deps1/dom12
1686       eps1_om12=faceps1_inv*chiom12
1687 c diagnostics only
1688 c      faceps1_inv=om12
1689 c      eps1=om12
1690 c      eps1_om12=1.0d0
1691 c      write (iout,*) "om12",om12," eps1",eps1
1692 C Calculate sigma(om1,om2,om12) and the derivatives of sigma**2 in om1,om2,
1693 C and om12.
1694       om1om2=om1*om2
1695       chiom1=chi1*om1
1696       chiom2=chi2*om2
1697       facsig=om1*chiom1+om2*chiom2-2.0D0*om1om2*chiom12
1698       sigsq=1.0D0-facsig*faceps1_inv
1699       sigsq_om1=(chiom1-chiom12*om2)*faceps1_inv
1700       sigsq_om2=(chiom2-chiom12*om1)*faceps1_inv
1701       sigsq_om12=-chi12*(om1om2*faceps1-om12*facsig)*faceps1_inv**2
1702 c diagnostics only
1703 c      sigsq=1.0d0
1704 c      sigsq_om1=0.0d0
1705 c      sigsq_om2=0.0d0
1706 c      sigsq_om12=0.0d0
1707 c      write (iout,*) "chiom1",chiom1," chiom2",chiom2," chiom12",chiom12
1708 c      write (iout,*) "faceps1",faceps1," faceps1_inv",faceps1_inv,
1709 c     &    " eps1",eps1
1710 C Calculate eps2 and its derivatives in om1, om2, and om12.
1711       chipom1=chip1*om1
1712       chipom2=chip2*om2
1713       chipom12=chip12*om12
1714       facp=1.0D0-om12*chipom12
1715       facp_inv=1.0D0/facp
1716       facp1=om1*chipom1+om2*chipom2-2.0D0*om1om2*chipom12
1717 c      write (iout,*) "chipom1",chipom1," chipom2",chipom2,
1718 c     &  " chipom12",chipom12," facp",facp," facp_inv",facp_inv
1719 C Following variable is the square root of eps2
1720       eps2rt=1.0D0-facp1*facp_inv
1721 C Following three variables are the derivatives of the square root of eps
1722 C in om1, om2, and om12.
1723       eps2rt_om1=-4.0D0*(chipom1-chipom12*om2)*facp_inv
1724       eps2rt_om2=-4.0D0*(chipom2-chipom12*om1)*facp_inv
1725       eps2rt_om12=4.0D0*chip12*(om1om2*facp-om12*facp1)*facp_inv**2 
1726 C Evaluate the "asymmetric" factor in the VDW constant, eps3
1727       eps3rt=1.0D0-alf1*om1+alf2*om2-alf12*om12 
1728 c      write (iout,*) "eps2rt",eps2rt," eps3rt",eps3rt
1729 c      write (iout,*) "eps2rt_om1",eps2rt_om1," eps2rt_om2",eps2rt_om2,
1730 c     &  " eps2rt_om12",eps2rt_om12
1731 C Calculate whole angle-dependent part of epsilon and contributions
1732 C to its derivatives
1733       return
1734       end
1735 C----------------------------------------------------------------------------
1736       subroutine sc_grad
1737       implicit real*8 (a-h,o-z)
1738       include 'DIMENSIONS'
1739       include 'COMMON.CHAIN'
1740       include 'COMMON.DERIV'
1741       include 'COMMON.CALC'
1742       include 'COMMON.IOUNITS'
1743       double precision dcosom1(3),dcosom2(3)
1744       eom1=eps2der*eps2rt_om1-2.0D0*alf1*eps3der+sigder*sigsq_om1
1745       eom2=eps2der*eps2rt_om2+2.0D0*alf2*eps3der+sigder*sigsq_om2
1746       eom12=evdwij*eps1_om12+eps2der*eps2rt_om12
1747      &     -2.0D0*alf12*eps3der+sigder*sigsq_om12
1748 c diagnostics only
1749 c      eom1=0.0d0
1750 c      eom2=0.0d0
1751 c      eom12=evdwij*eps1_om12
1752 c end diagnostics
1753 c      write (iout,*) "eps2der",eps2der," eps3der",eps3der,
1754 c     &  " sigder",sigder
1755 c      write (iout,*) "eps1_om12",eps1_om12," eps2rt_om12",eps2rt_om12
1756 c      write (iout,*) "eom1",eom1," eom2",eom2," eom12",eom12
1757       do k=1,3
1758         dcosom1(k)=rij*(dc_norm(k,nres+i)-om1*erij(k))
1759         dcosom2(k)=rij*(dc_norm(k,nres+j)-om2*erij(k))
1760       enddo
1761       do k=1,3
1762         gg(k)=gg(k)+eom1*dcosom1(k)+eom2*dcosom2(k)
1763       enddo 
1764 c      write (iout,*) "gg",(gg(k),k=1,3)
1765       do k=1,3
1766         gvdwx(k,i)=gvdwx(k,i)-gg(k)
1767      &            +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i))
1768      &            +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
1769         gvdwx(k,j)=gvdwx(k,j)+gg(k)
1770      &            +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j))
1771      &            +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
1772 c        write (iout,*)(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i))
1773 c     &            +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
1774 c        write (iout,*)(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j))
1775 c     &            +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
1776       enddo
1777
1778 C Calculate the components of the gradient in DC and X
1779 C
1780 cgrad      do k=i,j-1
1781 cgrad        do l=1,3
1782 cgrad          gvdwc(l,k)=gvdwc(l,k)+gg(l)
1783 cgrad        enddo
1784 cgrad      enddo
1785       do l=1,3
1786         gvdwc(l,i)=gvdwc(l,i)-gg(l)
1787         gvdwc(l,j)=gvdwc(l,j)+gg(l)
1788       enddo
1789       return
1790       end
1791 C-----------------------------------------------------------------------
1792       subroutine e_softsphere(evdw)
1793 C
1794 C This subroutine calculates the interaction energy of nonbonded side chains
1795 C assuming the LJ potential of interaction.
1796 C
1797       implicit real*8 (a-h,o-z)
1798       include 'DIMENSIONS'
1799       parameter (accur=1.0d-10)
1800       include 'COMMON.GEO'
1801       include 'COMMON.VAR'
1802       include 'COMMON.LOCAL'
1803       include 'COMMON.CHAIN'
1804       include 'COMMON.DERIV'
1805       include 'COMMON.INTERACT'
1806       include 'COMMON.TORSION'
1807       include 'COMMON.SBRIDGE'
1808       include 'COMMON.NAMES'
1809       include 'COMMON.IOUNITS'
1810       include 'COMMON.CONTACTS'
1811       dimension gg(3)
1812 cd    print *,'Entering Esoft_sphere nnt=',nnt,' nct=',nct
1813       evdw=0.0D0
1814       do i=iatsc_s,iatsc_e
1815         itypi=iabs(itype(i))
1816         if (itypi.eq.ntyp1) cycle
1817         itypi1=iabs(itype(i+1))
1818         xi=c(1,nres+i)
1819         yi=c(2,nres+i)
1820         zi=c(3,nres+i)
1821 C
1822 C Calculate SC interaction energy.
1823 C
1824         do iint=1,nint_gr(i)
1825 cd        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
1826 cd   &                  'iend=',iend(i,iint)
1827           do j=istart(i,iint),iend(i,iint)
1828             itypj=iabs(itype(j))
1829             if (itypj.eq.ntyp1) cycle
1830             xj=c(1,nres+j)-xi
1831             yj=c(2,nres+j)-yi
1832             zj=c(3,nres+j)-zi
1833             rij=xj*xj+yj*yj+zj*zj
1834 c           write (iout,*)'i=',i,' j=',j,' itypi=',itypi,' itypj=',itypj
1835             r0ij=r0(itypi,itypj)
1836             r0ijsq=r0ij*r0ij
1837 c            print *,i,j,r0ij,dsqrt(rij)
1838             if (rij.lt.r0ijsq) then
1839               evdwij=0.25d0*(rij-r0ijsq)**2
1840               fac=rij-r0ijsq
1841             else
1842               evdwij=0.0d0
1843               fac=0.0d0
1844             endif
1845             evdw=evdw+evdwij
1846
1847 C Calculate the components of the gradient in DC and X
1848 C
1849             gg(1)=xj*fac
1850             gg(2)=yj*fac
1851             gg(3)=zj*fac
1852             do k=1,3
1853               gvdwx(k,i)=gvdwx(k,i)-gg(k)
1854               gvdwx(k,j)=gvdwx(k,j)+gg(k)
1855               gvdwc(k,i)=gvdwc(k,i)-gg(k)
1856               gvdwc(k,j)=gvdwc(k,j)+gg(k)
1857             enddo
1858 cgrad            do k=i,j-1
1859 cgrad              do l=1,3
1860 cgrad                gvdwc(l,k)=gvdwc(l,k)+gg(l)
1861 cgrad              enddo
1862 cgrad            enddo
1863           enddo ! j
1864         enddo ! iint
1865       enddo ! i
1866       return
1867       end
1868 C--------------------------------------------------------------------------
1869       subroutine eelec_soft_sphere(ees,evdw1,eel_loc,eello_turn3,
1870      &              eello_turn4)
1871 C
1872 C Soft-sphere potential of p-p interaction
1873
1874       implicit real*8 (a-h,o-z)
1875       include 'DIMENSIONS'
1876       include 'COMMON.CONTROL'
1877       include 'COMMON.IOUNITS'
1878       include 'COMMON.GEO'
1879       include 'COMMON.VAR'
1880       include 'COMMON.LOCAL'
1881       include 'COMMON.CHAIN'
1882       include 'COMMON.DERIV'
1883       include 'COMMON.INTERACT'
1884       include 'COMMON.CONTACTS'
1885       include 'COMMON.TORSION'
1886       include 'COMMON.VECTORS'
1887       include 'COMMON.FFIELD'
1888       dimension ggg(3)
1889 cd      write(iout,*) 'In EELEC_soft_sphere'
1890       ees=0.0D0
1891       evdw1=0.0D0
1892       eel_loc=0.0d0 
1893       eello_turn3=0.0d0
1894       eello_turn4=0.0d0
1895       ind=0
1896       do i=iatel_s,iatel_e
1897         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
1898         dxi=dc(1,i)
1899         dyi=dc(2,i)
1900         dzi=dc(3,i)
1901         xmedi=c(1,i)+0.5d0*dxi
1902         ymedi=c(2,i)+0.5d0*dyi
1903         zmedi=c(3,i)+0.5d0*dzi
1904         num_conti=0
1905 c        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
1906         do j=ielstart(i),ielend(i)
1907           if (itype(j).eq.ntyp1 .or. itype(j+1).eq.ntyp1) cycle
1908           ind=ind+1
1909           iteli=itel(i)
1910           itelj=itel(j)
1911           if (j.eq.i+2 .and. itelj.eq.2) iteli=2
1912           r0ij=rpp(iteli,itelj)
1913           r0ijsq=r0ij*r0ij 
1914           dxj=dc(1,j)
1915           dyj=dc(2,j)
1916           dzj=dc(3,j)
1917           xj=c(1,j)+0.5D0*dxj-xmedi
1918           yj=c(2,j)+0.5D0*dyj-ymedi
1919           zj=c(3,j)+0.5D0*dzj-zmedi
1920           rij=xj*xj+yj*yj+zj*zj
1921           if (rij.lt.r0ijsq) then
1922             evdw1ij=0.25d0*(rij-r0ijsq)**2
1923             fac=rij-r0ijsq
1924           else
1925             evdw1ij=0.0d0
1926             fac=0.0d0
1927           endif
1928           evdw1=evdw1+evdw1ij
1929 C
1930 C Calculate contributions to the Cartesian gradient.
1931 C
1932           ggg(1)=fac*xj
1933           ggg(2)=fac*yj
1934           ggg(3)=fac*zj
1935           do k=1,3
1936             gvdwpp(k,i)=gvdwpp(k,i)-ggg(k)
1937             gvdwpp(k,j)=gvdwpp(k,j)+ggg(k)
1938           enddo
1939 *
1940 * Loop over residues i+1 thru j-1.
1941 *
1942 cgrad          do k=i+1,j-1
1943 cgrad            do l=1,3
1944 cgrad              gelc(l,k)=gelc(l,k)+ggg(l)
1945 cgrad            enddo
1946 cgrad          enddo
1947         enddo ! j
1948       enddo   ! i
1949 cgrad      do i=nnt,nct-1
1950 cgrad        do k=1,3
1951 cgrad          gelc(k,i)=gelc(k,i)+0.5d0*gelc(k,i)
1952 cgrad        enddo
1953 cgrad        do j=i+1,nct-1
1954 cgrad          do k=1,3
1955 cgrad            gelc(k,i)=gelc(k,i)+gelc(k,j)
1956 cgrad          enddo
1957 cgrad        enddo
1958 cgrad      enddo
1959       return
1960       end
1961 c------------------------------------------------------------------------------
1962       subroutine vec_and_deriv
1963       implicit real*8 (a-h,o-z)
1964       include 'DIMENSIONS'
1965 #ifdef MPI
1966       include 'mpif.h'
1967 #endif
1968       include 'COMMON.IOUNITS'
1969       include 'COMMON.GEO'
1970       include 'COMMON.VAR'
1971       include 'COMMON.LOCAL'
1972       include 'COMMON.CHAIN'
1973       include 'COMMON.VECTORS'
1974       include 'COMMON.SETUP'
1975       include 'COMMON.TIME1'
1976       dimension uyder(3,3,2),uzder(3,3,2),vbld_inv_temp(2)
1977 C Compute the local reference systems. For reference system (i), the
1978 C X-axis points from CA(i) to CA(i+1), the Y axis is in the 
1979 C CA(i)-CA(i+1)-CA(i+2) plane, and the Z axis is perpendicular to this plane.
1980 #ifdef PARVEC
1981       do i=ivec_start,ivec_end
1982 #else
1983       do i=1,nres-1
1984 #endif
1985           if (i.eq.nres-1) then
1986 C Case of the last full residue
1987 C Compute the Z-axis
1988             call vecpr(dc_norm(1,i),dc_norm(1,i-1),uz(1,i))
1989             costh=dcos(pi-theta(nres))
1990             fac=1.0d0/dsqrt(1.0d0-costh*costh)
1991             do k=1,3
1992               uz(k,i)=fac*uz(k,i)
1993             enddo
1994 C Compute the derivatives of uz
1995             uzder(1,1,1)= 0.0d0
1996             uzder(2,1,1)=-dc_norm(3,i-1)
1997             uzder(3,1,1)= dc_norm(2,i-1) 
1998             uzder(1,2,1)= dc_norm(3,i-1)
1999             uzder(2,2,1)= 0.0d0
2000             uzder(3,2,1)=-dc_norm(1,i-1)
2001             uzder(1,3,1)=-dc_norm(2,i-1)
2002             uzder(2,3,1)= dc_norm(1,i-1)
2003             uzder(3,3,1)= 0.0d0
2004             uzder(1,1,2)= 0.0d0
2005             uzder(2,1,2)= dc_norm(3,i)
2006             uzder(3,1,2)=-dc_norm(2,i) 
2007             uzder(1,2,2)=-dc_norm(3,i)
2008             uzder(2,2,2)= 0.0d0
2009             uzder(3,2,2)= dc_norm(1,i)
2010             uzder(1,3,2)= dc_norm(2,i)
2011             uzder(2,3,2)=-dc_norm(1,i)
2012             uzder(3,3,2)= 0.0d0
2013 C Compute the Y-axis
2014             facy=fac
2015             do k=1,3
2016               uy(k,i)=fac*(dc_norm(k,i-1)-costh*dc_norm(k,i))
2017             enddo
2018 C Compute the derivatives of uy
2019             do j=1,3
2020               do k=1,3
2021                 uyder(k,j,1)=2*dc_norm(k,i-1)*dc_norm(j,i)
2022      &                        -dc_norm(k,i)*dc_norm(j,i-1)
2023                 uyder(k,j,2)=-dc_norm(j,i)*dc_norm(k,i)
2024               enddo
2025               uyder(j,j,1)=uyder(j,j,1)-costh
2026               uyder(j,j,2)=1.0d0+uyder(j,j,2)
2027             enddo
2028             do j=1,2
2029               do k=1,3
2030                 do l=1,3
2031                   uygrad(l,k,j,i)=uyder(l,k,j)
2032                   uzgrad(l,k,j,i)=uzder(l,k,j)
2033                 enddo
2034               enddo
2035             enddo 
2036             call unormderiv(uy(1,i),uyder(1,1,1),facy,uygrad(1,1,1,i))
2037             call unormderiv(uy(1,i),uyder(1,1,2),facy,uygrad(1,1,2,i))
2038             call unormderiv(uz(1,i),uzder(1,1,1),fac,uzgrad(1,1,1,i))
2039             call unormderiv(uz(1,i),uzder(1,1,2),fac,uzgrad(1,1,2,i))
2040           else
2041 C Other residues
2042 C Compute the Z-axis
2043             call vecpr(dc_norm(1,i),dc_norm(1,i+1),uz(1,i))
2044             costh=dcos(pi-theta(i+2))
2045             fac=1.0d0/dsqrt(1.0d0-costh*costh)
2046             do k=1,3
2047               uz(k,i)=fac*uz(k,i)
2048             enddo
2049 C Compute the derivatives of uz
2050             uzder(1,1,1)= 0.0d0
2051             uzder(2,1,1)=-dc_norm(3,i+1)
2052             uzder(3,1,1)= dc_norm(2,i+1) 
2053             uzder(1,2,1)= dc_norm(3,i+1)
2054             uzder(2,2,1)= 0.0d0
2055             uzder(3,2,1)=-dc_norm(1,i+1)
2056             uzder(1,3,1)=-dc_norm(2,i+1)
2057             uzder(2,3,1)= dc_norm(1,i+1)
2058             uzder(3,3,1)= 0.0d0
2059             uzder(1,1,2)= 0.0d0
2060             uzder(2,1,2)= dc_norm(3,i)
2061             uzder(3,1,2)=-dc_norm(2,i) 
2062             uzder(1,2,2)=-dc_norm(3,i)
2063             uzder(2,2,2)= 0.0d0
2064             uzder(3,2,2)= dc_norm(1,i)
2065             uzder(1,3,2)= dc_norm(2,i)
2066             uzder(2,3,2)=-dc_norm(1,i)
2067             uzder(3,3,2)= 0.0d0
2068 C Compute the Y-axis
2069             facy=fac
2070             do k=1,3
2071               uy(k,i)=facy*(dc_norm(k,i+1)-costh*dc_norm(k,i))
2072             enddo
2073 C Compute the derivatives of uy
2074             do j=1,3
2075               do k=1,3
2076                 uyder(k,j,1)=2*dc_norm(k,i+1)*dc_norm(j,i)
2077      &                        -dc_norm(k,i)*dc_norm(j,i+1)
2078                 uyder(k,j,2)=-dc_norm(j,i)*dc_norm(k,i)
2079               enddo
2080               uyder(j,j,1)=uyder(j,j,1)-costh
2081               uyder(j,j,2)=1.0d0+uyder(j,j,2)
2082             enddo
2083             do j=1,2
2084               do k=1,3
2085                 do l=1,3
2086                   uygrad(l,k,j,i)=uyder(l,k,j)
2087                   uzgrad(l,k,j,i)=uzder(l,k,j)
2088                 enddo
2089               enddo
2090             enddo 
2091             call unormderiv(uy(1,i),uyder(1,1,1),facy,uygrad(1,1,1,i))
2092             call unormderiv(uy(1,i),uyder(1,1,2),facy,uygrad(1,1,2,i))
2093             call unormderiv(uz(1,i),uzder(1,1,1),fac,uzgrad(1,1,1,i))
2094             call unormderiv(uz(1,i),uzder(1,1,2),fac,uzgrad(1,1,2,i))
2095           endif
2096       enddo
2097       do i=1,nres-1
2098         vbld_inv_temp(1)=vbld_inv(i+1)
2099         if (i.lt.nres-1) then
2100           vbld_inv_temp(2)=vbld_inv(i+2)
2101           else
2102           vbld_inv_temp(2)=vbld_inv(i)
2103           endif
2104         do j=1,2
2105           do k=1,3
2106             do l=1,3
2107               uygrad(l,k,j,i)=vbld_inv_temp(j)*uygrad(l,k,j,i)
2108               uzgrad(l,k,j,i)=vbld_inv_temp(j)*uzgrad(l,k,j,i)
2109             enddo
2110           enddo
2111         enddo
2112       enddo
2113 #if defined(PARVEC) && defined(MPI)
2114       if (nfgtasks1.gt.1) then
2115         time00=MPI_Wtime()
2116 c        print *,"Processor",fg_rank1,kolor1," ivec_start",ivec_start,
2117 c     &   " ivec_displ",(ivec_displ(i),i=0,nfgtasks1-1),
2118 c     &   " ivec_count",(ivec_count(i),i=0,nfgtasks1-1)
2119         call MPI_Allgatherv(uy(1,ivec_start),ivec_count(fg_rank1),
2120      &   MPI_UYZ,uy(1,1),ivec_count(0),ivec_displ(0),MPI_UYZ,
2121      &   FG_COMM1,IERR)
2122         call MPI_Allgatherv(uz(1,ivec_start),ivec_count(fg_rank1),
2123      &   MPI_UYZ,uz(1,1),ivec_count(0),ivec_displ(0),MPI_UYZ,
2124      &   FG_COMM1,IERR)
2125         call MPI_Allgatherv(uygrad(1,1,1,ivec_start),
2126      &   ivec_count(fg_rank1),MPI_UYZGRAD,uygrad(1,1,1,1),ivec_count(0),
2127      &   ivec_displ(0),MPI_UYZGRAD,FG_COMM1,IERR)
2128         call MPI_Allgatherv(uzgrad(1,1,1,ivec_start),
2129      &   ivec_count(fg_rank1),MPI_UYZGRAD,uzgrad(1,1,1,1),ivec_count(0),
2130      &   ivec_displ(0),MPI_UYZGRAD,FG_COMM1,IERR)
2131         time_gather=time_gather+MPI_Wtime()-time00
2132       endif
2133 c      if (fg_rank.eq.0) then
2134 c        write (iout,*) "Arrays UY and UZ"
2135 c        do i=1,nres-1
2136 c          write (iout,'(i5,3f10.5,5x,3f10.5)') i,(uy(k,i),k=1,3),
2137 c     &     (uz(k,i),k=1,3)
2138 c        enddo
2139 c      endif
2140 #endif
2141       return
2142       end
2143 C-----------------------------------------------------------------------------
2144       subroutine check_vecgrad
2145       implicit real*8 (a-h,o-z)
2146       include 'DIMENSIONS'
2147       include 'COMMON.IOUNITS'
2148       include 'COMMON.GEO'
2149       include 'COMMON.VAR'
2150       include 'COMMON.LOCAL'
2151       include 'COMMON.CHAIN'
2152       include 'COMMON.VECTORS'
2153       dimension uygradt(3,3,2,maxres),uzgradt(3,3,2,maxres)
2154       dimension uyt(3,maxres),uzt(3,maxres)
2155       dimension uygradn(3,3,2),uzgradn(3,3,2),erij(3)
2156       double precision delta /1.0d-7/
2157       call vec_and_deriv
2158 cd      do i=1,nres
2159 crc          write(iout,'(2i5,2(3f10.5,5x))') i,1,dc_norm(:,i)
2160 crc          write(iout,'(2i5,2(3f10.5,5x))') i,2,uy(:,i)
2161 crc          write(iout,'(2i5,2(3f10.5,5x)/)')i,3,uz(:,i)
2162 cd          write(iout,'(2i5,2(3f10.5,5x))') i,1,
2163 cd     &     (dc_norm(if90,i),if90=1,3)
2164 cd          write(iout,'(2i5,2(3f10.5,5x))') i,2,(uy(if90,i),if90=1,3)
2165 cd          write(iout,'(2i5,2(3f10.5,5x)/)')i,3,(uz(if90,i),if90=1,3)
2166 cd          write(iout,'(a)')
2167 cd      enddo
2168       do i=1,nres
2169         do j=1,2
2170           do k=1,3
2171             do l=1,3
2172               uygradt(l,k,j,i)=uygrad(l,k,j,i)
2173               uzgradt(l,k,j,i)=uzgrad(l,k,j,i)
2174             enddo
2175           enddo
2176         enddo
2177       enddo
2178       call vec_and_deriv
2179       do i=1,nres
2180         do j=1,3
2181           uyt(j,i)=uy(j,i)
2182           uzt(j,i)=uz(j,i)
2183         enddo
2184       enddo
2185       do i=1,nres
2186 cd        write (iout,*) 'i=',i
2187         do k=1,3
2188           erij(k)=dc_norm(k,i)
2189         enddo
2190         do j=1,3
2191           do k=1,3
2192             dc_norm(k,i)=erij(k)
2193           enddo
2194           dc_norm(j,i)=dc_norm(j,i)+delta
2195 c          fac=dsqrt(scalar(dc_norm(1,i),dc_norm(1,i)))
2196 c          do k=1,3
2197 c            dc_norm(k,i)=dc_norm(k,i)/fac
2198 c          enddo
2199 c          write (iout,*) (dc_norm(k,i),k=1,3)
2200 c          write (iout,*) (erij(k),k=1,3)
2201           call vec_and_deriv
2202           do k=1,3
2203             uygradn(k,j,1)=(uy(k,i)-uyt(k,i))/delta
2204             uygradn(k,j,2)=(uy(k,i-1)-uyt(k,i-1))/delta
2205             uzgradn(k,j,1)=(uz(k,i)-uzt(k,i))/delta
2206             uzgradn(k,j,2)=(uz(k,i-1)-uzt(k,i-1))/delta
2207           enddo 
2208 c          write (iout,'(i5,3f8.5,3x,3f8.5,5x,3f8.5,3x,3f8.5)') 
2209 c     &      j,(uzgradt(k,j,1,i),k=1,3),(uzgradn(k,j,1),k=1,3),
2210 c     &      (uzgradt(k,j,2,i-1),k=1,3),(uzgradn(k,j,2),k=1,3)
2211         enddo
2212         do k=1,3
2213           dc_norm(k,i)=erij(k)
2214         enddo
2215 cd        do k=1,3
2216 cd          write (iout,'(i5,3f8.5,3x,3f8.5,5x,3f8.5,3x,3f8.5)') 
2217 cd     &      k,(uygradt(k,l,1,i),l=1,3),(uygradn(k,l,1),l=1,3),
2218 cd     &      (uygradt(k,l,2,i-1),l=1,3),(uygradn(k,l,2),l=1,3)
2219 cd          write (iout,'(i5,3f8.5,3x,3f8.5,5x,3f8.5,3x,3f8.5)') 
2220 cd     &      k,(uzgradt(k,l,1,i),l=1,3),(uzgradn(k,l,1),l=1,3),
2221 cd     &      (uzgradt(k,l,2,i-1),l=1,3),(uzgradn(k,l,2),l=1,3)
2222 cd          write (iout,'(a)')
2223 cd        enddo
2224       enddo
2225       return
2226       end
2227 C--------------------------------------------------------------------------
2228       subroutine set_matrices
2229       implicit real*8 (a-h,o-z)
2230       include 'DIMENSIONS'
2231 #ifdef MPI
2232       include "mpif.h"
2233       include "COMMON.SETUP"
2234       integer IERR
2235       integer status(MPI_STATUS_SIZE)
2236 #endif
2237       include 'COMMON.IOUNITS'
2238       include 'COMMON.GEO'
2239       include 'COMMON.VAR'
2240       include 'COMMON.LOCAL'
2241       include 'COMMON.CHAIN'
2242       include 'COMMON.DERIV'
2243       include 'COMMON.INTERACT'
2244       include 'COMMON.CONTACTS'
2245       include 'COMMON.TORSION'
2246       include 'COMMON.VECTORS'
2247       include 'COMMON.FFIELD'
2248       double precision auxvec(2),auxmat(2,2)
2249 C
2250 C Compute the virtual-bond-torsional-angle dependent quantities needed
2251 C to calculate the el-loc multibody terms of various order.
2252 C
2253 #ifdef PARMAT
2254       do i=ivec_start+2,ivec_end+2
2255 #else
2256       do i=3,nres+1
2257 #endif
2258         if (i .lt. nres+1) then
2259           sin1=dsin(phi(i))
2260           cos1=dcos(phi(i))
2261           sintab(i-2)=sin1
2262           costab(i-2)=cos1
2263           obrot(1,i-2)=cos1
2264           obrot(2,i-2)=sin1
2265           sin2=dsin(2*phi(i))
2266           cos2=dcos(2*phi(i))
2267           sintab2(i-2)=sin2
2268           costab2(i-2)=cos2
2269           obrot2(1,i-2)=cos2
2270           obrot2(2,i-2)=sin2
2271           Ug(1,1,i-2)=-cos1
2272           Ug(1,2,i-2)=-sin1
2273           Ug(2,1,i-2)=-sin1
2274           Ug(2,2,i-2)= cos1
2275           Ug2(1,1,i-2)=-cos2
2276           Ug2(1,2,i-2)=-sin2
2277           Ug2(2,1,i-2)=-sin2
2278           Ug2(2,2,i-2)= cos2
2279         else
2280           costab(i-2)=1.0d0
2281           sintab(i-2)=0.0d0
2282           obrot(1,i-2)=1.0d0
2283           obrot(2,i-2)=0.0d0
2284           obrot2(1,i-2)=0.0d0
2285           obrot2(2,i-2)=0.0d0
2286           Ug(1,1,i-2)=1.0d0
2287           Ug(1,2,i-2)=0.0d0
2288           Ug(2,1,i-2)=0.0d0
2289           Ug(2,2,i-2)=1.0d0
2290           Ug2(1,1,i-2)=0.0d0
2291           Ug2(1,2,i-2)=0.0d0
2292           Ug2(2,1,i-2)=0.0d0
2293           Ug2(2,2,i-2)=0.0d0
2294         endif
2295         if (i .gt. 3 .and. i .lt. nres+1) then
2296           obrot_der(1,i-2)=-sin1
2297           obrot_der(2,i-2)= cos1
2298           Ugder(1,1,i-2)= sin1
2299           Ugder(1,2,i-2)=-cos1
2300           Ugder(2,1,i-2)=-cos1
2301           Ugder(2,2,i-2)=-sin1
2302           dwacos2=cos2+cos2
2303           dwasin2=sin2+sin2
2304           obrot2_der(1,i-2)=-dwasin2
2305           obrot2_der(2,i-2)= dwacos2
2306           Ug2der(1,1,i-2)= dwasin2
2307           Ug2der(1,2,i-2)=-dwacos2
2308           Ug2der(2,1,i-2)=-dwacos2
2309           Ug2der(2,2,i-2)=-dwasin2
2310         else
2311           obrot_der(1,i-2)=0.0d0
2312           obrot_der(2,i-2)=0.0d0
2313           Ugder(1,1,i-2)=0.0d0
2314           Ugder(1,2,i-2)=0.0d0
2315           Ugder(2,1,i-2)=0.0d0
2316           Ugder(2,2,i-2)=0.0d0
2317           obrot2_der(1,i-2)=0.0d0
2318           obrot2_der(2,i-2)=0.0d0
2319           Ug2der(1,1,i-2)=0.0d0
2320           Ug2der(1,2,i-2)=0.0d0
2321           Ug2der(2,1,i-2)=0.0d0
2322           Ug2der(2,2,i-2)=0.0d0
2323         endif
2324 c        if (i.gt. iatel_s+2 .and. i.lt.iatel_e+5) then
2325         if (i.gt. nnt+2 .and. i.lt.nct+2) then
2326           iti = itortyp(itype(i-2))
2327         else
2328           iti=ntortyp+1
2329         endif
2330 c        if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
2331         if (i.gt. nnt+1 .and. i.lt.nct+1) then
2332           iti1 = itortyp(itype(i-1))
2333         else
2334           iti1=ntortyp+1
2335         endif
2336 cd        write (iout,*) '*******i',i,' iti1',iti
2337 cd        write (iout,*) 'b1',b1(:,iti)
2338 cd        write (iout,*) 'b2',b2(:,iti)
2339 cd        write (iout,*) 'Ug',Ug(:,:,i-2)
2340 c        if (i .gt. iatel_s+2) then
2341         if (i .gt. nnt+2) then
2342           call matvec2(Ug(1,1,i-2),b2(1,iti),Ub2(1,i-2))
2343           call matmat2(EE(1,1,iti),Ug(1,1,i-2),EUg(1,1,i-2))
2344           if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0) 
2345      &    then
2346           call matmat2(CC(1,1,iti),Ug(1,1,i-2),CUg(1,1,i-2))
2347           call matmat2(DD(1,1,iti),Ug(1,1,i-2),DUg(1,1,i-2))
2348           call matmat2(Dtilde(1,1,iti),Ug2(1,1,i-2),DtUg2(1,1,i-2))
2349           call matvec2(Ctilde(1,1,iti1),obrot(1,i-2),Ctobr(1,i-2))
2350           call matvec2(Dtilde(1,1,iti),obrot2(1,i-2),Dtobr2(1,i-2))
2351           endif
2352         else
2353           do k=1,2
2354             Ub2(k,i-2)=0.0d0
2355             Ctobr(k,i-2)=0.0d0 
2356             Dtobr2(k,i-2)=0.0d0
2357             do l=1,2
2358               EUg(l,k,i-2)=0.0d0
2359               CUg(l,k,i-2)=0.0d0
2360               DUg(l,k,i-2)=0.0d0
2361               DtUg2(l,k,i-2)=0.0d0
2362             enddo
2363           enddo
2364         endif
2365         call matvec2(Ugder(1,1,i-2),b2(1,iti),Ub2der(1,i-2))
2366         call matmat2(EE(1,1,iti),Ugder(1,1,i-2),EUgder(1,1,i-2))
2367         do k=1,2
2368           muder(k,i-2)=Ub2der(k,i-2)
2369         enddo
2370 c        if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
2371         if (i.gt. nnt+1 .and. i.lt.nct+1) then
2372           iti1 = itortyp(itype(i-1))
2373         else
2374           iti1=ntortyp+1
2375         endif
2376         do k=1,2
2377           mu(k,i-2)=Ub2(k,i-2)+b1(k,iti1)
2378         enddo
2379 cd        write (iout,*) 'mu ',mu(:,i-2)
2380 cd        write (iout,*) 'mu1',mu1(:,i-2)
2381 cd        write (iout,*) 'mu2',mu2(:,i-2)
2382         if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or.wcorr6.gt.0.0d0)
2383      &  then  
2384         call matmat2(CC(1,1,iti1),Ugder(1,1,i-2),CUgder(1,1,i-2))
2385         call matmat2(DD(1,1,iti),Ugder(1,1,i-2),DUgder(1,1,i-2))
2386         call matmat2(Dtilde(1,1,iti),Ug2der(1,1,i-2),DtUg2der(1,1,i-2))
2387         call matvec2(Ctilde(1,1,iti1),obrot_der(1,i-2),Ctobrder(1,i-2))
2388         call matvec2(Dtilde(1,1,iti),obrot2_der(1,i-2),Dtobr2der(1,i-2))
2389 C Vectors and matrices dependent on a single virtual-bond dihedral.
2390         call matvec2(DD(1,1,iti),b1tilde(1,iti1),auxvec(1))
2391         call matvec2(Ug2(1,1,i-2),auxvec(1),Ug2Db1t(1,i-2)) 
2392         call matvec2(Ug2der(1,1,i-2),auxvec(1),Ug2Db1tder(1,i-2)) 
2393         call matvec2(CC(1,1,iti1),Ub2(1,i-2),CUgb2(1,i-2))
2394         call matvec2(CC(1,1,iti1),Ub2der(1,i-2),CUgb2der(1,i-2))
2395         call matmat2(EUg(1,1,i-2),CC(1,1,iti1),EUgC(1,1,i-2))
2396         call matmat2(EUgder(1,1,i-2),CC(1,1,iti1),EUgCder(1,1,i-2))
2397         call matmat2(EUg(1,1,i-2),DD(1,1,iti1),EUgD(1,1,i-2))
2398         call matmat2(EUgder(1,1,i-2),DD(1,1,iti1),EUgDder(1,1,i-2))
2399         endif
2400       enddo
2401 C Matrices dependent on two consecutive virtual-bond dihedrals.
2402 C The order of matrices is from left to right.
2403       if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or.wcorr6.gt.0.0d0)
2404      &then
2405 c      do i=max0(ivec_start,2),ivec_end
2406       do i=2,nres-1
2407         call matmat2(DtUg2(1,1,i-1),EUg(1,1,i),DtUg2EUg(1,1,i))
2408         call matmat2(DtUg2der(1,1,i-1),EUg(1,1,i),DtUg2EUgder(1,1,1,i))
2409         call matmat2(DtUg2(1,1,i-1),EUgder(1,1,i),DtUg2EUgder(1,1,2,i))
2410         call transpose2(DtUg2(1,1,i-1),auxmat(1,1))
2411         call matmat2(auxmat(1,1),EUg(1,1,i),Ug2DtEUg(1,1,i))
2412         call matmat2(auxmat(1,1),EUgder(1,1,i),Ug2DtEUgder(1,1,2,i))
2413         call transpose2(DtUg2der(1,1,i-1),auxmat(1,1))
2414         call matmat2(auxmat(1,1),EUg(1,1,i),Ug2DtEUgder(1,1,1,i))
2415       enddo
2416       endif
2417 #if defined(MPI) && defined(PARMAT)
2418 #ifdef DEBUG
2419 c      if (fg_rank.eq.0) then
2420         write (iout,*) "Arrays UG and UGDER before GATHER"
2421         do i=1,nres-1
2422           write (iout,'(i5,4f10.5,5x,4f10.5)') i,
2423      &     ((ug(l,k,i),l=1,2),k=1,2),
2424      &     ((ugder(l,k,i),l=1,2),k=1,2)
2425         enddo
2426         write (iout,*) "Arrays UG2 and UG2DER"
2427         do i=1,nres-1
2428           write (iout,'(i5,4f10.5,5x,4f10.5)') i,
2429      &     ((ug2(l,k,i),l=1,2),k=1,2),
2430      &     ((ug2der(l,k,i),l=1,2),k=1,2)
2431         enddo
2432         write (iout,*) "Arrays OBROT OBROT2 OBROTDER and OBROT2DER"
2433         do i=1,nres-1
2434           write (iout,'(i5,4f10.5,5x,4f10.5)') i,
2435      &     (obrot(k,i),k=1,2),(obrot2(k,i),k=1,2),
2436      &     (obrot_der(k,i),k=1,2),(obrot2_der(k,i),k=1,2)
2437         enddo
2438         write (iout,*) "Arrays COSTAB SINTAB COSTAB2 and SINTAB2"
2439         do i=1,nres-1
2440           write (iout,'(i5,4f10.5,5x,4f10.5)') i,
2441      &     costab(i),sintab(i),costab2(i),sintab2(i)
2442         enddo
2443         write (iout,*) "Array MUDER"
2444         do i=1,nres-1
2445           write (iout,'(i5,2f10.5)') i,muder(1,i),muder(2,i)
2446         enddo
2447 c      endif
2448 #endif
2449       if (nfgtasks.gt.1) then
2450         time00=MPI_Wtime()
2451 c        write(iout,*)"Processor",fg_rank,kolor," ivec_start",ivec_start,
2452 c     &   " ivec_displ",(ivec_displ(i),i=0,nfgtasks-1),
2453 c     &   " ivec_count",(ivec_count(i),i=0,nfgtasks-1)
2454 #ifdef MATGATHER
2455         call MPI_Allgatherv(Ub2(1,ivec_start),ivec_count(fg_rank1),
2456      &   MPI_MU,Ub2(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2457      &   FG_COMM1,IERR)
2458         call MPI_Allgatherv(Ub2der(1,ivec_start),ivec_count(fg_rank1),
2459      &   MPI_MU,Ub2der(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2460      &   FG_COMM1,IERR)
2461         call MPI_Allgatherv(mu(1,ivec_start),ivec_count(fg_rank1),
2462      &   MPI_MU,mu(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2463      &   FG_COMM1,IERR)
2464         call MPI_Allgatherv(muder(1,ivec_start),ivec_count(fg_rank1),
2465      &   MPI_MU,muder(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2466      &   FG_COMM1,IERR)
2467         call MPI_Allgatherv(Eug(1,1,ivec_start),ivec_count(fg_rank1),
2468      &   MPI_MAT1,Eug(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2469      &   FG_COMM1,IERR)
2470         call MPI_Allgatherv(Eugder(1,1,ivec_start),ivec_count(fg_rank1),
2471      &   MPI_MAT1,Eugder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2472      &   FG_COMM1,IERR)
2473         call MPI_Allgatherv(costab(ivec_start),ivec_count(fg_rank1),
2474      &   MPI_DOUBLE_PRECISION,costab(1),ivec_count(0),ivec_displ(0),
2475      &   MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
2476         call MPI_Allgatherv(sintab(ivec_start),ivec_count(fg_rank1),
2477      &   MPI_DOUBLE_PRECISION,sintab(1),ivec_count(0),ivec_displ(0),
2478      &   MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
2479         call MPI_Allgatherv(costab2(ivec_start),ivec_count(fg_rank1),
2480      &   MPI_DOUBLE_PRECISION,costab2(1),ivec_count(0),ivec_displ(0),
2481      &   MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
2482         call MPI_Allgatherv(sintab2(ivec_start),ivec_count(fg_rank1),
2483      &   MPI_DOUBLE_PRECISION,sintab2(1),ivec_count(0),ivec_displ(0),
2484      &   MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
2485         if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0)
2486      &  then
2487         call MPI_Allgatherv(Ctobr(1,ivec_start),ivec_count(fg_rank1),
2488      &   MPI_MU,Ctobr(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2489      &   FG_COMM1,IERR)
2490         call MPI_Allgatherv(Ctobrder(1,ivec_start),ivec_count(fg_rank1),
2491      &   MPI_MU,Ctobrder(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2492      &   FG_COMM1,IERR)
2493         call MPI_Allgatherv(Dtobr2(1,ivec_start),ivec_count(fg_rank1),
2494      &   MPI_MU,Dtobr2(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2495      &   FG_COMM1,IERR)
2496        call MPI_Allgatherv(Dtobr2der(1,ivec_start),ivec_count(fg_rank1),
2497      &   MPI_MU,Dtobr2der(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2498      &   FG_COMM1,IERR)
2499         call MPI_Allgatherv(Ug2Db1t(1,ivec_start),ivec_count(fg_rank1),
2500      &   MPI_MU,Ug2Db1t(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2501      &   FG_COMM1,IERR)
2502         call MPI_Allgatherv(Ug2Db1tder(1,ivec_start),
2503      &   ivec_count(fg_rank1),
2504      &   MPI_MU,Ug2Db1tder(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2505      &   FG_COMM1,IERR)
2506         call MPI_Allgatherv(CUgb2(1,ivec_start),ivec_count(fg_rank1),
2507      &   MPI_MU,CUgb2(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2508      &   FG_COMM1,IERR)
2509         call MPI_Allgatherv(CUgb2der(1,ivec_start),ivec_count(fg_rank1),
2510      &   MPI_MU,CUgb2der(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
2511      &   FG_COMM1,IERR)
2512         call MPI_Allgatherv(Cug(1,1,ivec_start),ivec_count(fg_rank1),
2513      &   MPI_MAT1,Cug(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2514      &   FG_COMM1,IERR)
2515         call MPI_Allgatherv(Cugder(1,1,ivec_start),ivec_count(fg_rank1),
2516      &   MPI_MAT1,Cugder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2517      &   FG_COMM1,IERR)
2518         call MPI_Allgatherv(Dug(1,1,ivec_start),ivec_count(fg_rank1),
2519      &   MPI_MAT1,Dug(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2520      &   FG_COMM1,IERR)
2521         call MPI_Allgatherv(Dugder(1,1,ivec_start),ivec_count(fg_rank1),
2522      &   MPI_MAT1,Dugder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2523      &   FG_COMM1,IERR)
2524         call MPI_Allgatherv(Dtug2(1,1,ivec_start),ivec_count(fg_rank1),
2525      &   MPI_MAT1,Dtug2(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2526      &   FG_COMM1,IERR)
2527         call MPI_Allgatherv(Dtug2der(1,1,ivec_start),
2528      &   ivec_count(fg_rank1),
2529      &   MPI_MAT1,Dtug2der(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2530      &   FG_COMM1,IERR)
2531         call MPI_Allgatherv(EugC(1,1,ivec_start),ivec_count(fg_rank1),
2532      &   MPI_MAT1,EugC(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2533      &   FG_COMM1,IERR)
2534        call MPI_Allgatherv(EugCder(1,1,ivec_start),ivec_count(fg_rank1),
2535      &   MPI_MAT1,EugCder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2536      &   FG_COMM1,IERR)
2537         call MPI_Allgatherv(EugD(1,1,ivec_start),ivec_count(fg_rank1),
2538      &   MPI_MAT1,EugD(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2539      &   FG_COMM1,IERR)
2540        call MPI_Allgatherv(EugDder(1,1,ivec_start),ivec_count(fg_rank1),
2541      &   MPI_MAT1,EugDder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2542      &   FG_COMM1,IERR)
2543         call MPI_Allgatherv(DtUg2EUg(1,1,ivec_start),
2544      &   ivec_count(fg_rank1),
2545      &   MPI_MAT1,DtUg2EUg(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2546      &   FG_COMM1,IERR)
2547         call MPI_Allgatherv(Ug2DtEUg(1,1,ivec_start),
2548      &   ivec_count(fg_rank1),
2549      &   MPI_MAT1,Ug2DtEUg(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
2550      &   FG_COMM1,IERR)
2551         call MPI_Allgatherv(DtUg2EUgder(1,1,1,ivec_start),
2552      &   ivec_count(fg_rank1),
2553      &   MPI_MAT2,DtUg2EUgder(1,1,1,1),ivec_count(0),ivec_displ(0),
2554      &   MPI_MAT2,FG_COMM1,IERR)
2555         call MPI_Allgatherv(Ug2DtEUgder(1,1,1,ivec_start),
2556      &   ivec_count(fg_rank1),
2557      &   MPI_MAT2,Ug2DtEUgder(1,1,1,1),ivec_count(0),ivec_displ(0),
2558      &   MPI_MAT2,FG_COMM1,IERR)
2559         endif
2560 #else
2561 c Passes matrix info through the ring
2562       isend=fg_rank1
2563       irecv=fg_rank1-1
2564       if (irecv.lt.0) irecv=nfgtasks1-1 
2565       iprev=irecv
2566       inext=fg_rank1+1
2567       if (inext.ge.nfgtasks1) inext=0
2568       do i=1,nfgtasks1-1
2569 c        write (iout,*) "isend",isend," irecv",irecv
2570 c        call flush(iout)
2571         lensend=lentyp(isend)
2572         lenrecv=lentyp(irecv)
2573 c        write (iout,*) "lensend",lensend," lenrecv",lenrecv
2574 c        call MPI_SENDRECV(ug(1,1,ivec_displ(isend)+1),1,
2575 c     &   MPI_ROTAT1(lensend),inext,2200+isend,
2576 c     &   ug(1,1,ivec_displ(irecv)+1),1,MPI_ROTAT1(lenrecv),
2577 c     &   iprev,2200+irecv,FG_COMM,status,IERR)
2578 c        write (iout,*) "Gather ROTAT1"
2579 c        call flush(iout)
2580 c        call MPI_SENDRECV(obrot(1,ivec_displ(isend)+1),1,
2581 c     &   MPI_ROTAT2(lensend),inext,3300+isend,
2582 c     &   obrot(1,ivec_displ(irecv)+1),1,MPI_ROTAT2(lenrecv),
2583 c     &   iprev,3300+irecv,FG_COMM,status,IERR)
2584 c        write (iout,*) "Gather ROTAT2"
2585 c        call flush(iout)
2586         call MPI_SENDRECV(costab(ivec_displ(isend)+1),1,
2587      &   MPI_ROTAT_OLD(lensend),inext,4400+isend,
2588      &   costab(ivec_displ(irecv)+1),1,MPI_ROTAT_OLD(lenrecv),
2589      &   iprev,4400+irecv,FG_COMM,status,IERR)
2590 c        write (iout,*) "Gather ROTAT_OLD"
2591 c        call flush(iout)
2592         call MPI_SENDRECV(mu(1,ivec_displ(isend)+1),1,
2593      &   MPI_PRECOMP11(lensend),inext,5500+isend,
2594      &   mu(1,ivec_displ(irecv)+1),1,MPI_PRECOMP11(lenrecv),
2595      &   iprev,5500+irecv,FG_COMM,status,IERR)
2596 c        write (iout,*) "Gather PRECOMP11"
2597 c        call flush(iout)
2598         call MPI_SENDRECV(Eug(1,1,ivec_displ(isend)+1),1,
2599      &   MPI_PRECOMP12(lensend),inext,6600+isend,
2600      &   Eug(1,1,ivec_displ(irecv)+1),1,MPI_PRECOMP12(lenrecv),
2601      &   iprev,6600+irecv,FG_COMM,status,IERR)
2602 c        write (iout,*) "Gather PRECOMP12"
2603 c        call flush(iout)
2604         if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0) 
2605      &  then
2606         call MPI_SENDRECV(ug2db1t(1,ivec_displ(isend)+1),1,
2607      &   MPI_ROTAT2(lensend),inext,7700+isend,
2608      &   ug2db1t(1,ivec_displ(irecv)+1),1,MPI_ROTAT2(lenrecv),
2609      &   iprev,7700+irecv,FG_COMM,status,IERR)
2610 c        write (iout,*) "Gather PRECOMP21"
2611 c        call flush(iout)
2612         call MPI_SENDRECV(EUgC(1,1,ivec_displ(isend)+1),1,
2613      &   MPI_PRECOMP22(lensend),inext,8800+isend,
2614      &   EUgC(1,1,ivec_displ(irecv)+1),1,MPI_PRECOMP22(lenrecv),
2615      &   iprev,8800+irecv,FG_COMM,status,IERR)
2616 c        write (iout,*) "Gather PRECOMP22"
2617 c        call flush(iout)
2618         call MPI_SENDRECV(Ug2DtEUgder(1,1,1,ivec_displ(isend)+1),1,
2619      &   MPI_PRECOMP23(lensend),inext,9900+isend,
2620      &   Ug2DtEUgder(1,1,1,ivec_displ(irecv)+1),1,
2621      &   MPI_PRECOMP23(lenrecv),
2622      &   iprev,9900+irecv,FG_COMM,status,IERR)
2623 c        write (iout,*) "Gather PRECOMP23"
2624 c        call flush(iout)
2625         endif
2626         isend=irecv
2627         irecv=irecv-1
2628         if (irecv.lt.0) irecv=nfgtasks1-1
2629       enddo
2630 #endif
2631         time_gather=time_gather+MPI_Wtime()-time00
2632       endif
2633 #ifdef DEBUG
2634 c      if (fg_rank.eq.0) then
2635         write (iout,*) "Arrays UG and UGDER"
2636         do i=1,nres-1
2637           write (iout,'(i5,4f10.5,5x,4f10.5)') i,
2638      &     ((ug(l,k,i),l=1,2),k=1,2),
2639      &     ((ugder(l,k,i),l=1,2),k=1,2)
2640         enddo
2641         write (iout,*) "Arrays UG2 and UG2DER"
2642         do i=1,nres-1
2643           write (iout,'(i5,4f10.5,5x,4f10.5)') i,
2644      &     ((ug2(l,k,i),l=1,2),k=1,2),
2645      &     ((ug2der(l,k,i),l=1,2),k=1,2)
2646         enddo
2647         write (iout,*) "Arrays OBROT OBROT2 OBROTDER and OBROT2DER"
2648         do i=1,nres-1
2649           write (iout,'(i5,4f10.5,5x,4f10.5)') i,
2650      &     (obrot(k,i),k=1,2),(obrot2(k,i),k=1,2),
2651      &     (obrot_der(k,i),k=1,2),(obrot2_der(k,i),k=1,2)
2652         enddo
2653         write (iout,*) "Arrays COSTAB SINTAB COSTAB2 and SINTAB2"
2654         do i=1,nres-1
2655           write (iout,'(i5,4f10.5,5x,4f10.5)') i,
2656      &     costab(i),sintab(i),costab2(i),sintab2(i)
2657         enddo
2658         write (iout,*) "Array MUDER"
2659         do i=1,nres-1
2660           write (iout,'(i5,2f10.5)') i,muder(1,i),muder(2,i)
2661         enddo
2662 c      endif
2663 #endif
2664 #endif
2665 cd      do i=1,nres
2666 cd        iti = itortyp(itype(i))
2667 cd        write (iout,*) i
2668 cd        do j=1,2
2669 cd        write (iout,'(2f10.5,5x,2f10.5,5x,2f10.5)') 
2670 cd     &  (EE(j,k,iti),k=1,2),(Ug(j,k,i),k=1,2),(EUg(j,k,i),k=1,2)
2671 cd        enddo
2672 cd      enddo
2673       return
2674       end
2675 C--------------------------------------------------------------------------
2676       subroutine eelec(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
2677 C
2678 C This subroutine calculates the average interaction energy and its gradient
2679 C in the virtual-bond vectors between non-adjacent peptide groups, based on 
2680 C the potential described in Liwo et al., Protein Sci., 1993, 2, 1715. 
2681 C The potential depends both on the distance of peptide-group centers and on 
2682 C the orientation of the CA-CA virtual bonds.
2683
2684       implicit real*8 (a-h,o-z)
2685 #ifdef MPI
2686       include 'mpif.h'
2687 #endif
2688       include 'DIMENSIONS'
2689       include 'COMMON.CONTROL'
2690       include 'COMMON.SETUP'
2691       include 'COMMON.IOUNITS'
2692       include 'COMMON.GEO'
2693       include 'COMMON.VAR'
2694       include 'COMMON.LOCAL'
2695       include 'COMMON.CHAIN'
2696       include 'COMMON.DERIV'
2697       include 'COMMON.INTERACT'
2698       include 'COMMON.CONTACTS'
2699       include 'COMMON.TORSION'
2700       include 'COMMON.VECTORS'
2701       include 'COMMON.FFIELD'
2702       include 'COMMON.TIME1'
2703       dimension ggg(3),gggp(3),gggm(3),erij(3),dcosb(3),dcosg(3),
2704      &          erder(3,3),uryg(3,3),urzg(3,3),vryg(3,3),vrzg(3,3)
2705       double precision acipa(2,2),agg(3,4),aggi(3,4),aggi1(3,4),
2706      &    aggj(3,4),aggj1(3,4),a_temp(2,2),muij(4)
2707       common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,a22,a23,a32,a33,
2708      &    dxi,dyi,dzi,dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,
2709      &    num_conti,j1,j2
2710 c 4/26/02 - AL scaling factor for 1,4 repulsive VDW interactions
2711 #ifdef MOMENT
2712       double precision scal_el /1.0d0/
2713 #else
2714       double precision scal_el /0.5d0/
2715 #endif
2716 C 12/13/98 
2717 C 13-go grudnia roku pamietnego... 
2718       double precision unmat(3,3) /1.0d0,0.0d0,0.0d0,
2719      &                   0.0d0,1.0d0,0.0d0,
2720      &                   0.0d0,0.0d0,1.0d0/
2721 cd      write(iout,*) 'In EELEC'
2722 cd      do i=1,nloctyp
2723 cd        write(iout,*) 'Type',i
2724 cd        write(iout,*) 'B1',B1(:,i)
2725 cd        write(iout,*) 'B2',B2(:,i)
2726 cd        write(iout,*) 'CC',CC(:,:,i)
2727 cd        write(iout,*) 'DD',DD(:,:,i)
2728 cd        write(iout,*) 'EE',EE(:,:,i)
2729 cd      enddo
2730 cd      call check_vecgrad
2731 cd      stop
2732       if (icheckgrad.eq.1) then
2733         do i=1,nres-1
2734           fac=1.0d0/dsqrt(scalar(dc(1,i),dc(1,i)))
2735           do k=1,3
2736             dc_norm(k,i)=dc(k,i)*fac
2737           enddo
2738 c          write (iout,*) 'i',i,' fac',fac
2739         enddo
2740       endif
2741       if (wel_loc.gt.0.0d0 .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 
2742      &    .or. wcorr6.gt.0.0d0 .or. wturn3.gt.0.0d0 .or. 
2743      &    wturn4.gt.0.0d0 .or. wturn6.gt.0.0d0) then
2744 c        call vec_and_deriv
2745 #ifdef TIMING
2746         time01=MPI_Wtime()
2747 #endif
2748         call set_matrices
2749 #ifdef TIMING
2750         time_mat=time_mat+MPI_Wtime()-time01
2751 #endif
2752       endif
2753 cd      do i=1,nres-1
2754 cd        write (iout,*) 'i=',i
2755 cd        do k=1,3
2756 cd        write (iout,'(i5,2f10.5)') k,uy(k,i),uz(k,i)
2757 cd        enddo
2758 cd        do k=1,3
2759 cd          write (iout,'(f10.5,2x,3f10.5,2x,3f10.5)') 
2760 cd     &     uz(k,i),(uzgrad(k,l,1,i),l=1,3),(uzgrad(k,l,2,i),l=1,3)
2761 cd        enddo
2762 cd      enddo
2763       t_eelecij=0.0d0
2764       ees=0.0D0
2765       evdw1=0.0D0
2766       eel_loc=0.0d0 
2767       eello_turn3=0.0d0
2768       eello_turn4=0.0d0
2769       ind=0
2770       do i=1,nres
2771         num_cont_hb(i)=0
2772       enddo
2773 cd      print '(a)','Enter EELEC'
2774 cd      write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
2775       do i=1,nres
2776         gel_loc_loc(i)=0.0d0
2777         gcorr_loc(i)=0.0d0
2778       enddo
2779 c
2780 c
2781 c 9/27/08 AL Split the interaction loop to ensure load balancing of turn terms
2782 C
2783 C Loop over i,i+2 and i,i+3 pairs of the peptide groups
2784 C
2785       do i=iturn3_start,iturn3_end
2786         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
2787      &  .or. itype(i+2).eq.ntyp1 .or. itype(i+3).eq.ntyp1) cycle
2788         dxi=dc(1,i)
2789         dyi=dc(2,i)
2790         dzi=dc(3,i)
2791         dx_normi=dc_norm(1,i)
2792         dy_normi=dc_norm(2,i)
2793         dz_normi=dc_norm(3,i)
2794         xmedi=c(1,i)+0.5d0*dxi
2795         ymedi=c(2,i)+0.5d0*dyi
2796         zmedi=c(3,i)+0.5d0*dzi
2797         num_conti=0
2798         call eelecij(i,i+2,ees,evdw1,eel_loc)
2799         if (wturn3.gt.0.0d0) call eturn3(i,eello_turn3)
2800         num_cont_hb(i)=num_conti
2801       enddo
2802       do i=iturn4_start,iturn4_end
2803         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
2804      &    .or. itype(i+3).eq.ntyp1
2805      &    .or. itype(i+4).eq.ntyp1) cycle
2806         dxi=dc(1,i)
2807         dyi=dc(2,i)
2808         dzi=dc(3,i)
2809         dx_normi=dc_norm(1,i)
2810         dy_normi=dc_norm(2,i)
2811         dz_normi=dc_norm(3,i)
2812         xmedi=c(1,i)+0.5d0*dxi
2813         ymedi=c(2,i)+0.5d0*dyi
2814         zmedi=c(3,i)+0.5d0*dzi
2815         num_conti=num_cont_hb(i)
2816         call eelecij(i,i+3,ees,evdw1,eel_loc)
2817         if (wturn4.gt.0.0d0 .and. itype(i+2).ne.ntyp1) 
2818      &   call eturn4(i,eello_turn4)
2819         num_cont_hb(i)=num_conti
2820       enddo   ! i
2821 c
2822 c Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
2823 c
2824       do i=iatel_s,iatel_e
2825         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
2826         dxi=dc(1,i)
2827         dyi=dc(2,i)
2828         dzi=dc(3,i)
2829         dx_normi=dc_norm(1,i)
2830         dy_normi=dc_norm(2,i)
2831         dz_normi=dc_norm(3,i)
2832         xmedi=c(1,i)+0.5d0*dxi
2833         ymedi=c(2,i)+0.5d0*dyi
2834         zmedi=c(3,i)+0.5d0*dzi
2835 c        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
2836         num_conti=num_cont_hb(i)
2837         do j=ielstart(i),ielend(i)
2838 c          write (iout,*) i,j,itype(i),itype(j)
2839           if (itype(j).eq.ntyp1.or. itype(j+1).eq.ntyp1) cycle
2840           call eelecij(i,j,ees,evdw1,eel_loc)
2841         enddo ! j
2842         num_cont_hb(i)=num_conti
2843       enddo   ! i
2844 c      write (iout,*) "Number of loop steps in EELEC:",ind
2845 cd      do i=1,nres
2846 cd        write (iout,'(i3,3f10.5,5x,3f10.5)') 
2847 cd     &     i,(gel_loc(k,i),k=1,3),gel_loc_loc(i)
2848 cd      enddo
2849 c 12/7/99 Adam eello_turn3 will be considered as a separate energy term
2850 ccc      eel_loc=eel_loc+eello_turn3
2851 cd      print *,"Processor",fg_rank," t_eelecij",t_eelecij
2852       return
2853       end
2854 C-------------------------------------------------------------------------------
2855       subroutine eelecij(i,j,ees,evdw1,eel_loc)
2856       implicit real*8 (a-h,o-z)
2857       include 'DIMENSIONS'
2858 #ifdef MPI
2859       include "mpif.h"
2860 #endif
2861       include 'COMMON.CONTROL'
2862       include 'COMMON.IOUNITS'
2863       include 'COMMON.GEO'
2864       include 'COMMON.VAR'
2865       include 'COMMON.LOCAL'
2866       include 'COMMON.CHAIN'
2867       include 'COMMON.DERIV'
2868       include 'COMMON.INTERACT'
2869       include 'COMMON.CONTACTS'
2870       include 'COMMON.TORSION'
2871       include 'COMMON.VECTORS'
2872       include 'COMMON.FFIELD'
2873       include 'COMMON.TIME1'
2874       dimension ggg(3),gggp(3),gggm(3),erij(3),dcosb(3),dcosg(3),
2875      &          erder(3,3),uryg(3,3),urzg(3,3),vryg(3,3),vrzg(3,3)
2876       double precision acipa(2,2),agg(3,4),aggi(3,4),aggi1(3,4),
2877      &    aggj(3,4),aggj1(3,4),a_temp(2,2),muij(4)
2878       common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,a22,a23,a32,a33,
2879      &    dxi,dyi,dzi,dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,
2880      &    num_conti,j1,j2
2881 c 4/26/02 - AL scaling factor for 1,4 repulsive VDW interactions
2882 #ifdef MOMENT
2883       double precision scal_el /1.0d0/
2884 #else
2885       double precision scal_el /0.5d0/
2886 #endif
2887 C 12/13/98 
2888 C 13-go grudnia roku pamietnego... 
2889       double precision unmat(3,3) /1.0d0,0.0d0,0.0d0,
2890      &                   0.0d0,1.0d0,0.0d0,
2891      &                   0.0d0,0.0d0,1.0d0/
2892 c          time00=MPI_Wtime()
2893 cd      write (iout,*) "eelecij",i,j
2894 c          ind=ind+1
2895           iteli=itel(i)
2896           itelj=itel(j)
2897           if (j.eq.i+2 .and. itelj.eq.2) iteli=2
2898           aaa=app(iteli,itelj)
2899           bbb=bpp(iteli,itelj)
2900           ael6i=ael6(iteli,itelj)
2901           ael3i=ael3(iteli,itelj) 
2902           dxj=dc(1,j)
2903           dyj=dc(2,j)
2904           dzj=dc(3,j)
2905           dx_normj=dc_norm(1,j)
2906           dy_normj=dc_norm(2,j)
2907           dz_normj=dc_norm(3,j)
2908           xj=c(1,j)+0.5D0*dxj-xmedi
2909           yj=c(2,j)+0.5D0*dyj-ymedi
2910           zj=c(3,j)+0.5D0*dzj-zmedi
2911           rij=xj*xj+yj*yj+zj*zj
2912           rrmij=1.0D0/rij
2913           rij=dsqrt(rij)
2914           rmij=1.0D0/rij
2915           r3ij=rrmij*rmij
2916           r6ij=r3ij*r3ij  
2917           cosa=dx_normi*dx_normj+dy_normi*dy_normj+dz_normi*dz_normj
2918           cosb=(xj*dx_normi+yj*dy_normi+zj*dz_normi)*rmij
2919           cosg=(xj*dx_normj+yj*dy_normj+zj*dz_normj)*rmij
2920           fac=cosa-3.0D0*cosb*cosg
2921           ev1=aaa*r6ij*r6ij
2922 c 4/26/02 - AL scaling down 1,4 repulsive VDW interactions
2923           if (j.eq.i+2) ev1=scal_el*ev1
2924           ev2=bbb*r6ij
2925           fac3=ael6i*r6ij
2926           fac4=ael3i*r3ij
2927           evdwij=ev1+ev2
2928           el1=fac3*(4.0D0+fac*fac-3.0D0*(cosb*cosb+cosg*cosg))
2929           el2=fac4*fac       
2930           eesij=el1+el2
2931 C 12/26/95 - for the evaluation of multi-body H-bonding interactions
2932           ees0ij=4.0D0+fac*fac-3.0D0*(cosb*cosb+cosg*cosg)
2933           ees=ees+eesij
2934           evdw1=evdw1+evdwij
2935 cd          write(iout,'(2(2i3,2x),7(1pd12.4)/2(3(1pd12.4),5x)/)')
2936 cd     &      iteli,i,itelj,j,aaa,bbb,ael6i,ael3i,
2937 cd     &      1.0D0/dsqrt(rrmij),evdwij,eesij,
2938 cd     &      xmedi,ymedi,zmedi,xj,yj,zj
2939
2940           if (energy_dec) then 
2941               write (iout,'(a6,2i5,0pf7.3)') 'evdw1',i,j,evdwij
2942               write (iout,'(a6,2i5,0pf7.3)') 'ees',i,j,eesij
2943           endif
2944
2945 C
2946 C Calculate contributions to the Cartesian gradient.
2947 C
2948 #ifdef SPLITELE
2949           facvdw=-6*rrmij*(ev1+evdwij)
2950           facel=-3*rrmij*(el1+eesij)
2951           fac1=fac
2952           erij(1)=xj*rmij
2953           erij(2)=yj*rmij
2954           erij(3)=zj*rmij
2955 *
2956 * Radial derivatives. First process both termini of the fragment (i,j)
2957 *
2958           ggg(1)=facel*xj
2959           ggg(2)=facel*yj
2960           ggg(3)=facel*zj
2961 c          do k=1,3
2962 c            ghalf=0.5D0*ggg(k)
2963 c            gelc(k,i)=gelc(k,i)+ghalf
2964 c            gelc(k,j)=gelc(k,j)+ghalf
2965 c          enddo
2966 c 9/28/08 AL Gradient compotents will be summed only at the end
2967           do k=1,3
2968             gelc_long(k,j)=gelc_long(k,j)+ggg(k)
2969             gelc_long(k,i)=gelc_long(k,i)-ggg(k)
2970           enddo
2971 *
2972 * Loop over residues i+1 thru j-1.
2973 *
2974 cgrad          do k=i+1,j-1
2975 cgrad            do l=1,3
2976 cgrad              gelc(l,k)=gelc(l,k)+ggg(l)
2977 cgrad            enddo
2978 cgrad          enddo
2979           ggg(1)=facvdw*xj
2980           ggg(2)=facvdw*yj
2981           ggg(3)=facvdw*zj
2982 c          do k=1,3
2983 c            ghalf=0.5D0*ggg(k)
2984 c            gvdwpp(k,i)=gvdwpp(k,i)+ghalf
2985 c            gvdwpp(k,j)=gvdwpp(k,j)+ghalf
2986 c          enddo
2987 c 9/28/08 AL Gradient compotents will be summed only at the end
2988           do k=1,3
2989             gvdwpp(k,j)=gvdwpp(k,j)+ggg(k)
2990             gvdwpp(k,i)=gvdwpp(k,i)-ggg(k)
2991           enddo
2992 *
2993 * Loop over residues i+1 thru j-1.
2994 *
2995 cgrad          do k=i+1,j-1
2996 cgrad            do l=1,3
2997 cgrad              gvdwpp(l,k)=gvdwpp(l,k)+ggg(l)
2998 cgrad            enddo
2999 cgrad          enddo
3000 #else
3001           facvdw=ev1+evdwij 
3002           facel=el1+eesij  
3003           fac1=fac
3004           fac=-3*rrmij*(facvdw+facvdw+facel)
3005           erij(1)=xj*rmij
3006           erij(2)=yj*rmij
3007           erij(3)=zj*rmij
3008 *
3009 * Radial derivatives. First process both termini of the fragment (i,j)
3010
3011           ggg(1)=fac*xj
3012           ggg(2)=fac*yj
3013           ggg(3)=fac*zj
3014 c          do k=1,3
3015 c            ghalf=0.5D0*ggg(k)
3016 c            gelc(k,i)=gelc(k,i)+ghalf
3017 c            gelc(k,j)=gelc(k,j)+ghalf
3018 c          enddo
3019 c 9/28/08 AL Gradient compotents will be summed only at the end
3020           do k=1,3
3021             gelc_long(k,j)=gelc(k,j)+ggg(k)
3022             gelc_long(k,i)=gelc(k,i)-ggg(k)
3023           enddo
3024 *
3025 * Loop over residues i+1 thru j-1.
3026 *
3027 cgrad          do k=i+1,j-1
3028 cgrad            do l=1,3
3029 cgrad              gelc(l,k)=gelc(l,k)+ggg(l)
3030 cgrad            enddo
3031 cgrad          enddo
3032 c 9/28/08 AL Gradient compotents will be summed only at the end
3033           ggg(1)=facvdw*xj
3034           ggg(2)=facvdw*yj
3035           ggg(3)=facvdw*zj
3036           do k=1,3
3037             gvdwpp(k,j)=gvdwpp(k,j)+ggg(k)
3038             gvdwpp(k,i)=gvdwpp(k,i)-ggg(k)
3039           enddo
3040 #endif
3041 *
3042 * Angular part
3043 *          
3044           ecosa=2.0D0*fac3*fac1+fac4
3045           fac4=-3.0D0*fac4
3046           fac3=-6.0D0*fac3
3047           ecosb=(fac3*(fac1*cosg+cosb)+cosg*fac4)
3048           ecosg=(fac3*(fac1*cosb+cosg)+cosb*fac4)
3049           do k=1,3
3050             dcosb(k)=rmij*(dc_norm(k,i)-erij(k)*cosb)
3051             dcosg(k)=rmij*(dc_norm(k,j)-erij(k)*cosg)
3052           enddo
3053 cd        print '(2i3,2(3(1pd14.5),3x))',i,j,(dcosb(k),k=1,3),
3054 cd   &          (dcosg(k),k=1,3)
3055           do k=1,3
3056             ggg(k)=ecosb*dcosb(k)+ecosg*dcosg(k) 
3057           enddo
3058 c          do k=1,3
3059 c            ghalf=0.5D0*ggg(k)
3060 c            gelc(k,i)=gelc(k,i)+ghalf
3061 c     &               +(ecosa*(dc_norm(k,j)-cosa*dc_norm(k,i))
3062 c     &               + ecosb*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
3063 c            gelc(k,j)=gelc(k,j)+ghalf
3064 c     &               +(ecosa*(dc_norm(k,i)-cosa*dc_norm(k,j))
3065 c     &               + ecosg*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
3066 c          enddo
3067 cgrad          do k=i+1,j-1
3068 cgrad            do l=1,3
3069 cgrad              gelc(l,k)=gelc(l,k)+ggg(l)
3070 cgrad            enddo
3071 cgrad          enddo
3072           do k=1,3
3073             gelc(k,i)=gelc(k,i)
3074      &               +(ecosa*(dc_norm(k,j)-cosa*dc_norm(k,i))
3075      &               + ecosb*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
3076             gelc(k,j)=gelc(k,j)
3077      &               +(ecosa*(dc_norm(k,i)-cosa*dc_norm(k,j))
3078      &               + ecosg*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
3079             gelc_long(k,j)=gelc_long(k,j)+ggg(k)
3080             gelc_long(k,i)=gelc_long(k,i)-ggg(k)
3081           enddo
3082           IF (wel_loc.gt.0.0d0 .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0
3083      &        .or. wcorr6.gt.0.0d0 .or. wturn3.gt.0.0d0 
3084      &        .or. wturn4.gt.0.0d0 .or. wturn6.gt.0.0d0) THEN
3085 C
3086 C 9/25/99 Mixed third-order local-electrostatic terms. The local-interaction 
3087 C   energy of a peptide unit is assumed in the form of a second-order 
3088 C   Fourier series in the angles lambda1 and lambda2 (see Nishikawa et al.
3089 C   Macromolecules, 1974, 7, 797-806 for definition). This correlation terms
3090 C   are computed for EVERY pair of non-contiguous peptide groups.
3091 C
3092           if (j.lt.nres-1) then
3093             j1=j+1
3094             j2=j-1
3095           else
3096             j1=j-1
3097             j2=j-2
3098           endif
3099           kkk=0
3100           do k=1,2
3101             do l=1,2
3102               kkk=kkk+1
3103               muij(kkk)=mu(k,i)*mu(l,j)
3104             enddo
3105           enddo  
3106 cd         write (iout,*) 'EELEC: i',i,' j',j
3107 cd          write (iout,*) 'j',j,' j1',j1,' j2',j2
3108 cd          write(iout,*) 'muij',muij
3109           ury=scalar(uy(1,i),erij)
3110           urz=scalar(uz(1,i),erij)
3111           vry=scalar(uy(1,j),erij)
3112           vrz=scalar(uz(1,j),erij)
3113           a22=scalar(uy(1,i),uy(1,j))-3*ury*vry
3114           a23=scalar(uy(1,i),uz(1,j))-3*ury*vrz
3115           a32=scalar(uz(1,i),uy(1,j))-3*urz*vry
3116           a33=scalar(uz(1,i),uz(1,j))-3*urz*vrz
3117           fac=dsqrt(-ael6i)*r3ij
3118           a22=a22*fac
3119           a23=a23*fac
3120           a32=a32*fac
3121           a33=a33*fac
3122 cd          write (iout,'(4i5,4f10.5)')
3123 cd     &     i,itortyp(itype(i)),j,itortyp(itype(j)),a22,a23,a32,a33
3124 cd          write (iout,'(6f10.5)') (muij(k),k=1,4),fac,eel_loc_ij
3125 cd          write (iout,'(2(3f10.5,5x)/2(3f10.5,5x))') uy(:,i),uz(:,i),
3126 cd     &      uy(:,j),uz(:,j)
3127 cd          write (iout,'(4f10.5)') 
3128 cd     &      scalar(uy(1,i),uy(1,j)),scalar(uy(1,i),uz(1,j)),
3129 cd     &      scalar(uz(1,i),uy(1,j)),scalar(uz(1,i),uz(1,j))
3130 cd          write (iout,'(4f10.5)') ury,urz,vry,vrz
3131 cd           write (iout,'(9f10.5/)') 
3132 cd     &      fac22,a22,fac23,a23,fac32,a32,fac33,a33,eel_loc_ij
3133 C Derivatives of the elements of A in virtual-bond vectors
3134           call unormderiv(erij(1),unmat(1,1),rmij,erder(1,1))
3135           do k=1,3
3136             uryg(k,1)=scalar(erder(1,k),uy(1,i))
3137             uryg(k,2)=scalar(uygrad(1,k,1,i),erij(1))
3138             uryg(k,3)=scalar(uygrad(1,k,2,i),erij(1))
3139             urzg(k,1)=scalar(erder(1,k),uz(1,i))
3140             urzg(k,2)=scalar(uzgrad(1,k,1,i),erij(1))
3141             urzg(k,3)=scalar(uzgrad(1,k,2,i),erij(1))
3142             vryg(k,1)=scalar(erder(1,k),uy(1,j))
3143             vryg(k,2)=scalar(uygrad(1,k,1,j),erij(1))
3144             vryg(k,3)=scalar(uygrad(1,k,2,j),erij(1))
3145             vrzg(k,1)=scalar(erder(1,k),uz(1,j))
3146             vrzg(k,2)=scalar(uzgrad(1,k,1,j),erij(1))
3147             vrzg(k,3)=scalar(uzgrad(1,k,2,j),erij(1))
3148           enddo
3149 C Compute radial contributions to the gradient
3150           facr=-3.0d0*rrmij
3151           a22der=a22*facr
3152           a23der=a23*facr
3153           a32der=a32*facr
3154           a33der=a33*facr
3155           agg(1,1)=a22der*xj
3156           agg(2,1)=a22der*yj
3157           agg(3,1)=a22der*zj
3158           agg(1,2)=a23der*xj
3159           agg(2,2)=a23der*yj
3160           agg(3,2)=a23der*zj
3161           agg(1,3)=a32der*xj
3162           agg(2,3)=a32der*yj
3163           agg(3,3)=a32der*zj
3164           agg(1,4)=a33der*xj
3165           agg(2,4)=a33der*yj
3166           agg(3,4)=a33der*zj
3167 C Add the contributions coming from er
3168           fac3=-3.0d0*fac
3169           do k=1,3
3170             agg(k,1)=agg(k,1)+fac3*(uryg(k,1)*vry+vryg(k,1)*ury)
3171             agg(k,2)=agg(k,2)+fac3*(uryg(k,1)*vrz+vrzg(k,1)*ury)
3172             agg(k,3)=agg(k,3)+fac3*(urzg(k,1)*vry+vryg(k,1)*urz)
3173             agg(k,4)=agg(k,4)+fac3*(urzg(k,1)*vrz+vrzg(k,1)*urz)
3174           enddo
3175           do k=1,3
3176 C Derivatives in DC(i) 
3177 cgrad            ghalf1=0.5d0*agg(k,1)
3178 cgrad            ghalf2=0.5d0*agg(k,2)
3179 cgrad            ghalf3=0.5d0*agg(k,3)
3180 cgrad            ghalf4=0.5d0*agg(k,4)
3181             aggi(k,1)=fac*(scalar(uygrad(1,k,1,i),uy(1,j))
3182      &      -3.0d0*uryg(k,2)*vry)!+ghalf1
3183             aggi(k,2)=fac*(scalar(uygrad(1,k,1,i),uz(1,j))
3184      &      -3.0d0*uryg(k,2)*vrz)!+ghalf2
3185             aggi(k,3)=fac*(scalar(uzgrad(1,k,1,i),uy(1,j))
3186      &      -3.0d0*urzg(k,2)*vry)!+ghalf3
3187             aggi(k,4)=fac*(scalar(uzgrad(1,k,1,i),uz(1,j))
3188      &      -3.0d0*urzg(k,2)*vrz)!+ghalf4
3189 C Derivatives in DC(i+1)
3190             aggi1(k,1)=fac*(scalar(uygrad(1,k,2,i),uy(1,j))
3191      &      -3.0d0*uryg(k,3)*vry)!+agg(k,1)
3192             aggi1(k,2)=fac*(scalar(uygrad(1,k,2,i),uz(1,j))
3193      &      -3.0d0*uryg(k,3)*vrz)!+agg(k,2)
3194             aggi1(k,3)=fac*(scalar(uzgrad(1,k,2,i),uy(1,j))
3195      &      -3.0d0*urzg(k,3)*vry)!+agg(k,3)
3196             aggi1(k,4)=fac*(scalar(uzgrad(1,k,2,i),uz(1,j))
3197      &      -3.0d0*urzg(k,3)*vrz)!+agg(k,4)
3198 C Derivatives in DC(j)
3199             aggj(k,1)=fac*(scalar(uygrad(1,k,1,j),uy(1,i))
3200      &      -3.0d0*vryg(k,2)*ury)!+ghalf1
3201             aggj(k,2)=fac*(scalar(uzgrad(1,k,1,j),uy(1,i))
3202      &      -3.0d0*vrzg(k,2)*ury)!+ghalf2
3203             aggj(k,3)=fac*(scalar(uygrad(1,k,1,j),uz(1,i))
3204      &      -3.0d0*vryg(k,2)*urz)!+ghalf3
3205             aggj(k,4)=fac*(scalar(uzgrad(1,k,1,j),uz(1,i)) 
3206      &      -3.0d0*vrzg(k,2)*urz)!+ghalf4
3207 C Derivatives in DC(j+1) or DC(nres-1)
3208             aggj1(k,1)=fac*(scalar(uygrad(1,k,2,j),uy(1,i))
3209      &      -3.0d0*vryg(k,3)*ury)
3210             aggj1(k,2)=fac*(scalar(uzgrad(1,k,2,j),uy(1,i))
3211      &      -3.0d0*vrzg(k,3)*ury)
3212             aggj1(k,3)=fac*(scalar(uygrad(1,k,2,j),uz(1,i))
3213      &      -3.0d0*vryg(k,3)*urz)
3214             aggj1(k,4)=fac*(scalar(uzgrad(1,k,2,j),uz(1,i)) 
3215      &      -3.0d0*vrzg(k,3)*urz)
3216 cgrad            if (j.eq.nres-1 .and. i.lt.j-2) then
3217 cgrad              do l=1,4
3218 cgrad                aggj1(k,l)=aggj1(k,l)+agg(k,l)
3219 cgrad              enddo
3220 cgrad            endif
3221           enddo
3222           acipa(1,1)=a22
3223           acipa(1,2)=a23
3224           acipa(2,1)=a32
3225           acipa(2,2)=a33
3226           a22=-a22
3227           a23=-a23
3228           do l=1,2
3229             do k=1,3
3230               agg(k,l)=-agg(k,l)
3231               aggi(k,l)=-aggi(k,l)
3232               aggi1(k,l)=-aggi1(k,l)
3233               aggj(k,l)=-aggj(k,l)
3234               aggj1(k,l)=-aggj1(k,l)
3235             enddo
3236           enddo
3237           if (j.lt.nres-1) then
3238             a22=-a22
3239             a32=-a32
3240             do l=1,3,2
3241               do k=1,3
3242                 agg(k,l)=-agg(k,l)
3243                 aggi(k,l)=-aggi(k,l)
3244                 aggi1(k,l)=-aggi1(k,l)
3245                 aggj(k,l)=-aggj(k,l)
3246                 aggj1(k,l)=-aggj1(k,l)
3247               enddo
3248             enddo
3249           else
3250             a22=-a22
3251             a23=-a23
3252             a32=-a32
3253             a33=-a33
3254             do l=1,4
3255               do k=1,3
3256                 agg(k,l)=-agg(k,l)
3257                 aggi(k,l)=-aggi(k,l)
3258                 aggi1(k,l)=-aggi1(k,l)
3259                 aggj(k,l)=-aggj(k,l)
3260                 aggj1(k,l)=-aggj1(k,l)
3261               enddo
3262             enddo 
3263           endif    
3264           ENDIF ! WCORR
3265           IF (wel_loc.gt.0.0d0) THEN
3266 C Contribution to the local-electrostatic energy coming from the i-j pair
3267           eel_loc_ij=a22*muij(1)+a23*muij(2)+a32*muij(3)
3268      &     +a33*muij(4)
3269 cd          write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
3270
3271           if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
3272      &            'eelloc',i,j,eel_loc_ij
3273
3274           eel_loc=eel_loc+eel_loc_ij
3275 C Partial derivatives in virtual-bond dihedral angles gamma
3276           if (i.gt.1)
3277      &    gel_loc_loc(i-1)=gel_loc_loc(i-1)+ 
3278      &            a22*muder(1,i)*mu(1,j)+a23*muder(1,i)*mu(2,j)
3279      &           +a32*muder(2,i)*mu(1,j)+a33*muder(2,i)*mu(2,j)
3280           gel_loc_loc(j-1)=gel_loc_loc(j-1)+ 
3281      &            a22*mu(1,i)*muder(1,j)+a23*mu(1,i)*muder(2,j)
3282      &           +a32*mu(2,i)*muder(1,j)+a33*mu(2,i)*muder(2,j)
3283 C Derivatives of eello in DC(i+1) thru DC(j-1) or DC(nres-2)
3284           do l=1,3
3285             ggg(l)=agg(l,1)*muij(1)+
3286      &          agg(l,2)*muij(2)+agg(l,3)*muij(3)+agg(l,4)*muij(4)
3287             gel_loc_long(l,j)=gel_loc_long(l,j)+ggg(l)
3288             gel_loc_long(l,i)=gel_loc_long(l,i)-ggg(l)
3289 cgrad            ghalf=0.5d0*ggg(l)
3290 cgrad            gel_loc(l,i)=gel_loc(l,i)+ghalf
3291 cgrad            gel_loc(l,j)=gel_loc(l,j)+ghalf
3292           enddo
3293 cgrad          do k=i+1,j2
3294 cgrad            do l=1,3
3295 cgrad              gel_loc(l,k)=gel_loc(l,k)+ggg(l)
3296 cgrad            enddo
3297 cgrad          enddo
3298 C Remaining derivatives of eello
3299           do l=1,3
3300             gel_loc(l,i)=gel_loc(l,i)+aggi(l,1)*muij(1)+
3301      &          aggi(l,2)*muij(2)+aggi(l,3)*muij(3)+aggi(l,4)*muij(4)
3302             gel_loc(l,i+1)=gel_loc(l,i+1)+aggi1(l,1)*muij(1)+
3303      &          aggi1(l,2)*muij(2)+aggi1(l,3)*muij(3)+aggi1(l,4)*muij(4)
3304             gel_loc(l,j)=gel_loc(l,j)+aggj(l,1)*muij(1)+
3305      &          aggj(l,2)*muij(2)+aggj(l,3)*muij(3)+aggj(l,4)*muij(4)
3306             gel_loc(l,j1)=gel_loc(l,j1)+aggj1(l,1)*muij(1)+
3307      &          aggj1(l,2)*muij(2)+aggj1(l,3)*muij(3)+aggj1(l,4)*muij(4)
3308           enddo
3309           ENDIF
3310 C Change 12/26/95 to calculate four-body contributions to H-bonding energy
3311 c          if (j.gt.i+1 .and. num_conti.le.maxconts) then
3312           if (wcorr+wcorr4+wcorr5+wcorr6.gt.0.0d0
3313      &       .and. num_conti.le.maxconts) then
3314 c            write (iout,*) i,j," entered corr"
3315 C
3316 C Calculate the contact function. The ith column of the array JCONT will 
3317 C contain the numbers of atoms that make contacts with the atom I (of numbers
3318 C greater than I). The arrays FACONT and GACONT will contain the values of
3319 C the contact function and its derivative.
3320 c           r0ij=1.02D0*rpp(iteli,itelj)
3321 c           r0ij=1.11D0*rpp(iteli,itelj)
3322             r0ij=2.20D0*rpp(iteli,itelj)
3323 c           r0ij=1.55D0*rpp(iteli,itelj)
3324             call gcont(rij,r0ij,1.0D0,0.2d0*r0ij,fcont,fprimcont)
3325             if (fcont.gt.0.0D0) then
3326               num_conti=num_conti+1
3327               if (num_conti.gt.maxconts) then
3328                 write (iout,*) 'WARNING - max. # of contacts exceeded;',
3329      &                         ' will skip next contacts for this conf.'
3330               else
3331                 jcont_hb(num_conti,i)=j
3332 cd                write (iout,*) "i",i," j",j," num_conti",num_conti,
3333 cd     &           " jcont_hb",jcont_hb(num_conti,i)
3334                 IF (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. 
3335      &          wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0) THEN
3336 C 9/30/99 (AL) - store components necessary to evaluate higher-order loc-el
3337 C  terms.
3338                 d_cont(num_conti,i)=rij
3339 cd                write (2,'(3e15.5)') rij,r0ij+0.2d0*r0ij,rij
3340 C     --- Electrostatic-interaction matrix --- 
3341                 a_chuj(1,1,num_conti,i)=a22
3342                 a_chuj(1,2,num_conti,i)=a23
3343                 a_chuj(2,1,num_conti,i)=a32
3344                 a_chuj(2,2,num_conti,i)=a33
3345 C     --- Gradient of rij
3346                 do kkk=1,3
3347                   grij_hb_cont(kkk,num_conti,i)=erij(kkk)
3348                 enddo
3349                 kkll=0
3350                 do k=1,2
3351                   do l=1,2
3352                     kkll=kkll+1
3353                     do m=1,3
3354                       a_chuj_der(k,l,m,1,num_conti,i)=agg(m,kkll)
3355                       a_chuj_der(k,l,m,2,num_conti,i)=aggi(m,kkll)
3356                       a_chuj_der(k,l,m,3,num_conti,i)=aggi1(m,kkll)
3357                       a_chuj_der(k,l,m,4,num_conti,i)=aggj(m,kkll)
3358                       a_chuj_der(k,l,m,5,num_conti,i)=aggj1(m,kkll)
3359                     enddo
3360                   enddo
3361                 enddo
3362                 ENDIF
3363                 IF (wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) THEN
3364 C Calculate contact energies
3365                 cosa4=4.0D0*cosa
3366                 wij=cosa-3.0D0*cosb*cosg
3367                 cosbg1=cosb+cosg
3368                 cosbg2=cosb-cosg
3369 c               fac3=dsqrt(-ael6i)/r0ij**3     
3370                 fac3=dsqrt(-ael6i)*r3ij
3371 c                 ees0pij=dsqrt(4.0D0+cosa4+wij*wij-3.0D0*cosbg1*cosbg1)
3372                 ees0tmp=4.0D0+cosa4+wij*wij-3.0D0*cosbg1*cosbg1
3373                 if (ees0tmp.gt.0) then
3374                   ees0pij=dsqrt(ees0tmp)
3375                 else
3376                   ees0pij=0
3377                 endif
3378 c                ees0mij=dsqrt(4.0D0-cosa4+wij*wij-3.0D0*cosbg2*cosbg2)
3379                 ees0tmp=4.0D0-cosa4+wij*wij-3.0D0*cosbg2*cosbg2
3380                 if (ees0tmp.gt.0) then
3381                   ees0mij=dsqrt(ees0tmp)
3382                 else
3383                   ees0mij=0
3384                 endif
3385 c               ees0mij=0.0D0
3386                 ees0p(num_conti,i)=0.5D0*fac3*(ees0pij+ees0mij)
3387                 ees0m(num_conti,i)=0.5D0*fac3*(ees0pij-ees0mij)
3388 C Diagnostics. Comment out or remove after debugging!
3389 c               ees0p(num_conti,i)=0.5D0*fac3*ees0pij
3390 c               ees0m(num_conti,i)=0.5D0*fac3*ees0mij
3391 c               ees0m(num_conti,i)=0.0D0
3392 C End diagnostics.
3393 c               write (iout,*) 'i=',i,' j=',j,' rij=',rij,' r0ij=',r0ij,
3394 c    & ' ees0ij=',ees0p(num_conti,i),ees0m(num_conti,i),' fcont=',fcont
3395 C Angular derivatives of the contact function
3396                 ees0pij1=fac3/ees0pij 
3397                 ees0mij1=fac3/ees0mij
3398                 fac3p=-3.0D0*fac3*rrmij
3399                 ees0pijp=0.5D0*fac3p*(ees0pij+ees0mij)
3400                 ees0mijp=0.5D0*fac3p*(ees0pij-ees0mij)
3401 c               ees0mij1=0.0D0
3402                 ecosa1=       ees0pij1*( 1.0D0+0.5D0*wij)
3403                 ecosb1=-1.5D0*ees0pij1*(wij*cosg+cosbg1)
3404                 ecosg1=-1.5D0*ees0pij1*(wij*cosb+cosbg1)
3405                 ecosa2=       ees0mij1*(-1.0D0+0.5D0*wij)
3406                 ecosb2=-1.5D0*ees0mij1*(wij*cosg+cosbg2) 
3407                 ecosg2=-1.5D0*ees0mij1*(wij*cosb-cosbg2)
3408                 ecosap=ecosa1+ecosa2
3409                 ecosbp=ecosb1+ecosb2
3410                 ecosgp=ecosg1+ecosg2
3411                 ecosam=ecosa1-ecosa2
3412                 ecosbm=ecosb1-ecosb2
3413                 ecosgm=ecosg1-ecosg2
3414 C Diagnostics
3415 c               ecosap=ecosa1
3416 c               ecosbp=ecosb1
3417 c               ecosgp=ecosg1
3418 c               ecosam=0.0D0
3419 c               ecosbm=0.0D0
3420 c               ecosgm=0.0D0
3421 C End diagnostics
3422                 facont_hb(num_conti,i)=fcont
3423                 fprimcont=fprimcont/rij
3424 cd              facont_hb(num_conti,i)=1.0D0
3425 C Following line is for diagnostics.
3426 cd              fprimcont=0.0D0
3427                 do k=1,3
3428                   dcosb(k)=rmij*(dc_norm(k,i)-erij(k)*cosb)
3429                   dcosg(k)=rmij*(dc_norm(k,j)-erij(k)*cosg)
3430                 enddo
3431                 do k=1,3
3432                   gggp(k)=ecosbp*dcosb(k)+ecosgp*dcosg(k)
3433                   gggm(k)=ecosbm*dcosb(k)+ecosgm*dcosg(k)
3434                 enddo
3435                 gggp(1)=gggp(1)+ees0pijp*xj
3436                 gggp(2)=gggp(2)+ees0pijp*yj
3437                 gggp(3)=gggp(3)+ees0pijp*zj
3438                 gggm(1)=gggm(1)+ees0mijp*xj
3439                 gggm(2)=gggm(2)+ees0mijp*yj
3440                 gggm(3)=gggm(3)+ees0mijp*zj
3441 C Derivatives due to the contact function
3442                 gacont_hbr(1,num_conti,i)=fprimcont*xj
3443                 gacont_hbr(2,num_conti,i)=fprimcont*yj
3444                 gacont_hbr(3,num_conti,i)=fprimcont*zj
3445                 do k=1,3
3446 c
3447 c 10/24/08 cgrad and ! comments indicate the parts of the code removed 
3448 c          following the change of gradient-summation algorithm.
3449 c
3450 cgrad                  ghalfp=0.5D0*gggp(k)
3451 cgrad                  ghalfm=0.5D0*gggm(k)
3452                   gacontp_hb1(k,num_conti,i)=!ghalfp
3453      &              +(ecosap*(dc_norm(k,j)-cosa*dc_norm(k,i))
3454      &              + ecosbp*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
3455                   gacontp_hb2(k,num_conti,i)=!ghalfp
3456      &              +(ecosap*(dc_norm(k,i)-cosa*dc_norm(k,j))
3457      &              + ecosgp*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
3458                   gacontp_hb3(k,num_conti,i)=gggp(k)
3459                   gacontm_hb1(k,num_conti,i)=!ghalfm
3460      &              +(ecosam*(dc_norm(k,j)-cosa*dc_norm(k,i))
3461      &              + ecosbm*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
3462                   gacontm_hb2(k,num_conti,i)=!ghalfm
3463      &              +(ecosam*(dc_norm(k,i)-cosa*dc_norm(k,j))
3464      &              + ecosgm*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
3465                   gacontm_hb3(k,num_conti,i)=gggm(k)
3466                 enddo
3467 C Diagnostics. Comment out or remove after debugging!
3468 cdiag           do k=1,3
3469 cdiag             gacontp_hb1(k,num_conti,i)=0.0D0
3470 cdiag             gacontp_hb2(k,num_conti,i)=0.0D0
3471 cdiag             gacontp_hb3(k,num_conti,i)=0.0D0
3472 cdiag             gacontm_hb1(k,num_conti,i)=0.0D0
3473 cdiag             gacontm_hb2(k,num_conti,i)=0.0D0
3474 cdiag             gacontm_hb3(k,num_conti,i)=0.0D0
3475 cdiag           enddo
3476               ENDIF ! wcorr
3477               endif  ! num_conti.le.maxconts
3478             endif  ! fcont.gt.0
3479           endif    ! j.gt.i+1
3480           if (wturn3.gt.0.0d0 .or. wturn4.gt.0.0d0) then
3481             do k=1,4
3482               do l=1,3
3483                 ghalf=0.5d0*agg(l,k)
3484                 aggi(l,k)=aggi(l,k)+ghalf
3485                 aggi1(l,k)=aggi1(l,k)+agg(l,k)
3486                 aggj(l,k)=aggj(l,k)+ghalf
3487               enddo
3488             enddo
3489             if (j.eq.nres-1 .and. i.lt.j-2) then
3490               do k=1,4
3491                 do l=1,3
3492                   aggj1(l,k)=aggj1(l,k)+agg(l,k)
3493                 enddo
3494               enddo
3495             endif
3496           endif
3497 c          t_eelecij=t_eelecij+MPI_Wtime()-time00
3498       return
3499       end
3500 C-----------------------------------------------------------------------------
3501       subroutine eturn3(i,eello_turn3)
3502 C Third- and fourth-order contributions from turns
3503       implicit real*8 (a-h,o-z)
3504       include 'DIMENSIONS'
3505       include 'COMMON.IOUNITS'
3506       include 'COMMON.GEO'
3507       include 'COMMON.VAR'
3508       include 'COMMON.LOCAL'
3509       include 'COMMON.CHAIN'
3510       include 'COMMON.DERIV'
3511       include 'COMMON.INTERACT'
3512       include 'COMMON.CONTACTS'
3513       include 'COMMON.TORSION'
3514       include 'COMMON.VECTORS'
3515       include 'COMMON.FFIELD'
3516       include 'COMMON.CONTROL'
3517       dimension ggg(3)
3518       double precision auxmat(2,2),auxmat1(2,2),auxmat2(2,2),pizda(2,2),
3519      &  e1t(2,2),e2t(2,2),e3t(2,2),e1tder(2,2),e2tder(2,2),e3tder(2,2),
3520      &  e1a(2,2),ae3(2,2),ae3e2(2,2),auxvec(2),auxvec1(2)
3521       double precision agg(3,4),aggi(3,4),aggi1(3,4),
3522      &    aggj(3,4),aggj1(3,4),a_temp(2,2),auxmat3(2,2)
3523       common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,a22,a23,a32,a33,
3524      &    dxi,dyi,dzi,dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,
3525      &    num_conti,j1,j2
3526       j=i+2
3527 c      write (iout,*) "eturn3",i,j,j1,j2
3528       a_temp(1,1)=a22
3529       a_temp(1,2)=a23
3530       a_temp(2,1)=a32
3531       a_temp(2,2)=a33
3532 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
3533 C
3534 C               Third-order contributions
3535 C        
3536 C                 (i+2)o----(i+3)
3537 C                      | |
3538 C                      | |
3539 C                 (i+1)o----i
3540 C
3541 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC   
3542 cd        call checkint_turn3(i,a_temp,eello_turn3_num)
3543         call matmat2(EUg(1,1,i+1),EUg(1,1,i+2),auxmat(1,1))
3544         call transpose2(auxmat(1,1),auxmat1(1,1))
3545         call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
3546         eello_turn3=eello_turn3+0.5d0*(pizda(1,1)+pizda(2,2))
3547         if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
3548      &          'eturn3',i,j,0.5d0*(pizda(1,1)+pizda(2,2))
3549 cd        write (2,*) 'i,',i,' j',j,'eello_turn3',
3550 cd     &    0.5d0*(pizda(1,1)+pizda(2,2)),
3551 cd     &    ' eello_turn3_num',4*eello_turn3_num
3552 C Derivatives in gamma(i)
3553         call matmat2(EUgder(1,1,i+1),EUg(1,1,i+2),auxmat2(1,1))
3554         call transpose2(auxmat2(1,1),auxmat3(1,1))
3555         call matmat2(a_temp(1,1),auxmat3(1,1),pizda(1,1))
3556         gel_loc_turn3(i)=gel_loc_turn3(i)+0.5d0*(pizda(1,1)+pizda(2,2))
3557 C Derivatives in gamma(i+1)
3558         call matmat2(EUg(1,1,i+1),EUgder(1,1,i+2),auxmat2(1,1))
3559         call transpose2(auxmat2(1,1),auxmat3(1,1))
3560         call matmat2(a_temp(1,1),auxmat3(1,1),pizda(1,1))
3561         gel_loc_turn3(i+1)=gel_loc_turn3(i+1)
3562      &    +0.5d0*(pizda(1,1)+pizda(2,2))
3563 C Cartesian derivatives
3564         do l=1,3
3565 c            ghalf1=0.5d0*agg(l,1)
3566 c            ghalf2=0.5d0*agg(l,2)
3567 c            ghalf3=0.5d0*agg(l,3)
3568 c            ghalf4=0.5d0*agg(l,4)
3569           a_temp(1,1)=aggi(l,1)!+ghalf1
3570           a_temp(1,2)=aggi(l,2)!+ghalf2
3571           a_temp(2,1)=aggi(l,3)!+ghalf3
3572           a_temp(2,2)=aggi(l,4)!+ghalf4
3573           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
3574           gcorr3_turn(l,i)=gcorr3_turn(l,i)
3575      &      +0.5d0*(pizda(1,1)+pizda(2,2))
3576           a_temp(1,1)=aggi1(l,1)!+agg(l,1)
3577           a_temp(1,2)=aggi1(l,2)!+agg(l,2)
3578           a_temp(2,1)=aggi1(l,3)!+agg(l,3)
3579           a_temp(2,2)=aggi1(l,4)!+agg(l,4)
3580           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
3581           gcorr3_turn(l,i+1)=gcorr3_turn(l,i+1)
3582      &      +0.5d0*(pizda(1,1)+pizda(2,2))
3583           a_temp(1,1)=aggj(l,1)!+ghalf1
3584           a_temp(1,2)=aggj(l,2)!+ghalf2
3585           a_temp(2,1)=aggj(l,3)!+ghalf3
3586           a_temp(2,2)=aggj(l,4)!+ghalf4
3587           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
3588           gcorr3_turn(l,j)=gcorr3_turn(l,j)
3589      &      +0.5d0*(pizda(1,1)+pizda(2,2))
3590           a_temp(1,1)=aggj1(l,1)
3591           a_temp(1,2)=aggj1(l,2)
3592           a_temp(2,1)=aggj1(l,3)
3593           a_temp(2,2)=aggj1(l,4)
3594           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
3595           gcorr3_turn(l,j1)=gcorr3_turn(l,j1)
3596      &      +0.5d0*(pizda(1,1)+pizda(2,2))
3597         enddo
3598       return
3599       end
3600 C-------------------------------------------------------------------------------
3601       subroutine eturn4(i,eello_turn4)
3602 C Third- and fourth-order contributions from turns
3603       implicit real*8 (a-h,o-z)
3604       include 'DIMENSIONS'
3605       include 'COMMON.IOUNITS'
3606       include 'COMMON.GEO'
3607       include 'COMMON.VAR'
3608       include 'COMMON.LOCAL'
3609       include 'COMMON.CHAIN'
3610       include 'COMMON.DERIV'
3611       include 'COMMON.INTERACT'
3612       include 'COMMON.CONTACTS'
3613       include 'COMMON.TORSION'
3614       include 'COMMON.VECTORS'
3615       include 'COMMON.FFIELD'
3616       include 'COMMON.CONTROL'
3617       dimension ggg(3)
3618       double precision auxmat(2,2),auxmat1(2,2),auxmat2(2,2),pizda(2,2),
3619      &  e1t(2,2),e2t(2,2),e3t(2,2),e1tder(2,2),e2tder(2,2),e3tder(2,2),
3620      &  e1a(2,2),ae3(2,2),ae3e2(2,2),auxvec(2),auxvec1(2)
3621       double precision agg(3,4),aggi(3,4),aggi1(3,4),
3622      &    aggj(3,4),aggj1(3,4),a_temp(2,2),auxmat3(2,2)
3623       common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,a22,a23,a32,a33,
3624      &    dxi,dyi,dzi,dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,
3625      &    num_conti,j1,j2
3626       j=i+3
3627 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
3628 C
3629 C               Fourth-order contributions
3630 C        
3631 C                 (i+3)o----(i+4)
3632 C                     /  |
3633 C               (i+2)o   |
3634 C                     \  |
3635 C                 (i+1)o----i
3636 C
3637 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC   
3638 cd        call checkint_turn4(i,a_temp,eello_turn4_num)
3639 c        write (iout,*) "eturn4 i",i," j",j," j1",j1," j2",j2
3640         a_temp(1,1)=a22
3641         a_temp(1,2)=a23
3642         a_temp(2,1)=a32
3643         a_temp(2,2)=a33
3644         iti1=itortyp(itype(i+1))
3645         iti2=itortyp(itype(i+2))
3646         iti3=itortyp(itype(i+3))
3647 c        write(iout,*) "iti1",iti1," iti2",iti2," iti3",iti3
3648         call transpose2(EUg(1,1,i+1),e1t(1,1))
3649         call transpose2(Eug(1,1,i+2),e2t(1,1))
3650         call transpose2(Eug(1,1,i+3),e3t(1,1))
3651         call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
3652         call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
3653         s1=scalar2(b1(1,iti2),auxvec(1))
3654         call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
3655         call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
3656         s2=scalar2(b1(1,iti1),auxvec(1))
3657         call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
3658         call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
3659         s3=0.5d0*(pizda(1,1)+pizda(2,2))
3660         eello_turn4=eello_turn4-(s1+s2+s3)
3661         if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
3662      &      'eturn4',i,j,-(s1+s2+s3)
3663 cd        write (2,*) 'i,',i,' j',j,'eello_turn4',-(s1+s2+s3),
3664 cd     &    ' eello_turn4_num',8*eello_turn4_num
3665 C Derivatives in gamma(i)
3666         call transpose2(EUgder(1,1,i+1),e1tder(1,1))
3667         call matmat2(e1tder(1,1),a_temp(1,1),auxmat(1,1))
3668         call matvec2(auxmat(1,1),Ub2(1,i+3),auxvec(1))
3669         s1=scalar2(b1(1,iti2),auxvec(1))
3670         call matmat2(ae3e2(1,1),e1tder(1,1),pizda(1,1))
3671         s3=0.5d0*(pizda(1,1)+pizda(2,2))
3672         gel_loc_turn4(i)=gel_loc_turn4(i)-(s1+s3)
3673 C Derivatives in gamma(i+1)
3674         call transpose2(EUgder(1,1,i+2),e2tder(1,1))
3675         call matvec2(ae3(1,1),Ub2der(1,i+2),auxvec(1)) 
3676         s2=scalar2(b1(1,iti1),auxvec(1))
3677         call matmat2(ae3(1,1),e2tder(1,1),auxmat(1,1))
3678         call matmat2(auxmat(1,1),e1t(1,1),pizda(1,1))
3679         s3=0.5d0*(pizda(1,1)+pizda(2,2))
3680         gel_loc_turn4(i+1)=gel_loc_turn4(i+1)-(s2+s3)
3681 C Derivatives in gamma(i+2)
3682         call transpose2(EUgder(1,1,i+3),e3tder(1,1))
3683         call matvec2(e1a(1,1),Ub2der(1,i+3),auxvec(1))
3684         s1=scalar2(b1(1,iti2),auxvec(1))
3685         call matmat2(a_temp(1,1),e3tder(1,1),auxmat(1,1))
3686         call matvec2(auxmat(1,1),Ub2(1,i+2),auxvec(1)) 
3687         s2=scalar2(b1(1,iti1),auxvec(1))
3688         call matmat2(auxmat(1,1),e2t(1,1),auxmat3(1,1))
3689         call matmat2(auxmat3(1,1),e1t(1,1),pizda(1,1))
3690         s3=0.5d0*(pizda(1,1)+pizda(2,2))
3691         gel_loc_turn4(i+2)=gel_loc_turn4(i+2)-(s1+s2+s3)
3692 C Cartesian derivatives
3693 C Derivatives of this turn contributions in DC(i+2)
3694         if (j.lt.nres-1) then
3695           do l=1,3
3696             a_temp(1,1)=agg(l,1)
3697             a_temp(1,2)=agg(l,2)
3698             a_temp(2,1)=agg(l,3)
3699             a_temp(2,2)=agg(l,4)
3700             call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
3701             call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
3702             s1=scalar2(b1(1,iti2),auxvec(1))
3703             call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
3704             call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
3705             s2=scalar2(b1(1,iti1),auxvec(1))
3706             call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
3707             call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
3708             s3=0.5d0*(pizda(1,1)+pizda(2,2))
3709             ggg(l)=-(s1+s2+s3)
3710             gcorr4_turn(l,i+2)=gcorr4_turn(l,i+2)-(s1+s2+s3)
3711           enddo
3712         endif
3713 C Remaining derivatives of this turn contribution
3714         do l=1,3
3715           a_temp(1,1)=aggi(l,1)
3716           a_temp(1,2)=aggi(l,2)
3717           a_temp(2,1)=aggi(l,3)
3718           a_temp(2,2)=aggi(l,4)
3719           call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
3720           call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
3721           s1=scalar2(b1(1,iti2),auxvec(1))
3722           call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
3723           call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
3724           s2=scalar2(b1(1,iti1),auxvec(1))
3725           call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
3726           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
3727           s3=0.5d0*(pizda(1,1)+pizda(2,2))
3728           gcorr4_turn(l,i)=gcorr4_turn(l,i)-(s1+s2+s3)
3729           a_temp(1,1)=aggi1(l,1)
3730           a_temp(1,2)=aggi1(l,2)
3731           a_temp(2,1)=aggi1(l,3)
3732           a_temp(2,2)=aggi1(l,4)
3733           call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
3734           call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
3735           s1=scalar2(b1(1,iti2),auxvec(1))
3736           call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
3737           call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
3738           s2=scalar2(b1(1,iti1),auxvec(1))
3739           call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
3740           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
3741           s3=0.5d0*(pizda(1,1)+pizda(2,2))
3742           gcorr4_turn(l,i+1)=gcorr4_turn(l,i+1)-(s1+s2+s3)
3743           a_temp(1,1)=aggj(l,1)
3744           a_temp(1,2)=aggj(l,2)
3745           a_temp(2,1)=aggj(l,3)
3746           a_temp(2,2)=aggj(l,4)
3747           call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
3748           call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
3749           s1=scalar2(b1(1,iti2),auxvec(1))
3750           call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
3751           call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
3752           s2=scalar2(b1(1,iti1),auxvec(1))
3753           call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
3754           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
3755           s3=0.5d0*(pizda(1,1)+pizda(2,2))
3756           gcorr4_turn(l,j)=gcorr4_turn(l,j)-(s1+s2+s3)
3757           a_temp(1,1)=aggj1(l,1)
3758           a_temp(1,2)=aggj1(l,2)
3759           a_temp(2,1)=aggj1(l,3)
3760           a_temp(2,2)=aggj1(l,4)
3761           call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
3762           call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
3763           s1=scalar2(b1(1,iti2),auxvec(1))
3764           call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
3765           call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
3766           s2=scalar2(b1(1,iti1),auxvec(1))
3767           call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
3768           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
3769           s3=0.5d0*(pizda(1,1)+pizda(2,2))
3770 c          write (iout,*) "s1",s1," s2",s2," s3",s3," s1+s2+s3",s1+s2+s3
3771           gcorr4_turn(l,j1)=gcorr4_turn(l,j1)-(s1+s2+s3)
3772         enddo
3773       return
3774       end
3775 C-----------------------------------------------------------------------------
3776       subroutine vecpr(u,v,w)
3777       implicit real*8(a-h,o-z)
3778       dimension u(3),v(3),w(3)
3779       w(1)=u(2)*v(3)-u(3)*v(2)
3780       w(2)=-u(1)*v(3)+u(3)*v(1)
3781       w(3)=u(1)*v(2)-u(2)*v(1)
3782       return
3783       end
3784 C-----------------------------------------------------------------------------
3785       subroutine unormderiv(u,ugrad,unorm,ungrad)
3786 C This subroutine computes the derivatives of a normalized vector u, given
3787 C the derivatives computed without normalization conditions, ugrad. Returns
3788 C ungrad.
3789       implicit none
3790       double precision u(3),ugrad(3,3),unorm,ungrad(3,3)
3791       double precision vec(3)
3792       double precision scalar
3793       integer i,j
3794 c      write (2,*) 'ugrad',ugrad
3795 c      write (2,*) 'u',u
3796       do i=1,3
3797         vec(i)=scalar(ugrad(1,i),u(1))
3798       enddo
3799 c      write (2,*) 'vec',vec
3800       do i=1,3
3801         do j=1,3
3802           ungrad(j,i)=(ugrad(j,i)-u(j)*vec(i))*unorm
3803         enddo
3804       enddo
3805 c      write (2,*) 'ungrad',ungrad
3806       return
3807       end
3808 C-----------------------------------------------------------------------------
3809       subroutine escp_soft_sphere(evdw2,evdw2_14)
3810 C
3811 C This subroutine calculates the excluded-volume interaction energy between
3812 C peptide-group centers and side chains and its gradient in virtual-bond and
3813 C side-chain vectors.
3814 C
3815       implicit real*8 (a-h,o-z)
3816       include 'DIMENSIONS'
3817       include 'COMMON.GEO'
3818       include 'COMMON.VAR'
3819       include 'COMMON.LOCAL'
3820       include 'COMMON.CHAIN'
3821       include 'COMMON.DERIV'
3822       include 'COMMON.INTERACT'
3823       include 'COMMON.FFIELD'
3824       include 'COMMON.IOUNITS'
3825       include 'COMMON.CONTROL'
3826       dimension ggg(3)
3827       evdw2=0.0D0
3828       evdw2_14=0.0d0
3829       r0_scp=4.5d0
3830 cd    print '(a)','Enter ESCP'
3831 cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
3832       do i=iatscp_s,iatscp_e
3833         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
3834         iteli=itel(i)
3835         xi=0.5D0*(c(1,i)+c(1,i+1))
3836         yi=0.5D0*(c(2,i)+c(2,i+1))
3837         zi=0.5D0*(c(3,i)+c(3,i+1))
3838
3839         do iint=1,nscp_gr(i)
3840
3841         do j=iscpstart(i,iint),iscpend(i,iint)
3842           if (itype(j).eq.ntyp1) cycle
3843           itypj=iabs(itype(j))
3844 C Uncomment following three lines for SC-p interactions
3845 c         xj=c(1,nres+j)-xi
3846 c         yj=c(2,nres+j)-yi
3847 c         zj=c(3,nres+j)-zi
3848 C Uncomment following three lines for Ca-p interactions
3849           xj=c(1,j)-xi
3850           yj=c(2,j)-yi
3851           zj=c(3,j)-zi
3852           rij=xj*xj+yj*yj+zj*zj
3853           r0ij=r0_scp
3854           r0ijsq=r0ij*r0ij
3855           if (rij.lt.r0ijsq) then
3856             evdwij=0.25d0*(rij-r0ijsq)**2
3857             fac=rij-r0ijsq
3858           else
3859             evdwij=0.0d0
3860             fac=0.0d0
3861           endif 
3862           evdw2=evdw2+evdwij
3863 C
3864 C Calculate contributions to the gradient in the virtual-bond and SC vectors.
3865 C
3866           ggg(1)=xj*fac
3867           ggg(2)=yj*fac
3868           ggg(3)=zj*fac
3869 cgrad          if (j.lt.i) then
3870 cd          write (iout,*) 'j<i'
3871 C Uncomment following three lines for SC-p interactions
3872 c           do k=1,3
3873 c             gradx_scp(k,j)=gradx_scp(k,j)+ggg(k)
3874 c           enddo
3875 cgrad          else
3876 cd          write (iout,*) 'j>i'
3877 cgrad            do k=1,3
3878 cgrad              ggg(k)=-ggg(k)
3879 C Uncomment following line for SC-p interactions
3880 c             gradx_scp(k,j)=gradx_scp(k,j)-ggg(k)
3881 cgrad            enddo
3882 cgrad          endif
3883 cgrad          do k=1,3
3884 cgrad            gvdwc_scp(k,i)=gvdwc_scp(k,i)-0.5D0*ggg(k)
3885 cgrad          enddo
3886 cgrad          kstart=min0(i+1,j)
3887 cgrad          kend=max0(i-1,j-1)
3888 cd        write (iout,*) 'i=',i,' j=',j,' kstart=',kstart,' kend=',kend
3889 cd        write (iout,*) ggg(1),ggg(2),ggg(3)
3890 cgrad          do k=kstart,kend
3891 cgrad            do l=1,3
3892 cgrad              gvdwc_scp(l,k)=gvdwc_scp(l,k)-ggg(l)
3893 cgrad            enddo
3894 cgrad          enddo
3895           do k=1,3
3896             gvdwc_scpp(k,i)=gvdwc_scpp(k,i)-ggg(k)
3897             gvdwc_scp(k,j)=gvdwc_scp(k,j)+ggg(k)
3898           enddo
3899         enddo
3900
3901         enddo ! iint
3902       enddo ! i
3903       return
3904       end
3905 C-----------------------------------------------------------------------------
3906       subroutine escp(evdw2,evdw2_14)
3907 C
3908 C This subroutine calculates the excluded-volume interaction energy between
3909 C peptide-group centers and side chains and its gradient in virtual-bond and
3910 C side-chain vectors.
3911 C
3912       implicit real*8 (a-h,o-z)
3913       include 'DIMENSIONS'
3914       include 'COMMON.GEO'
3915       include 'COMMON.VAR'
3916       include 'COMMON.LOCAL'
3917       include 'COMMON.CHAIN'
3918       include 'COMMON.DERIV'
3919       include 'COMMON.INTERACT'
3920       include 'COMMON.FFIELD'
3921       include 'COMMON.IOUNITS'
3922       include 'COMMON.CONTROL'
3923       dimension ggg(3)
3924       evdw2=0.0D0
3925       evdw2_14=0.0d0
3926 cd    print '(a)','Enter ESCP'
3927 cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
3928       do i=iatscp_s,iatscp_e
3929         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
3930         iteli=itel(i)
3931         xi=0.5D0*(c(1,i)+c(1,i+1))
3932         yi=0.5D0*(c(2,i)+c(2,i+1))
3933         zi=0.5D0*(c(3,i)+c(3,i+1))
3934
3935         do iint=1,nscp_gr(i)
3936
3937         do j=iscpstart(i,iint),iscpend(i,iint)
3938           itypj=iabs(itype(j))
3939           if (itypj.eq.ntyp1) cycle
3940 C Uncomment following three lines for SC-p interactions
3941 c         xj=c(1,nres+j)-xi
3942 c         yj=c(2,nres+j)-yi
3943 c         zj=c(3,nres+j)-zi
3944 C Uncomment following three lines for Ca-p interactions
3945           xj=c(1,j)-xi
3946           yj=c(2,j)-yi
3947           zj=c(3,j)-zi
3948           rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
3949           fac=rrij**expon2
3950           e1=fac*fac*aad(itypj,iteli)
3951           e2=fac*bad(itypj,iteli)
3952           if (iabs(j-i) .le. 2) then
3953             e1=scal14*e1
3954             e2=scal14*e2
3955             evdw2_14=evdw2_14+e1+e2
3956           endif
3957           evdwij=e1+e2
3958           evdw2=evdw2+evdwij
3959           if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
3960      &        'evdw2',i,j,evdwij
3961 C
3962 C Calculate contributions to the gradient in the virtual-bond and SC vectors.
3963 C
3964           fac=-(evdwij+e1)*rrij
3965           ggg(1)=xj*fac
3966           ggg(2)=yj*fac
3967           ggg(3)=zj*fac
3968 cgrad          if (j.lt.i) then
3969 cd          write (iout,*) 'j<i'
3970 C Uncomment following three lines for SC-p interactions
3971 c           do k=1,3
3972 c             gradx_scp(k,j)=gradx_scp(k,j)+ggg(k)
3973 c           enddo
3974 cgrad          else
3975 cd          write (iout,*) 'j>i'
3976 cgrad            do k=1,3
3977 cgrad              ggg(k)=-ggg(k)
3978 C Uncomment following line for SC-p interactions
3979 ccgrad             gradx_scp(k,j)=gradx_scp(k,j)-ggg(k)
3980 c             gradx_scp(k,j)=gradx_scp(k,j)+ggg(k)
3981 cgrad            enddo
3982 cgrad          endif
3983 cgrad          do k=1,3
3984 cgrad            gvdwc_scp(k,i)=gvdwc_scp(k,i)-0.5D0*ggg(k)
3985 cgrad          enddo
3986 cgrad          kstart=min0(i+1,j)
3987 cgrad          kend=max0(i-1,j-1)
3988 cd        write (iout,*) 'i=',i,' j=',j,' kstart=',kstart,' kend=',kend
3989 cd        write (iout,*) ggg(1),ggg(2),ggg(3)
3990 cgrad          do k=kstart,kend
3991 cgrad            do l=1,3
3992 cgrad              gvdwc_scp(l,k)=gvdwc_scp(l,k)-ggg(l)
3993 cgrad            enddo
3994 cgrad          enddo
3995           do k=1,3
3996             gvdwc_scpp(k,i)=gvdwc_scpp(k,i)-ggg(k)
3997             gvdwc_scp(k,j)=gvdwc_scp(k,j)+ggg(k)
3998           enddo
3999         enddo
4000
4001         enddo ! iint
4002       enddo ! i
4003       do i=1,nct
4004         do j=1,3
4005           gvdwc_scp(j,i)=expon*gvdwc_scp(j,i)
4006           gvdwc_scpp(j,i)=expon*gvdwc_scpp(j,i)
4007           gradx_scp(j,i)=expon*gradx_scp(j,i)
4008         enddo
4009       enddo
4010 C******************************************************************************
4011 C
4012 C                              N O T E !!!
4013 C
4014 C To save time the factor EXPON has been extracted from ALL components
4015 C of GVDWC and GRADX. Remember to multiply them by this factor before further 
4016 C use!
4017 C
4018 C******************************************************************************
4019       return
4020       end
4021 C--------------------------------------------------------------------------
4022       subroutine edis(ehpb)
4023
4024 C Evaluate bridge-strain energy and its gradient in virtual-bond and SC vectors.
4025 C
4026       implicit real*8 (a-h,o-z)
4027       include 'DIMENSIONS'
4028       include 'COMMON.SBRIDGE'
4029       include 'COMMON.CHAIN'
4030       include 'COMMON.DERIV'
4031       include 'COMMON.VAR'
4032       include 'COMMON.INTERACT'
4033       include 'COMMON.IOUNITS'
4034       dimension ggg(3)
4035       ehpb=0.0D0
4036 cd      write(iout,*)'edis: nhpb=',nhpb,' fbr=',fbr
4037 cd      write(iout,*)'link_start=',link_start,' link_end=',link_end
4038       if (link_end.eq.0) return
4039       do i=link_start,link_end
4040 C If ihpb(i) and jhpb(i) > NRES, this is a SC-SC distance, otherwise a
4041 C CA-CA distance used in regularization of structure.
4042         ii=ihpb(i)
4043         jj=jhpb(i)
4044 C iii and jjj point to the residues for which the distance is assigned.
4045         if (ii.gt.nres) then
4046           iii=ii-nres
4047           jjj=jj-nres 
4048         else
4049           iii=ii
4050           jjj=jj
4051         endif
4052 cd        write (iout,*) "i",i," ii",ii," iii",iii," jj",jj," jjj",jjj
4053 C 24/11/03 AL: SS bridges handled separately because of introducing a specific
4054 C    distance and angle dependent SS bond potential.
4055         if (ii.gt.nres .and. iabs(itype(iii)).eq.1 .and.
4056      & iabs(itype(jjj)).eq.1) then
4057           call ssbond_ene(iii,jjj,eij)
4058           ehpb=ehpb+2*eij
4059 cd          write (iout,*) "eij",eij
4060         else
4061 C Calculate the distance between the two points and its difference from the
4062 C target distance.
4063         dd=dist(ii,jj)
4064         rdis=dd-dhpb(i)
4065 C Get the force constant corresponding to this distance.
4066         waga=forcon(i)
4067 C Calculate the contribution to energy.
4068         ehpb=ehpb+waga*rdis*rdis
4069 C
4070 C Evaluate gradient.
4071 C
4072         fac=waga*rdis/dd
4073 cd      print *,'i=',i,' ii=',ii,' jj=',jj,' dhpb=',dhpb(i),' dd=',dd,
4074 cd   &   ' waga=',waga,' fac=',fac
4075         do j=1,3
4076           ggg(j)=fac*(c(j,jj)-c(j,ii))
4077         enddo
4078 cd      print '(i3,3(1pe14.5))',i,(ggg(j),j=1,3)
4079 C If this is a SC-SC distance, we need to calculate the contributions to the
4080 C Cartesian gradient in the SC vectors (ghpbx).
4081         if (iii.lt.ii) then
4082           do j=1,3
4083             ghpbx(j,iii)=ghpbx(j,iii)-ggg(j)
4084             ghpbx(j,jjj)=ghpbx(j,jjj)+ggg(j)
4085           enddo
4086         endif
4087 cgrad        do j=iii,jjj-1
4088 cgrad          do k=1,3
4089 cgrad            ghpbc(k,j)=ghpbc(k,j)+ggg(k)
4090 cgrad          enddo
4091 cgrad        enddo
4092         do k=1,3
4093           ghpbc(k,jjj)=ghpbc(k,jjj)+ggg(k)
4094           ghpbc(k,iii)=ghpbc(k,iii)-ggg(k)
4095         enddo
4096         endif
4097       enddo
4098       ehpb=0.5D0*ehpb
4099       return
4100       end
4101 C--------------------------------------------------------------------------
4102       subroutine ssbond_ene(i,j,eij)
4103
4104 C Calculate the distance and angle dependent SS-bond potential energy
4105 C using a free-energy function derived based on RHF/6-31G** ab initio
4106 C calculations of diethyl disulfide.
4107 C
4108 C A. Liwo and U. Kozlowska, 11/24/03
4109 C
4110       implicit real*8 (a-h,o-z)
4111       include 'DIMENSIONS'
4112       include 'COMMON.SBRIDGE'
4113       include 'COMMON.CHAIN'
4114       include 'COMMON.DERIV'
4115       include 'COMMON.LOCAL'
4116       include 'COMMON.INTERACT'
4117       include 'COMMON.VAR'
4118       include 'COMMON.IOUNITS'
4119       double precision erij(3),dcosom1(3),dcosom2(3),gg(3)
4120       itypi=iabs(itype(i))
4121       xi=c(1,nres+i)
4122       yi=c(2,nres+i)
4123       zi=c(3,nres+i)
4124       dxi=dc_norm(1,nres+i)
4125       dyi=dc_norm(2,nres+i)
4126       dzi=dc_norm(3,nres+i)
4127 c      dsci_inv=dsc_inv(itypi)
4128       dsci_inv=vbld_inv(nres+i)
4129       itypj=iabs(itype(j))
4130 c      dscj_inv=dsc_inv(itypj)
4131       dscj_inv=vbld_inv(nres+j)
4132       xj=c(1,nres+j)-xi
4133       yj=c(2,nres+j)-yi
4134       zj=c(3,nres+j)-zi
4135       dxj=dc_norm(1,nres+j)
4136       dyj=dc_norm(2,nres+j)
4137       dzj=dc_norm(3,nres+j)
4138       rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
4139       rij=dsqrt(rrij)
4140       erij(1)=xj*rij
4141       erij(2)=yj*rij
4142       erij(3)=zj*rij
4143       om1=dxi*erij(1)+dyi*erij(2)+dzi*erij(3)
4144       om2=dxj*erij(1)+dyj*erij(2)+dzj*erij(3)
4145       om12=dxi*dxj+dyi*dyj+dzi*dzj
4146       do k=1,3
4147         dcosom1(k)=rij*(dc_norm(k,nres+i)-om1*erij(k))
4148         dcosom2(k)=rij*(dc_norm(k,nres+j)-om2*erij(k))
4149       enddo
4150       rij=1.0d0/rij
4151       deltad=rij-d0cm
4152       deltat1=1.0d0-om1
4153       deltat2=1.0d0+om2
4154       deltat12=om2-om1+2.0d0
4155       cosphi=om12-om1*om2
4156       eij=akcm*deltad*deltad+akth*(deltat1*deltat1+deltat2*deltat2)
4157      &  +akct*deltad*deltat12
4158      &  +v1ss*cosphi+v2ss*cosphi*cosphi+v3ss*cosphi*cosphi*cosphi
4159 c      write(iout,*) i,j,"rij",rij,"d0cm",d0cm," akcm",akcm," akth",akth,
4160 c     &  " akct",akct," deltad",deltad," deltat",deltat1,deltat2,
4161 c     &  " deltat12",deltat12," eij",eij 
4162       ed=2*akcm*deltad+akct*deltat12
4163       pom1=akct*deltad
4164       pom2=v1ss+2*v2ss*cosphi+3*v3ss*cosphi*cosphi
4165       eom1=-2*akth*deltat1-pom1-om2*pom2
4166       eom2= 2*akth*deltat2+pom1-om1*pom2
4167       eom12=pom2
4168       do k=1,3
4169         ggk=ed*erij(k)+eom1*dcosom1(k)+eom2*dcosom2(k)
4170         ghpbx(k,i)=ghpbx(k,i)-ggk
4171      &            +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i))
4172      &            +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
4173         ghpbx(k,j)=ghpbx(k,j)+ggk
4174      &            +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j))
4175      &            +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
4176         ghpbc(k,i)=ghpbc(k,i)-ggk
4177         ghpbc(k,j)=ghpbc(k,j)+ggk
4178       enddo
4179 C
4180 C Calculate the components of the gradient in DC and X
4181 C
4182 cgrad      do k=i,j-1
4183 cgrad        do l=1,3
4184 cgrad          ghpbc(l,k)=ghpbc(l,k)+gg(l)
4185 cgrad        enddo
4186 cgrad      enddo
4187       return
4188       end
4189 C--------------------------------------------------------------------------
4190       subroutine ebond(estr)
4191 c
4192 c Evaluate the energy of stretching of the CA-CA and CA-SC virtual bonds
4193 c
4194       implicit real*8 (a-h,o-z)
4195       include 'DIMENSIONS'
4196       include 'COMMON.LOCAL'
4197       include 'COMMON.GEO'
4198       include 'COMMON.INTERACT'
4199       include 'COMMON.DERIV'
4200       include 'COMMON.VAR'
4201       include 'COMMON.CHAIN'
4202       include 'COMMON.IOUNITS'
4203       include 'COMMON.NAMES'
4204       include 'COMMON.FFIELD'
4205       include 'COMMON.CONTROL'
4206       include 'COMMON.SETUP'
4207       double precision u(3),ud(3)
4208       estr=0.0d0
4209       estr1=0.0d0
4210       do i=ibondp_start,ibondp_end
4211         if (itype(i-1).eq.ntyp1 .or. itype(i).eq.ntyp1) then
4212           estr1=estr1+gnmr1(vbld(i),-1.0d0,distchainmax)
4213           do j=1,3
4214           gradb(j,i-1)=gnmr1prim(vbld(i),-1.0d0,distchainmax)
4215      &      *dc(j,i-1)/vbld(i)
4216           enddo
4217           if (energy_dec) write(iout,*) 
4218      &       "estr1",i,gnmr1(vbld(i),-1.0d0,distchainmax)
4219         else
4220         diff = vbld(i)-vbldp0
4221         if (energy_dec) write (iout,*) 
4222      &     "estr bb",i,vbld(i),vbldp0,diff,AKP*diff*diff
4223         estr=estr+diff*diff
4224         do j=1,3
4225           gradb(j,i-1)=AKP*diff*dc(j,i-1)/vbld(i)
4226         enddo
4227 c        write (iout,'(i5,3f10.5)') i,(gradb(j,i-1),j=1,3)
4228         endif
4229       enddo
4230       estr=0.5d0*AKP*estr+estr1
4231 c
4232 c 09/18/07 AL: multimodal bond potential based on AM1 CA-SC PMF's included
4233 c
4234       do i=ibond_start,ibond_end
4235         iti=iabs(itype(i))
4236         if (iti.ne.10 .and. iti.ne.ntyp1) then
4237           nbi=nbondterm(iti)
4238           if (nbi.eq.1) then
4239             diff=vbld(i+nres)-vbldsc0(1,iti)
4240             if (energy_dec) write (iout,*) 
4241      &      "estr sc",i,iti,vbld(i+nres),vbldsc0(1,iti),diff,
4242      &      AKSC(1,iti),AKSC(1,iti)*diff*diff
4243             estr=estr+0.5d0*AKSC(1,iti)*diff*diff
4244             do j=1,3
4245               gradbx(j,i)=AKSC(1,iti)*diff*dc(j,i+nres)/vbld(i+nres)
4246             enddo
4247           else
4248             do j=1,nbi
4249               diff=vbld(i+nres)-vbldsc0(j,iti) 
4250               ud(j)=aksc(j,iti)*diff
4251               u(j)=abond0(j,iti)+0.5d0*ud(j)*diff
4252             enddo
4253             uprod=u(1)
4254             do j=2,nbi
4255               uprod=uprod*u(j)
4256             enddo
4257             usum=0.0d0
4258             usumsqder=0.0d0
4259             do j=1,nbi
4260               uprod1=1.0d0
4261               uprod2=1.0d0
4262               do k=1,nbi
4263                 if (k.ne.j) then
4264                   uprod1=uprod1*u(k)
4265                   uprod2=uprod2*u(k)*u(k)
4266                 endif
4267               enddo
4268               usum=usum+uprod1
4269               usumsqder=usumsqder+ud(j)*uprod2   
4270             enddo
4271             estr=estr+uprod/usum
4272             do j=1,3
4273              gradbx(j,i)=usumsqder/(usum*usum)*dc(j,i+nres)/vbld(i+nres)
4274             enddo
4275           endif
4276         endif
4277       enddo
4278       return
4279       end 
4280 #ifdef CRYST_THETA
4281 C--------------------------------------------------------------------------
4282       subroutine ebend(etheta)
4283 C
4284 C Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
4285 C angles gamma and its derivatives in consecutive thetas and gammas.
4286 C
4287       implicit real*8 (a-h,o-z)
4288       include 'DIMENSIONS'
4289       include 'COMMON.LOCAL'
4290       include 'COMMON.GEO'
4291       include 'COMMON.INTERACT'
4292       include 'COMMON.DERIV'
4293       include 'COMMON.VAR'
4294       include 'COMMON.CHAIN'
4295       include 'COMMON.IOUNITS'
4296       include 'COMMON.NAMES'
4297       include 'COMMON.FFIELD'
4298       include 'COMMON.CONTROL'
4299       common /calcthet/ term1,term2,termm,diffak,ratak,
4300      & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
4301      & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
4302       double precision y(2),z(2)
4303       delta=0.02d0*pi
4304 c      time11=dexp(-2*time)
4305 c      time12=1.0d0
4306       etheta=0.0D0
4307 c     write (*,'(a,i2)') 'EBEND ICG=',icg
4308       do i=ithet_start,ithet_end
4309         if (itype(i-1).eq.ntyp1) cycle
4310 C Zero the energy function and its derivative at 0 or pi.
4311         call splinthet(theta(i),0.5d0*delta,ss,ssd)
4312         it=itype(i-1)
4313         ichir1=isign(1,itype(i-2))
4314         ichir2=isign(1,itype(i))
4315          if (itype(i-2).eq.10) ichir1=isign(1,itype(i-1))
4316          if (itype(i).eq.10) ichir2=isign(1,itype(i-1))
4317          if (itype(i-1).eq.10) then
4318           itype1=isign(10,itype(i-2))
4319           ichir11=isign(1,itype(i-2))
4320           ichir12=isign(1,itype(i-2))
4321           itype2=isign(10,itype(i))
4322           ichir21=isign(1,itype(i))
4323           ichir22=isign(1,itype(i))
4324          endif
4325
4326         if (i.gt.3 .and. itype(i-2).ne.ntyp1) then
4327 #ifdef OSF
4328           phii=phi(i)
4329           if (phii.ne.phii) phii=150.0
4330 #else
4331           phii=phi(i)
4332 #endif
4333           y(1)=dcos(phii)
4334           y(2)=dsin(phii)
4335         else 
4336           y(1)=0.0D0
4337           y(2)=0.0D0
4338         endif
4339         if (i.lt.nres .and. itype(i).ne.ntyp1) then
4340 #ifdef OSF
4341           phii1=phi(i+1)
4342           if (phii1.ne.phii1) phii1=150.0
4343           phii1=pinorm(phii1)
4344           z(1)=cos(phii1)
4345 #else
4346           phii1=phi(i+1)
4347           z(1)=dcos(phii1)
4348 #endif
4349           z(2)=dsin(phii1)
4350         else
4351           z(1)=0.0D0
4352           z(2)=0.0D0
4353         endif  
4354 C Calculate the "mean" value of theta from the part of the distribution
4355 C dependent on the adjacent virtual-bond-valence angles (gamma1 & gamma2).
4356 C In following comments this theta will be referred to as t_c.
4357         thet_pred_mean=0.0d0
4358         do k=1,2
4359             athetk=athet(k,it,ichir1,ichir2)
4360             bthetk=bthet(k,it,ichir1,ichir2)
4361           if (it.eq.10) then
4362              athetk=athet(k,itype1,ichir11,ichir12)
4363              bthetk=bthet(k,itype2,ichir21,ichir22)
4364           endif
4365          thet_pred_mean=thet_pred_mean+athetk*y(k)+bthetk*z(k)
4366         enddo
4367         dthett=thet_pred_mean*ssd
4368         thet_pred_mean=thet_pred_mean*ss+a0thet(it)
4369 C Derivatives of the "mean" values in gamma1 and gamma2.
4370         dthetg1=(-athet(1,it,ichir1,ichir2)*y(2)
4371      &+athet(2,it,ichir1,ichir2)*y(1))*ss
4372          dthetg2=(-bthet(1,it,ichir1,ichir2)*z(2)
4373      &          +bthet(2,it,ichir1,ichir2)*z(1))*ss
4374          if (it.eq.10) then
4375       dthetg1=(-athet(1,itype1,ichir11,ichir12)*y(2)
4376      &+athet(2,itype1,ichir11,ichir12)*y(1))*ss
4377         dthetg2=(-bthet(1,itype2,ichir21,ichir22)*z(2)
4378      &         +bthet(2,itype2,ichir21,ichir22)*z(1))*ss
4379          endif
4380         if (theta(i).gt.pi-delta) then
4381           call theteng(pi-delta,thet_pred_mean,theta0(it),f0,fprim0,
4382      &         E_tc0)
4383           call mixder(pi-delta,thet_pred_mean,theta0(it),fprim_tc0)
4384           call theteng(pi,thet_pred_mean,theta0(it),f1,fprim1,E_tc1)
4385           call spline1(theta(i),pi-delta,delta,f0,f1,fprim0,ethetai,
4386      &        E_theta)
4387           call spline2(theta(i),pi-delta,delta,E_tc0,E_tc1,fprim_tc0,
4388      &        E_tc)
4389         else if (theta(i).lt.delta) then
4390           call theteng(delta,thet_pred_mean,theta0(it),f0,fprim0,E_tc0)
4391           call theteng(0.0d0,thet_pred_mean,theta0(it),f1,fprim1,E_tc1)
4392           call spline1(theta(i),delta,-delta,f0,f1,fprim0,ethetai,
4393      &        E_theta)
4394           call mixder(delta,thet_pred_mean,theta0(it),fprim_tc0)
4395           call spline2(theta(i),delta,-delta,E_tc0,E_tc1,fprim_tc0,
4396      &        E_tc)
4397         else
4398           call theteng(theta(i),thet_pred_mean,theta0(it),ethetai,
4399      &        E_theta,E_tc)
4400         endif
4401         etheta=etheta+ethetai
4402         if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
4403      &      'ebend',i,ethetai
4404         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*E_tc*dthetg1
4405         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*E_tc*dthetg2
4406         gloc(nphi+i-2,icg)=wang*(E_theta+E_tc*dthett)
4407       enddo
4408 C Ufff.... We've done all this!!! 
4409       return
4410       end
4411 C---------------------------------------------------------------------------
4412       subroutine theteng(thetai,thet_pred_mean,theta0i,ethetai,E_theta,
4413      &     E_tc)
4414       implicit real*8 (a-h,o-z)
4415       include 'DIMENSIONS'
4416       include 'COMMON.LOCAL'
4417       include 'COMMON.IOUNITS'
4418       common /calcthet/ term1,term2,termm,diffak,ratak,
4419      & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
4420      & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
4421 C Calculate the contributions to both Gaussian lobes.
4422 C 6/6/97 - Deform the Gaussians using the factor of 1/(1+time)
4423 C The "polynomial part" of the "standard deviation" of this part of 
4424 C the distribution.
4425         sig=polthet(3,it)
4426         do j=2,0,-1
4427           sig=sig*thet_pred_mean+polthet(j,it)
4428         enddo
4429 C Derivative of the "interior part" of the "standard deviation of the" 
4430 C gamma-dependent Gaussian lobe in t_c.
4431         sigtc=3*polthet(3,it)
4432         do j=2,1,-1
4433           sigtc=sigtc*thet_pred_mean+j*polthet(j,it)
4434         enddo
4435         sigtc=sig*sigtc
4436 C Set the parameters of both Gaussian lobes of the distribution.
4437 C "Standard deviation" of the gamma-dependent Gaussian lobe (sigtc)
4438         fac=sig*sig+sigc0(it)
4439         sigcsq=fac+fac
4440         sigc=1.0D0/sigcsq
4441 C Following variable (sigsqtc) is -(1/2)d[sigma(t_c)**(-2))]/dt_c
4442         sigsqtc=-4.0D0*sigcsq*sigtc
4443 c       print *,i,sig,sigtc,sigsqtc
4444 C Following variable (sigtc) is d[sigma(t_c)]/dt_c
4445         sigtc=-sigtc/(fac*fac)
4446 C Following variable is sigma(t_c)**(-2)
4447         sigcsq=sigcsq*sigcsq
4448         sig0i=sig0(it)
4449         sig0inv=1.0D0/sig0i**2
4450         delthec=thetai-thet_pred_mean
4451         delthe0=thetai-theta0i
4452         term1=-0.5D0*sigcsq*delthec*delthec
4453         term2=-0.5D0*sig0inv*delthe0*delthe0
4454 C Following fuzzy logic is to avoid underflows in dexp and subsequent INFs and
4455 C NaNs in taking the logarithm. We extract the largest exponent which is added
4456 C to the energy (this being the log of the distribution) at the end of energy
4457 C term evaluation for this virtual-bond angle.
4458         if (term1.gt.term2) then
4459           termm=term1
4460           term2=dexp(term2-termm)
4461           term1=1.0d0
4462         else
4463           termm=term2
4464           term1=dexp(term1-termm)
4465           term2=1.0d0
4466         endif
4467 C The ratio between the gamma-independent and gamma-dependent lobes of
4468 C the distribution is a Gaussian function of thet_pred_mean too.
4469         diffak=gthet(2,it)-thet_pred_mean
4470         ratak=diffak/gthet(3,it)**2
4471         ak=dexp(gthet(1,it)-0.5D0*diffak*ratak)
4472 C Let's differentiate it in thet_pred_mean NOW.
4473         aktc=ak*ratak
4474 C Now put together the distribution terms to make complete distribution.
4475         termexp=term1+ak*term2
4476         termpre=sigc+ak*sig0i
4477 C Contribution of the bending energy from this theta is just the -log of
4478 C the sum of the contributions from the two lobes and the pre-exponential
4479 C factor. Simple enough, isn't it?
4480         ethetai=(-dlog(termexp)-termm+dlog(termpre))
4481 C NOW the derivatives!!!
4482 C 6/6/97 Take into account the deformation.
4483         E_theta=(delthec*sigcsq*term1
4484      &       +ak*delthe0*sig0inv*term2)/termexp
4485         E_tc=((sigtc+aktc*sig0i)/termpre
4486      &      -((delthec*sigcsq+delthec*delthec*sigsqtc)*term1+
4487      &       aktc*term2)/termexp)
4488       return
4489       end
4490 c-----------------------------------------------------------------------------
4491       subroutine mixder(thetai,thet_pred_mean,theta0i,E_tc_t)
4492       implicit real*8 (a-h,o-z)
4493       include 'DIMENSIONS'
4494       include 'COMMON.LOCAL'
4495       include 'COMMON.IOUNITS'
4496       common /calcthet/ term1,term2,termm,diffak,ratak,
4497      & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
4498      & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
4499       delthec=thetai-thet_pred_mean
4500       delthe0=thetai-theta0i
4501 C "Thank you" to MAPLE (probably spared one day of hand-differentiation).
4502       t3 = thetai-thet_pred_mean
4503       t6 = t3**2
4504       t9 = term1
4505       t12 = t3*sigcsq
4506       t14 = t12+t6*sigsqtc
4507       t16 = 1.0d0
4508       t21 = thetai-theta0i
4509       t23 = t21**2
4510       t26 = term2
4511       t27 = t21*t26
4512       t32 = termexp
4513       t40 = t32**2
4514       E_tc_t = -((sigcsq+2.D0*t3*sigsqtc)*t9-t14*sigcsq*t3*t16*t9
4515      & -aktc*sig0inv*t27)/t32+(t14*t9+aktc*t26)/t40
4516      & *(-t12*t9-ak*sig0inv*t27)
4517       return
4518       end
4519 #else
4520 C--------------------------------------------------------------------------
4521       subroutine ebend(etheta)
4522 C
4523 C Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
4524 C angles gamma and its derivatives in consecutive thetas and gammas.
4525 C ab initio-derived potentials from 
4526 c Kozlowska et al., J. Phys.: Condens. Matter 19 (2007) 285203
4527 C
4528       implicit real*8 (a-h,o-z)
4529       include 'DIMENSIONS'
4530       include 'COMMON.LOCAL'
4531       include 'COMMON.GEO'
4532       include 'COMMON.INTERACT'
4533       include 'COMMON.DERIV'
4534       include 'COMMON.VAR'
4535       include 'COMMON.CHAIN'
4536       include 'COMMON.IOUNITS'
4537       include 'COMMON.NAMES'
4538       include 'COMMON.FFIELD'
4539       include 'COMMON.CONTROL'
4540       double precision coskt(mmaxtheterm),sinkt(mmaxtheterm),
4541      & cosph1(maxsingle),sinph1(maxsingle),cosph2(maxsingle),
4542      & sinph2(maxsingle),cosph1ph2(maxdouble,maxdouble),
4543      & sinph1ph2(maxdouble,maxdouble)
4544       logical lprn /.false./, lprn1 /.false./
4545       etheta=0.0D0
4546       do i=ithet_start,ithet_end
4547         if (itype(i-1).eq.ntyp1) cycle
4548         dethetai=0.0d0
4549         dephii=0.0d0
4550         dephii1=0.0d0
4551         theti2=0.5d0*theta(i)
4552         ityp2=ithetyp(iabs(itype(i-1)))
4553         do k=1,nntheterm
4554           coskt(k)=dcos(k*theti2)
4555           sinkt(k)=dsin(k*theti2)
4556         enddo
4557         if (i.gt.3 .and. itype(i-2).ne.ntyp1) then
4558 #ifdef OSF
4559           phii=phi(i)
4560           if (phii.ne.phii) phii=150.0
4561 #else
4562           phii=phi(i)
4563 #endif
4564           ityp1=ithetyp(iabs(itype(i-2)))
4565           do k=1,nsingle
4566             cosph1(k)=dcos(k*phii)
4567             sinph1(k)=dsin(k*phii)
4568           enddo
4569         else
4570           phii=0.0d0
4571           ityp1=nthetyp+1
4572           do k=1,nsingle
4573             cosph1(k)=0.0d0
4574             sinph1(k)=0.0d0
4575           enddo 
4576         endif
4577         if (i.lt.nres .and. itype(i).ne.ntyp1) then
4578 #ifdef OSF
4579           phii1=phi(i+1)
4580           if (phii1.ne.phii1) phii1=150.0
4581           phii1=pinorm(phii1)
4582 #else
4583           phii1=phi(i+1)
4584 #endif
4585           ityp3=ithetyp(iabs(itype(i)))
4586           do k=1,nsingle
4587             cosph2(k)=dcos(k*phii1)
4588             sinph2(k)=dsin(k*phii1)
4589           enddo
4590         else
4591           phii1=0.0d0
4592           ityp3=nthetyp+1
4593           do k=1,nsingle
4594             cosph2(k)=0.0d0
4595             sinph2(k)=0.0d0
4596           enddo
4597         endif  
4598         ethetai=aa0thet(ityp1,ityp2,ityp3)
4599         do k=1,ndouble
4600           do l=1,k-1
4601             ccl=cosph1(l)*cosph2(k-l)
4602             ssl=sinph1(l)*sinph2(k-l)
4603             scl=sinph1(l)*cosph2(k-l)
4604             csl=cosph1(l)*sinph2(k-l)
4605             cosph1ph2(l,k)=ccl-ssl
4606             cosph1ph2(k,l)=ccl+ssl
4607             sinph1ph2(l,k)=scl+csl
4608             sinph1ph2(k,l)=scl-csl
4609           enddo
4610         enddo
4611         if (lprn) then
4612         write (iout,*) "i",i," ityp1",ityp1," ityp2",ityp2,
4613      &    " ityp3",ityp3," theti2",theti2," phii",phii," phii1",phii1
4614         write (iout,*) "coskt and sinkt"
4615         do k=1,nntheterm
4616           write (iout,*) k,coskt(k),sinkt(k)
4617         enddo
4618         endif
4619         do k=1,ntheterm
4620           ethetai=ethetai+aathet(k,ityp1,ityp2,ityp3)*sinkt(k)
4621           dethetai=dethetai+0.5d0*k*aathet(k,ityp1,ityp2,ityp3)
4622      &      *coskt(k)
4623           if (lprn)
4624      &    write (iout,*) "k",k," aathet",aathet(k,ityp1,ityp2,ityp3),
4625      &     " ethetai",ethetai
4626         enddo
4627         if (lprn) then
4628         write (iout,*) "cosph and sinph"
4629         do k=1,nsingle
4630           write (iout,*) k,cosph1(k),sinph1(k),cosph2(k),sinph2(k)
4631         enddo
4632         write (iout,*) "cosph1ph2 and sinph2ph2"
4633         do k=2,ndouble
4634           do l=1,k-1
4635             write (iout,*) l,k,cosph1ph2(l,k),cosph1ph2(k,l),
4636      &         sinph1ph2(l,k),sinph1ph2(k,l) 
4637           enddo
4638         enddo
4639         write(iout,*) "ethetai",ethetai
4640         endif
4641         do m=1,ntheterm2
4642           do k=1,nsingle
4643             aux=bbthet(k,m,ityp1,ityp2,ityp3)*cosph1(k)
4644      &         +ccthet(k,m,ityp1,ityp2,ityp3)*sinph1(k)
4645      &         +ddthet(k,m,ityp1,ityp2,ityp3)*cosph2(k)
4646      &         +eethet(k,m,ityp1,ityp2,ityp3)*sinph2(k)
4647             ethetai=ethetai+sinkt(m)*aux
4648             dethetai=dethetai+0.5d0*m*aux*coskt(m)
4649             dephii=dephii+k*sinkt(m)*(
4650      &          ccthet(k,m,ityp1,ityp2,ityp3)*cosph1(k)-
4651      &          bbthet(k,m,ityp1,ityp2,ityp3)*sinph1(k))
4652             dephii1=dephii1+k*sinkt(m)*(
4653      &          eethet(k,m,ityp1,ityp2,ityp3)*cosph2(k)-
4654      &          ddthet(k,m,ityp1,ityp2,ityp3)*sinph2(k))
4655             if (lprn)
4656      &      write (iout,*) "m",m," k",k," bbthet",
4657      &         bbthet(k,m,ityp1,ityp2,ityp3)," ccthet",
4658      &         ccthet(k,m,ityp1,ityp2,ityp3)," ddthet",
4659      &         ddthet(k,m,ityp1,ityp2,ityp3)," eethet",
4660      &         eethet(k,m,ityp1,ityp2,ityp3)," ethetai",ethetai
4661           enddo
4662         enddo
4663         if (lprn)
4664      &  write(iout,*) "ethetai",ethetai
4665         do m=1,ntheterm3
4666           do k=2,ndouble
4667             do l=1,k-1
4668               aux=ffthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)+
4669      &            ffthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l)+
4670      &            ggthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)+
4671      &            ggthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)
4672               ethetai=ethetai+sinkt(m)*aux
4673               dethetai=dethetai+0.5d0*m*coskt(m)*aux
4674               dephii=dephii+l*sinkt(m)*(
4675      &           -ffthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)-
4676      &            ffthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)+
4677      &            ggthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)+
4678      &            ggthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l))
4679               dephii1=dephii1+(k-l)*sinkt(m)*(
4680      &           -ffthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)+
4681      &            ffthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)+
4682      &            ggthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)-
4683      &            ggthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l))
4684               if (lprn) then
4685               write (iout,*) "m",m," k",k," l",l," ffthet",
4686      &            ffthet(l,k,m,ityp1,ityp2,ityp3),
4687      &            ffthet(k,l,m,ityp1,ityp2,ityp3)," ggthet",
4688      &            ggthet(l,k,m,ityp1,ityp2,ityp3),
4689      &            ggthet(k,l,m,ityp1,ityp2,ityp3)," ethetai",ethetai
4690               write (iout,*) cosph1ph2(l,k)*sinkt(m),
4691      &            cosph1ph2(k,l)*sinkt(m),
4692      &            sinph1ph2(l,k)*sinkt(m),sinph1ph2(k,l)*sinkt(m)
4693               endif
4694             enddo
4695           enddo
4696         enddo
4697 10      continue
4698         if (lprn1) write (iout,'(i2,3f8.1,9h ethetai ,f10.5)') 
4699      &   i,theta(i)*rad2deg,phii*rad2deg,
4700      &   phii1*rad2deg,ethetai
4701         etheta=etheta+ethetai
4702         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*dephii
4703         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*dephii1
4704         gloc(nphi+i-2,icg)=wang*dethetai
4705       enddo
4706       return
4707       end
4708 #endif
4709 #ifdef CRYST_SC
4710 c-----------------------------------------------------------------------------
4711       subroutine esc(escloc)
4712 C Calculate the local energy of a side chain and its derivatives in the
4713 C corresponding virtual-bond valence angles THETA and the spherical angles 
4714 C ALPHA and OMEGA.
4715       implicit real*8 (a-h,o-z)
4716       include 'DIMENSIONS'
4717       include 'COMMON.GEO'
4718       include 'COMMON.LOCAL'
4719       include 'COMMON.VAR'
4720       include 'COMMON.INTERACT'
4721       include 'COMMON.DERIV'
4722       include 'COMMON.CHAIN'
4723       include 'COMMON.IOUNITS'
4724       include 'COMMON.NAMES'
4725       include 'COMMON.FFIELD'
4726       include 'COMMON.CONTROL'
4727       double precision x(3),dersc(3),xemp(3),dersc0(3),dersc1(3),
4728      &     ddersc0(3),ddummy(3),xtemp(3),temp(3)
4729       common /sccalc/ time11,time12,time112,theti,it,nlobit
4730       delta=0.02d0*pi
4731       escloc=0.0D0
4732 c     write (iout,'(a)') 'ESC'
4733       do i=loc_start,loc_end
4734         it=itype(i)
4735         if (it.eq.ntyp1) cycle
4736         if (it.eq.10) goto 1
4737         nlobit=nlob(iabs(it))
4738 c       print *,'i=',i,' it=',it,' nlobit=',nlobit
4739 c       write (iout,*) 'i=',i,' ssa=',ssa,' ssad=',ssad
4740         theti=theta(i+1)-pipol
4741         x(1)=dtan(theti)
4742         x(2)=alph(i)
4743         x(3)=omeg(i)
4744
4745         if (x(2).gt.pi-delta) then
4746           xtemp(1)=x(1)
4747           xtemp(2)=pi-delta
4748           xtemp(3)=x(3)
4749           call enesc(xtemp,escloci0,dersc0,ddersc0,.true.)
4750           xtemp(2)=pi
4751           call enesc(xtemp,escloci1,dersc1,ddummy,.false.)
4752           call spline1(x(2),pi-delta,delta,escloci0,escloci1,dersc0(2),
4753      &        escloci,dersc(2))
4754           call spline2(x(2),pi-delta,delta,dersc0(1),dersc1(1),
4755      &        ddersc0(1),dersc(1))
4756           call spline2(x(2),pi-delta,delta,dersc0(3),dersc1(3),
4757      &        ddersc0(3),dersc(3))
4758           xtemp(2)=pi-delta
4759           call enesc_bound(xtemp,esclocbi0,dersc0,dersc12,.true.)
4760           xtemp(2)=pi
4761           call enesc_bound(xtemp,esclocbi1,dersc1,chuju,.false.)
4762           call spline1(x(2),pi-delta,delta,esclocbi0,esclocbi1,
4763      &            dersc0(2),esclocbi,dersc02)
4764           call spline2(x(2),pi-delta,delta,dersc0(1),dersc1(1),
4765      &            dersc12,dersc01)
4766           call splinthet(x(2),0.5d0*delta,ss,ssd)
4767           dersc0(1)=dersc01
4768           dersc0(2)=dersc02
4769           dersc0(3)=0.0d0
4770           do k=1,3
4771             dersc(k)=ss*dersc(k)+(1.0d0-ss)*dersc0(k)
4772           enddo
4773           dersc(2)=dersc(2)+ssd*(escloci-esclocbi)
4774 c         write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
4775 c    &             esclocbi,ss,ssd
4776           escloci=ss*escloci+(1.0d0-ss)*esclocbi
4777 c         escloci=esclocbi
4778 c         write (iout,*) escloci
4779         else if (x(2).lt.delta) then
4780           xtemp(1)=x(1)
4781           xtemp(2)=delta
4782           xtemp(3)=x(3)
4783           call enesc(xtemp,escloci0,dersc0,ddersc0,.true.)
4784           xtemp(2)=0.0d0
4785           call enesc(xtemp,escloci1,dersc1,ddummy,.false.)
4786           call spline1(x(2),delta,-delta,escloci0,escloci1,dersc0(2),
4787      &        escloci,dersc(2))
4788           call spline2(x(2),delta,-delta,dersc0(1),dersc1(1),
4789      &        ddersc0(1),dersc(1))
4790           call spline2(x(2),delta,-delta,dersc0(3),dersc1(3),
4791      &        ddersc0(3),dersc(3))
4792           xtemp(2)=delta
4793           call enesc_bound(xtemp,esclocbi0,dersc0,dersc12,.true.)
4794           xtemp(2)=0.0d0
4795           call enesc_bound(xtemp,esclocbi1,dersc1,chuju,.false.)
4796           call spline1(x(2),delta,-delta,esclocbi0,esclocbi1,
4797      &            dersc0(2),esclocbi,dersc02)
4798           call spline2(x(2),delta,-delta,dersc0(1),dersc1(1),
4799      &            dersc12,dersc01)
4800           dersc0(1)=dersc01
4801           dersc0(2)=dersc02
4802           dersc0(3)=0.0d0
4803           call splinthet(x(2),0.5d0*delta,ss,ssd)
4804           do k=1,3
4805             dersc(k)=ss*dersc(k)+(1.0d0-ss)*dersc0(k)
4806           enddo
4807           dersc(2)=dersc(2)+ssd*(escloci-esclocbi)
4808 c         write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
4809 c    &             esclocbi,ss,ssd
4810           escloci=ss*escloci+(1.0d0-ss)*esclocbi
4811 c         write (iout,*) escloci
4812         else
4813           call enesc(x,escloci,dersc,ddummy,.false.)
4814         endif
4815
4816         escloc=escloc+escloci
4817         if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
4818      &     'escloc',i,escloci
4819 c       write (iout,*) 'i=',i,' escloci=',escloci,' dersc=',dersc
4820
4821         gloc(nphi+i-1,icg)=gloc(nphi+i-1,icg)+
4822      &   wscloc*dersc(1)
4823         gloc(ialph(i,1),icg)=wscloc*dersc(2)
4824         gloc(ialph(i,1)+nside,icg)=wscloc*dersc(3)
4825     1   continue
4826       enddo
4827       return
4828       end
4829 C---------------------------------------------------------------------------
4830       subroutine enesc(x,escloci,dersc,ddersc,mixed)
4831       implicit real*8 (a-h,o-z)
4832       include 'DIMENSIONS'
4833       include 'COMMON.GEO'
4834       include 'COMMON.LOCAL'
4835       include 'COMMON.IOUNITS'
4836       common /sccalc/ time11,time12,time112,theti,it,nlobit
4837       double precision x(3),z(3),Ax(3,maxlob,-1:1),dersc(3),ddersc(3)
4838       double precision contr(maxlob,-1:1)
4839       logical mixed
4840 c       write (iout,*) 'it=',it,' nlobit=',nlobit
4841         escloc_i=0.0D0
4842         do j=1,3
4843           dersc(j)=0.0D0
4844           if (mixed) ddersc(j)=0.0d0
4845         enddo
4846         x3=x(3)
4847
4848 C Because of periodicity of the dependence of the SC energy in omega we have
4849 C to add up the contributions from x(3)-2*pi, x(3), and x(3+2*pi).
4850 C To avoid underflows, first compute & store the exponents.
4851
4852         do iii=-1,1
4853
4854           x(3)=x3+iii*dwapi
4855  
4856           do j=1,nlobit
4857             do k=1,3
4858               z(k)=x(k)-censc(k,j,it)
4859             enddo
4860             do k=1,3
4861               Axk=0.0D0
4862               do l=1,3
4863                 Axk=Axk+gaussc(l,k,j,it)*z(l)
4864               enddo
4865               Ax(k,j,iii)=Axk
4866             enddo 
4867             expfac=0.0D0 
4868             do k=1,3
4869               expfac=expfac+Ax(k,j,iii)*z(k)
4870             enddo
4871             contr(j,iii)=expfac
4872           enddo ! j
4873
4874         enddo ! iii
4875
4876         x(3)=x3
4877 C As in the case of ebend, we want to avoid underflows in exponentiation and
4878 C subsequent NaNs and INFs in energy calculation.
4879 C Find the largest exponent
4880         emin=contr(1,-1)
4881         do iii=-1,1
4882           do j=1,nlobit
4883             if (emin.gt.contr(j,iii)) emin=contr(j,iii)
4884           enddo 
4885         enddo
4886         emin=0.5D0*emin
4887 cd      print *,'it=',it,' emin=',emin
4888
4889 C Compute the contribution to SC energy and derivatives
4890         do iii=-1,1
4891
4892           do j=1,nlobit
4893 #ifdef OSF
4894             adexp=bsc(j,iabs(it))-0.5D0*contr(j,iii)+emin
4895             if(adexp.ne.adexp) adexp=1.0
4896             expfac=dexp(adexp)
4897 #else
4898             expfac=dexp(bsc(j,iabs(it))-0.5D0*contr(j,iii)+emin)
4899 #endif
4900 cd          print *,'j=',j,' expfac=',expfac
4901             escloc_i=escloc_i+expfac
4902             do k=1,3
4903               dersc(k)=dersc(k)+Ax(k,j,iii)*expfac
4904             enddo
4905             if (mixed) then
4906               do k=1,3,2
4907                 ddersc(k)=ddersc(k)+(-Ax(2,j,iii)*Ax(k,j,iii)
4908      &            +gaussc(k,2,j,it))*expfac
4909               enddo
4910             endif
4911           enddo
4912
4913         enddo ! iii
4914
4915         dersc(1)=dersc(1)/cos(theti)**2
4916         ddersc(1)=ddersc(1)/cos(theti)**2
4917         ddersc(3)=ddersc(3)
4918
4919         escloci=-(dlog(escloc_i)-emin)
4920         do j=1,3
4921           dersc(j)=dersc(j)/escloc_i
4922         enddo
4923         if (mixed) then
4924           do j=1,3,2
4925             ddersc(j)=(ddersc(j)/escloc_i+dersc(2)*dersc(j))
4926           enddo
4927         endif
4928       return
4929       end
4930 C------------------------------------------------------------------------------
4931       subroutine enesc_bound(x,escloci,dersc,dersc12,mixed)
4932       implicit real*8 (a-h,o-z)
4933       include 'DIMENSIONS'
4934       include 'COMMON.GEO'
4935       include 'COMMON.LOCAL'
4936       include 'COMMON.IOUNITS'
4937       common /sccalc/ time11,time12,time112,theti,it,nlobit
4938       double precision x(3),z(3),Ax(3,maxlob),dersc(3)
4939       double precision contr(maxlob)
4940       logical mixed
4941
4942       escloc_i=0.0D0
4943
4944       do j=1,3
4945         dersc(j)=0.0D0
4946       enddo
4947
4948       do j=1,nlobit
4949         do k=1,2
4950           z(k)=x(k)-censc(k,j,it)
4951         enddo
4952         z(3)=dwapi
4953         do k=1,3
4954           Axk=0.0D0
4955           do l=1,3
4956             Axk=Axk+gaussc(l,k,j,it)*z(l)
4957           enddo
4958           Ax(k,j)=Axk
4959         enddo 
4960         expfac=0.0D0 
4961         do k=1,3
4962           expfac=expfac+Ax(k,j)*z(k)
4963         enddo
4964         contr(j)=expfac
4965       enddo ! j
4966
4967 C As in the case of ebend, we want to avoid underflows in exponentiation and
4968 C subsequent NaNs and INFs in energy calculation.
4969 C Find the largest exponent
4970       emin=contr(1)
4971       do j=1,nlobit
4972         if (emin.gt.contr(j)) emin=contr(j)
4973       enddo 
4974       emin=0.5D0*emin
4975  
4976 C Compute the contribution to SC energy and derivatives
4977
4978       dersc12=0.0d0
4979       do j=1,nlobit
4980         expfac=dexp(bsc(j,iabs(it))-0.5D0*contr(j)+emin)
4981         escloc_i=escloc_i+expfac
4982         do k=1,2
4983           dersc(k)=dersc(k)+Ax(k,j)*expfac
4984         enddo
4985         if (mixed) dersc12=dersc12+(-Ax(2,j)*Ax(1,j)
4986      &            +gaussc(1,2,j,it))*expfac
4987         dersc(3)=0.0d0
4988       enddo
4989
4990       dersc(1)=dersc(1)/cos(theti)**2
4991       dersc12=dersc12/cos(theti)**2
4992       escloci=-(dlog(escloc_i)-emin)
4993       do j=1,2
4994         dersc(j)=dersc(j)/escloc_i
4995       enddo
4996       if (mixed) dersc12=(dersc12/escloc_i+dersc(2)*dersc(1))
4997       return
4998       end
4999 #else
5000 c----------------------------------------------------------------------------------
5001       subroutine esc(escloc)
5002 C Calculate the local energy of a side chain and its derivatives in the
5003 C corresponding virtual-bond valence angles THETA and the spherical angles 
5004 C ALPHA and OMEGA derived from AM1 all-atom calculations.
5005 C added by Urszula Kozlowska. 07/11/2007
5006 C
5007       implicit real*8 (a-h,o-z)
5008       include 'DIMENSIONS'
5009       include 'COMMON.GEO'
5010       include 'COMMON.LOCAL'
5011       include 'COMMON.VAR'
5012       include 'COMMON.SCROT'
5013       include 'COMMON.INTERACT'
5014       include 'COMMON.DERIV'
5015       include 'COMMON.CHAIN'
5016       include 'COMMON.IOUNITS'
5017       include 'COMMON.NAMES'
5018       include 'COMMON.FFIELD'
5019       include 'COMMON.CONTROL'
5020       include 'COMMON.VECTORS'
5021       double precision x_prime(3),y_prime(3),z_prime(3)
5022      &    , sumene,dsc_i,dp2_i,x(65),
5023      &     xx,yy,zz,sumene1,sumene2,sumene3,sumene4,s1,s1_6,s2,s2_6,
5024      &    de_dxx,de_dyy,de_dzz,de_dt
5025       double precision s1_t,s1_6_t,s2_t,s2_6_t
5026       double precision 
5027      & dXX_Ci1(3),dYY_Ci1(3),dZZ_Ci1(3),dXX_Ci(3),
5028      & dYY_Ci(3),dZZ_Ci(3),dXX_XYZ(3),dYY_XYZ(3),dZZ_XYZ(3),
5029      & dt_dCi(3),dt_dCi1(3)
5030       common /sccalc/ time11,time12,time112,theti,it,nlobit
5031       delta=0.02d0*pi
5032       escloc=0.0D0
5033       do i=loc_start,loc_end
5034         if (itype(i).eq.ntyp1) cycle
5035         costtab(i+1) =dcos(theta(i+1))
5036         sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
5037         cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
5038         sint2tab(i+1)=dsqrt(0.5d0*(1.0d0-costtab(i+1)))
5039         cosfac2=0.5d0/(1.0d0+costtab(i+1))
5040         cosfac=dsqrt(cosfac2)
5041         sinfac2=0.5d0/(1.0d0-costtab(i+1))
5042         sinfac=dsqrt(sinfac2)
5043         it=itype(i)
5044         if (it.eq.10) goto 1
5045 c
5046 C  Compute the axes of tghe local cartesian coordinates system; store in
5047 c   x_prime, y_prime and z_prime 
5048 c
5049         do j=1,3
5050           x_prime(j) = 0.00
5051           y_prime(j) = 0.00
5052           z_prime(j) = 0.00
5053         enddo
5054 C        write(2,*) "dc_norm", dc_norm(1,i+nres),dc_norm(2,i+nres),
5055 C     &   dc_norm(3,i+nres)
5056         do j = 1,3
5057           x_prime(j) = (dc_norm(j,i) - dc_norm(j,i-1))*cosfac
5058           y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
5059         enddo
5060         do j = 1,3
5061           z_prime(j) = -uz(j,i-1)
5062         enddo     
5063 c       write (2,*) "i",i
5064 c       write (2,*) "x_prime",(x_prime(j),j=1,3)
5065 c       write (2,*) "y_prime",(y_prime(j),j=1,3)
5066 c       write (2,*) "z_prime",(z_prime(j),j=1,3)
5067 c       write (2,*) "xx",scalar(x_prime(1),x_prime(1)),
5068 c      & " xy",scalar(x_prime(1),y_prime(1)),
5069 c      & " xz",scalar(x_prime(1),z_prime(1)),
5070 c      & " yy",scalar(y_prime(1),y_prime(1)),
5071 c      & " yz",scalar(y_prime(1),z_prime(1)),
5072 c      & " zz",scalar(z_prime(1),z_prime(1))
5073 c
5074 C Transform the unit vector of the ith side-chain centroid, dC_norm(*,i),
5075 C to local coordinate system. Store in xx, yy, zz.
5076 c
5077         xx=0.0d0
5078         yy=0.0d0
5079         zz=0.0d0
5080         do j = 1,3
5081           xx = xx + x_prime(j)*dc_norm(j,i+nres)
5082           yy = yy + y_prime(j)*dc_norm(j,i+nres)
5083           zz = zz + dsign(1.0,itype(i))*z_prime(j)*dc_norm(j,i+nres)
5084         enddo
5085
5086         xxtab(i)=xx
5087         yytab(i)=yy
5088         zztab(i)=zz
5089 C
5090 C Compute the energy of the ith side cbain
5091 C
5092 c        write (2,*) "xx",xx," yy",yy," zz",zz
5093         it=iabs(itype(i))
5094         do j = 1,65
5095           x(j) = sc_parmin(j,it) 
5096         enddo
5097 #ifdef CHECK_COORD
5098 Cc diagnostics - remove later
5099         xx1 = dcos(alph(2))
5100         yy1 = dsin(alph(2))*dcos(omeg(2))
5101         zz1 = -dsign(1.0,itype(i))*dsin(alph(2))*dsin(omeg(2))
5102         write(2,'(3f8.1,3f9.3,1x,3f9.3)') 
5103      &    alph(2)*rad2deg,omeg(2)*rad2deg,theta(3)*rad2deg,xx,yy,zz,
5104      &    xx1,yy1,zz1
5105 C,"  --- ", xx_w,yy_w,zz_w
5106 c end diagnostics
5107 #endif
5108         sumene1= x(1)+  x(2)*xx+  x(3)*yy+  x(4)*zz+  x(5)*xx**2
5109      &   + x(6)*yy**2+  x(7)*zz**2+  x(8)*xx*zz+  x(9)*xx*yy
5110      &   + x(10)*yy*zz
5111         sumene2=  x(11) + x(12)*xx + x(13)*yy + x(14)*zz + x(15)*xx**2
5112      & + x(16)*yy**2 + x(17)*zz**2 + x(18)*xx*zz + x(19)*xx*yy
5113      & + x(20)*yy*zz
5114         sumene3=  x(21) +x(22)*xx +x(23)*yy +x(24)*zz +x(25)*xx**2
5115      &  +x(26)*yy**2 +x(27)*zz**2 +x(28)*xx*zz +x(29)*xx*yy
5116      &  +x(30)*yy*zz +x(31)*xx**3 +x(32)*yy**3 +x(33)*zz**3
5117      &  +x(34)*(xx**2)*yy +x(35)*(xx**2)*zz +x(36)*(yy**2)*xx
5118      &  +x(37)*(yy**2)*zz +x(38)*(zz**2)*xx +x(39)*(zz**2)*yy
5119      &  +x(40)*xx*yy*zz
5120         sumene4= x(41) +x(42)*xx +x(43)*yy +x(44)*zz +x(45)*xx**2
5121      &  +x(46)*yy**2 +x(47)*zz**2 +x(48)*xx*zz +x(49)*xx*yy
5122      &  +x(50)*yy*zz +x(51)*xx**3 +x(52)*yy**3 +x(53)*zz**3
5123      &  +x(54)*(xx**2)*yy +x(55)*(xx**2)*zz +x(56)*(yy**2)*xx
5124      &  +x(57)*(yy**2)*zz +x(58)*(zz**2)*xx +x(59)*(zz**2)*yy
5125      &  +x(60)*xx*yy*zz
5126         dsc_i   = 0.743d0+x(61)
5127         dp2_i   = 1.9d0+x(62)
5128         dscp1=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
5129      &          *(xx*cost2tab(i+1)+yy*sint2tab(i+1)))
5130         dscp2=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
5131      &          *(xx*cost2tab(i+1)-yy*sint2tab(i+1)))
5132         s1=(1+x(63))/(0.1d0 + dscp1)
5133         s1_6=(1+x(64))/(0.1d0 + dscp1**6)
5134         s2=(1+x(65))/(0.1d0 + dscp2)
5135         s2_6=(1+x(65))/(0.1d0 + dscp2**6)
5136         sumene = ( sumene3*sint2tab(i+1) + sumene1)*(s1+s1_6)
5137      & + (sumene4*cost2tab(i+1) +sumene2)*(s2+s2_6)
5138 c        write(2,'(i2," sumene",7f9.3)') i,sumene1,sumene2,sumene3,
5139 c     &   sumene4,
5140 c     &   dscp1,dscp2,sumene
5141 c        sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
5142         escloc = escloc + sumene
5143 c        write (2,*) "i",i," escloc",sumene,escloc
5144 #ifdef DEBUG
5145 C
5146 C This section to check the numerical derivatives of the energy of ith side
5147 C chain in xx, yy, zz, and theta. Use the -DDEBUG compiler option or insert
5148 C #define DEBUG in the code to turn it on.
5149 C
5150         write (2,*) "sumene               =",sumene
5151         aincr=1.0d-7
5152         xxsave=xx
5153         xx=xx+aincr
5154         write (2,*) xx,yy,zz
5155         sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
5156         de_dxx_num=(sumenep-sumene)/aincr
5157         xx=xxsave
5158         write (2,*) "xx+ sumene from enesc=",sumenep
5159         yysave=yy
5160         yy=yy+aincr
5161         write (2,*) xx,yy,zz
5162         sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
5163         de_dyy_num=(sumenep-sumene)/aincr
5164         yy=yysave
5165         write (2,*) "yy+ sumene from enesc=",sumenep
5166         zzsave=zz
5167         zz=zz+aincr
5168         write (2,*) xx,yy,zz
5169         sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
5170         de_dzz_num=(sumenep-sumene)/aincr
5171         zz=zzsave
5172         write (2,*) "zz+ sumene from enesc=",sumenep
5173         costsave=cost2tab(i+1)
5174         sintsave=sint2tab(i+1)
5175         cost2tab(i+1)=dcos(0.5d0*(theta(i+1)+aincr))
5176         sint2tab(i+1)=dsin(0.5d0*(theta(i+1)+aincr))
5177         sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
5178         de_dt_num=(sumenep-sumene)/aincr
5179         write (2,*) " t+ sumene from enesc=",sumenep
5180         cost2tab(i+1)=costsave
5181         sint2tab(i+1)=sintsave
5182 C End of diagnostics section.
5183 #endif
5184 C        
5185 C Compute the gradient of esc
5186 C
5187         pom_s1=(1.0d0+x(63))/(0.1d0 + dscp1)**2
5188         pom_s16=6*(1.0d0+x(64))/(0.1d0 + dscp1**6)**2
5189         pom_s2=(1.0d0+x(65))/(0.1d0 + dscp2)**2
5190         pom_s26=6*(1.0d0+x(65))/(0.1d0 + dscp2**6)**2
5191         pom_dx=dsc_i*dp2_i*cost2tab(i+1)
5192         pom_dy=dsc_i*dp2_i*sint2tab(i+1)
5193         pom_dt1=-0.5d0*dsc_i*dp2_i*(xx*sint2tab(i+1)-yy*cost2tab(i+1))
5194         pom_dt2=-0.5d0*dsc_i*dp2_i*(xx*sint2tab(i+1)+yy*cost2tab(i+1))
5195         pom1=(sumene3*sint2tab(i+1)+sumene1)
5196      &     *(pom_s1/dscp1+pom_s16*dscp1**4)
5197         pom2=(sumene4*cost2tab(i+1)+sumene2)
5198      &     *(pom_s2/dscp2+pom_s26*dscp2**4)
5199         sumene1x=x(2)+2*x(5)*xx+x(8)*zz+ x(9)*yy
5200         sumene3x=x(22)+2*x(25)*xx+x(28)*zz+x(29)*yy+3*x(31)*xx**2
5201      &  +2*x(34)*xx*yy +2*x(35)*xx*zz +x(36)*(yy**2) +x(38)*(zz**2)
5202      &  +x(40)*yy*zz
5203         sumene2x=x(12)+2*x(15)*xx+x(18)*zz+ x(19)*yy
5204         sumene4x=x(42)+2*x(45)*xx +x(48)*zz +x(49)*yy +3*x(51)*xx**2
5205      &  +2*x(54)*xx*yy+2*x(55)*xx*zz+x(56)*(yy**2)+x(58)*(zz**2)
5206      &  +x(60)*yy*zz
5207         de_dxx =(sumene1x+sumene3x*sint2tab(i+1))*(s1+s1_6)
5208      &        +(sumene2x+sumene4x*cost2tab(i+1))*(s2+s2_6)
5209      &        +(pom1+pom2)*pom_dx
5210 #ifdef DEBUG
5211         write(2,*), "de_dxx = ", de_dxx,de_dxx_num
5212 #endif
5213 C
5214         sumene1y=x(3) + 2*x(6)*yy + x(9)*xx + x(10)*zz
5215         sumene3y=x(23) +2*x(26)*yy +x(29)*xx +x(30)*zz +3*x(32)*yy**2
5216      &  +x(34)*(xx**2) +2*x(36)*yy*xx +2*x(37)*yy*zz +x(39)*(zz**2)
5217      &  +x(40)*xx*zz
5218         sumene2y=x(13) + 2*x(16)*yy + x(19)*xx + x(20)*zz
5219         sumene4y=x(43)+2*x(46)*yy+x(49)*xx +x(50)*zz
5220      &  +3*x(52)*yy**2+x(54)*xx**2+2*x(56)*yy*xx +2*x(57)*yy*zz
5221      &  +x(59)*zz**2 +x(60)*xx*zz
5222         de_dyy =(sumene1y+sumene3y*sint2tab(i+1))*(s1+s1_6)
5223      &        +(sumene2y+sumene4y*cost2tab(i+1))*(s2+s2_6)
5224      &        +(pom1-pom2)*pom_dy
5225 #ifdef DEBUG
5226         write(2,*), "de_dyy = ", de_dyy,de_dyy_num
5227 #endif
5228 C
5229         de_dzz =(x(24) +2*x(27)*zz +x(28)*xx +x(30)*yy
5230      &  +3*x(33)*zz**2 +x(35)*xx**2 +x(37)*yy**2 +2*x(38)*zz*xx 
5231      &  +2*x(39)*zz*yy +x(40)*xx*yy)*sint2tab(i+1)*(s1+s1_6) 
5232      &  +(x(4) + 2*x(7)*zz+  x(8)*xx + x(10)*yy)*(s1+s1_6) 
5233      &  +(x(44)+2*x(47)*zz +x(48)*xx   +x(50)*yy  +3*x(53)*zz**2   
5234      &  +x(55)*xx**2 +x(57)*(yy**2)+2*x(58)*zz*xx +2*x(59)*zz*yy  
5235      &  +x(60)*xx*yy)*cost2tab(i+1)*(s2+s2_6)
5236      &  + ( x(14) + 2*x(17)*zz+  x(18)*xx + x(20)*yy)*(s2+s2_6)
5237 #ifdef DEBUG
5238         write(2,*), "de_dzz = ", de_dzz,de_dzz_num
5239 #endif
5240 C
5241         de_dt =  0.5d0*sumene3*cost2tab(i+1)*(s1+s1_6) 
5242      &  -0.5d0*sumene4*sint2tab(i+1)*(s2+s2_6)
5243      &  +pom1*pom_dt1+pom2*pom_dt2
5244 #ifdef DEBUG
5245         write(2,*), "de_dt = ", de_dt,de_dt_num
5246 #endif
5247
5248 C
5249        cossc=scalar(dc_norm(1,i),dc_norm(1,i+nres))
5250        cossc1=scalar(dc_norm(1,i-1),dc_norm(1,i+nres))
5251        cosfac2xx=cosfac2*xx
5252        sinfac2yy=sinfac2*yy
5253        do k = 1,3
5254          dt_dCi(k) = -(dc_norm(k,i-1)+costtab(i+1)*dc_norm(k,i))*
5255      &      vbld_inv(i+1)
5256          dt_dCi1(k)= -(dc_norm(k,i)+costtab(i+1)*dc_norm(k,i-1))*
5257      &      vbld_inv(i)
5258          pom=(dC_norm(k,i+nres)-cossc*dC_norm(k,i))*vbld_inv(i+1)
5259          pom1=(dC_norm(k,i+nres)-cossc1*dC_norm(k,i-1))*vbld_inv(i)
5260 c         write (iout,*) "i",i," k",k," pom",pom," pom1",pom1,
5261 c     &    " dt_dCi",dt_dCi(k)," dt_dCi1",dt_dCi1(k)
5262 c         write (iout,*) "dC_norm",(dC_norm(j,i),j=1,3),
5263 c     &   (dC_norm(j,i-1),j=1,3)," vbld_inv",vbld_inv(i+1),vbld_inv(i)
5264          dXX_Ci(k)=pom*cosfac-dt_dCi(k)*cosfac2xx
5265          dXX_Ci1(k)=-pom1*cosfac-dt_dCi1(k)*cosfac2xx
5266          dYY_Ci(k)=pom*sinfac+dt_dCi(k)*sinfac2yy
5267          dYY_Ci1(k)=pom1*sinfac+dt_dCi1(k)*sinfac2yy
5268          dZZ_Ci1(k)=0.0d0
5269          dZZ_Ci(k)=0.0d0
5270          do j=1,3
5271            dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1)*dC_norm(j,i+nres)
5272            dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1)*dC_norm(j,i+nres)
5273          enddo
5274           
5275          dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
5276          dYY_XYZ(k)=vbld_inv(i+nres)*(y_prime(k)-yy*dC_norm(k,i+nres))
5277          dZZ_XYZ(k)=vbld_inv(i+nres)*(z_prime(k)-zz*dC_norm(k,i+nres))
5278 c
5279          dt_dCi(k) = -dt_dCi(k)/sinttab(i+1)
5280          dt_dCi1(k)= -dt_dCi1(k)/sinttab(i+1)
5281        enddo
5282
5283        do k=1,3
5284          dXX_Ctab(k,i)=dXX_Ci(k)
5285          dXX_C1tab(k,i)=dXX_Ci1(k)
5286          dYY_Ctab(k,i)=dYY_Ci(k)
5287          dYY_C1tab(k,i)=dYY_Ci1(k)
5288          dZZ_Ctab(k,i)=dZZ_Ci(k)
5289          dZZ_C1tab(k,i)=dZZ_Ci1(k)
5290          dXX_XYZtab(k,i)=dXX_XYZ(k)
5291          dYY_XYZtab(k,i)=dYY_XYZ(k)
5292          dZZ_XYZtab(k,i)=dZZ_XYZ(k)
5293        enddo
5294
5295        do k = 1,3
5296 c         write (iout,*) "k",k," dxx_ci1",dxx_ci1(k)," dyy_ci1",
5297 c     &    dyy_ci1(k)," dzz_ci1",dzz_ci1(k)
5298 c         write (iout,*) "k",k," dxx_ci",dxx_ci(k)," dyy_ci",
5299 c     &    dyy_ci(k)," dzz_ci",dzz_ci(k)
5300 c         write (iout,*) "k",k," dt_dci",dt_dci(k)," dt_dci",
5301 c     &    dt_dci(k)
5302 c         write (iout,*) "k",k," dxx_XYZ",dxx_XYZ(k)," dyy_XYZ",
5303 c     &    dyy_XYZ(k)," dzz_XYZ",dzz_XYZ(k) 
5304          gscloc(k,i-1)=gscloc(k,i-1)+de_dxx*dxx_ci1(k)
5305      &    +de_dyy*dyy_ci1(k)+de_dzz*dzz_ci1(k)+de_dt*dt_dCi1(k)
5306          gscloc(k,i)=gscloc(k,i)+de_dxx*dxx_Ci(k)
5307      &    +de_dyy*dyy_Ci(k)+de_dzz*dzz_Ci(k)+de_dt*dt_dCi(k)
5308          gsclocx(k,i)=                 de_dxx*dxx_XYZ(k)
5309      &    +de_dyy*dyy_XYZ(k)+de_dzz*dzz_XYZ(k)
5310        enddo
5311 c       write(iout,*) "ENERGY GRAD = ", (gscloc(k,i-1),k=1,3),
5312 c     &  (gscloc(k,i),k=1,3),(gsclocx(k,i),k=1,3)  
5313
5314 C to check gradient call subroutine check_grad
5315
5316     1 continue
5317       enddo
5318       return
5319       end
5320 c------------------------------------------------------------------------------
5321       double precision function enesc(x,xx,yy,zz,cost2,sint2)
5322       implicit none
5323       double precision x(65),xx,yy,zz,cost2,sint2,sumene1,sumene2,
5324      & sumene3,sumene4,sumene,dsc_i,dp2_i,dscp1,dscp2,s1,s1_6,s2,s2_6
5325       sumene1= x(1)+  x(2)*xx+  x(3)*yy+  x(4)*zz+  x(5)*xx**2
5326      &   + x(6)*yy**2+  x(7)*zz**2+  x(8)*xx*zz+  x(9)*xx*yy
5327      &   + x(10)*yy*zz
5328       sumene2=  x(11) + x(12)*xx + x(13)*yy + x(14)*zz + x(15)*xx**2
5329      & + x(16)*yy**2 + x(17)*zz**2 + x(18)*xx*zz + x(19)*xx*yy
5330      & + x(20)*yy*zz
5331       sumene3=  x(21) +x(22)*xx +x(23)*yy +x(24)*zz +x(25)*xx**2
5332      &  +x(26)*yy**2 +x(27)*zz**2 +x(28)*xx*zz +x(29)*xx*yy
5333      &  +x(30)*yy*zz +x(31)*xx**3 +x(32)*yy**3 +x(33)*zz**3
5334      &  +x(34)*(xx**2)*yy +x(35)*(xx**2)*zz +x(36)*(yy**2)*xx
5335      &  +x(37)*(yy**2)*zz +x(38)*(zz**2)*xx +x(39)*(zz**2)*yy
5336      &  +x(40)*xx*yy*zz
5337       sumene4= x(41) +x(42)*xx +x(43)*yy +x(44)*zz +x(45)*xx**2
5338      &  +x(46)*yy**2 +x(47)*zz**2 +x(48)*xx*zz +x(49)*xx*yy
5339      &  +x(50)*yy*zz +x(51)*xx**3 +x(52)*yy**3 +x(53)*zz**3
5340      &  +x(54)*(xx**2)*yy +x(55)*(xx**2)*zz +x(56)*(yy**2)*xx
5341      &  +x(57)*(yy**2)*zz +x(58)*(zz**2)*xx +x(59)*(zz**2)*yy
5342      &  +x(60)*xx*yy*zz
5343       dsc_i   = 0.743d0+x(61)
5344       dp2_i   = 1.9d0+x(62)
5345       dscp1=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
5346      &          *(xx*cost2+yy*sint2))
5347       dscp2=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
5348      &          *(xx*cost2-yy*sint2))
5349       s1=(1+x(63))/(0.1d0 + dscp1)
5350       s1_6=(1+x(64))/(0.1d0 + dscp1**6)
5351       s2=(1+x(65))/(0.1d0 + dscp2)
5352       s2_6=(1+x(65))/(0.1d0 + dscp2**6)
5353       sumene = ( sumene3*sint2 + sumene1)*(s1+s1_6)
5354      & + (sumene4*cost2 +sumene2)*(s2+s2_6)
5355       enesc=sumene
5356       return
5357       end
5358 #endif
5359 c------------------------------------------------------------------------------
5360       subroutine gcont(rij,r0ij,eps0ij,delta,fcont,fprimcont)
5361 C
5362 C This procedure calculates two-body contact function g(rij) and its derivative:
5363 C
5364 C           eps0ij                                     !       x < -1
5365 C g(rij) =  esp0ij*(-0.9375*x+0.625*x**3-0.1875*x**5)  ! -1 =< x =< 1
5366 C            0                                         !       x > 1
5367 C
5368 C where x=(rij-r0ij)/delta
5369 C
5370 C rij - interbody distance, r0ij - contact distance, eps0ij - contact energy
5371 C
5372       implicit none
5373       double precision rij,r0ij,eps0ij,fcont,fprimcont
5374       double precision x,x2,x4,delta
5375 c     delta=0.02D0*r0ij
5376 c      delta=0.2D0*r0ij
5377       x=(rij-r0ij)/delta
5378       if (x.lt.-1.0D0) then
5379         fcont=eps0ij
5380         fprimcont=0.0D0
5381       else if (x.le.1.0D0) then  
5382         x2=x*x
5383         x4=x2*x2
5384         fcont=eps0ij*(x*(-0.9375D0+0.6250D0*x2-0.1875D0*x4)+0.5D0)
5385         fprimcont=eps0ij * (-0.9375D0+1.8750D0*x2-0.9375D0*x4)/delta
5386       else
5387         fcont=0.0D0
5388         fprimcont=0.0D0
5389       endif
5390       return
5391       end
5392 c------------------------------------------------------------------------------
5393       subroutine splinthet(theti,delta,ss,ssder)
5394       implicit real*8 (a-h,o-z)
5395       include 'DIMENSIONS'
5396       include 'COMMON.VAR'
5397       include 'COMMON.GEO'
5398       thetup=pi-delta
5399       thetlow=delta
5400       if (theti.gt.pipol) then
5401         call gcont(theti,thetup,1.0d0,delta,ss,ssder)
5402       else
5403         call gcont(-theti,-thetlow,1.0d0,delta,ss,ssder)
5404         ssder=-ssder
5405       endif
5406       return
5407       end
5408 c------------------------------------------------------------------------------
5409       subroutine spline1(x,x0,delta,f0,f1,fprim0,f,fprim)
5410       implicit none
5411       double precision x,x0,delta,f0,f1,fprim0,f,fprim
5412       double precision ksi,ksi2,ksi3,a1,a2,a3
5413       a1=fprim0*delta/(f1-f0)
5414       a2=3.0d0-2.0d0*a1
5415       a3=a1-2.0d0
5416       ksi=(x-x0)/delta
5417       ksi2=ksi*ksi
5418       ksi3=ksi2*ksi  
5419       f=f0+(f1-f0)*ksi*(a1+ksi*(a2+a3*ksi))
5420       fprim=(f1-f0)/delta*(a1+ksi*(2*a2+3*ksi*a3))
5421       return
5422       end
5423 c------------------------------------------------------------------------------
5424       subroutine spline2(x,x0,delta,f0x,f1x,fprim0x,fx)
5425       implicit none
5426       double precision x,x0,delta,f0x,f1x,fprim0x,fx
5427       double precision ksi,ksi2,ksi3,a1,a2,a3
5428       ksi=(x-x0)/delta  
5429       ksi2=ksi*ksi
5430       ksi3=ksi2*ksi
5431       a1=fprim0x*delta
5432       a2=3*(f1x-f0x)-2*fprim0x*delta
5433       a3=fprim0x*delta-2*(f1x-f0x)
5434       fx=f0x+a1*ksi+a2*ksi2+a3*ksi3
5435       return
5436       end
5437 C-----------------------------------------------------------------------------
5438 #ifdef CRYST_TOR
5439 C-----------------------------------------------------------------------------
5440       subroutine etor(etors,edihcnstr)
5441       implicit real*8 (a-h,o-z)
5442       include 'DIMENSIONS'
5443       include 'COMMON.VAR'
5444       include 'COMMON.GEO'
5445       include 'COMMON.LOCAL'
5446       include 'COMMON.TORSION'
5447       include 'COMMON.INTERACT'
5448       include 'COMMON.DERIV'
5449       include 'COMMON.CHAIN'
5450       include 'COMMON.NAMES'
5451       include 'COMMON.IOUNITS'
5452       include 'COMMON.FFIELD'
5453       include 'COMMON.TORCNSTR'
5454       include 'COMMON.CONTROL'
5455       logical lprn
5456 C Set lprn=.true. for debugging
5457       lprn=.false.
5458 c      lprn=.true.
5459       etors=0.0D0
5460       do i=iphi_start,iphi_end
5461       etors_ii=0.0D0
5462         if (itype(i-2).eq.ntyp1.or. itype(i-1).eq.ntyp1
5463      &      .or. itype(i).eq.ntyp1) cycle
5464         itori=itortyp(itype(i-2))
5465         itori1=itortyp(itype(i-1))
5466         phii=phi(i)
5467         gloci=0.0D0
5468 C Proline-Proline pair is a special case...
5469         if (itori.eq.3 .and. itori1.eq.3) then
5470           if (phii.gt.-dwapi3) then
5471             cosphi=dcos(3*phii)
5472             fac=1.0D0/(1.0D0-cosphi)
5473             etorsi=v1(1,3,3)*fac
5474             etorsi=etorsi+etorsi
5475             etors=etors+etorsi-v1(1,3,3)
5476             if (energy_dec) etors_ii=etors_ii+etorsi-v1(1,3,3)      
5477             gloci=gloci-3*fac*etorsi*dsin(3*phii)
5478           endif
5479           do j=1,3
5480             v1ij=v1(j+1,itori,itori1)
5481             v2ij=v2(j+1,itori,itori1)
5482             cosphi=dcos(j*phii)
5483             sinphi=dsin(j*phii)
5484             etors=etors+v1ij*cosphi+v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
5485             if (energy_dec) etors_ii=etors_ii+
5486      &                              v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
5487             gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
5488           enddo
5489         else 
5490           do j=1,nterm_old
5491             v1ij=v1(j,itori,itori1)
5492             v2ij=v2(j,itori,itori1)
5493             cosphi=dcos(j*phii)
5494             sinphi=dsin(j*phii)
5495             etors=etors+v1ij*cosphi+v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
5496             if (energy_dec) etors_ii=etors_ii+
5497      &                  v1ij*cosphi+v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
5498             gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
5499           enddo
5500         endif
5501         if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
5502              'etor',i,etors_ii
5503         if (lprn)
5504      &  write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
5505      &  restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,
5506      &  (v1(j,itori,itori1),j=1,6),(v2(j,itori,itori1),j=1,6)
5507         gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
5508 c       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
5509       enddo
5510 ! 6/20/98 - dihedral angle constraints
5511       edihcnstr=0.0d0
5512       do i=1,ndih_constr
5513         itori=idih_constr(i)
5514         phii=phi(itori)
5515         difi=phii-phi0(i)
5516         if (difi.gt.drange(i)) then
5517           difi=difi-drange(i)
5518           edihcnstr=edihcnstr+0.25d0*ftors*difi**4
5519           gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
5520         else if (difi.lt.-drange(i)) then
5521           difi=difi+drange(i)
5522           edihcnstr=edihcnstr+0.25d0*ftors*difi**4
5523           gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
5524         endif
5525 !        write (iout,'(2i5,2f8.3,2e14.5)') i,itori,rad2deg*phii,
5526 !     &    rad2deg*difi,0.25d0*ftors*difi**4,gloc(itori-3,icg)
5527       enddo
5528 !      write (iout,*) 'edihcnstr',edihcnstr
5529       return
5530       end
5531 c------------------------------------------------------------------------------
5532       subroutine etor_d(etors_d)
5533       etors_d=0.0d0
5534       return
5535       end
5536 c----------------------------------------------------------------------------
5537 #else
5538       subroutine etor(etors,edihcnstr)
5539       implicit real*8 (a-h,o-z)
5540       include 'DIMENSIONS'
5541       include 'COMMON.VAR'
5542       include 'COMMON.GEO'
5543       include 'COMMON.LOCAL'
5544       include 'COMMON.TORSION'
5545       include 'COMMON.INTERACT'
5546       include 'COMMON.DERIV'
5547       include 'COMMON.CHAIN'
5548       include 'COMMON.NAMES'
5549       include 'COMMON.IOUNITS'
5550       include 'COMMON.FFIELD'
5551       include 'COMMON.TORCNSTR'
5552       include 'COMMON.CONTROL'
5553       logical lprn
5554 C Set lprn=.true. for debugging
5555       lprn=.false.
5556 c     lprn=.true.
5557       etors=0.0D0
5558       do i=iphi_start,iphi_end
5559         if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1 
5560      &       .or. itype(i).eq.ntyp1) cycle
5561         etors_ii=0.0D0
5562          if (iabs(itype(i)).eq.20) then
5563          iblock=2
5564          else
5565          iblock=1
5566          endif
5567         itori=itortyp(itype(i-2))
5568         itori1=itortyp(itype(i-1))
5569         phii=phi(i)
5570         gloci=0.0D0
5571 C Regular cosine and sine terms
5572         do j=1,nterm(itori,itori1,iblock)
5573           v1ij=v1(j,itori,itori1,iblock)
5574           v2ij=v2(j,itori,itori1,iblock)
5575           cosphi=dcos(j*phii)
5576           sinphi=dsin(j*phii)
5577           etors=etors+v1ij*cosphi+v2ij*sinphi
5578           if (energy_dec) etors_ii=etors_ii+
5579      &                v1ij*cosphi+v2ij*sinphi
5580           gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
5581         enddo
5582 C Lorentz terms
5583 C                         v1
5584 C  E = SUM ----------------------------------- - v1
5585 C          [v2 cos(phi/2)+v3 sin(phi/2)]^2 + 1
5586 C
5587         cosphi=dcos(0.5d0*phii)
5588         sinphi=dsin(0.5d0*phii)
5589         do j=1,nlor(itori,itori1,iblock)
5590           vl1ij=vlor1(j,itori,itori1)
5591           vl2ij=vlor2(j,itori,itori1)
5592           vl3ij=vlor3(j,itori,itori1)
5593           pom=vl2ij*cosphi+vl3ij*sinphi
5594           pom1=1.0d0/(pom*pom+1.0d0)
5595           etors=etors+vl1ij*pom1
5596           if (energy_dec) etors_ii=etors_ii+
5597      &                vl1ij*pom1
5598           pom=-pom*pom1*pom1
5599           gloci=gloci+vl1ij*(vl3ij*cosphi-vl2ij*sinphi)*pom
5600         enddo
5601 C Subtract the constant term
5602         etors=etors-v0(itori,itori1,iblock)
5603           if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
5604      &         'etor',i,etors_ii-v0(itori,itori1,iblock)
5605         if (lprn)
5606      &  write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
5607      &  restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,
5608      &  (v1(j,itori,itori1,iblock),j=1,6),
5609      &  (v2(j,itori,itori1,iblock),j=1,6)
5610         gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
5611 c       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
5612       enddo
5613 ! 6/20/98 - dihedral angle constraints
5614       edihcnstr=0.0d0
5615 c      do i=1,ndih_constr
5616       do i=idihconstr_start,idihconstr_end
5617         itori=idih_constr(i)
5618         phii=phi(itori)
5619         difi=pinorm(phii-phi0(i))
5620         if (difi.gt.drange(i)) then
5621           difi=difi-drange(i)
5622           edihcnstr=edihcnstr+0.25d0*ftors*difi**4
5623           gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
5624         else if (difi.lt.-drange(i)) then
5625           difi=difi+drange(i)
5626           edihcnstr=edihcnstr+0.25d0*ftors*difi**4
5627           gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
5628         else
5629           difi=0.0
5630         endif
5631 cd        write (iout,'(2i5,4f8.3,2e14.5)') i,itori,rad2deg*phii,
5632 cd     &    rad2deg*phi0(i),  rad2deg*drange(i),
5633 cd     &    rad2deg*difi,0.25d0*ftors*difi**4,gloc(itori-3,icg)
5634       enddo
5635 cd       write (iout,*) 'edihcnstr',edihcnstr
5636       return
5637       end
5638 c----------------------------------------------------------------------------
5639       subroutine etor_d(etors_d)
5640 C 6/23/01 Compute double torsional energy
5641       implicit real*8 (a-h,o-z)
5642       include 'DIMENSIONS'
5643       include 'COMMON.VAR'
5644       include 'COMMON.GEO'
5645       include 'COMMON.LOCAL'
5646       include 'COMMON.TORSION'
5647       include 'COMMON.INTERACT'
5648       include 'COMMON.DERIV'
5649       include 'COMMON.CHAIN'
5650       include 'COMMON.NAMES'
5651       include 'COMMON.IOUNITS'
5652       include 'COMMON.FFIELD'
5653       include 'COMMON.TORCNSTR'
5654       logical lprn
5655 C Set lprn=.true. for debugging
5656       lprn=.false.
5657 c     lprn=.true.
5658       etors_d=0.0D0
5659 c      write(iout,*) "a tu??"
5660       do i=iphid_start,iphid_end
5661         if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1
5662      &      .or. itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
5663         itori=itortyp(itype(i-2))
5664         itori1=itortyp(itype(i-1))
5665         itori2=itortyp(itype(i))
5666         phii=phi(i)
5667         phii1=phi(i+1)
5668         gloci1=0.0D0
5669         gloci2=0.0D0
5670         iblock=1
5671         if (iabs(itype(i+1)).eq.20) iblock=2
5672
5673 C Regular cosine and sine terms
5674         do j=1,ntermd_1(itori,itori1,itori2,iblock)
5675           v1cij=v1c(1,j,itori,itori1,itori2,iblock)
5676           v1sij=v1s(1,j,itori,itori1,itori2,iblock)
5677           v2cij=v1c(2,j,itori,itori1,itori2,iblock)
5678           v2sij=v1s(2,j,itori,itori1,itori2,iblock)
5679           cosphi1=dcos(j*phii)
5680           sinphi1=dsin(j*phii)
5681           cosphi2=dcos(j*phii1)
5682           sinphi2=dsin(j*phii1)
5683           etors_d=etors_d+v1cij*cosphi1+v1sij*sinphi1+
5684      &     v2cij*cosphi2+v2sij*sinphi2
5685           gloci1=gloci1+j*(v1sij*cosphi1-v1cij*sinphi1)
5686           gloci2=gloci2+j*(v2sij*cosphi2-v2cij*sinphi2)
5687         enddo
5688         do k=2,ntermd_2(itori,itori1,itori2,iblock)
5689           do l=1,k-1
5690             v1cdij = v2c(k,l,itori,itori1,itori2,iblock)
5691             v2cdij = v2c(l,k,itori,itori1,itori2,iblock)
5692             v1sdij = v2s(k,l,itori,itori1,itori2,iblock)
5693             v2sdij = v2s(l,k,itori,itori1,itori2,iblock)
5694             cosphi1p2=dcos(l*phii+(k-l)*phii1)
5695             cosphi1m2=dcos(l*phii-(k-l)*phii1)
5696             sinphi1p2=dsin(l*phii+(k-l)*phii1)
5697             sinphi1m2=dsin(l*phii-(k-l)*phii1)
5698             etors_d=etors_d+v1cdij*cosphi1p2+v2cdij*cosphi1m2+
5699      &        v1sdij*sinphi1p2+v2sdij*sinphi1m2
5700             gloci1=gloci1+l*(v1sdij*cosphi1p2+v2sdij*cosphi1m2
5701      &        -v1cdij*sinphi1p2-v2cdij*sinphi1m2)
5702             gloci2=gloci2+(k-l)*(v1sdij*cosphi1p2-v2sdij*cosphi1m2
5703      &        -v1cdij*sinphi1p2+v2cdij*sinphi1m2) 
5704           enddo
5705         enddo
5706         gloc(i-3,icg)=gloc(i-3,icg)+wtor_d*gloci1
5707         gloc(i-2,icg)=gloc(i-2,icg)+wtor_d*gloci2
5708       enddo
5709       return
5710       end
5711 #endif
5712 c------------------------------------------------------------------------------
5713       subroutine eback_sc_corr(esccor)
5714 c 7/21/2007 Correlations between the backbone-local and side-chain-local
5715 c        conformational states; temporarily implemented as differences
5716 c        between UNRES torsional potentials (dependent on three types of
5717 c        residues) and the torsional potentials dependent on all 20 types
5718 c        of residues computed from AM1  energy surfaces of terminally-blocked
5719 c        amino-acid residues.
5720       implicit real*8 (a-h,o-z)
5721       include 'DIMENSIONS'
5722       include 'COMMON.VAR'
5723       include 'COMMON.GEO'
5724       include 'COMMON.LOCAL'
5725       include 'COMMON.TORSION'
5726       include 'COMMON.SCCOR'
5727       include 'COMMON.INTERACT'
5728       include 'COMMON.DERIV'
5729       include 'COMMON.CHAIN'
5730       include 'COMMON.NAMES'
5731       include 'COMMON.IOUNITS'
5732       include 'COMMON.FFIELD'
5733       include 'COMMON.CONTROL'
5734       logical lprn
5735 C Set lprn=.true. for debugging
5736       lprn=.false.
5737 c      lprn=.true.
5738 c      write (iout,*) "EBACK_SC_COR",itau_start,itau_end
5739       esccor=0.0D0
5740       do i=itau_start,itau_end
5741         esccor_ii=0.0D0
5742         isccori=isccortyp(itype(i-2))
5743         isccori1=isccortyp(itype(i-1))
5744 c      write (iout,*) "EBACK_SC_COR",i,nterm_sccor(isccori,isccori1)
5745         phii=phi(i)
5746         do intertyp=1,3 !intertyp
5747 cc Added 09 May 2012 (Adasko)
5748 cc  Intertyp means interaction type of backbone mainchain correlation: 
5749 c   1 = SC...Ca...Ca...Ca
5750 c   2 = Ca...Ca...Ca...SC
5751 c   3 = SC...Ca...Ca...SCi
5752         gloci=0.0D0
5753         if (((intertyp.eq.3).and.((itype(i-2).eq.10).or.
5754      &      (itype(i-1).eq.10).or.(itype(i-2).eq.ntyp1).or.
5755      &      (itype(i-1).eq.ntyp1)))
5756      &    .or. ((intertyp.eq.1).and.((itype(i-2).eq.10)
5757      &     .or.(itype(i-2).eq.ntyp1).or.(itype(i-1).eq.ntyp1)
5758      &     .or.(itype(i).eq.ntyp1)))
5759      &    .or.((intertyp.eq.2).and.((itype(i-1).eq.10).or.
5760      &      (itype(i-1).eq.ntyp1).or.(itype(i-2).eq.ntyp1).or.
5761      &      (itype(i-3).eq.ntyp1)))) cycle
5762         if ((intertyp.eq.2).and.(i.eq.4).and.(itype(1).eq.ntyp1)) cycle
5763         if ((intertyp.eq.1).and.(i.eq.nres).and.(itype(nres).eq.ntyp1))
5764      & cycle
5765        do j=1,nterm_sccor(isccori,isccori1)
5766           v1ij=v1sccor(j,intertyp,isccori,isccori1)
5767           v2ij=v2sccor(j,intertyp,isccori,isccori1)
5768           cosphi=dcos(j*tauangle(intertyp,i))
5769           sinphi=dsin(j*tauangle(intertyp,i))
5770           esccor=esccor+v1ij*cosphi+v2ij*sinphi
5771           gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
5772         enddo
5773 c      write (iout,*) "EBACK_SC_COR",i,esccor,intertyp
5774         gloc_sc(intertyp,i-3,icg)=gloc_sc(intertyp,i-3,icg)+wsccor*gloci
5775         if (lprn)
5776      &  write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
5777      &  restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,isccori,isccori1,
5778      &  (v1sccor(j,intertyp,isccori,isccori1),j=1,6)
5779      & ,(v2sccor(j,intertyp,isccori,isccori1),j=1,6)
5780         gsccor_loc(i-3)=gsccor_loc(i-3)+gloci
5781        enddo !intertyp
5782       enddo
5783
5784       return
5785       end
5786 c----------------------------------------------------------------------------
5787       subroutine multibody(ecorr)
5788 C This subroutine calculates multi-body contributions to energy following
5789 C the idea of Skolnick et al. If side chains I and J make a contact and
5790 C at the same time side chains I+1 and J+1 make a contact, an extra 
5791 C contribution equal to sqrt(eps(i,j)*eps(i+1,j+1)) is added.
5792       implicit real*8 (a-h,o-z)
5793       include 'DIMENSIONS'
5794       include 'COMMON.IOUNITS'
5795       include 'COMMON.DERIV'
5796       include 'COMMON.INTERACT'
5797       include 'COMMON.CONTACTS'
5798       double precision gx(3),gx1(3)
5799       logical lprn
5800
5801 C Set lprn=.true. for debugging
5802       lprn=.false.
5803
5804       if (lprn) then
5805         write (iout,'(a)') 'Contact function values:'
5806         do i=nnt,nct-2
5807           write (iout,'(i2,20(1x,i2,f10.5))') 
5808      &        i,(jcont(j,i),facont(j,i),j=1,num_cont(i))
5809         enddo
5810       endif
5811       ecorr=0.0D0
5812       do i=nnt,nct
5813         do j=1,3
5814           gradcorr(j,i)=0.0D0
5815           gradxorr(j,i)=0.0D0
5816         enddo
5817       enddo
5818       do i=nnt,nct-2
5819
5820         DO ISHIFT = 3,4
5821
5822         i1=i+ishift
5823         num_conti=num_cont(i)
5824         num_conti1=num_cont(i1)
5825         do jj=1,num_conti
5826           j=jcont(jj,i)
5827           do kk=1,num_conti1
5828             j1=jcont(kk,i1)
5829             if (j1.eq.j+ishift .or. j1.eq.j-ishift) then
5830 cd          write(iout,*)'i=',i,' j=',j,' i1=',i1,' j1=',j1,
5831 cd   &                   ' ishift=',ishift
5832 C Contacts I--J and I+ISHIFT--J+-ISHIFT1 occur simultaneously. 
5833 C The system gains extra energy.
5834               ecorr=ecorr+esccorr(i,j,i1,j1,jj,kk)
5835             endif   ! j1==j+-ishift
5836           enddo     ! kk  
5837         enddo       ! jj
5838
5839         ENDDO ! ISHIFT
5840
5841       enddo         ! i
5842       return
5843       end
5844 c------------------------------------------------------------------------------
5845       double precision function esccorr(i,j,k,l,jj,kk)
5846       implicit real*8 (a-h,o-z)
5847       include 'DIMENSIONS'
5848       include 'COMMON.IOUNITS'
5849       include 'COMMON.DERIV'
5850       include 'COMMON.INTERACT'
5851       include 'COMMON.CONTACTS'
5852       double precision gx(3),gx1(3)
5853       logical lprn
5854       lprn=.false.
5855       eij=facont(jj,i)
5856       ekl=facont(kk,k)
5857 cd    write (iout,'(4i5,3f10.5)') i,j,k,l,eij,ekl,-eij*ekl
5858 C Calculate the multi-body contribution to energy.
5859 C Calculate multi-body contributions to the gradient.
5860 cd    write (iout,'(2(2i3,3f10.5))')i,j,(gacont(m,jj,i),m=1,3),
5861 cd   & k,l,(gacont(m,kk,k),m=1,3)
5862       do m=1,3
5863         gx(m) =ekl*gacont(m,jj,i)
5864         gx1(m)=eij*gacont(m,kk,k)
5865         gradxorr(m,i)=gradxorr(m,i)-gx(m)
5866         gradxorr(m,j)=gradxorr(m,j)+gx(m)
5867         gradxorr(m,k)=gradxorr(m,k)-gx1(m)
5868         gradxorr(m,l)=gradxorr(m,l)+gx1(m)
5869       enddo
5870       do m=i,j-1
5871         do ll=1,3
5872           gradcorr(ll,m)=gradcorr(ll,m)+gx(ll)
5873         enddo
5874       enddo
5875       do m=k,l-1
5876         do ll=1,3
5877           gradcorr(ll,m)=gradcorr(ll,m)+gx1(ll)
5878         enddo
5879       enddo 
5880       esccorr=-eij*ekl
5881       return
5882       end
5883 c------------------------------------------------------------------------------
5884       subroutine multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
5885 C This subroutine calculates multi-body contributions to hydrogen-bonding 
5886       implicit real*8 (a-h,o-z)
5887       include 'DIMENSIONS'
5888       include 'COMMON.IOUNITS'
5889 #ifdef MPI
5890       include "mpif.h"
5891       parameter (max_cont=maxconts)
5892       parameter (max_dim=26)
5893       integer source,CorrelType,CorrelID,CorrelType1,CorrelID1,Error
5894       double precision zapas(max_dim,maxconts,max_fg_procs),
5895      &  zapas_recv(max_dim,maxconts,max_fg_procs)
5896       common /przechowalnia/ zapas
5897       integer status(MPI_STATUS_SIZE),req(maxconts*2),
5898      &  status_array(MPI_STATUS_SIZE,maxconts*2)
5899 #endif
5900       include 'COMMON.SETUP'
5901       include 'COMMON.FFIELD'
5902       include 'COMMON.DERIV'
5903       include 'COMMON.INTERACT'
5904       include 'COMMON.CONTACTS'
5905       include 'COMMON.CONTROL'
5906       include 'COMMON.LOCAL'
5907       double precision gx(3),gx1(3),time00
5908       logical lprn,ldone
5909
5910 C Set lprn=.true. for debugging
5911       lprn=.false.
5912 #ifdef MPI
5913       n_corr=0
5914       n_corr1=0
5915       if (nfgtasks.le.1) goto 30
5916       if (lprn) then
5917         write (iout,'(a)') 'Contact function values before RECEIVE:'
5918         do i=nnt,nct-2
5919           write (iout,'(2i3,50(1x,i2,f5.2))') 
5920      &    i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
5921      &    j=1,num_cont_hb(i))
5922         enddo
5923       endif
5924       call flush(iout)
5925       do i=1,ntask_cont_from
5926         ncont_recv(i)=0
5927       enddo
5928       do i=1,ntask_cont_to
5929         ncont_sent(i)=0
5930       enddo
5931 c      write (iout,*) "ntask_cont_from",ntask_cont_from," ntask_cont_to",
5932 c     & ntask_cont_to
5933 C Make the list of contacts to send to send to other procesors
5934 c      write (iout,*) "limits",max0(iturn4_end-1,iatel_s),iturn3_end
5935 c      call flush(iout)
5936       do i=iturn3_start,iturn3_end
5937 c        write (iout,*) "make contact list turn3",i," num_cont",
5938 c     &    num_cont_hb(i)
5939         call add_hb_contact(i,i+2,iturn3_sent_local(1,i))
5940       enddo
5941       do i=iturn4_start,iturn4_end
5942 c        write (iout,*) "make contact list turn4",i," num_cont",
5943 c     &   num_cont_hb(i)
5944         call add_hb_contact(i,i+3,iturn4_sent_local(1,i))
5945       enddo
5946       do ii=1,nat_sent
5947         i=iat_sent(ii)
5948 c        write (iout,*) "make contact list longrange",i,ii," num_cont",
5949 c     &    num_cont_hb(i)
5950         do j=1,num_cont_hb(i)
5951         do k=1,4
5952           jjc=jcont_hb(j,i)
5953           iproc=iint_sent_local(k,jjc,ii)
5954 c          write (iout,*) "i",i," j",j," k",k," jjc",jjc," iproc",iproc
5955           if (iproc.gt.0) then
5956             ncont_sent(iproc)=ncont_sent(iproc)+1
5957             nn=ncont_sent(iproc)
5958             zapas(1,nn,iproc)=i
5959             zapas(2,nn,iproc)=jjc
5960             zapas(3,nn,iproc)=facont_hb(j,i)
5961             zapas(4,nn,iproc)=ees0p(j,i)
5962             zapas(5,nn,iproc)=ees0m(j,i)
5963             zapas(6,nn,iproc)=gacont_hbr(1,j,i)
5964             zapas(7,nn,iproc)=gacont_hbr(2,j,i)
5965             zapas(8,nn,iproc)=gacont_hbr(3,j,i)
5966             zapas(9,nn,iproc)=gacontm_hb1(1,j,i)
5967             zapas(10,nn,iproc)=gacontm_hb1(2,j,i)
5968             zapas(11,nn,iproc)=gacontm_hb1(3,j,i)
5969             zapas(12,nn,iproc)=gacontp_hb1(1,j,i)
5970             zapas(13,nn,iproc)=gacontp_hb1(2,j,i)
5971             zapas(14,nn,iproc)=gacontp_hb1(3,j,i)
5972             zapas(15,nn,iproc)=gacontm_hb2(1,j,i)
5973             zapas(16,nn,iproc)=gacontm_hb2(2,j,i)
5974             zapas(17,nn,iproc)=gacontm_hb2(3,j,i)
5975             zapas(18,nn,iproc)=gacontp_hb2(1,j,i)
5976             zapas(19,nn,iproc)=gacontp_hb2(2,j,i)
5977             zapas(20,nn,iproc)=gacontp_hb2(3,j,i)
5978             zapas(21,nn,iproc)=gacontm_hb3(1,j,i)
5979             zapas(22,nn,iproc)=gacontm_hb3(2,j,i)
5980             zapas(23,nn,iproc)=gacontm_hb3(3,j,i)
5981             zapas(24,nn,iproc)=gacontp_hb3(1,j,i)
5982             zapas(25,nn,iproc)=gacontp_hb3(2,j,i)
5983             zapas(26,nn,iproc)=gacontp_hb3(3,j,i)
5984           endif
5985         enddo
5986         enddo
5987       enddo
5988       if (lprn) then
5989       write (iout,*) 
5990      &  "Numbers of contacts to be sent to other processors",
5991      &  (ncont_sent(i),i=1,ntask_cont_to)
5992       write (iout,*) "Contacts sent"
5993       do ii=1,ntask_cont_to
5994         nn=ncont_sent(ii)
5995         iproc=itask_cont_to(ii)
5996         write (iout,*) nn," contacts to processor",iproc,
5997      &   " of CONT_TO_COMM group"
5998         do i=1,nn
5999           write(iout,'(2f5.0,4f10.5)')(zapas(j,i,ii),j=1,5)
6000         enddo
6001       enddo
6002       call flush(iout)
6003       endif
6004       CorrelType=477
6005       CorrelID=fg_rank+1
6006       CorrelType1=478
6007       CorrelID1=nfgtasks+fg_rank+1
6008       ireq=0
6009 C Receive the numbers of needed contacts from other processors 
6010       do ii=1,ntask_cont_from
6011         iproc=itask_cont_from(ii)
6012         ireq=ireq+1
6013         call MPI_Irecv(ncont_recv(ii),1,MPI_INTEGER,iproc,CorrelType,
6014      &    FG_COMM,req(ireq),IERR)
6015       enddo
6016 c      write (iout,*) "IRECV ended"
6017 c      call flush(iout)
6018 C Send the number of contacts needed by other processors
6019       do ii=1,ntask_cont_to
6020         iproc=itask_cont_to(ii)
6021         ireq=ireq+1
6022         call MPI_Isend(ncont_sent(ii),1,MPI_INTEGER,iproc,CorrelType,
6023      &    FG_COMM,req(ireq),IERR)
6024       enddo
6025 c      write (iout,*) "ISEND ended"
6026 c      write (iout,*) "number of requests (nn)",ireq
6027       call flush(iout)
6028       if (ireq.gt.0) 
6029      &  call MPI_Waitall(ireq,req,status_array,ierr)
6030 c      write (iout,*) 
6031 c     &  "Numbers of contacts to be received from other processors",
6032 c     &  (ncont_recv(i),i=1,ntask_cont_from)
6033 c      call flush(iout)
6034 C Receive contacts
6035       ireq=0
6036       do ii=1,ntask_cont_from
6037         iproc=itask_cont_from(ii)
6038         nn=ncont_recv(ii)
6039 c        write (iout,*) "Receiving",nn," contacts from processor",iproc,
6040 c     &   " of CONT_TO_COMM group"
6041         call flush(iout)
6042         if (nn.gt.0) then
6043           ireq=ireq+1
6044           call MPI_Irecv(zapas_recv(1,1,ii),nn*max_dim,
6045      &    MPI_DOUBLE_PRECISION,iproc,CorrelType1,FG_COMM,req(ireq),IERR)
6046 c          write (iout,*) "ireq,req",ireq,req(ireq)
6047         endif
6048       enddo
6049 C Send the contacts to processors that need them
6050       do ii=1,ntask_cont_to
6051         iproc=itask_cont_to(ii)
6052         nn=ncont_sent(ii)
6053 c        write (iout,*) nn," contacts to processor",iproc,
6054 c     &   " of CONT_TO_COMM group"
6055         if (nn.gt.0) then
6056           ireq=ireq+1 
6057           call MPI_Isend(zapas(1,1,ii),nn*max_dim,MPI_DOUBLE_PRECISION,
6058      &      iproc,CorrelType1,FG_COMM,req(ireq),IERR)
6059 c          write (iout,*) "ireq,req",ireq,req(ireq)
6060 c          do i=1,nn
6061 c            write(iout,'(2f5.0,4f10.5)')(zapas(j,i,ii),j=1,5)
6062 c          enddo
6063         endif  
6064       enddo
6065 c      write (iout,*) "number of requests (contacts)",ireq
6066 c      write (iout,*) "req",(req(i),i=1,4)
6067 c      call flush(iout)
6068       if (ireq.gt.0) 
6069      & call MPI_Waitall(ireq,req,status_array,ierr)
6070       do iii=1,ntask_cont_from
6071         iproc=itask_cont_from(iii)
6072         nn=ncont_recv(iii)
6073         if (lprn) then
6074         write (iout,*) "Received",nn," contacts from processor",iproc,
6075      &   " of CONT_FROM_COMM group"
6076         call flush(iout)
6077         do i=1,nn
6078           write(iout,'(2f5.0,4f10.5)')(zapas_recv(j,i,iii),j=1,5)
6079         enddo
6080         call flush(iout)
6081         endif
6082         do i=1,nn
6083           ii=zapas_recv(1,i,iii)
6084 c Flag the received contacts to prevent double-counting
6085           jj=-zapas_recv(2,i,iii)
6086 c          write (iout,*) "iii",iii," i",i," ii",ii," jj",jj
6087 c          call flush(iout)
6088           nnn=num_cont_hb(ii)+1
6089           num_cont_hb(ii)=nnn
6090           jcont_hb(nnn,ii)=jj
6091           facont_hb(nnn,ii)=zapas_recv(3,i,iii)
6092           ees0p(nnn,ii)=zapas_recv(4,i,iii)
6093           ees0m(nnn,ii)=zapas_recv(5,i,iii)
6094           gacont_hbr(1,nnn,ii)=zapas_recv(6,i,iii)
6095           gacont_hbr(2,nnn,ii)=zapas_recv(7,i,iii)
6096           gacont_hbr(3,nnn,ii)=zapas_recv(8,i,iii)
6097           gacontm_hb1(1,nnn,ii)=zapas_recv(9,i,iii)
6098           gacontm_hb1(2,nnn,ii)=zapas_recv(10,i,iii)
6099           gacontm_hb1(3,nnn,ii)=zapas_recv(11,i,iii)
6100           gacontp_hb1(1,nnn,ii)=zapas_recv(12,i,iii)
6101           gacontp_hb1(2,nnn,ii)=zapas_recv(13,i,iii)
6102           gacontp_hb1(3,nnn,ii)=zapas_recv(14,i,iii)
6103           gacontm_hb2(1,nnn,ii)=zapas_recv(15,i,iii)
6104           gacontm_hb2(2,nnn,ii)=zapas_recv(16,i,iii)
6105           gacontm_hb2(3,nnn,ii)=zapas_recv(17,i,iii)
6106           gacontp_hb2(1,nnn,ii)=zapas_recv(18,i,iii)
6107           gacontp_hb2(2,nnn,ii)=zapas_recv(19,i,iii)
6108           gacontp_hb2(3,nnn,ii)=zapas_recv(20,i,iii)
6109           gacontm_hb3(1,nnn,ii)=zapas_recv(21,i,iii)
6110           gacontm_hb3(2,nnn,ii)=zapas_recv(22,i,iii)
6111           gacontm_hb3(3,nnn,ii)=zapas_recv(23,i,iii)
6112           gacontp_hb3(1,nnn,ii)=zapas_recv(24,i,iii)
6113           gacontp_hb3(2,nnn,ii)=zapas_recv(25,i,iii)
6114           gacontp_hb3(3,nnn,ii)=zapas_recv(26,i,iii)
6115         enddo
6116       enddo
6117       call flush(iout)
6118       if (lprn) then
6119         write (iout,'(a)') 'Contact function values after receive:'
6120         do i=nnt,nct-2
6121           write (iout,'(2i3,50(1x,i3,f5.2))') 
6122      &    i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
6123      &    j=1,num_cont_hb(i))
6124         enddo
6125         call flush(iout)
6126       endif
6127    30 continue
6128 #endif
6129       if (lprn) then
6130         write (iout,'(a)') 'Contact function values:'
6131         do i=nnt,nct-2
6132           write (iout,'(2i3,50(1x,i3,f5.2))') 
6133      &    i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
6134      &    j=1,num_cont_hb(i))
6135         enddo
6136       endif
6137       ecorr=0.0D0
6138 C Remove the loop below after debugging !!!
6139       do i=nnt,nct
6140         do j=1,3
6141           gradcorr(j,i)=0.0D0
6142           gradxorr(j,i)=0.0D0
6143         enddo
6144       enddo
6145 C Calculate the local-electrostatic correlation terms
6146       do i=min0(iatel_s,iturn4_start),max0(iatel_e,iturn3_end)
6147         i1=i+1
6148         num_conti=num_cont_hb(i)
6149         num_conti1=num_cont_hb(i+1)
6150         do jj=1,num_conti
6151           j=jcont_hb(jj,i)
6152           jp=iabs(j)
6153           do kk=1,num_conti1
6154             j1=jcont_hb(kk,i1)
6155             jp1=iabs(j1)
6156 c            write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
6157 c     &         ' jj=',jj,' kk=',kk
6158             if ((j.gt.0 .and. j1.gt.0 .or. j.gt.0 .and. j1.lt.0 
6159      &          .or. j.lt.0 .and. j1.gt.0) .and.
6160      &         (jp1.eq.jp+1 .or. jp1.eq.jp-1)) then
6161 C Contacts I-J and (I+1)-(J+1) or (I+1)-(J-1) occur simultaneously. 
6162 C The system gains extra energy.
6163               ecorr=ecorr+ehbcorr(i,jp,i+1,jp1,jj,kk,0.72D0,0.32D0)
6164               if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
6165      &            'ecorrh',i,j,ehbcorr(i,j,i+1,j1,jj,kk,0.72D0,0.32D0)
6166               n_corr=n_corr+1
6167             else if (j1.eq.j) then
6168 C Contacts I-J and I-(J+1) occur simultaneously. 
6169 C The system loses extra energy.
6170 c             ecorr=ecorr+ehbcorr(i,j,i+1,j,jj,kk,0.60D0,-0.40D0) 
6171             endif
6172           enddo ! kk
6173           do kk=1,num_conti
6174             j1=jcont_hb(kk,i)
6175 c           write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
6176 c    &         ' jj=',jj,' kk=',kk
6177             if (j1.eq.j+1) then
6178 C Contacts I-J and (I+1)-J occur simultaneously. 
6179 C The system loses extra energy.
6180 c             ecorr=ecorr+ehbcorr(i,j,i,j+1,jj,kk,0.60D0,-0.40D0)
6181             endif ! j1==j+1
6182           enddo ! kk
6183         enddo ! jj
6184       enddo ! i
6185       return
6186       end
6187 c------------------------------------------------------------------------------
6188       subroutine add_hb_contact(ii,jj,itask)
6189       implicit real*8 (a-h,o-z)
6190       include "DIMENSIONS"
6191       include "COMMON.IOUNITS"
6192       integer max_cont
6193       integer max_dim
6194       parameter (max_cont=maxconts)
6195       parameter (max_dim=26)
6196       include "COMMON.CONTACTS"
6197       double precision zapas(max_dim,maxconts,max_fg_procs),
6198      &  zapas_recv(max_dim,maxconts,max_fg_procs)
6199       common /przechowalnia/ zapas
6200       integer i,j,ii,jj,iproc,itask(4),nn
6201 c      write (iout,*) "itask",itask
6202       do i=1,2
6203         iproc=itask(i)
6204         if (iproc.gt.0) then
6205           do j=1,num_cont_hb(ii)
6206             jjc=jcont_hb(j,ii)
6207 c            write (iout,*) "i",ii," j",jj," jjc",jjc
6208             if (jjc.eq.jj) then
6209               ncont_sent(iproc)=ncont_sent(iproc)+1
6210               nn=ncont_sent(iproc)
6211               zapas(1,nn,iproc)=ii
6212               zapas(2,nn,iproc)=jjc
6213               zapas(3,nn,iproc)=facont_hb(j,ii)
6214               zapas(4,nn,iproc)=ees0p(j,ii)
6215               zapas(5,nn,iproc)=ees0m(j,ii)
6216               zapas(6,nn,iproc)=gacont_hbr(1,j,ii)
6217               zapas(7,nn,iproc)=gacont_hbr(2,j,ii)
6218               zapas(8,nn,iproc)=gacont_hbr(3,j,ii)
6219               zapas(9,nn,iproc)=gacontm_hb1(1,j,ii)
6220               zapas(10,nn,iproc)=gacontm_hb1(2,j,ii)
6221               zapas(11,nn,iproc)=gacontm_hb1(3,j,ii)
6222               zapas(12,nn,iproc)=gacontp_hb1(1,j,ii)
6223               zapas(13,nn,iproc)=gacontp_hb1(2,j,ii)
6224               zapas(14,nn,iproc)=gacontp_hb1(3,j,ii)
6225               zapas(15,nn,iproc)=gacontm_hb2(1,j,ii)
6226               zapas(16,nn,iproc)=gacontm_hb2(2,j,ii)
6227               zapas(17,nn,iproc)=gacontm_hb2(3,j,ii)
6228               zapas(18,nn,iproc)=gacontp_hb2(1,j,ii)
6229               zapas(19,nn,iproc)=gacontp_hb2(2,j,ii)
6230               zapas(20,nn,iproc)=gacontp_hb2(3,j,ii)
6231               zapas(21,nn,iproc)=gacontm_hb3(1,j,ii)
6232               zapas(22,nn,iproc)=gacontm_hb3(2,j,ii)
6233               zapas(23,nn,iproc)=gacontm_hb3(3,j,ii)
6234               zapas(24,nn,iproc)=gacontp_hb3(1,j,ii)
6235               zapas(25,nn,iproc)=gacontp_hb3(2,j,ii)
6236               zapas(26,nn,iproc)=gacontp_hb3(3,j,ii)
6237               exit
6238             endif
6239           enddo
6240         endif
6241       enddo
6242       return
6243       end
6244 c------------------------------------------------------------------------------
6245       subroutine multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,
6246      &  n_corr1)
6247 C This subroutine calculates multi-body contributions to hydrogen-bonding 
6248       implicit real*8 (a-h,o-z)
6249       include 'DIMENSIONS'
6250       include 'COMMON.IOUNITS'
6251 #ifdef MPI
6252       include "mpif.h"
6253       parameter (max_cont=maxconts)
6254       parameter (max_dim=70)
6255       integer source,CorrelType,CorrelID,CorrelType1,CorrelID1,Error
6256       double precision zapas(max_dim,maxconts,max_fg_procs),
6257      &  zapas_recv(max_dim,maxconts,max_fg_procs)
6258       common /przechowalnia/ zapas
6259       integer status(MPI_STATUS_SIZE),req(maxconts*2),
6260      &  status_array(MPI_STATUS_SIZE,maxconts*2)
6261 #endif
6262       include 'COMMON.SETUP'
6263       include 'COMMON.FFIELD'
6264       include 'COMMON.DERIV'
6265       include 'COMMON.LOCAL'
6266       include 'COMMON.INTERACT'
6267       include 'COMMON.CONTACTS'
6268       include 'COMMON.CHAIN'
6269       include 'COMMON.CONTROL'
6270       double precision gx(3),gx1(3)
6271       integer num_cont_hb_old(maxres)
6272       logical lprn,ldone
6273       double precision eello4,eello5,eelo6,eello_turn6
6274       external eello4,eello5,eello6,eello_turn6
6275 C Set lprn=.true. for debugging
6276       lprn=.false.
6277       eturn6=0.0d0
6278 #ifdef MPI
6279       do i=1,nres
6280         num_cont_hb_old(i)=num_cont_hb(i)
6281       enddo
6282       n_corr=0
6283       n_corr1=0
6284       if (nfgtasks.le.1) goto 30
6285       if (lprn) then
6286         write (iout,'(a)') 'Contact function values before RECEIVE:'
6287         do i=nnt,nct-2
6288           write (iout,'(2i3,50(1x,i2,f5.2))') 
6289      &    i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
6290      &    j=1,num_cont_hb(i))
6291         enddo
6292       endif
6293       call flush(iout)
6294       do i=1,ntask_cont_from
6295         ncont_recv(i)=0
6296       enddo
6297       do i=1,ntask_cont_to
6298         ncont_sent(i)=0
6299       enddo
6300 c      write (iout,*) "ntask_cont_from",ntask_cont_from," ntask_cont_to",
6301 c     & ntask_cont_to
6302 C Make the list of contacts to send to send to other procesors
6303       do i=iturn3_start,iturn3_end
6304 c        write (iout,*) "make contact list turn3",i," num_cont",
6305 c     &    num_cont_hb(i)
6306         call add_hb_contact_eello(i,i+2,iturn3_sent_local(1,i))
6307       enddo
6308       do i=iturn4_start,iturn4_end
6309 c        write (iout,*) "make contact list turn4",i," num_cont",
6310 c     &   num_cont_hb(i)
6311         call add_hb_contact_eello(i,i+3,iturn4_sent_local(1,i))
6312       enddo
6313       do ii=1,nat_sent
6314         i=iat_sent(ii)
6315 c        write (iout,*) "make contact list longrange",i,ii," num_cont",
6316 c     &    num_cont_hb(i)
6317         do j=1,num_cont_hb(i)
6318         do k=1,4
6319           jjc=jcont_hb(j,i)
6320           iproc=iint_sent_local(k,jjc,ii)
6321 c          write (iout,*) "i",i," j",j," k",k," jjc",jjc," iproc",iproc
6322           if (iproc.ne.0) then
6323             ncont_sent(iproc)=ncont_sent(iproc)+1
6324             nn=ncont_sent(iproc)
6325             zapas(1,nn,iproc)=i
6326             zapas(2,nn,iproc)=jjc
6327             zapas(3,nn,iproc)=d_cont(j,i)
6328             ind=3
6329             do kk=1,3
6330               ind=ind+1
6331               zapas(ind,nn,iproc)=grij_hb_cont(kk,j,i)
6332             enddo
6333             do kk=1,2
6334               do ll=1,2
6335                 ind=ind+1
6336                 zapas(ind,nn,iproc)=a_chuj(ll,kk,j,i)
6337               enddo
6338             enddo
6339             do jj=1,5
6340               do kk=1,3
6341                 do ll=1,2
6342                   do mm=1,2
6343                     ind=ind+1
6344                     zapas(ind,nn,iproc)=a_chuj_der(mm,ll,kk,jj,j,i)
6345                   enddo
6346                 enddo
6347               enddo
6348             enddo
6349           endif
6350         enddo
6351         enddo
6352       enddo
6353       if (lprn) then
6354       write (iout,*) 
6355      &  "Numbers of contacts to be sent to other processors",
6356      &  (ncont_sent(i),i=1,ntask_cont_to)
6357       write (iout,*) "Contacts sent"
6358       do ii=1,ntask_cont_to
6359         nn=ncont_sent(ii)
6360         iproc=itask_cont_to(ii)
6361         write (iout,*) nn," contacts to processor",iproc,
6362      &   " of CONT_TO_COMM group"
6363         do i=1,nn
6364           write(iout,'(2f5.0,10f10.5)')(zapas(j,i,ii),j=1,10)
6365         enddo
6366       enddo
6367       call flush(iout)
6368       endif
6369       CorrelType=477
6370       CorrelID=fg_rank+1
6371       CorrelType1=478
6372       CorrelID1=nfgtasks+fg_rank+1
6373       ireq=0
6374 C Receive the numbers of needed contacts from other processors 
6375       do ii=1,ntask_cont_from
6376         iproc=itask_cont_from(ii)
6377         ireq=ireq+1
6378         call MPI_Irecv(ncont_recv(ii),1,MPI_INTEGER,iproc,CorrelType,
6379      &    FG_COMM,req(ireq),IERR)
6380       enddo
6381 c      write (iout,*) "IRECV ended"
6382 c      call flush(iout)
6383 C Send the number of contacts needed by other processors
6384       do ii=1,ntask_cont_to
6385         iproc=itask_cont_to(ii)
6386         ireq=ireq+1
6387         call MPI_Isend(ncont_sent(ii),1,MPI_INTEGER,iproc,CorrelType,
6388      &    FG_COMM,req(ireq),IERR)
6389       enddo
6390 c      write (iout,*) "ISEND ended"
6391 c      write (iout,*) "number of requests (nn)",ireq
6392       call flush(iout)
6393       if (ireq.gt.0) 
6394      &  call MPI_Waitall(ireq,req,status_array,ierr)
6395 c      write (iout,*) 
6396 c     &  "Numbers of contacts to be received from other processors",
6397 c     &  (ncont_recv(i),i=1,ntask_cont_from)
6398 c      call flush(iout)
6399 C Receive contacts
6400       ireq=0
6401       do ii=1,ntask_cont_from
6402         iproc=itask_cont_from(ii)
6403         nn=ncont_recv(ii)
6404 c        write (iout,*) "Receiving",nn," contacts from processor",iproc,
6405 c     &   " of CONT_TO_COMM group"
6406         call flush(iout)
6407         if (nn.gt.0) then
6408           ireq=ireq+1
6409           call MPI_Irecv(zapas_recv(1,1,ii),nn*max_dim,
6410      &    MPI_DOUBLE_PRECISION,iproc,CorrelType1,FG_COMM,req(ireq),IERR)
6411 c          write (iout,*) "ireq,req",ireq,req(ireq)
6412         endif
6413       enddo
6414 C Send the contacts to processors that need them
6415       do ii=1,ntask_cont_to
6416         iproc=itask_cont_to(ii)
6417         nn=ncont_sent(ii)
6418 c        write (iout,*) nn," contacts to processor",iproc,
6419 c     &   " of CONT_TO_COMM group"
6420         if (nn.gt.0) then
6421           ireq=ireq+1 
6422           call MPI_Isend(zapas(1,1,ii),nn*max_dim,MPI_DOUBLE_PRECISION,
6423      &      iproc,CorrelType1,FG_COMM,req(ireq),IERR)
6424 c          write (iout,*) "ireq,req",ireq,req(ireq)
6425 c          do i=1,nn
6426 c            write(iout,'(2f5.0,4f10.5)')(zapas(j,i,ii),j=1,5)
6427 c          enddo
6428         endif  
6429       enddo
6430 c      write (iout,*) "number of requests (contacts)",ireq
6431 c      write (iout,*) "req",(req(i),i=1,4)
6432 c      call flush(iout)
6433       if (ireq.gt.0) 
6434      & call MPI_Waitall(ireq,req,status_array,ierr)
6435       do iii=1,ntask_cont_from
6436         iproc=itask_cont_from(iii)
6437         nn=ncont_recv(iii)
6438         if (lprn) then
6439         write (iout,*) "Received",nn," contacts from processor",iproc,
6440      &   " of CONT_FROM_COMM group"
6441         call flush(iout)
6442         do i=1,nn
6443           write(iout,'(2f5.0,10f10.5)')(zapas_recv(j,i,iii),j=1,10)
6444         enddo
6445         call flush(iout)
6446         endif
6447         do i=1,nn
6448           ii=zapas_recv(1,i,iii)
6449 c Flag the received contacts to prevent double-counting
6450           jj=-zapas_recv(2,i,iii)
6451 c          write (iout,*) "iii",iii," i",i," ii",ii," jj",jj
6452 c          call flush(iout)
6453           nnn=num_cont_hb(ii)+1
6454           num_cont_hb(ii)=nnn
6455           jcont_hb(nnn,ii)=jj
6456           d_cont(nnn,ii)=zapas_recv(3,i,iii)
6457           ind=3
6458           do kk=1,3
6459             ind=ind+1
6460             grij_hb_cont(kk,nnn,ii)=zapas_recv(ind,i,iii)
6461           enddo
6462           do kk=1,2
6463             do ll=1,2
6464               ind=ind+1
6465               a_chuj(ll,kk,nnn,ii)=zapas_recv(ind,i,iii)
6466             enddo
6467           enddo
6468           do jj=1,5
6469             do kk=1,3
6470               do ll=1,2
6471                 do mm=1,2
6472                   ind=ind+1
6473                   a_chuj_der(mm,ll,kk,jj,nnn,ii)=zapas_recv(ind,i,iii)
6474                 enddo
6475               enddo
6476             enddo
6477           enddo
6478         enddo
6479       enddo
6480       call flush(iout)
6481       if (lprn) then
6482         write (iout,'(a)') 'Contact function values after receive:'
6483         do i=nnt,nct-2
6484           write (iout,'(2i3,50(1x,i3,5f6.3))') 
6485      &    i,num_cont_hb(i),(jcont_hb(j,i),d_cont(j,i),
6486      &    ((a_chuj(ll,kk,j,i),ll=1,2),kk=1,2),j=1,num_cont_hb(i))
6487         enddo
6488         call flush(iout)
6489       endif
6490    30 continue
6491 #endif
6492       if (lprn) then
6493         write (iout,'(a)') 'Contact function values:'
6494         do i=nnt,nct-2
6495           write (iout,'(2i3,50(1x,i2,5f6.3))') 
6496      &    i,num_cont_hb(i),(jcont_hb(j,i),d_cont(j,i),
6497      &    ((a_chuj(ll,kk,j,i),ll=1,2),kk=1,2),j=1,num_cont_hb(i))
6498         enddo
6499       endif
6500       ecorr=0.0D0
6501       ecorr5=0.0d0
6502       ecorr6=0.0d0
6503 C Remove the loop below after debugging !!!
6504       do i=nnt,nct
6505         do j=1,3
6506           gradcorr(j,i)=0.0D0
6507           gradxorr(j,i)=0.0D0
6508         enddo
6509       enddo
6510 C Calculate the dipole-dipole interaction energies
6511       if (wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0) then
6512       do i=iatel_s,iatel_e+1
6513         num_conti=num_cont_hb(i)
6514         do jj=1,num_conti
6515           j=jcont_hb(jj,i)
6516 #ifdef MOMENT
6517           call dipole(i,j,jj)
6518 #endif
6519         enddo
6520       enddo
6521       endif
6522 C Calculate the local-electrostatic correlation terms
6523 c                write (iout,*) "gradcorr5 in eello5 before loop"
6524 c                do iii=1,nres
6525 c                  write (iout,'(i5,3f10.5)') 
6526 c     &             iii,(gradcorr5(jjj,iii),jjj=1,3)
6527 c                enddo
6528       do i=min0(iatel_s,iturn4_start),max0(iatel_e+1,iturn3_end+1)
6529 c        write (iout,*) "corr loop i",i
6530         i1=i+1
6531         num_conti=num_cont_hb(i)
6532         num_conti1=num_cont_hb(i+1)
6533         do jj=1,num_conti
6534           j=jcont_hb(jj,i)
6535           jp=iabs(j)
6536           do kk=1,num_conti1
6537             j1=jcont_hb(kk,i1)
6538             jp1=iabs(j1)
6539 c            write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
6540 c     &         ' jj=',jj,' kk=',kk
6541 c            if (j1.eq.j+1 .or. j1.eq.j-1) then
6542             if ((j.gt.0 .and. j1.gt.0 .or. j.gt.0 .and. j1.lt.0 
6543      &          .or. j.lt.0 .and. j1.gt.0) .and.
6544      &         (jp1.eq.jp+1 .or. jp1.eq.jp-1)) then
6545 C Contacts I-J and (I+1)-(J+1) or (I+1)-(J-1) occur simultaneously. 
6546 C The system gains extra energy.
6547               n_corr=n_corr+1
6548               sqd1=dsqrt(d_cont(jj,i))
6549               sqd2=dsqrt(d_cont(kk,i1))
6550               sred_geom = sqd1*sqd2
6551               IF (sred_geom.lt.cutoff_corr) THEN
6552                 call gcont(sred_geom,r0_corr,1.0D0,delt_corr,
6553      &            ekont,fprimcont)
6554 cd               write (iout,*) 'i=',i,' j=',jp,' i1=',i1,' j1=',jp1,
6555 cd     &         ' jj=',jj,' kk=',kk
6556                 fac_prim1=0.5d0*sqd2/sqd1*fprimcont
6557                 fac_prim2=0.5d0*sqd1/sqd2*fprimcont
6558                 do l=1,3
6559                   g_contij(l,1)=fac_prim1*grij_hb_cont(l,jj,i)
6560                   g_contij(l,2)=fac_prim2*grij_hb_cont(l,kk,i1)
6561                 enddo
6562                 n_corr1=n_corr1+1
6563 cd               write (iout,*) 'sred_geom=',sred_geom,
6564 cd     &          ' ekont=',ekont,' fprim=',fprimcont,
6565 cd     &          ' fac_prim1',fac_prim1,' fac_prim2',fac_prim2
6566 cd               write (iout,*) "g_contij",g_contij
6567 cd               write (iout,*) "grij_hb_cont i",grij_hb_cont(:,jj,i)
6568 cd               write (iout,*) "grij_hb_cont i1",grij_hb_cont(:,jj,i1)
6569                 call calc_eello(i,jp,i+1,jp1,jj,kk)
6570                 if (wcorr4.gt.0.0d0) 
6571      &            ecorr=ecorr+eello4(i,jp,i+1,jp1,jj,kk)
6572                   if (energy_dec.and.wcorr4.gt.0.0d0) 
6573      1                 write (iout,'(a6,4i5,0pf7.3)')
6574      2                'ecorr4',i,j,i+1,j1,eello4(i,jp,i+1,jp1,jj,kk)
6575 c                write (iout,*) "gradcorr5 before eello5"
6576 c                do iii=1,nres
6577 c                  write (iout,'(i5,3f10.5)') 
6578 c     &             iii,(gradcorr5(jjj,iii),jjj=1,3)
6579 c                enddo
6580                 if (wcorr5.gt.0.0d0)
6581      &            ecorr5=ecorr5+eello5(i,jp,i+1,jp1,jj,kk)
6582 c                write (iout,*) "gradcorr5 after eello5"
6583 c                do iii=1,nres
6584 c                  write (iout,'(i5,3f10.5)') 
6585 c     &             iii,(gradcorr5(jjj,iii),jjj=1,3)
6586 c                enddo
6587                   if (energy_dec.and.wcorr5.gt.0.0d0) 
6588      1                 write (iout,'(a6,4i5,0pf7.3)')
6589      2                'ecorr5',i,j,i+1,j1,eello5(i,jp,i+1,jp1,jj,kk)
6590 cd                write(2,*)'wcorr6',wcorr6,' wturn6',wturn6
6591 cd                write(2,*)'ijkl',i,jp,i+1,jp1 
6592                 if (wcorr6.gt.0.0d0 .and. (jp.ne.i+4 .or. jp1.ne.i+3
6593      &               .or. wturn6.eq.0.0d0))then
6594 cd                  write (iout,*) '******ecorr6: i,j,i+1,j1',i,j,i+1,j1
6595                   ecorr6=ecorr6+eello6(i,jp,i+1,jp1,jj,kk)
6596                   if (energy_dec) write (iout,'(a6,4i5,0pf7.3)')
6597      1                'ecorr6',i,j,i+1,j1,eello6(i,jp,i+1,jp1,jj,kk)
6598 cd                write (iout,*) 'ecorr',ecorr,' ecorr5=',ecorr5,
6599 cd     &            'ecorr6=',ecorr6
6600 cd                write (iout,'(4e15.5)') sred_geom,
6601 cd     &          dabs(eello4(i,jp,i+1,jp1,jj,kk)),
6602 cd     &          dabs(eello5(i,jp,i+1,jp1,jj,kk)),
6603 cd     &          dabs(eello6(i,jp,i+1,jp1,jj,kk))
6604                 else if (wturn6.gt.0.0d0
6605      &            .and. (jp.eq.i+4 .and. jp1.eq.i+3)) then
6606 cd                  write (iout,*) '******eturn6: i,j,i+1,j1',i,jip,i+1,jp1
6607                   eturn6=eturn6+eello_turn6(i,jj,kk)
6608                   if (energy_dec) write (iout,'(a6,4i5,0pf7.3)')
6609      1                 'eturn6',i,j,i+1,j1,eello_turn6(i,jj,kk)
6610 cd                  write (2,*) 'multibody_eello:eturn6',eturn6
6611                 endif
6612               ENDIF
6613 1111          continue
6614             endif
6615           enddo ! kk
6616         enddo ! jj
6617       enddo ! i
6618       do i=1,nres
6619         num_cont_hb(i)=num_cont_hb_old(i)
6620       enddo
6621 c                write (iout,*) "gradcorr5 in eello5"
6622 c                do iii=1,nres
6623 c                  write (iout,'(i5,3f10.5)') 
6624 c     &             iii,(gradcorr5(jjj,iii),jjj=1,3)
6625 c                enddo
6626       return
6627       end
6628 c------------------------------------------------------------------------------
6629       subroutine add_hb_contact_eello(ii,jj,itask)
6630       implicit real*8 (a-h,o-z)
6631       include "DIMENSIONS"
6632       include "COMMON.IOUNITS"
6633       integer max_cont
6634       integer max_dim
6635       parameter (max_cont=maxconts)
6636       parameter (max_dim=70)
6637       include "COMMON.CONTACTS"
6638       double precision zapas(max_dim,maxconts,max_fg_procs),
6639      &  zapas_recv(max_dim,maxconts,max_fg_procs)
6640       common /przechowalnia/ zapas
6641       integer i,j,ii,jj,iproc,itask(4),nn
6642 c      write (iout,*) "itask",itask
6643       do i=1,2
6644         iproc=itask(i)
6645         if (iproc.gt.0) then
6646           do j=1,num_cont_hb(ii)
6647             jjc=jcont_hb(j,ii)
6648 c            write (iout,*) "send turns i",ii," j",jj," jjc",jjc
6649             if (jjc.eq.jj) then
6650               ncont_sent(iproc)=ncont_sent(iproc)+1
6651               nn=ncont_sent(iproc)
6652               zapas(1,nn,iproc)=ii
6653               zapas(2,nn,iproc)=jjc
6654               zapas(3,nn,iproc)=d_cont(j,ii)
6655               ind=3
6656               do kk=1,3
6657                 ind=ind+1
6658                 zapas(ind,nn,iproc)=grij_hb_cont(kk,j,ii)
6659               enddo
6660               do kk=1,2
6661                 do ll=1,2
6662                   ind=ind+1
6663                   zapas(ind,nn,iproc)=a_chuj(ll,kk,j,ii)
6664                 enddo
6665               enddo
6666               do jj=1,5
6667                 do kk=1,3
6668                   do ll=1,2
6669                     do mm=1,2
6670                       ind=ind+1
6671                       zapas(ind,nn,iproc)=a_chuj_der(mm,ll,kk,jj,j,ii)
6672                     enddo
6673                   enddo
6674                 enddo
6675               enddo
6676               exit
6677             endif
6678           enddo
6679         endif
6680       enddo
6681       return
6682       end
6683 c------------------------------------------------------------------------------
6684       double precision function ehbcorr(i,j,k,l,jj,kk,coeffp,coeffm)
6685       implicit real*8 (a-h,o-z)
6686       include 'DIMENSIONS'
6687       include 'COMMON.IOUNITS'
6688       include 'COMMON.DERIV'
6689       include 'COMMON.INTERACT'
6690       include 'COMMON.CONTACTS'
6691       double precision gx(3),gx1(3)
6692       logical lprn
6693       lprn=.false.
6694       eij=facont_hb(jj,i)
6695       ekl=facont_hb(kk,k)
6696       ees0pij=ees0p(jj,i)
6697       ees0pkl=ees0p(kk,k)
6698       ees0mij=ees0m(jj,i)
6699       ees0mkl=ees0m(kk,k)
6700       ekont=eij*ekl
6701       ees=-(coeffp*ees0pij*ees0pkl+coeffm*ees0mij*ees0mkl)
6702 cd    ees=-(coeffp*ees0pkl+coeffm*ees0mkl)
6703 C Following 4 lines for diagnostics.
6704 cd    ees0pkl=0.0D0
6705 cd    ees0pij=1.0D0
6706 cd    ees0mkl=0.0D0
6707 cd    ees0mij=1.0D0
6708 c      write (iout,'(2(a,2i3,a,f10.5,a,2f10.5),a,f10.5,a,$)')
6709 c     & 'Contacts ',i,j,
6710 c     & ' eij',eij,' eesij',ees0pij,ees0mij,' and ',k,l
6711 c     & ,' fcont ',ekl,' eeskl',ees0pkl,ees0mkl,' energy=',ekont*ees,
6712 c     & 'gradcorr_long'
6713 C Calculate the multi-body contribution to energy.
6714 c      ecorr=ecorr+ekont*ees
6715 C Calculate multi-body contributions to the gradient.
6716       coeffpees0pij=coeffp*ees0pij
6717       coeffmees0mij=coeffm*ees0mij
6718       coeffpees0pkl=coeffp*ees0pkl
6719       coeffmees0mkl=coeffm*ees0mkl
6720       do ll=1,3
6721 cgrad        ghalfi=ees*ekl*gacont_hbr(ll,jj,i)
6722         gradcorr(ll,i)=gradcorr(ll,i)!+0.5d0*ghalfi
6723      &  -ekont*(coeffpees0pkl*gacontp_hb1(ll,jj,i)+
6724      &  coeffmees0mkl*gacontm_hb1(ll,jj,i))
6725         gradcorr(ll,j)=gradcorr(ll,j)!+0.5d0*ghalfi
6726      &  -ekont*(coeffpees0pkl*gacontp_hb2(ll,jj,i)+
6727      &  coeffmees0mkl*gacontm_hb2(ll,jj,i))
6728 cgrad        ghalfk=ees*eij*gacont_hbr(ll,kk,k)
6729         gradcorr(ll,k)=gradcorr(ll,k)!+0.5d0*ghalfk
6730      &  -ekont*(coeffpees0pij*gacontp_hb1(ll,kk,k)+
6731      &  coeffmees0mij*gacontm_hb1(ll,kk,k))
6732         gradcorr(ll,l)=gradcorr(ll,l)!+0.5d0*ghalfk
6733      &  -ekont*(coeffpees0pij*gacontp_hb2(ll,kk,k)+
6734      &  coeffmees0mij*gacontm_hb2(ll,kk,k))
6735         gradlongij=ees*ekl*gacont_hbr(ll,jj,i)-
6736      &     ekont*(coeffpees0pkl*gacontp_hb3(ll,jj,i)+
6737      &     coeffmees0mkl*gacontm_hb3(ll,jj,i))
6738         gradcorr_long(ll,j)=gradcorr_long(ll,j)+gradlongij
6739         gradcorr_long(ll,i)=gradcorr_long(ll,i)-gradlongij
6740         gradlongkl=ees*eij*gacont_hbr(ll,kk,k)-
6741      &     ekont*(coeffpees0pij*gacontp_hb3(ll,kk,k)+
6742      &     coeffmees0mij*gacontm_hb3(ll,kk,k))
6743         gradcorr_long(ll,l)=gradcorr_long(ll,l)+gradlongkl
6744         gradcorr_long(ll,k)=gradcorr_long(ll,k)-gradlongkl
6745 c        write (iout,'(2f10.5,2x,$)') gradlongij,gradlongkl
6746       enddo
6747 c      write (iout,*)
6748 cgrad      do m=i+1,j-1
6749 cgrad        do ll=1,3
6750 cgrad          gradcorr(ll,m)=gradcorr(ll,m)+
6751 cgrad     &     ees*ekl*gacont_hbr(ll,jj,i)-
6752 cgrad     &     ekont*(coeffp*ees0pkl*gacontp_hb3(ll,jj,i)+
6753 cgrad     &     coeffm*ees0mkl*gacontm_hb3(ll,jj,i))
6754 cgrad        enddo
6755 cgrad      enddo
6756 cgrad      do m=k+1,l-1
6757 cgrad        do ll=1,3
6758 cgrad          gradcorr(ll,m)=gradcorr(ll,m)+
6759 cgrad     &     ees*eij*gacont_hbr(ll,kk,k)-
6760 cgrad     &     ekont*(coeffp*ees0pij*gacontp_hb3(ll,kk,k)+
6761 cgrad     &     coeffm*ees0mij*gacontm_hb3(ll,kk,k))
6762 cgrad        enddo
6763 cgrad      enddo 
6764 c      write (iout,*) "ehbcorr",ekont*ees
6765       ehbcorr=ekont*ees
6766       return
6767       end
6768 #ifdef MOMENT
6769 C---------------------------------------------------------------------------
6770       subroutine dipole(i,j,jj)
6771       implicit real*8 (a-h,o-z)
6772       include 'DIMENSIONS'
6773       include 'COMMON.IOUNITS'
6774       include 'COMMON.CHAIN'
6775       include 'COMMON.FFIELD'
6776       include 'COMMON.DERIV'
6777       include 'COMMON.INTERACT'
6778       include 'COMMON.CONTACTS'
6779       include 'COMMON.TORSION'
6780       include 'COMMON.VAR'
6781       include 'COMMON.GEO'
6782       dimension dipi(2,2),dipj(2,2),dipderi(2),dipderj(2),auxvec(2),
6783      &  auxmat(2,2)
6784       iti1 = itortyp(itype(i+1))
6785       if (j.lt.nres-1) then
6786         itj1 = itortyp(itype(j+1))
6787       else
6788         itj1=ntortyp+1
6789       endif
6790       do iii=1,2
6791         dipi(iii,1)=Ub2(iii,i)
6792         dipderi(iii)=Ub2der(iii,i)
6793         dipi(iii,2)=b1(iii,iti1)
6794         dipj(iii,1)=Ub2(iii,j)
6795         dipderj(iii)=Ub2der(iii,j)
6796         dipj(iii,2)=b1(iii,itj1)
6797       enddo
6798       kkk=0
6799       do iii=1,2
6800         call matvec2(a_chuj(1,1,jj,i),dipj(1,iii),auxvec(1)) 
6801         do jjj=1,2
6802           kkk=kkk+1
6803           dip(kkk,jj,i)=scalar2(dipi(1,jjj),auxvec(1))
6804         enddo
6805       enddo
6806       do kkk=1,5
6807         do lll=1,3
6808           mmm=0
6809           do iii=1,2
6810             call matvec2(a_chuj_der(1,1,lll,kkk,jj,i),dipj(1,iii),
6811      &        auxvec(1))
6812             do jjj=1,2
6813               mmm=mmm+1
6814               dipderx(lll,kkk,mmm,jj,i)=scalar2(dipi(1,jjj),auxvec(1))
6815             enddo
6816           enddo
6817         enddo
6818       enddo
6819       call transpose2(a_chuj(1,1,jj,i),auxmat(1,1))
6820       call matvec2(auxmat(1,1),dipderi(1),auxvec(1))
6821       do iii=1,2
6822         dipderg(iii,jj,i)=scalar2(auxvec(1),dipj(1,iii))
6823       enddo
6824       call matvec2(a_chuj(1,1,jj,i),dipderj(1),auxvec(1))
6825       do iii=1,2
6826         dipderg(iii+2,jj,i)=scalar2(auxvec(1),dipi(1,iii))
6827       enddo
6828       return
6829       end
6830 #endif
6831 C---------------------------------------------------------------------------
6832       subroutine calc_eello(i,j,k,l,jj,kk)
6833
6834 C This subroutine computes matrices and vectors needed to calculate 
6835 C the fourth-, fifth-, and sixth-order local-electrostatic terms.
6836 C
6837       implicit real*8 (a-h,o-z)
6838       include 'DIMENSIONS'
6839       include 'COMMON.IOUNITS'
6840       include 'COMMON.CHAIN'
6841       include 'COMMON.DERIV'
6842       include 'COMMON.INTERACT'
6843       include 'COMMON.CONTACTS'
6844       include 'COMMON.TORSION'
6845       include 'COMMON.VAR'
6846       include 'COMMON.GEO'
6847       include 'COMMON.FFIELD'
6848       double precision aa1(2,2),aa2(2,2),aa1t(2,2),aa2t(2,2),
6849      &  aa1tder(2,2,3,5),aa2tder(2,2,3,5),auxmat(2,2)
6850       logical lprn
6851       common /kutas/ lprn
6852 cd      write (iout,*) 'calc_eello: i=',i,' j=',j,' k=',k,' l=',l,
6853 cd     & ' jj=',jj,' kk=',kk
6854 cd      if (i.ne.2 .or. j.ne.4 .or. k.ne.3 .or. l.ne.5) return
6855 cd      write (iout,*) "a_chujij",((a_chuj(iii,jjj,jj,i),iii=1,2),jjj=1,2)
6856 cd      write (iout,*) "a_chujkl",((a_chuj(iii,jjj,kk,k),iii=1,2),jjj=1,2)
6857       do iii=1,2
6858         do jjj=1,2
6859           aa1(iii,jjj)=a_chuj(iii,jjj,jj,i)
6860           aa2(iii,jjj)=a_chuj(iii,jjj,kk,k)
6861         enddo
6862       enddo
6863       call transpose2(aa1(1,1),aa1t(1,1))
6864       call transpose2(aa2(1,1),aa2t(1,1))
6865       do kkk=1,5
6866         do lll=1,3
6867           call transpose2(a_chuj_der(1,1,lll,kkk,jj,i),
6868      &      aa1tder(1,1,lll,kkk))
6869           call transpose2(a_chuj_der(1,1,lll,kkk,kk,k),
6870      &      aa2tder(1,1,lll,kkk))
6871         enddo
6872       enddo 
6873       if (l.eq.j+1) then
6874 C parallel orientation of the two CA-CA-CA frames.
6875         if (i.gt.1) then
6876           iti=itortyp(itype(i))
6877         else
6878           iti=ntortyp+1
6879         endif
6880         itk1=itortyp(itype(k+1))
6881         itj=itortyp(itype(j))
6882         if (l.lt.nres-1) then
6883           itl1=itortyp(itype(l+1))
6884         else
6885           itl1=ntortyp+1
6886         endif
6887 C A1 kernel(j+1) A2T
6888 cd        do iii=1,2
6889 cd          write (iout,'(3f10.5,5x,3f10.5)') 
6890 cd     &     (EUg(iii,jjj,k),jjj=1,2),(EUg(iii,jjj,l),jjj=1,2)
6891 cd        enddo
6892         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
6893      &   aa2tder(1,1,1,1),1,.false.,EUg(1,1,l),EUgder(1,1,l),
6894      &   AEA(1,1,1),AEAderg(1,1,1),AEAderx(1,1,1,1,1,1))
6895 C Following matrices are needed only for 6-th order cumulants
6896         IF (wcorr6.gt.0.0d0) THEN
6897         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
6898      &   aa2tder(1,1,1,1),1,.false.,EUgC(1,1,l),EUgCder(1,1,l),
6899      &   AECA(1,1,1),AECAderg(1,1,1),AECAderx(1,1,1,1,1,1))
6900         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
6901      &   aa2tder(1,1,1,1),2,.false.,Ug2DtEUg(1,1,l),
6902      &   Ug2DtEUgder(1,1,1,l),ADtEA(1,1,1),ADtEAderg(1,1,1,1),
6903      &   ADtEAderx(1,1,1,1,1,1))
6904         lprn=.false.
6905         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
6906      &   aa2tder(1,1,1,1),2,.false.,DtUg2EUg(1,1,l),
6907      &   DtUg2EUgder(1,1,1,l),ADtEA1(1,1,1),ADtEA1derg(1,1,1,1),
6908      &   ADtEA1derx(1,1,1,1,1,1))
6909         ENDIF
6910 C End 6-th order cumulants
6911 cd        lprn=.false.
6912 cd        if (lprn) then
6913 cd        write (2,*) 'In calc_eello6'
6914 cd        do iii=1,2
6915 cd          write (2,*) 'iii=',iii
6916 cd          do kkk=1,5
6917 cd            write (2,*) 'kkk=',kkk
6918 cd            do jjj=1,2
6919 cd              write (2,'(3(2f10.5),5x)') 
6920 cd     &        ((ADtEA1derx(jjj,mmm,lll,kkk,iii,1),mmm=1,2),lll=1,3)
6921 cd            enddo
6922 cd          enddo
6923 cd        enddo
6924 cd        endif
6925         call transpose2(EUgder(1,1,k),auxmat(1,1))
6926         call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,1,1))
6927         call transpose2(EUg(1,1,k),auxmat(1,1))
6928         call matmat2(auxmat(1,1),AEA(1,1,1),EAEA(1,1,1))
6929         call matmat2(auxmat(1,1),AEAderg(1,1,1),EAEAderg(1,1,2,1))
6930         do iii=1,2
6931           do kkk=1,5
6932             do lll=1,3
6933               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
6934      &          EAEAderx(1,1,lll,kkk,iii,1))
6935             enddo
6936           enddo
6937         enddo
6938 C A1T kernel(i+1) A2
6939         call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
6940      &   a_chuj_der(1,1,1,1,kk,k),1,.false.,EUg(1,1,k),EUgder(1,1,k),
6941      &   AEA(1,1,2),AEAderg(1,1,2),AEAderx(1,1,1,1,1,2))
6942 C Following matrices are needed only for 6-th order cumulants
6943         IF (wcorr6.gt.0.0d0) THEN
6944         call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
6945      &   a_chuj_der(1,1,1,1,kk,k),1,.false.,EUgC(1,1,k),EUgCder(1,1,k),
6946      &   AECA(1,1,2),AECAderg(1,1,2),AECAderx(1,1,1,1,1,2))
6947         call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
6948      &   a_chuj_der(1,1,1,1,kk,k),2,.false.,Ug2DtEUg(1,1,k),
6949      &   Ug2DtEUgder(1,1,1,k),ADtEA(1,1,2),ADtEAderg(1,1,1,2),
6950      &   ADtEAderx(1,1,1,1,1,2))
6951         call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
6952      &   a_chuj_der(1,1,1,1,kk,k),2,.false.,DtUg2EUg(1,1,k),
6953      &   DtUg2EUgder(1,1,1,k),ADtEA1(1,1,2),ADtEA1derg(1,1,1,2),
6954      &   ADtEA1derx(1,1,1,1,1,2))
6955         ENDIF
6956 C End 6-th order cumulants
6957         call transpose2(EUgder(1,1,l),auxmat(1,1))
6958         call matmat2(auxmat(1,1),AEA(1,1,2),EAEAderg(1,1,1,2))
6959         call transpose2(EUg(1,1,l),auxmat(1,1))
6960         call matmat2(auxmat(1,1),AEA(1,1,2),EAEA(1,1,2))
6961         call matmat2(auxmat(1,1),AEAderg(1,1,2),EAEAderg(1,1,2,2))
6962         do iii=1,2
6963           do kkk=1,5
6964             do lll=1,3
6965               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
6966      &          EAEAderx(1,1,lll,kkk,iii,2))
6967             enddo
6968           enddo
6969         enddo
6970 C AEAb1 and AEAb2
6971 C Calculate the vectors and their derivatives in virtual-bond dihedral angles.
6972 C They are needed only when the fifth- or the sixth-order cumulants are
6973 C indluded.
6974         IF (wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0) THEN
6975         call transpose2(AEA(1,1,1),auxmat(1,1))
6976         call matvec2(auxmat(1,1),b1(1,iti),AEAb1(1,1,1))
6977         call matvec2(auxmat(1,1),Ub2(1,i),AEAb2(1,1,1))
6978         call matvec2(auxmat(1,1),Ub2der(1,i),AEAb2derg(1,2,1,1))
6979         call transpose2(AEAderg(1,1,1),auxmat(1,1))
6980         call matvec2(auxmat(1,1),b1(1,iti),AEAb1derg(1,1,1))
6981         call matvec2(auxmat(1,1),Ub2(1,i),AEAb2derg(1,1,1,1))
6982         call matvec2(AEA(1,1,1),b1(1,itk1),AEAb1(1,2,1))
6983         call matvec2(AEAderg(1,1,1),b1(1,itk1),AEAb1derg(1,2,1))
6984         call matvec2(AEA(1,1,1),Ub2(1,k+1),AEAb2(1,2,1))
6985         call matvec2(AEAderg(1,1,1),Ub2(1,k+1),AEAb2derg(1,1,2,1))
6986         call matvec2(AEA(1,1,1),Ub2der(1,k+1),AEAb2derg(1,2,2,1))
6987         call transpose2(AEA(1,1,2),auxmat(1,1))
6988         call matvec2(auxmat(1,1),b1(1,itj),AEAb1(1,1,2))
6989         call matvec2(auxmat(1,1),Ub2(1,j),AEAb2(1,1,2))
6990         call matvec2(auxmat(1,1),Ub2der(1,j),AEAb2derg(1,2,1,2))
6991         call transpose2(AEAderg(1,1,2),auxmat(1,1))
6992         call matvec2(auxmat(1,1),b1(1,itj),AEAb1derg(1,1,2))
6993         call matvec2(auxmat(1,1),Ub2(1,j),AEAb2derg(1,1,1,2))
6994         call matvec2(AEA(1,1,2),b1(1,itl1),AEAb1(1,2,2))
6995         call matvec2(AEAderg(1,1,2),b1(1,itl1),AEAb1derg(1,2,2))
6996         call matvec2(AEA(1,1,2),Ub2(1,l+1),AEAb2(1,2,2))
6997         call matvec2(AEAderg(1,1,2),Ub2(1,l+1),AEAb2derg(1,1,2,2))
6998         call matvec2(AEA(1,1,2),Ub2der(1,l+1),AEAb2derg(1,2,2,2))
6999 C Calculate the Cartesian derivatives of the vectors.
7000         do iii=1,2
7001           do kkk=1,5
7002             do lll=1,3
7003               call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1))
7004               call matvec2(auxmat(1,1),b1(1,iti),
7005      &          AEAb1derx(1,lll,kkk,iii,1,1))
7006               call matvec2(auxmat(1,1),Ub2(1,i),
7007      &          AEAb2derx(1,lll,kkk,iii,1,1))
7008               call matvec2(AEAderx(1,1,lll,kkk,iii,1),b1(1,itk1),
7009      &          AEAb1derx(1,lll,kkk,iii,2,1))
7010               call matvec2(AEAderx(1,1,lll,kkk,iii,1),Ub2(1,k+1),
7011      &          AEAb2derx(1,lll,kkk,iii,2,1))
7012               call transpose2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1))
7013               call matvec2(auxmat(1,1),b1(1,itj),
7014      &          AEAb1derx(1,lll,kkk,iii,1,2))
7015               call matvec2(auxmat(1,1),Ub2(1,j),
7016      &          AEAb2derx(1,lll,kkk,iii,1,2))
7017               call matvec2(AEAderx(1,1,lll,kkk,iii,2),b1(1,itl1),
7018      &          AEAb1derx(1,lll,kkk,iii,2,2))
7019               call matvec2(AEAderx(1,1,lll,kkk,iii,2),Ub2(1,l+1),
7020      &          AEAb2derx(1,lll,kkk,iii,2,2))
7021             enddo
7022           enddo
7023         enddo
7024         ENDIF
7025 C End vectors
7026       else
7027 C Antiparallel orientation of the two CA-CA-CA frames.
7028         if (i.gt.1) then
7029           iti=itortyp(itype(i))
7030         else
7031           iti=ntortyp+1
7032         endif
7033         itk1=itortyp(itype(k+1))
7034         itl=itortyp(itype(l))
7035         itj=itortyp(itype(j))
7036         if (j.lt.nres-1) then
7037           itj1=itortyp(itype(j+1))
7038         else 
7039           itj1=ntortyp+1
7040         endif
7041 C A2 kernel(j-1)T A1T
7042         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
7043      &   aa2tder(1,1,1,1),1,.true.,EUg(1,1,j),EUgder(1,1,j),
7044      &   AEA(1,1,1),AEAderg(1,1,1),AEAderx(1,1,1,1,1,1))
7045 C Following matrices are needed only for 6-th order cumulants
7046         IF (wcorr6.gt.0.0d0 .or. (wturn6.gt.0.0d0 .and.
7047      &     j.eq.i+4 .and. l.eq.i+3)) THEN
7048         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
7049      &   aa2tder(1,1,1,1),1,.true.,EUgC(1,1,j),EUgCder(1,1,j),
7050      &   AECA(1,1,1),AECAderg(1,1,1),AECAderx(1,1,1,1,1,1))
7051         call kernel(aa2(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
7052      &   aa2tder(1,1,1,1),2,.true.,Ug2DtEUg(1,1,j),
7053      &   Ug2DtEUgder(1,1,1,j),ADtEA(1,1,1),ADtEAderg(1,1,1,1),
7054      &   ADtEAderx(1,1,1,1,1,1))
7055         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
7056      &   aa2tder(1,1,1,1),2,.true.,DtUg2EUg(1,1,j),
7057      &   DtUg2EUgder(1,1,1,j),ADtEA1(1,1,1),ADtEA1derg(1,1,1,1),
7058      &   ADtEA1derx(1,1,1,1,1,1))
7059         ENDIF
7060 C End 6-th order cumulants
7061         call transpose2(EUgder(1,1,k),auxmat(1,1))
7062         call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,1,1))
7063         call transpose2(EUg(1,1,k),auxmat(1,1))
7064         call matmat2(auxmat(1,1),AEA(1,1,1),EAEA(1,1,1))
7065         call matmat2(auxmat(1,1),AEAderg(1,1,1),EAEAderg(1,1,2,1))
7066         do iii=1,2
7067           do kkk=1,5
7068             do lll=1,3
7069               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
7070      &          EAEAderx(1,1,lll,kkk,iii,1))
7071             enddo
7072           enddo
7073         enddo
7074 C A2T kernel(i+1)T A1
7075         call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
7076      &   a_chuj_der(1,1,1,1,jj,i),1,.true.,EUg(1,1,k),EUgder(1,1,k),
7077      &   AEA(1,1,2),AEAderg(1,1,2),AEAderx(1,1,1,1,1,2))
7078 C Following matrices are needed only for 6-th order cumulants
7079         IF (wcorr6.gt.0.0d0 .or. (wturn6.gt.0.0d0 .and.
7080      &     j.eq.i+4 .and. l.eq.i+3)) THEN
7081         call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
7082      &   a_chuj_der(1,1,1,1,jj,i),1,.true.,EUgC(1,1,k),EUgCder(1,1,k),
7083      &   AECA(1,1,2),AECAderg(1,1,2),AECAderx(1,1,1,1,1,2))
7084         call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
7085      &   a_chuj_der(1,1,1,1,jj,i),2,.true.,Ug2DtEUg(1,1,k),
7086      &   Ug2DtEUgder(1,1,1,k),ADtEA(1,1,2),ADtEAderg(1,1,1,2),
7087      &   ADtEAderx(1,1,1,1,1,2))
7088         call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
7089      &   a_chuj_der(1,1,1,1,jj,i),2,.true.,DtUg2EUg(1,1,k),
7090      &   DtUg2EUgder(1,1,1,k),ADtEA1(1,1,2),ADtEA1derg(1,1,1,2),
7091      &   ADtEA1derx(1,1,1,1,1,2))
7092         ENDIF
7093 C End 6-th order cumulants
7094         call transpose2(EUgder(1,1,j),auxmat(1,1))
7095         call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,2,2))
7096         call transpose2(EUg(1,1,j),auxmat(1,1))
7097         call matmat2(auxmat(1,1),AEA(1,1,2),EAEA(1,1,2))
7098         call matmat2(auxmat(1,1),AEAderg(1,1,2),EAEAderg(1,1,2,2))
7099         do iii=1,2
7100           do kkk=1,5
7101             do lll=1,3
7102               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
7103      &          EAEAderx(1,1,lll,kkk,iii,2))
7104             enddo
7105           enddo
7106         enddo
7107 C AEAb1 and AEAb2
7108 C Calculate the vectors and their derivatives in virtual-bond dihedral angles.
7109 C They are needed only when the fifth- or the sixth-order cumulants are
7110 C indluded.
7111         IF (wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0 .or.
7112      &    (wturn6.gt.0.0d0 .and. j.eq.i+4 .and. l.eq.i+3)) THEN
7113         call transpose2(AEA(1,1,1),auxmat(1,1))
7114         call matvec2(auxmat(1,1),b1(1,iti),AEAb1(1,1,1))
7115         call matvec2(auxmat(1,1),Ub2(1,i),AEAb2(1,1,1))
7116         call matvec2(auxmat(1,1),Ub2der(1,i),AEAb2derg(1,2,1,1))
7117         call transpose2(AEAderg(1,1,1),auxmat(1,1))
7118         call matvec2(auxmat(1,1),b1(1,iti),AEAb1derg(1,1,1))
7119         call matvec2(auxmat(1,1),Ub2(1,i),AEAb2derg(1,1,1,1))
7120         call matvec2(AEA(1,1,1),b1(1,itk1),AEAb1(1,2,1))
7121         call matvec2(AEAderg(1,1,1),b1(1,itk1),AEAb1derg(1,2,1))
7122         call matvec2(AEA(1,1,1),Ub2(1,k+1),AEAb2(1,2,1))
7123         call matvec2(AEAderg(1,1,1),Ub2(1,k+1),AEAb2derg(1,1,2,1))
7124         call matvec2(AEA(1,1,1),Ub2der(1,k+1),AEAb2derg(1,2,2,1))
7125         call transpose2(AEA(1,1,2),auxmat(1,1))
7126         call matvec2(auxmat(1,1),b1(1,itj1),AEAb1(1,1,2))
7127         call matvec2(auxmat(1,1),Ub2(1,l),AEAb2(1,1,2))
7128         call matvec2(auxmat(1,1),Ub2der(1,l),AEAb2derg(1,2,1,2))
7129         call transpose2(AEAderg(1,1,2),auxmat(1,1))
7130         call matvec2(auxmat(1,1),b1(1,itl),AEAb1(1,1,2))
7131         call matvec2(auxmat(1,1),Ub2(1,l),AEAb2derg(1,1,1,2))
7132         call matvec2(AEA(1,1,2),b1(1,itj1),AEAb1(1,2,2))
7133         call matvec2(AEAderg(1,1,2),b1(1,itj1),AEAb1derg(1,2,2))
7134         call matvec2(AEA(1,1,2),Ub2(1,j),AEAb2(1,2,2))
7135         call matvec2(AEAderg(1,1,2),Ub2(1,j),AEAb2derg(1,1,2,2))
7136         call matvec2(AEA(1,1,2),Ub2der(1,j),AEAb2derg(1,2,2,2))
7137 C Calculate the Cartesian derivatives of the vectors.
7138         do iii=1,2
7139           do kkk=1,5
7140             do lll=1,3
7141               call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1))
7142               call matvec2(auxmat(1,1),b1(1,iti),
7143      &          AEAb1derx(1,lll,kkk,iii,1,1))
7144               call matvec2(auxmat(1,1),Ub2(1,i),
7145      &          AEAb2derx(1,lll,kkk,iii,1,1))
7146               call matvec2(AEAderx(1,1,lll,kkk,iii,1),b1(1,itk1),
7147      &          AEAb1derx(1,lll,kkk,iii,2,1))
7148               call matvec2(AEAderx(1,1,lll,kkk,iii,1),Ub2(1,k+1),
7149      &          AEAb2derx(1,lll,kkk,iii,2,1))
7150               call transpose2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1))
7151               call matvec2(auxmat(1,1),b1(1,itl),
7152      &          AEAb1derx(1,lll,kkk,iii,1,2))
7153               call matvec2(auxmat(1,1),Ub2(1,l),
7154      &          AEAb2derx(1,lll,kkk,iii,1,2))
7155               call matvec2(AEAderx(1,1,lll,kkk,iii,2),b1(1,itj1),
7156      &          AEAb1derx(1,lll,kkk,iii,2,2))
7157               call matvec2(AEAderx(1,1,lll,kkk,iii,2),Ub2(1,j),
7158      &          AEAb2derx(1,lll,kkk,iii,2,2))
7159             enddo
7160           enddo
7161         enddo
7162         ENDIF
7163 C End vectors
7164       endif
7165       return
7166       end
7167 C---------------------------------------------------------------------------
7168       subroutine kernel(aa1,aa2t,aa1derx,aa2tderx,nderg,transp,
7169      &  KK,KKderg,AKA,AKAderg,AKAderx)
7170       implicit none
7171       integer nderg
7172       logical transp
7173       double precision aa1(2,2),aa2t(2,2),aa1derx(2,2,3,5),
7174      &  aa2tderx(2,2,3,5),KK(2,2),KKderg(2,2,nderg),AKA(2,2),
7175      &  AKAderg(2,2,nderg),AKAderx(2,2,3,5,2)
7176       integer iii,kkk,lll
7177       integer jjj,mmm
7178       logical lprn
7179       common /kutas/ lprn
7180       call prodmat3(aa1(1,1),aa2t(1,1),KK(1,1),transp,AKA(1,1))
7181       do iii=1,nderg 
7182         call prodmat3(aa1(1,1),aa2t(1,1),KKderg(1,1,iii),transp,
7183      &    AKAderg(1,1,iii))
7184       enddo
7185 cd      if (lprn) write (2,*) 'In kernel'
7186       do kkk=1,5
7187 cd        if (lprn) write (2,*) 'kkk=',kkk
7188         do lll=1,3
7189           call prodmat3(aa1derx(1,1,lll,kkk),aa2t(1,1),
7190      &      KK(1,1),transp,AKAderx(1,1,lll,kkk,1))
7191 cd          if (lprn) then
7192 cd            write (2,*) 'lll=',lll
7193 cd            write (2,*) 'iii=1'
7194 cd            do jjj=1,2
7195 cd              write (2,'(3(2f10.5),5x)') 
7196 cd     &        (AKAderx(jjj,mmm,lll,kkk,1),mmm=1,2)
7197 cd            enddo
7198 cd          endif
7199           call prodmat3(aa1(1,1),aa2tderx(1,1,lll,kkk),
7200      &      KK(1,1),transp,AKAderx(1,1,lll,kkk,2))
7201 cd          if (lprn) then
7202 cd            write (2,*) 'lll=',lll
7203 cd            write (2,*) 'iii=2'
7204 cd            do jjj=1,2
7205 cd              write (2,'(3(2f10.5),5x)') 
7206 cd     &        (AKAderx(jjj,mmm,lll,kkk,2),mmm=1,2)
7207 cd            enddo
7208 cd          endif
7209         enddo
7210       enddo
7211       return
7212       end
7213 C---------------------------------------------------------------------------
7214       double precision function eello4(i,j,k,l,jj,kk)
7215       implicit real*8 (a-h,o-z)
7216       include 'DIMENSIONS'
7217       include 'COMMON.IOUNITS'
7218       include 'COMMON.CHAIN'
7219       include 'COMMON.DERIV'
7220       include 'COMMON.INTERACT'
7221       include 'COMMON.CONTACTS'
7222       include 'COMMON.TORSION'
7223       include 'COMMON.VAR'
7224       include 'COMMON.GEO'
7225       double precision pizda(2,2),ggg1(3),ggg2(3)
7226 cd      if (i.ne.1 .or. j.ne.5 .or. k.ne.2 .or.l.ne.4) then
7227 cd        eello4=0.0d0
7228 cd        return
7229 cd      endif
7230 cd      print *,'eello4:',i,j,k,l,jj,kk
7231 cd      write (2,*) 'i',i,' j',j,' k',k,' l',l
7232 cd      call checkint4(i,j,k,l,jj,kk,eel4_num)
7233 cold      eij=facont_hb(jj,i)
7234 cold      ekl=facont_hb(kk,k)
7235 cold      ekont=eij*ekl
7236       eel4=-EAEA(1,1,1)-EAEA(2,2,1)
7237 cd      eel41=-EAEA(1,1,2)-EAEA(2,2,2)
7238       gcorr_loc(k-1)=gcorr_loc(k-1)
7239      &   -ekont*(EAEAderg(1,1,1,1)+EAEAderg(2,2,1,1))
7240       if (l.eq.j+1) then
7241         gcorr_loc(l-1)=gcorr_loc(l-1)
7242      &     -ekont*(EAEAderg(1,1,2,1)+EAEAderg(2,2,2,1))
7243       else
7244         gcorr_loc(j-1)=gcorr_loc(j-1)
7245      &     -ekont*(EAEAderg(1,1,2,1)+EAEAderg(2,2,2,1))
7246       endif
7247       do iii=1,2
7248         do kkk=1,5
7249           do lll=1,3
7250             derx(lll,kkk,iii)=-EAEAderx(1,1,lll,kkk,iii,1)
7251      &                        -EAEAderx(2,2,lll,kkk,iii,1)
7252 cd            derx(lll,kkk,iii)=0.0d0
7253           enddo
7254         enddo
7255       enddo
7256 cd      gcorr_loc(l-1)=0.0d0
7257 cd      gcorr_loc(j-1)=0.0d0
7258 cd      gcorr_loc(k-1)=0.0d0
7259 cd      eel4=1.0d0
7260 cd      write (iout,*)'Contacts have occurred for peptide groups',
7261 cd     &  i,j,' fcont:',eij,' eij',' and ',k,l,
7262 cd     &  ' fcont ',ekl,' eel4=',eel4,' eel4_num',16*eel4_num
7263       if (j.lt.nres-1) then
7264         j1=j+1
7265         j2=j-1
7266       else
7267         j1=j-1
7268         j2=j-2
7269       endif
7270       if (l.lt.nres-1) then
7271         l1=l+1
7272         l2=l-1
7273       else
7274         l1=l-1
7275         l2=l-2
7276       endif
7277       do ll=1,3
7278 cgrad        ggg1(ll)=eel4*g_contij(ll,1)
7279 cgrad        ggg2(ll)=eel4*g_contij(ll,2)
7280         glongij=eel4*g_contij(ll,1)+ekont*derx(ll,1,1)
7281         glongkl=eel4*g_contij(ll,2)+ekont*derx(ll,1,2)
7282 cgrad        ghalf=0.5d0*ggg1(ll)
7283         gradcorr(ll,i)=gradcorr(ll,i)+ekont*derx(ll,2,1)
7284         gradcorr(ll,i+1)=gradcorr(ll,i+1)+ekont*derx(ll,3,1)
7285         gradcorr(ll,j)=gradcorr(ll,j)+ekont*derx(ll,4,1)
7286         gradcorr(ll,j1)=gradcorr(ll,j1)+ekont*derx(ll,5,1)
7287         gradcorr_long(ll,j)=gradcorr_long(ll,j)+glongij
7288         gradcorr_long(ll,i)=gradcorr_long(ll,i)-glongij
7289 cgrad        ghalf=0.5d0*ggg2(ll)
7290         gradcorr(ll,k)=gradcorr(ll,k)+ekont*derx(ll,2,2)
7291         gradcorr(ll,k+1)=gradcorr(ll,k+1)+ekont*derx(ll,3,2)
7292         gradcorr(ll,l)=gradcorr(ll,l)+ekont*derx(ll,4,2)
7293         gradcorr(ll,l1)=gradcorr(ll,l1)+ekont*derx(ll,5,2)
7294         gradcorr_long(ll,l)=gradcorr_long(ll,l)+glongkl
7295         gradcorr_long(ll,k)=gradcorr_long(ll,k)-glongkl
7296       enddo
7297 cgrad      do m=i+1,j-1
7298 cgrad        do ll=1,3
7299 cgrad          gradcorr(ll,m)=gradcorr(ll,m)+ggg1(ll)
7300 cgrad        enddo
7301 cgrad      enddo
7302 cgrad      do m=k+1,l-1
7303 cgrad        do ll=1,3
7304 cgrad          gradcorr(ll,m)=gradcorr(ll,m)+ggg2(ll)
7305 cgrad        enddo
7306 cgrad      enddo
7307 cgrad      do m=i+2,j2
7308 cgrad        do ll=1,3
7309 cgrad          gradcorr(ll,m)=gradcorr(ll,m)+ekont*derx(ll,1,1)
7310 cgrad        enddo
7311 cgrad      enddo
7312 cgrad      do m=k+2,l2
7313 cgrad        do ll=1,3
7314 cgrad          gradcorr(ll,m)=gradcorr(ll,m)+ekont*derx(ll,1,2)
7315 cgrad        enddo
7316 cgrad      enddo 
7317 cd      do iii=1,nres-3
7318 cd        write (2,*) iii,gcorr_loc(iii)
7319 cd      enddo
7320       eello4=ekont*eel4
7321 cd      write (2,*) 'ekont',ekont
7322 cd      write (iout,*) 'eello4',ekont*eel4
7323       return
7324       end
7325 C---------------------------------------------------------------------------
7326       double precision function eello5(i,j,k,l,jj,kk)
7327       implicit real*8 (a-h,o-z)
7328       include 'DIMENSIONS'
7329       include 'COMMON.IOUNITS'
7330       include 'COMMON.CHAIN'
7331       include 'COMMON.DERIV'
7332       include 'COMMON.INTERACT'
7333       include 'COMMON.CONTACTS'
7334       include 'COMMON.TORSION'
7335       include 'COMMON.VAR'
7336       include 'COMMON.GEO'
7337       double precision pizda(2,2),auxmat(2,2),auxmat1(2,2),vv(2)
7338       double precision ggg1(3),ggg2(3)
7339 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
7340 C                                                                              C
7341 C                            Parallel chains                                   C
7342 C                                                                              C
7343 C          o             o                   o             o                   C
7344 C         /l\           / \             \   / \           / \   /              C
7345 C        /   \         /   \             \ /   \         /   \ /               C
7346 C       j| o |l1       | o |              o| o |         | o |o                C
7347 C     \  |/k\|         |/ \|  /            |/ \|         |/ \|                 C
7348 C      \i/   \         /   \ /             /   \         /   \                 C
7349 C       o    k1             o                                                  C
7350 C         (I)          (II)                (III)          (IV)                 C
7351 C                                                                              C
7352 C      eello5_1        eello5_2            eello5_3       eello5_4             C
7353 C                                                                              C
7354 C                            Antiparallel chains                               C
7355 C                                                                              C
7356 C          o             o                   o             o                   C
7357 C         /j\           / \             \   / \           / \   /              C
7358 C        /   \         /   \             \ /   \         /   \ /               C
7359 C      j1| o |l        | o |              o| o |         | o |o                C
7360 C     \  |/k\|         |/ \|  /            |/ \|         |/ \|                 C
7361 C      \i/   \         /   \ /             /   \         /   \                 C
7362 C       o     k1            o                                                  C
7363 C         (I)          (II)                (III)          (IV)                 C
7364 C                                                                              C
7365 C      eello5_1        eello5_2            eello5_3       eello5_4             C
7366 C                                                                              C
7367 C o denotes a local interaction, vertical lines an electrostatic interaction.  C
7368 C                                                                              C
7369 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
7370 cd      if (i.ne.2 .or. j.ne.6 .or. k.ne.3 .or. l.ne.5) then
7371 cd        eello5=0.0d0
7372 cd        return
7373 cd      endif
7374 cd      write (iout,*)
7375 cd     &   'EELLO5: Contacts have occurred for peptide groups',i,j,
7376 cd     &   ' and',k,l
7377       itk=itortyp(itype(k))
7378       itl=itortyp(itype(l))
7379       itj=itortyp(itype(j))
7380       eello5_1=0.0d0
7381       eello5_2=0.0d0
7382       eello5_3=0.0d0
7383       eello5_4=0.0d0
7384 cd      call checkint5(i,j,k,l,jj,kk,eel5_1_num,eel5_2_num,
7385 cd     &   eel5_3_num,eel5_4_num)
7386       do iii=1,2
7387         do kkk=1,5
7388           do lll=1,3
7389             derx(lll,kkk,iii)=0.0d0
7390           enddo
7391         enddo
7392       enddo
7393 cd      eij=facont_hb(jj,i)
7394 cd      ekl=facont_hb(kk,k)
7395 cd      ekont=eij*ekl
7396 cd      write (iout,*)'Contacts have occurred for peptide groups',
7397 cd     &  i,j,' fcont:',eij,' eij',' and ',k,l
7398 cd      goto 1111
7399 C Contribution from the graph I.
7400 cd      write (2,*) 'AEA  ',AEA(1,1,1),AEA(2,1,1),AEA(1,2,1),AEA(2,2,1)
7401 cd      write (2,*) 'AEAb2',AEAb2(1,1,1),AEAb2(2,1,1)
7402       call transpose2(EUg(1,1,k),auxmat(1,1))
7403       call matmat2(AEA(1,1,1),auxmat(1,1),pizda(1,1))
7404       vv(1)=pizda(1,1)-pizda(2,2)
7405       vv(2)=pizda(1,2)+pizda(2,1)
7406       eello5_1=scalar2(AEAb2(1,1,1),Ub2(1,k))
7407      & +0.5d0*scalar2(vv(1),Dtobr2(1,i))
7408 C Explicit gradient in virtual-dihedral angles.
7409       if (i.gt.1) g_corr5_loc(i-1)=g_corr5_loc(i-1)
7410      & +ekont*(scalar2(AEAb2derg(1,2,1,1),Ub2(1,k))
7411      & +0.5d0*scalar2(vv(1),Dtobr2der(1,i)))
7412       call transpose2(EUgder(1,1,k),auxmat1(1,1))
7413       call matmat2(AEA(1,1,1),auxmat1(1,1),pizda(1,1))
7414       vv(1)=pizda(1,1)-pizda(2,2)
7415       vv(2)=pizda(1,2)+pizda(2,1)
7416       g_corr5_loc(k-1)=g_corr5_loc(k-1)
7417      & +ekont*(scalar2(AEAb2(1,1,1),Ub2der(1,k))
7418      & +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
7419       call matmat2(AEAderg(1,1,1),auxmat(1,1),pizda(1,1))
7420       vv(1)=pizda(1,1)-pizda(2,2)
7421       vv(2)=pizda(1,2)+pizda(2,1)
7422       if (l.eq.j+1) then
7423         if (l.lt.nres-1) g_corr5_loc(l-1)=g_corr5_loc(l-1)
7424      &   +ekont*(scalar2(AEAb2derg(1,1,1,1),Ub2(1,k))
7425      &   +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
7426       else
7427         if (j.lt.nres-1) g_corr5_loc(j-1)=g_corr5_loc(j-1)
7428      &   +ekont*(scalar2(AEAb2derg(1,1,1,1),Ub2(1,k))
7429      &   +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
7430       endif 
7431 C Cartesian gradient
7432       do iii=1,2
7433         do kkk=1,5
7434           do lll=1,3
7435             call matmat2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1),
7436      &        pizda(1,1))
7437             vv(1)=pizda(1,1)-pizda(2,2)
7438             vv(2)=pizda(1,2)+pizda(2,1)
7439             derx(lll,kkk,iii)=derx(lll,kkk,iii)
7440      &       +scalar2(AEAb2derx(1,lll,kkk,iii,1,1),Ub2(1,k))
7441      &       +0.5d0*scalar2(vv(1),Dtobr2(1,i))
7442           enddo
7443         enddo
7444       enddo
7445 c      goto 1112
7446 c1111  continue
7447 C Contribution from graph II 
7448       call transpose2(EE(1,1,itk),auxmat(1,1))
7449       call matmat2(auxmat(1,1),AEA(1,1,1),pizda(1,1))
7450       vv(1)=pizda(1,1)+pizda(2,2)
7451       vv(2)=pizda(2,1)-pizda(1,2)
7452       eello5_2=scalar2(AEAb1(1,2,1),b1(1,itk))
7453      & -0.5d0*scalar2(vv(1),Ctobr(1,k))
7454 C Explicit gradient in virtual-dihedral angles.
7455       g_corr5_loc(k-1)=g_corr5_loc(k-1)
7456      & -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,k))
7457       call matmat2(auxmat(1,1),AEAderg(1,1,1),pizda(1,1))
7458       vv(1)=pizda(1,1)+pizda(2,2)
7459       vv(2)=pizda(2,1)-pizda(1,2)
7460       if (l.eq.j+1) then
7461         g_corr5_loc(l-1)=g_corr5_loc(l-1)
7462      &   +ekont*(scalar2(AEAb1derg(1,2,1),b1(1,itk))
7463      &   -0.5d0*scalar2(vv(1),Ctobr(1,k)))
7464       else
7465         g_corr5_loc(j-1)=g_corr5_loc(j-1)
7466      &   +ekont*(scalar2(AEAb1derg(1,2,1),b1(1,itk))
7467      &   -0.5d0*scalar2(vv(1),Ctobr(1,k)))
7468       endif
7469 C Cartesian gradient
7470       do iii=1,2
7471         do kkk=1,5
7472           do lll=1,3
7473             call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
7474      &        pizda(1,1))
7475             vv(1)=pizda(1,1)+pizda(2,2)
7476             vv(2)=pizda(2,1)-pizda(1,2)
7477             derx(lll,kkk,iii)=derx(lll,kkk,iii)
7478      &       +scalar2(AEAb1derx(1,lll,kkk,iii,2,1),b1(1,itk))
7479      &       -0.5d0*scalar2(vv(1),Ctobr(1,k))
7480           enddo
7481         enddo
7482       enddo
7483 cd      goto 1112
7484 cd1111  continue
7485       if (l.eq.j+1) then
7486 cd        goto 1110
7487 C Parallel orientation
7488 C Contribution from graph III
7489         call transpose2(EUg(1,1,l),auxmat(1,1))
7490         call matmat2(AEA(1,1,2),auxmat(1,1),pizda(1,1))
7491         vv(1)=pizda(1,1)-pizda(2,2)
7492         vv(2)=pizda(1,2)+pizda(2,1)
7493         eello5_3=scalar2(AEAb2(1,1,2),Ub2(1,l))
7494      &   +0.5d0*scalar2(vv(1),Dtobr2(1,j))
7495 C Explicit gradient in virtual-dihedral angles.
7496         g_corr5_loc(j-1)=g_corr5_loc(j-1)
7497      &   +ekont*(scalar2(AEAb2derg(1,2,1,2),Ub2(1,l))
7498      &   +0.5d0*scalar2(vv(1),Dtobr2der(1,j)))
7499         call matmat2(AEAderg(1,1,2),auxmat(1,1),pizda(1,1))
7500         vv(1)=pizda(1,1)-pizda(2,2)
7501         vv(2)=pizda(1,2)+pizda(2,1)
7502         g_corr5_loc(k-1)=g_corr5_loc(k-1)
7503      &   +ekont*(scalar2(AEAb2derg(1,1,1,2),Ub2(1,l))
7504      &   +0.5d0*scalar2(vv(1),Dtobr2(1,j)))
7505         call transpose2(EUgder(1,1,l),auxmat1(1,1))
7506         call matmat2(AEA(1,1,2),auxmat1(1,1),pizda(1,1))
7507         vv(1)=pizda(1,1)-pizda(2,2)
7508         vv(2)=pizda(1,2)+pizda(2,1)
7509         g_corr5_loc(l-1)=g_corr5_loc(l-1)
7510      &   +ekont*(scalar2(AEAb2(1,1,2),Ub2der(1,l))
7511      &   +0.5d0*scalar2(vv(1),Dtobr2(1,j)))
7512 C Cartesian gradient
7513         do iii=1,2
7514           do kkk=1,5
7515             do lll=1,3
7516               call matmat2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1),
7517      &          pizda(1,1))
7518               vv(1)=pizda(1,1)-pizda(2,2)
7519               vv(2)=pizda(1,2)+pizda(2,1)
7520               derx(lll,kkk,iii)=derx(lll,kkk,iii)
7521      &         +scalar2(AEAb2derx(1,lll,kkk,iii,1,2),Ub2(1,l))
7522      &         +0.5d0*scalar2(vv(1),Dtobr2(1,j))
7523             enddo
7524           enddo
7525         enddo
7526 cd        goto 1112
7527 C Contribution from graph IV
7528 cd1110    continue
7529         call transpose2(EE(1,1,itl),auxmat(1,1))
7530         call matmat2(auxmat(1,1),AEA(1,1,2),pizda(1,1))
7531         vv(1)=pizda(1,1)+pizda(2,2)
7532         vv(2)=pizda(2,1)-pizda(1,2)
7533         eello5_4=scalar2(AEAb1(1,2,2),b1(1,itl))
7534      &   -0.5d0*scalar2(vv(1),Ctobr(1,l))
7535 C Explicit gradient in virtual-dihedral angles.
7536         g_corr5_loc(l-1)=g_corr5_loc(l-1)
7537      &   -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,l))
7538         call matmat2(auxmat(1,1),AEAderg(1,1,2),pizda(1,1))
7539         vv(1)=pizda(1,1)+pizda(2,2)
7540         vv(2)=pizda(2,1)-pizda(1,2)
7541         g_corr5_loc(k-1)=g_corr5_loc(k-1)
7542      &   +ekont*(scalar2(AEAb1derg(1,2,2),b1(1,itl))
7543      &   -0.5d0*scalar2(vv(1),Ctobr(1,l)))
7544 C Cartesian gradient
7545         do iii=1,2
7546           do kkk=1,5
7547             do lll=1,3
7548               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
7549      &          pizda(1,1))
7550               vv(1)=pizda(1,1)+pizda(2,2)
7551               vv(2)=pizda(2,1)-pizda(1,2)
7552               derx(lll,kkk,iii)=derx(lll,kkk,iii)
7553      &         +scalar2(AEAb1derx(1,lll,kkk,iii,2,2),b1(1,itl))
7554      &         -0.5d0*scalar2(vv(1),Ctobr(1,l))
7555             enddo
7556           enddo
7557         enddo
7558       else
7559 C Antiparallel orientation
7560 C Contribution from graph III
7561 c        goto 1110
7562         call transpose2(EUg(1,1,j),auxmat(1,1))
7563         call matmat2(AEA(1,1,2),auxmat(1,1),pizda(1,1))
7564         vv(1)=pizda(1,1)-pizda(2,2)
7565         vv(2)=pizda(1,2)+pizda(2,1)
7566         eello5_3=scalar2(AEAb2(1,1,2),Ub2(1,j))
7567      &   +0.5d0*scalar2(vv(1),Dtobr2(1,l))
7568 C Explicit gradient in virtual-dihedral angles.
7569         g_corr5_loc(l-1)=g_corr5_loc(l-1)
7570      &   +ekont*(scalar2(AEAb2derg(1,2,1,2),Ub2(1,j))
7571      &   +0.5d0*scalar2(vv(1),Dtobr2der(1,l)))
7572         call matmat2(AEAderg(1,1,2),auxmat(1,1),pizda(1,1))
7573         vv(1)=pizda(1,1)-pizda(2,2)
7574         vv(2)=pizda(1,2)+pizda(2,1)
7575         g_corr5_loc(k-1)=g_corr5_loc(k-1)
7576      &   +ekont*(scalar2(AEAb2derg(1,1,1,2),Ub2(1,j))
7577      &   +0.5d0*scalar2(vv(1),Dtobr2(1,l)))
7578         call transpose2(EUgder(1,1,j),auxmat1(1,1))
7579         call matmat2(AEA(1,1,2),auxmat1(1,1),pizda(1,1))
7580         vv(1)=pizda(1,1)-pizda(2,2)
7581         vv(2)=pizda(1,2)+pizda(2,1)
7582         g_corr5_loc(j-1)=g_corr5_loc(j-1)
7583      &   +ekont*(scalar2(AEAb2(1,1,2),Ub2der(1,j))
7584      &   +0.5d0*scalar2(vv(1),Dtobr2(1,l)))
7585 C Cartesian gradient
7586         do iii=1,2
7587           do kkk=1,5
7588             do lll=1,3
7589               call matmat2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1),
7590      &          pizda(1,1))
7591               vv(1)=pizda(1,1)-pizda(2,2)
7592               vv(2)=pizda(1,2)+pizda(2,1)
7593               derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)
7594      &         +scalar2(AEAb2derx(1,lll,kkk,iii,1,2),Ub2(1,j))
7595      &         +0.5d0*scalar2(vv(1),Dtobr2(1,l))
7596             enddo
7597           enddo
7598         enddo
7599 cd        goto 1112
7600 C Contribution from graph IV
7601 1110    continue
7602         call transpose2(EE(1,1,itj),auxmat(1,1))
7603         call matmat2(auxmat(1,1),AEA(1,1,2),pizda(1,1))
7604         vv(1)=pizda(1,1)+pizda(2,2)
7605         vv(2)=pizda(2,1)-pizda(1,2)
7606         eello5_4=scalar2(AEAb1(1,2,2),b1(1,itj))
7607      &   -0.5d0*scalar2(vv(1),Ctobr(1,j))
7608 C Explicit gradient in virtual-dihedral angles.
7609         g_corr5_loc(j-1)=g_corr5_loc(j-1)
7610      &   -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,j))
7611         call matmat2(auxmat(1,1),AEAderg(1,1,2),pizda(1,1))
7612         vv(1)=pizda(1,1)+pizda(2,2)
7613         vv(2)=pizda(2,1)-pizda(1,2)
7614         g_corr5_loc(k-1)=g_corr5_loc(k-1)
7615      &   +ekont*(scalar2(AEAb1derg(1,2,2),b1(1,itj))
7616      &   -0.5d0*scalar2(vv(1),Ctobr(1,j)))
7617 C Cartesian gradient
7618         do iii=1,2
7619           do kkk=1,5
7620             do lll=1,3
7621               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
7622      &          pizda(1,1))
7623               vv(1)=pizda(1,1)+pizda(2,2)
7624               vv(2)=pizda(2,1)-pizda(1,2)
7625               derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)
7626      &         +scalar2(AEAb1derx(1,lll,kkk,iii,2,2),b1(1,itj))
7627      &         -0.5d0*scalar2(vv(1),Ctobr(1,j))
7628             enddo
7629           enddo
7630         enddo
7631       endif
7632 1112  continue
7633       eel5=eello5_1+eello5_2+eello5_3+eello5_4
7634 cd      if (i.eq.2 .and. j.eq.8 .and. k.eq.3 .and. l.eq.7) then
7635 cd        write (2,*) 'ijkl',i,j,k,l
7636 cd        write (2,*) 'eello5_1',eello5_1,' eello5_2',eello5_2,
7637 cd     &     ' eello5_3',eello5_3,' eello5_4',eello5_4
7638 cd      endif
7639 cd      write(iout,*) 'eello5_1',eello5_1,' eel5_1_num',16*eel5_1_num
7640 cd      write(iout,*) 'eello5_2',eello5_2,' eel5_2_num',16*eel5_2_num
7641 cd      write(iout,*) 'eello5_3',eello5_3,' eel5_3_num',16*eel5_3_num
7642 cd      write(iout,*) 'eello5_4',eello5_4,' eel5_4_num',16*eel5_4_num
7643       if (j.lt.nres-1) then
7644         j1=j+1
7645         j2=j-1
7646       else
7647         j1=j-1
7648         j2=j-2
7649       endif
7650       if (l.lt.nres-1) then
7651         l1=l+1
7652         l2=l-1
7653       else
7654         l1=l-1
7655         l2=l-2
7656       endif
7657 cd      eij=1.0d0
7658 cd      ekl=1.0d0
7659 cd      ekont=1.0d0
7660 cd      write (2,*) 'eij',eij,' ekl',ekl,' ekont',ekont
7661 C 2/11/08 AL Gradients over DC's connecting interacting sites will be
7662 C        summed up outside the subrouine as for the other subroutines 
7663 C        handling long-range interactions. The old code is commented out
7664 C        with "cgrad" to keep track of changes.
7665       do ll=1,3
7666 cgrad        ggg1(ll)=eel5*g_contij(ll,1)
7667 cgrad        ggg2(ll)=eel5*g_contij(ll,2)
7668         gradcorr5ij=eel5*g_contij(ll,1)+ekont*derx(ll,1,1)
7669         gradcorr5kl=eel5*g_contij(ll,2)+ekont*derx(ll,1,2)
7670 c        write (iout,'(a,3i3,a,5f8.3,2i3,a,5f8.3,a,f8.3)') 
7671 c     &   "ecorr5",ll,i,j," derx",derx(ll,2,1),derx(ll,3,1),derx(ll,4,1),
7672 c     &   derx(ll,5,1),k,l," derx",derx(ll,2,2),derx(ll,3,2),
7673 c     &   derx(ll,4,2),derx(ll,5,2)," ekont",ekont
7674 c        write (iout,'(a,3i3,a,3f8.3,2i3,a,3f8.3)') 
7675 c     &   "ecorr5",ll,i,j," gradcorr5",g_contij(ll,1),derx(ll,1,1),
7676 c     &   gradcorr5ij,
7677 c     &   k,l," gradcorr5",g_contij(ll,2),derx(ll,1,2),gradcorr5kl
7678 cold        ghalf=0.5d0*eel5*ekl*gacont_hbr(ll,jj,i)
7679 cgrad        ghalf=0.5d0*ggg1(ll)
7680 cd        ghalf=0.0d0
7681         gradcorr5(ll,i)=gradcorr5(ll,i)+ekont*derx(ll,2,1)
7682         gradcorr5(ll,i+1)=gradcorr5(ll,i+1)+ekont*derx(ll,3,1)
7683         gradcorr5(ll,j)=gradcorr5(ll,j)+ekont*derx(ll,4,1)
7684         gradcorr5(ll,j1)=gradcorr5(ll,j1)+ekont*derx(ll,5,1)
7685         gradcorr5_long(ll,j)=gradcorr5_long(ll,j)+gradcorr5ij
7686         gradcorr5_long(ll,i)=gradcorr5_long(ll,i)-gradcorr5ij
7687 cold        ghalf=0.5d0*eel5*eij*gacont_hbr(ll,kk,k)
7688 cgrad        ghalf=0.5d0*ggg2(ll)
7689 cd        ghalf=0.0d0
7690         gradcorr5(ll,k)=gradcorr5(ll,k)+ghalf+ekont*derx(ll,2,2)
7691         gradcorr5(ll,k+1)=gradcorr5(ll,k+1)+ekont*derx(ll,3,2)
7692         gradcorr5(ll,l)=gradcorr5(ll,l)+ghalf+ekont*derx(ll,4,2)
7693         gradcorr5(ll,l1)=gradcorr5(ll,l1)+ekont*derx(ll,5,2)
7694         gradcorr5_long(ll,l)=gradcorr5_long(ll,l)+gradcorr5kl
7695         gradcorr5_long(ll,k)=gradcorr5_long(ll,k)-gradcorr5kl
7696       enddo
7697 cd      goto 1112
7698 cgrad      do m=i+1,j-1
7699 cgrad        do ll=1,3
7700 cold          gradcorr5(ll,m)=gradcorr5(ll,m)+eel5*ekl*gacont_hbr(ll,jj,i)
7701 cgrad          gradcorr5(ll,m)=gradcorr5(ll,m)+ggg1(ll)
7702 cgrad        enddo
7703 cgrad      enddo
7704 cgrad      do m=k+1,l-1
7705 cgrad        do ll=1,3
7706 cold          gradcorr5(ll,m)=gradcorr5(ll,m)+eel5*eij*gacont_hbr(ll,kk,k)
7707 cgrad          gradcorr5(ll,m)=gradcorr5(ll,m)+ggg2(ll)
7708 cgrad        enddo
7709 cgrad      enddo
7710 c1112  continue
7711 cgrad      do m=i+2,j2
7712 cgrad        do ll=1,3
7713 cgrad          gradcorr5(ll,m)=gradcorr5(ll,m)+ekont*derx(ll,1,1)
7714 cgrad        enddo
7715 cgrad      enddo
7716 cgrad      do m=k+2,l2
7717 cgrad        do ll=1,3
7718 cgrad          gradcorr5(ll,m)=gradcorr5(ll,m)+ekont*derx(ll,1,2)
7719 cgrad        enddo
7720 cgrad      enddo 
7721 cd      do iii=1,nres-3
7722 cd        write (2,*) iii,g_corr5_loc(iii)
7723 cd      enddo
7724       eello5=ekont*eel5
7725 cd      write (2,*) 'ekont',ekont
7726 cd      write (iout,*) 'eello5',ekont*eel5
7727       return
7728       end
7729 c--------------------------------------------------------------------------
7730       double precision function eello6(i,j,k,l,jj,kk)
7731       implicit real*8 (a-h,o-z)
7732       include 'DIMENSIONS'
7733       include 'COMMON.IOUNITS'
7734       include 'COMMON.CHAIN'
7735       include 'COMMON.DERIV'
7736       include 'COMMON.INTERACT'
7737       include 'COMMON.CONTACTS'
7738       include 'COMMON.TORSION'
7739       include 'COMMON.VAR'
7740       include 'COMMON.GEO'
7741       include 'COMMON.FFIELD'
7742       double precision ggg1(3),ggg2(3)
7743 cd      if (i.ne.1 .or. j.ne.3 .or. k.ne.2 .or. l.ne.4) then
7744 cd        eello6=0.0d0
7745 cd        return
7746 cd      endif
7747 cd      write (iout,*)
7748 cd     &   'EELLO6: Contacts have occurred for peptide groups',i,j,
7749 cd     &   ' and',k,l
7750       eello6_1=0.0d0
7751       eello6_2=0.0d0
7752       eello6_3=0.0d0
7753       eello6_4=0.0d0
7754       eello6_5=0.0d0
7755       eello6_6=0.0d0
7756 cd      call checkint6(i,j,k,l,jj,kk,eel6_1_num,eel6_2_num,
7757 cd     &   eel6_3_num,eel6_4_num,eel6_5_num,eel6_6_num)
7758       do iii=1,2
7759         do kkk=1,5
7760           do lll=1,3
7761             derx(lll,kkk,iii)=0.0d0
7762           enddo
7763         enddo
7764       enddo
7765 cd      eij=facont_hb(jj,i)
7766 cd      ekl=facont_hb(kk,k)
7767 cd      ekont=eij*ekl
7768 cd      eij=1.0d0
7769 cd      ekl=1.0d0
7770 cd      ekont=1.0d0
7771       if (l.eq.j+1) then
7772         eello6_1=eello6_graph1(i,j,k,l,1,.false.)
7773         eello6_2=eello6_graph1(j,i,l,k,2,.false.)
7774         eello6_3=eello6_graph2(i,j,k,l,jj,kk,.false.)
7775         eello6_4=eello6_graph4(i,j,k,l,jj,kk,1,.false.)
7776         eello6_5=eello6_graph4(j,i,l,k,jj,kk,2,.false.)
7777         eello6_6=eello6_graph3(i,j,k,l,jj,kk,.false.)
7778       else
7779         eello6_1=eello6_graph1(i,j,k,l,1,.false.)
7780         eello6_2=eello6_graph1(l,k,j,i,2,.true.)
7781         eello6_3=eello6_graph2(i,l,k,j,jj,kk,.true.)
7782         eello6_4=eello6_graph4(i,j,k,l,jj,kk,1,.false.)
7783         if (wturn6.eq.0.0d0 .or. j.ne.i+4) then
7784           eello6_5=eello6_graph4(l,k,j,i,kk,jj,2,.true.)
7785         else
7786           eello6_5=0.0d0
7787         endif
7788         eello6_6=eello6_graph3(i,l,k,j,jj,kk,.true.)
7789       endif
7790 C If turn contributions are considered, they will be handled separately.
7791       eel6=eello6_1+eello6_2+eello6_3+eello6_4+eello6_5+eello6_6
7792 cd      write(iout,*) 'eello6_1',eello6_1!,' eel6_1_num',16*eel6_1_num
7793 cd      write(iout,*) 'eello6_2',eello6_2!,' eel6_2_num',16*eel6_2_num
7794 cd      write(iout,*) 'eello6_3',eello6_3!,' eel6_3_num',16*eel6_3_num
7795 cd      write(iout,*) 'eello6_4',eello6_4!,' eel6_4_num',16*eel6_4_num
7796 cd      write(iout,*) 'eello6_5',eello6_5!,' eel6_5_num',16*eel6_5_num
7797 cd      write(iout,*) 'eello6_6',eello6_6!,' eel6_6_num',16*eel6_6_num
7798 cd      goto 1112
7799       if (j.lt.nres-1) then
7800         j1=j+1
7801         j2=j-1
7802       else
7803         j1=j-1
7804         j2=j-2
7805       endif
7806       if (l.lt.nres-1) then
7807         l1=l+1
7808         l2=l-1
7809       else
7810         l1=l-1
7811         l2=l-2
7812       endif
7813       do ll=1,3
7814 cgrad        ggg1(ll)=eel6*g_contij(ll,1)
7815 cgrad        ggg2(ll)=eel6*g_contij(ll,2)
7816 cold        ghalf=0.5d0*eel6*ekl*gacont_hbr(ll,jj,i)
7817 cgrad        ghalf=0.5d0*ggg1(ll)
7818 cd        ghalf=0.0d0
7819         gradcorr6ij=eel6*g_contij(ll,1)+ekont*derx(ll,1,1)
7820         gradcorr6kl=eel6*g_contij(ll,2)+ekont*derx(ll,1,2)
7821         gradcorr6(ll,i)=gradcorr6(ll,i)+ekont*derx(ll,2,1)
7822         gradcorr6(ll,i+1)=gradcorr6(ll,i+1)+ekont*derx(ll,3,1)
7823         gradcorr6(ll,j)=gradcorr6(ll,j)+ekont*derx(ll,4,1)
7824         gradcorr6(ll,j1)=gradcorr6(ll,j1)+ekont*derx(ll,5,1)
7825         gradcorr6_long(ll,j)=gradcorr6_long(ll,j)+gradcorr6ij
7826         gradcorr6_long(ll,i)=gradcorr6_long(ll,i)-gradcorr6ij
7827 cgrad        ghalf=0.5d0*ggg2(ll)
7828 cold        ghalf=0.5d0*eel6*eij*gacont_hbr(ll,kk,k)
7829 cd        ghalf=0.0d0
7830         gradcorr6(ll,k)=gradcorr6(ll,k)+ekont*derx(ll,2,2)
7831         gradcorr6(ll,k+1)=gradcorr6(ll,k+1)+ekont*derx(ll,3,2)
7832         gradcorr6(ll,l)=gradcorr6(ll,l)+ekont*derx(ll,4,2)
7833         gradcorr6(ll,l1)=gradcorr6(ll,l1)+ekont*derx(ll,5,2)
7834         gradcorr6_long(ll,l)=gradcorr6_long(ll,l)+gradcorr6kl
7835         gradcorr6_long(ll,k)=gradcorr6_long(ll,k)-gradcorr6kl
7836       enddo
7837 cd      goto 1112
7838 cgrad      do m=i+1,j-1
7839 cgrad        do ll=1,3
7840 cold          gradcorr6(ll,m)=gradcorr6(ll,m)+eel6*ekl*gacont_hbr(ll,jj,i)
7841 cgrad          gradcorr6(ll,m)=gradcorr6(ll,m)+ggg1(ll)
7842 cgrad        enddo
7843 cgrad      enddo
7844 cgrad      do m=k+1,l-1
7845 cgrad        do ll=1,3
7846 cold          gradcorr6(ll,m)=gradcorr6(ll,m)+eel6*eij*gacont_hbr(ll,kk,k)
7847 cgrad          gradcorr6(ll,m)=gradcorr6(ll,m)+ggg2(ll)
7848 cgrad        enddo
7849 cgrad      enddo
7850 cgrad1112  continue
7851 cgrad      do m=i+2,j2
7852 cgrad        do ll=1,3
7853 cgrad          gradcorr6(ll,m)=gradcorr6(ll,m)+ekont*derx(ll,1,1)
7854 cgrad        enddo
7855 cgrad      enddo
7856 cgrad      do m=k+2,l2
7857 cgrad        do ll=1,3
7858 cgrad          gradcorr6(ll,m)=gradcorr6(ll,m)+ekont*derx(ll,1,2)
7859 cgrad        enddo
7860 cgrad      enddo 
7861 cd      do iii=1,nres-3
7862 cd        write (2,*) iii,g_corr6_loc(iii)
7863 cd      enddo
7864       eello6=ekont*eel6
7865 cd      write (2,*) 'ekont',ekont
7866 cd      write (iout,*) 'eello6',ekont*eel6
7867       return
7868       end
7869 c--------------------------------------------------------------------------
7870       double precision function eello6_graph1(i,j,k,l,imat,swap)
7871       implicit real*8 (a-h,o-z)
7872       include 'DIMENSIONS'
7873       include 'COMMON.IOUNITS'
7874       include 'COMMON.CHAIN'
7875       include 'COMMON.DERIV'
7876       include 'COMMON.INTERACT'
7877       include 'COMMON.CONTACTS'
7878       include 'COMMON.TORSION'
7879       include 'COMMON.VAR'
7880       include 'COMMON.GEO'
7881       double precision vv(2),vv1(2),pizda(2,2),auxmat(2,2),pizda1(2,2)
7882       logical swap
7883       logical lprn
7884       common /kutas/ lprn
7885 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
7886 C                                                                              C
7887 C      Parallel       Antiparallel                                             C
7888 C                                                                              C
7889 C          o             o                                                     C
7890 C         /l\           /j\                                                    C
7891 C        /   \         /   \                                                   C
7892 C       /| o |         | o |\                                                  C
7893 C     \ j|/k\|  /   \  |/k\|l /                                                C
7894 C      \ /   \ /     \ /   \ /                                                 C
7895 C       o     o       o     o                                                  C
7896 C       i             i                                                        C
7897 C                                                                              C
7898 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
7899       itk=itortyp(itype(k))
7900       s1= scalar2(AEAb1(1,2,imat),CUgb2(1,i))
7901       s2=-scalar2(AEAb2(1,1,imat),Ug2Db1t(1,k))
7902       s3= scalar2(AEAb2(1,1,imat),CUgb2(1,k))
7903       call transpose2(EUgC(1,1,k),auxmat(1,1))
7904       call matmat2(AEA(1,1,imat),auxmat(1,1),pizda1(1,1))
7905       vv1(1)=pizda1(1,1)-pizda1(2,2)
7906       vv1(2)=pizda1(1,2)+pizda1(2,1)
7907       s4=0.5d0*scalar2(vv1(1),Dtobr2(1,i))
7908       vv(1)=AEAb1(1,2,imat)*b1(1,itk)-AEAb1(2,2,imat)*b1(2,itk)
7909       vv(2)=AEAb1(1,2,imat)*b1(2,itk)+AEAb1(2,2,imat)*b1(1,itk)
7910       s5=scalar2(vv(1),Dtobr2(1,i))
7911 cd      write (2,*) 's1',s1,' s2',s2,' s3',s3,' s4', s4,' s5',s5
7912       eello6_graph1=-0.5d0*(s1+s2+s3+s4+s5)
7913       if (i.gt.1) g_corr6_loc(i-1)=g_corr6_loc(i-1)
7914      & -0.5d0*ekont*(scalar2(AEAb1(1,2,imat),CUgb2der(1,i))
7915      & -scalar2(AEAb2derg(1,2,1,imat),Ug2Db1t(1,k))
7916      & +scalar2(AEAb2derg(1,2,1,imat),CUgb2(1,k))
7917      & +0.5d0*scalar2(vv1(1),Dtobr2der(1,i))
7918      & +scalar2(vv(1),Dtobr2der(1,i)))
7919       call matmat2(AEAderg(1,1,imat),auxmat(1,1),pizda1(1,1))
7920       vv1(1)=pizda1(1,1)-pizda1(2,2)
7921       vv1(2)=pizda1(1,2)+pizda1(2,1)
7922       vv(1)=AEAb1derg(1,2,imat)*b1(1,itk)-AEAb1derg(2,2,imat)*b1(2,itk)
7923       vv(2)=AEAb1derg(1,2,imat)*b1(2,itk)+AEAb1derg(2,2,imat)*b1(1,itk)
7924       if (l.eq.j+1) then
7925         g_corr6_loc(l-1)=g_corr6_loc(l-1)
7926      & +ekont*(-0.5d0*(scalar2(AEAb1derg(1,2,imat),CUgb2(1,i))
7927      & -scalar2(AEAb2derg(1,1,1,imat),Ug2Db1t(1,k))
7928      & +scalar2(AEAb2derg(1,1,1,imat),CUgb2(1,k))
7929      & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))+scalar2(vv(1),Dtobr2(1,i))))
7930       else
7931         g_corr6_loc(j-1)=g_corr6_loc(j-1)
7932      & +ekont*(-0.5d0*(scalar2(AEAb1derg(1,2,imat),CUgb2(1,i))
7933      & -scalar2(AEAb2derg(1,1,1,imat),Ug2Db1t(1,k))
7934      & +scalar2(AEAb2derg(1,1,1,imat),CUgb2(1,k))
7935      & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))+scalar2(vv(1),Dtobr2(1,i))))
7936       endif
7937       call transpose2(EUgCder(1,1,k),auxmat(1,1))
7938       call matmat2(AEA(1,1,imat),auxmat(1,1),pizda1(1,1))
7939       vv1(1)=pizda1(1,1)-pizda1(2,2)
7940       vv1(2)=pizda1(1,2)+pizda1(2,1)
7941       if (k.gt.1) g_corr6_loc(k-1)=g_corr6_loc(k-1)
7942      & +ekont*(-0.5d0*(-scalar2(AEAb2(1,1,imat),Ug2Db1tder(1,k))
7943      & +scalar2(AEAb2(1,1,imat),CUgb2der(1,k))
7944      & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))))
7945       do iii=1,2
7946         if (swap) then
7947           ind=3-iii
7948         else
7949           ind=iii
7950         endif
7951         do kkk=1,5
7952           do lll=1,3
7953             s1= scalar2(AEAb1derx(1,lll,kkk,iii,2,imat),CUgb2(1,i))
7954             s2=-scalar2(AEAb2derx(1,lll,kkk,iii,1,imat),Ug2Db1t(1,k))
7955             s3= scalar2(AEAb2derx(1,lll,kkk,iii,1,imat),CUgb2(1,k))
7956             call transpose2(EUgC(1,1,k),auxmat(1,1))
7957             call matmat2(AEAderx(1,1,lll,kkk,iii,imat),auxmat(1,1),
7958      &        pizda1(1,1))
7959             vv1(1)=pizda1(1,1)-pizda1(2,2)
7960             vv1(2)=pizda1(1,2)+pizda1(2,1)
7961             s4=0.5d0*scalar2(vv1(1),Dtobr2(1,i))
7962             vv(1)=AEAb1derx(1,lll,kkk,iii,2,imat)*b1(1,itk)
7963      &       -AEAb1derx(2,lll,kkk,iii,2,imat)*b1(2,itk)
7964             vv(2)=AEAb1derx(1,lll,kkk,iii,2,imat)*b1(2,itk)
7965      &       +AEAb1derx(2,lll,kkk,iii,2,imat)*b1(1,itk)
7966             s5=scalar2(vv(1),Dtobr2(1,i))
7967             derx(lll,kkk,ind)=derx(lll,kkk,ind)-0.5d0*(s1+s2+s3+s4+s5)
7968           enddo
7969         enddo
7970       enddo
7971       return
7972       end
7973 c----------------------------------------------------------------------------
7974       double precision function eello6_graph2(i,j,k,l,jj,kk,swap)
7975       implicit real*8 (a-h,o-z)
7976       include 'DIMENSIONS'
7977       include 'COMMON.IOUNITS'
7978       include 'COMMON.CHAIN'
7979       include 'COMMON.DERIV'
7980       include 'COMMON.INTERACT'
7981       include 'COMMON.CONTACTS'
7982       include 'COMMON.TORSION'
7983       include 'COMMON.VAR'
7984       include 'COMMON.GEO'
7985       logical swap
7986       double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2),
7987      & auxvec1(2),auxvec2(1),auxmat1(2,2)
7988       logical lprn
7989       common /kutas/ lprn
7990 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
7991 C                                                                              C
7992 C      Parallel       Antiparallel                                             C
7993 C                                                                              C
7994 C          o             o                                                     C
7995 C     \   /l\           /j\   /                                                C
7996 C      \ /   \         /   \ /                                                 C
7997 C       o| o |         | o |o                                                  C
7998 C     \ j|/k\|      \  |/k\|l                                                  C
7999 C      \ /   \       \ /   \                                                   C
8000 C       o             o                                                        C
8001 C       i             i                                                        C
8002 C                                                                              C
8003 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
8004 cd      write (2,*) 'eello6_graph2: i,',i,' j',j,' k',k,' l',l
8005 C AL 7/4/01 s1 would occur in the sixth-order moment, 
8006 C           but not in a cluster cumulant
8007 #ifdef MOMENT
8008       s1=dip(1,jj,i)*dip(1,kk,k)
8009 #endif
8010       call matvec2(ADtEA1(1,1,1),Ub2(1,k),auxvec(1))
8011       s2=-0.5d0*scalar2(Ub2(1,i),auxvec(1))
8012       call matvec2(ADtEA(1,1,2),Ub2(1,l),auxvec1(1))
8013       s3=-0.5d0*scalar2(Ub2(1,j),auxvec1(1))
8014       call transpose2(EUg(1,1,k),auxmat(1,1))
8015       call matmat2(ADtEA1(1,1,1),auxmat(1,1),pizda(1,1))
8016       vv(1)=pizda(1,1)-pizda(2,2)
8017       vv(2)=pizda(1,2)+pizda(2,1)
8018       s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
8019 cd      write (2,*) 'eello6_graph2:','s1',s1,' s2',s2,' s3',s3,' s4',s4
8020 #ifdef MOMENT
8021       eello6_graph2=-(s1+s2+s3+s4)
8022 #else
8023       eello6_graph2=-(s2+s3+s4)
8024 #endif
8025 c      eello6_graph2=-s3
8026 C Derivatives in gamma(i-1)
8027       if (i.gt.1) then
8028 #ifdef MOMENT
8029         s1=dipderg(1,jj,i)*dip(1,kk,k)
8030 #endif
8031         s2=-0.5d0*scalar2(Ub2der(1,i),auxvec(1))
8032         call matvec2(ADtEAderg(1,1,1,2),Ub2(1,l),auxvec2(1))
8033         s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
8034         s4=-0.25d0*scalar2(vv(1),Dtobr2der(1,i))
8035 #ifdef MOMENT
8036         g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s1+s2+s3+s4)
8037 #else
8038         g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s2+s3+s4)
8039 #endif
8040 c        g_corr6_loc(i-1)=g_corr6_loc(i-1)-s3
8041       endif
8042 C Derivatives in gamma(k-1)
8043 #ifdef MOMENT
8044       s1=dip(1,jj,i)*dipderg(1,kk,k)
8045 #endif
8046       call matvec2(ADtEA1(1,1,1),Ub2der(1,k),auxvec2(1))
8047       s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
8048       call matvec2(ADtEAderg(1,1,2,2),Ub2(1,l),auxvec2(1))
8049       s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
8050       call transpose2(EUgder(1,1,k),auxmat1(1,1))
8051       call matmat2(ADtEA1(1,1,1),auxmat1(1,1),pizda(1,1))
8052       vv(1)=pizda(1,1)-pizda(2,2)
8053       vv(2)=pizda(1,2)+pizda(2,1)
8054       s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
8055 #ifdef MOMENT
8056       g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s1+s2+s3+s4)
8057 #else
8058       g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s2+s3+s4)
8059 #endif
8060 c      g_corr6_loc(k-1)=g_corr6_loc(k-1)-s3
8061 C Derivatives in gamma(j-1) or gamma(l-1)
8062       if (j.gt.1) then
8063 #ifdef MOMENT
8064         s1=dipderg(3,jj,i)*dip(1,kk,k) 
8065 #endif
8066         call matvec2(ADtEA1derg(1,1,1,1),Ub2(1,k),auxvec2(1))
8067         s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
8068         s3=-0.5d0*scalar2(Ub2der(1,j),auxvec1(1))
8069         call matmat2(ADtEA1derg(1,1,1,1),auxmat(1,1),pizda(1,1))
8070         vv(1)=pizda(1,1)-pizda(2,2)
8071         vv(2)=pizda(1,2)+pizda(2,1)
8072         s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
8073 #ifdef MOMENT
8074         if (swap) then
8075           g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*s1
8076         else
8077           g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*s1
8078         endif
8079 #endif
8080         g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*(s2+s3+s4)
8081 c        g_corr6_loc(j-1)=g_corr6_loc(j-1)-s3
8082       endif
8083 C Derivatives in gamma(l-1) or gamma(j-1)
8084       if (l.gt.1) then 
8085 #ifdef MOMENT
8086         s1=dip(1,jj,i)*dipderg(3,kk,k)
8087 #endif
8088         call matvec2(ADtEA1derg(1,1,2,1),Ub2(1,k),auxvec2(1))
8089         s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
8090         call matvec2(ADtEA(1,1,2),Ub2der(1,l),auxvec2(1))
8091         s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
8092         call matmat2(ADtEA1derg(1,1,2,1),auxmat(1,1),pizda(1,1))
8093         vv(1)=pizda(1,1)-pizda(2,2)
8094         vv(2)=pizda(1,2)+pizda(2,1)
8095         s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
8096 #ifdef MOMENT
8097         if (swap) then
8098           g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*s1
8099         else
8100           g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*s1
8101         endif
8102 #endif
8103         g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s3+s4)
8104 c        g_corr6_loc(l-1)=g_corr6_loc(l-1)-s3
8105       endif
8106 C Cartesian derivatives.
8107       if (lprn) then
8108         write (2,*) 'In eello6_graph2'
8109         do iii=1,2
8110           write (2,*) 'iii=',iii
8111           do kkk=1,5
8112             write (2,*) 'kkk=',kkk
8113             do jjj=1,2
8114               write (2,'(3(2f10.5),5x)') 
8115      &        ((ADtEA1derx(jjj,mmm,lll,kkk,iii,1),mmm=1,2),lll=1,3)
8116             enddo
8117           enddo
8118         enddo
8119       endif
8120       do iii=1,2
8121         do kkk=1,5
8122           do lll=1,3
8123 #ifdef MOMENT
8124             if (iii.eq.1) then
8125               s1=dipderx(lll,kkk,1,jj,i)*dip(1,kk,k)
8126             else
8127               s1=dip(1,jj,i)*dipderx(lll,kkk,1,kk,k)
8128             endif
8129 #endif
8130             call matvec2(ADtEA1derx(1,1,lll,kkk,iii,1),Ub2(1,k),
8131      &        auxvec(1))
8132             s2=-0.5d0*scalar2(Ub2(1,i),auxvec(1))
8133             call matvec2(ADtEAderx(1,1,lll,kkk,iii,2),Ub2(1,l),
8134      &        auxvec(1))
8135             s3=-0.5d0*scalar2(Ub2(1,j),auxvec(1))
8136             call transpose2(EUg(1,1,k),auxmat(1,1))
8137             call matmat2(ADtEA1derx(1,1,lll,kkk,iii,1),auxmat(1,1),
8138      &        pizda(1,1))
8139             vv(1)=pizda(1,1)-pizda(2,2)
8140             vv(2)=pizda(1,2)+pizda(2,1)
8141             s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
8142 cd            write (2,*) 's1',s1,' s2',s2,' s3',s3,' s4',s4
8143 #ifdef MOMENT
8144             derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
8145 #else
8146             derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
8147 #endif
8148             if (swap) then
8149               derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
8150             else
8151               derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
8152             endif
8153           enddo
8154         enddo
8155       enddo
8156       return
8157       end
8158 c----------------------------------------------------------------------------
8159       double precision function eello6_graph3(i,j,k,l,jj,kk,swap)
8160       implicit real*8 (a-h,o-z)
8161       include 'DIMENSIONS'
8162       include 'COMMON.IOUNITS'
8163       include 'COMMON.CHAIN'
8164       include 'COMMON.DERIV'
8165       include 'COMMON.INTERACT'
8166       include 'COMMON.CONTACTS'
8167       include 'COMMON.TORSION'
8168       include 'COMMON.VAR'
8169       include 'COMMON.GEO'
8170       double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2)
8171       logical swap
8172 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
8173 C                                                                              C
8174 C      Parallel       Antiparallel                                             C
8175 C                                                                              C
8176 C          o             o                                                     C
8177 C         /l\   /   \   /j\                                                    C 
8178 C        /   \ /     \ /   \                                                   C
8179 C       /| o |o       o| o |\                                                  C
8180 C       j|/k\|  /      |/k\|l /                                                C
8181 C        /   \ /       /   \ /                                                 C
8182 C       /     o       /     o                                                  C
8183 C       i             i                                                        C
8184 C                                                                              C
8185 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
8186 C
8187 C 4/7/01 AL Component s1 was removed, because it pertains to the respective 
8188 C           energy moment and not to the cluster cumulant.
8189       iti=itortyp(itype(i))
8190       if (j.lt.nres-1) then
8191         itj1=itortyp(itype(j+1))
8192       else
8193         itj1=ntortyp+1
8194       endif
8195       itk=itortyp(itype(k))
8196       itk1=itortyp(itype(k+1))
8197       if (l.lt.nres-1) then
8198         itl1=itortyp(itype(l+1))
8199       else
8200         itl1=ntortyp+1
8201       endif
8202 #ifdef MOMENT
8203       s1=dip(4,jj,i)*dip(4,kk,k)
8204 #endif
8205       call matvec2(AECA(1,1,1),b1(1,itk1),auxvec(1))
8206       s2=0.5d0*scalar2(b1(1,itk),auxvec(1))
8207       call matvec2(AECA(1,1,2),b1(1,itl1),auxvec(1))
8208       s3=0.5d0*scalar2(b1(1,itj1),auxvec(1))
8209       call transpose2(EE(1,1,itk),auxmat(1,1))
8210       call matmat2(auxmat(1,1),AECA(1,1,1),pizda(1,1))
8211       vv(1)=pizda(1,1)+pizda(2,2)
8212       vv(2)=pizda(2,1)-pizda(1,2)
8213       s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
8214 cd      write (2,*) 'eello6_graph3:','s1',s1,' s2',s2,' s3',s3,' s4',s4,
8215 cd     & "sum",-(s2+s3+s4)
8216 #ifdef MOMENT
8217       eello6_graph3=-(s1+s2+s3+s4)
8218 #else
8219       eello6_graph3=-(s2+s3+s4)
8220 #endif
8221 c      eello6_graph3=-s4
8222 C Derivatives in gamma(k-1)
8223       call matvec2(AECAderg(1,1,2),b1(1,itl1),auxvec(1))
8224       s3=0.5d0*scalar2(b1(1,itj1),auxvec(1))
8225       s4=-0.25d0*scalar2(vv(1),Ctobrder(1,k))
8226       g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s3+s4)
8227 C Derivatives in gamma(l-1)
8228       call matvec2(AECAderg(1,1,1),b1(1,itk1),auxvec(1))
8229       s2=0.5d0*scalar2(b1(1,itk),auxvec(1))
8230       call matmat2(auxmat(1,1),AECAderg(1,1,1),pizda(1,1))
8231       vv(1)=pizda(1,1)+pizda(2,2)
8232       vv(2)=pizda(2,1)-pizda(1,2)
8233       s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
8234       g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s4) 
8235 C Cartesian derivatives.
8236       do iii=1,2
8237         do kkk=1,5
8238           do lll=1,3
8239 #ifdef MOMENT
8240             if (iii.eq.1) then
8241               s1=dipderx(lll,kkk,4,jj,i)*dip(4,kk,k)
8242             else
8243               s1=dip(4,jj,i)*dipderx(lll,kkk,4,kk,k)
8244             endif
8245 #endif
8246             call matvec2(AECAderx(1,1,lll,kkk,iii,1),b1(1,itk1),
8247      &        auxvec(1))
8248             s2=0.5d0*scalar2(b1(1,itk),auxvec(1))
8249             call matvec2(AECAderx(1,1,lll,kkk,iii,2),b1(1,itl1),
8250      &        auxvec(1))
8251             s3=0.5d0*scalar2(b1(1,itj1),auxvec(1))
8252             call matmat2(auxmat(1,1),AECAderx(1,1,lll,kkk,iii,1),
8253      &        pizda(1,1))
8254             vv(1)=pizda(1,1)+pizda(2,2)
8255             vv(2)=pizda(2,1)-pizda(1,2)
8256             s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
8257 #ifdef MOMENT
8258             derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
8259 #else
8260             derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
8261 #endif
8262             if (swap) then
8263               derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
8264             else
8265               derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
8266             endif
8267 c            derx(lll,kkk,iii)=derx(lll,kkk,iii)-s4
8268           enddo
8269         enddo
8270       enddo
8271       return
8272       end
8273 c----------------------------------------------------------------------------
8274       double precision function eello6_graph4(i,j,k,l,jj,kk,imat,swap)
8275       implicit real*8 (a-h,o-z)
8276       include 'DIMENSIONS'
8277       include 'COMMON.IOUNITS'
8278       include 'COMMON.CHAIN'
8279       include 'COMMON.DERIV'
8280       include 'COMMON.INTERACT'
8281       include 'COMMON.CONTACTS'
8282       include 'COMMON.TORSION'
8283       include 'COMMON.VAR'
8284       include 'COMMON.GEO'
8285       include 'COMMON.FFIELD'
8286       double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2),
8287      & auxvec1(2),auxmat1(2,2)
8288       logical swap
8289 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
8290 C                                                                              C
8291 C      Parallel       Antiparallel                                             C
8292 C                                                                              C
8293 C          o             o                                                     C
8294 C         /l\   /   \   /j\                                                    C
8295 C        /   \ /     \ /   \                                                   C
8296 C       /| o |o       o| o |\                                                  C
8297 C     \ j|/k\|      \  |/k\|l                                                  C
8298 C      \ /   \       \ /   \                                                   C
8299 C       o     \       o     \                                                  C
8300 C       i             i                                                        C
8301 C                                                                              C
8302 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
8303 C
8304 C 4/7/01 AL Component s1 was removed, because it pertains to the respective 
8305 C           energy moment and not to the cluster cumulant.
8306 cd      write (2,*) 'eello_graph4: wturn6',wturn6
8307       iti=itortyp(itype(i))
8308       itj=itortyp(itype(j))
8309       if (j.lt.nres-1) then
8310         itj1=itortyp(itype(j+1))
8311       else
8312         itj1=ntortyp+1
8313       endif
8314       itk=itortyp(itype(k))
8315       if (k.lt.nres-1) then
8316         itk1=itortyp(itype(k+1))
8317       else
8318         itk1=ntortyp+1
8319       endif
8320       itl=itortyp(itype(l))
8321       if (l.lt.nres-1) then
8322         itl1=itortyp(itype(l+1))
8323       else
8324         itl1=ntortyp+1
8325       endif
8326 cd      write (2,*) 'eello6_graph4:','i',i,' j',j,' k',k,' l',l
8327 cd      write (2,*) 'iti',iti,' itj',itj,' itj1',itj1,' itk',itk,
8328 cd     & ' itl',itl,' itl1',itl1
8329 #ifdef MOMENT
8330       if (imat.eq.1) then
8331         s1=dip(3,jj,i)*dip(3,kk,k)
8332       else
8333         s1=dip(2,jj,j)*dip(2,kk,l)
8334       endif
8335 #endif
8336       call matvec2(AECA(1,1,imat),Ub2(1,k),auxvec(1))
8337       s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
8338       if (j.eq.l+1) then
8339         call matvec2(ADtEA1(1,1,3-imat),b1(1,itj1),auxvec1(1))
8340         s3=-0.5d0*scalar2(b1(1,itj),auxvec1(1))
8341       else
8342         call matvec2(ADtEA1(1,1,3-imat),b1(1,itl1),auxvec1(1))
8343         s3=-0.5d0*scalar2(b1(1,itl),auxvec1(1))
8344       endif
8345       call transpose2(EUg(1,1,k),auxmat(1,1))
8346       call matmat2(AECA(1,1,imat),auxmat(1,1),pizda(1,1))
8347       vv(1)=pizda(1,1)-pizda(2,2)
8348       vv(2)=pizda(2,1)+pizda(1,2)
8349       s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
8350 cd      write (2,*) 'eello6_graph4:','s1',s1,' s2',s2,' s3',s3,' s4',s4
8351 #ifdef MOMENT
8352       eello6_graph4=-(s1+s2+s3+s4)
8353 #else
8354       eello6_graph4=-(s2+s3+s4)
8355 #endif
8356 C Derivatives in gamma(i-1)
8357       if (i.gt.1) then
8358 #ifdef MOMENT
8359         if (imat.eq.1) then
8360           s1=dipderg(2,jj,i)*dip(3,kk,k)
8361         else
8362           s1=dipderg(4,jj,j)*dip(2,kk,l)
8363         endif
8364 #endif
8365         s2=0.5d0*scalar2(Ub2der(1,i),auxvec(1))
8366         if (j.eq.l+1) then
8367           call matvec2(ADtEA1derg(1,1,1,3-imat),b1(1,itj1),auxvec1(1))
8368           s3=-0.5d0*scalar2(b1(1,itj),auxvec1(1))
8369         else
8370           call matvec2(ADtEA1derg(1,1,1,3-imat),b1(1,itl1),auxvec1(1))
8371           s3=-0.5d0*scalar2(b1(1,itl),auxvec1(1))
8372         endif
8373         s4=0.25d0*scalar2(vv(1),Dtobr2der(1,i))
8374         if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
8375 cd          write (2,*) 'turn6 derivatives'
8376 #ifdef MOMENT
8377           gel_loc_turn6(i-1)=gel_loc_turn6(i-1)-ekont*(s1+s2+s3+s4)
8378 #else
8379           gel_loc_turn6(i-1)=gel_loc_turn6(i-1)-ekont*(s2+s3+s4)
8380 #endif
8381         else
8382 #ifdef MOMENT
8383           g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s1+s2+s3+s4)
8384 #else
8385           g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s2+s3+s4)
8386 #endif
8387         endif
8388       endif
8389 C Derivatives in gamma(k-1)
8390 #ifdef MOMENT
8391       if (imat.eq.1) then
8392         s1=dip(3,jj,i)*dipderg(2,kk,k)
8393       else
8394         s1=dip(2,jj,j)*dipderg(4,kk,l)
8395       endif
8396 #endif
8397       call matvec2(AECA(1,1,imat),Ub2der(1,k),auxvec1(1))
8398       s2=0.5d0*scalar2(Ub2(1,i),auxvec1(1))
8399       if (j.eq.l+1) then
8400         call matvec2(ADtEA1derg(1,1,2,3-imat),b1(1,itj1),auxvec1(1))
8401         s3=-0.5d0*scalar2(b1(1,itj),auxvec1(1))
8402       else
8403         call matvec2(ADtEA1derg(1,1,2,3-imat),b1(1,itl1),auxvec1(1))
8404         s3=-0.5d0*scalar2(b1(1,itl),auxvec1(1))
8405       endif
8406       call transpose2(EUgder(1,1,k),auxmat1(1,1))
8407       call matmat2(AECA(1,1,imat),auxmat1(1,1),pizda(1,1))
8408       vv(1)=pizda(1,1)-pizda(2,2)
8409       vv(2)=pizda(2,1)+pizda(1,2)
8410       s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
8411       if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
8412 #ifdef MOMENT
8413         gel_loc_turn6(k-1)=gel_loc_turn6(k-1)-ekont*(s1+s2+s3+s4)
8414 #else
8415         gel_loc_turn6(k-1)=gel_loc_turn6(k-1)-ekont*(s2+s3+s4)
8416 #endif
8417       else
8418 #ifdef MOMENT
8419         g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s1+s2+s3+s4)
8420 #else
8421         g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s2+s3+s4)
8422 #endif
8423       endif
8424 C Derivatives in gamma(j-1) or gamma(l-1)
8425       if (l.eq.j+1 .and. l.gt.1) then
8426         call matvec2(AECAderg(1,1,imat),Ub2(1,k),auxvec(1))
8427         s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
8428         call matmat2(AECAderg(1,1,imat),auxmat(1,1),pizda(1,1))
8429         vv(1)=pizda(1,1)-pizda(2,2)
8430         vv(2)=pizda(2,1)+pizda(1,2)
8431         s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
8432         g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s4)
8433       else if (j.gt.1) then
8434         call matvec2(AECAderg(1,1,imat),Ub2(1,k),auxvec(1))
8435         s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
8436         call matmat2(AECAderg(1,1,imat),auxmat(1,1),pizda(1,1))
8437         vv(1)=pizda(1,1)-pizda(2,2)
8438         vv(2)=pizda(2,1)+pizda(1,2)
8439         s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
8440         if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
8441           gel_loc_turn6(j-1)=gel_loc_turn6(j-1)-ekont*(s2+s4)
8442         else
8443           g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*(s2+s4)
8444         endif
8445       endif
8446 C Cartesian derivatives.
8447       do iii=1,2
8448         do kkk=1,5
8449           do lll=1,3
8450 #ifdef MOMENT
8451             if (iii.eq.1) then
8452               if (imat.eq.1) then
8453                 s1=dipderx(lll,kkk,3,jj,i)*dip(3,kk,k)
8454               else
8455                 s1=dipderx(lll,kkk,2,jj,j)*dip(2,kk,l)
8456               endif
8457             else
8458               if (imat.eq.1) then
8459                 s1=dip(3,jj,i)*dipderx(lll,kkk,3,kk,k)
8460               else
8461                 s1=dip(2,jj,j)*dipderx(lll,kkk,2,kk,l)
8462               endif
8463             endif
8464 #endif
8465             call matvec2(AECAderx(1,1,lll,kkk,iii,imat),Ub2(1,k),
8466      &        auxvec(1))
8467             s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
8468             if (j.eq.l+1) then
8469               call matvec2(ADtEA1derx(1,1,lll,kkk,iii,3-imat),
8470      &          b1(1,itj1),auxvec(1))
8471               s3=-0.5d0*scalar2(b1(1,itj),auxvec(1))
8472             else
8473               call matvec2(ADtEA1derx(1,1,lll,kkk,iii,3-imat),
8474      &          b1(1,itl1),auxvec(1))
8475               s3=-0.5d0*scalar2(b1(1,itl),auxvec(1))
8476             endif
8477             call matmat2(AECAderx(1,1,lll,kkk,iii,imat),auxmat(1,1),
8478      &        pizda(1,1))
8479             vv(1)=pizda(1,1)-pizda(2,2)
8480             vv(2)=pizda(2,1)+pizda(1,2)
8481             s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
8482             if (swap) then
8483               if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
8484 #ifdef MOMENT
8485                 derx_turn(lll,kkk,3-iii)=derx_turn(lll,kkk,3-iii)
8486      &             -(s1+s2+s4)
8487 #else
8488                 derx_turn(lll,kkk,3-iii)=derx_turn(lll,kkk,3-iii)
8489      &             -(s2+s4)
8490 #endif
8491                 derx_turn(lll,kkk,iii)=derx_turn(lll,kkk,iii)-s3
8492               else
8493 #ifdef MOMENT
8494                 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-(s1+s2+s4)
8495 #else
8496                 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-(s2+s4)
8497 #endif
8498                 derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
8499               endif
8500             else
8501 #ifdef MOMENT
8502               derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
8503 #else
8504               derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
8505 #endif
8506               if (l.eq.j+1) then
8507                 derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
8508               else 
8509                 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
8510               endif
8511             endif 
8512           enddo
8513         enddo
8514       enddo
8515       return
8516       end
8517 c----------------------------------------------------------------------------
8518       double precision function eello_turn6(i,jj,kk)
8519       implicit real*8 (a-h,o-z)
8520       include 'DIMENSIONS'
8521       include 'COMMON.IOUNITS'
8522       include 'COMMON.CHAIN'
8523       include 'COMMON.DERIV'
8524       include 'COMMON.INTERACT'
8525       include 'COMMON.CONTACTS'
8526       include 'COMMON.TORSION'
8527       include 'COMMON.VAR'
8528       include 'COMMON.GEO'
8529       double precision vtemp1(2),vtemp2(2),vtemp3(2),vtemp4(2),
8530      &  atemp(2,2),auxmat(2,2),achuj_temp(2,2),gtemp(2,2),gvec(2),
8531      &  ggg1(3),ggg2(3)
8532       double precision vtemp1d(2),vtemp2d(2),vtemp3d(2),vtemp4d(2),
8533      &  atempd(2,2),auxmatd(2,2),achuj_tempd(2,2),gtempd(2,2),gvecd(2)
8534 C 4/7/01 AL Components s1, s8, and s13 were removed, because they pertain to
8535 C           the respective energy moment and not to the cluster cumulant.
8536       s1=0.0d0
8537       s8=0.0d0
8538       s13=0.0d0
8539 c
8540       eello_turn6=0.0d0
8541       j=i+4
8542       k=i+1
8543       l=i+3
8544       iti=itortyp(itype(i))
8545       itk=itortyp(itype(k))
8546       itk1=itortyp(itype(k+1))
8547       itl=itortyp(itype(l))
8548       itj=itortyp(itype(j))
8549 cd      write (2,*) 'itk',itk,' itk1',itk1,' itl',itl,' itj',itj
8550 cd      write (2,*) 'i',i,' k',k,' j',j,' l',l
8551 cd      if (i.ne.1 .or. j.ne.3 .or. k.ne.2 .or. l.ne.4) then
8552 cd        eello6=0.0d0
8553 cd        return
8554 cd      endif
8555 cd      write (iout,*)
8556 cd     &   'EELLO6: Contacts have occurred for peptide groups',i,j,
8557 cd     &   ' and',k,l
8558 cd      call checkint_turn6(i,jj,kk,eel_turn6_num)
8559       do iii=1,2
8560         do kkk=1,5
8561           do lll=1,3
8562             derx_turn(lll,kkk,iii)=0.0d0
8563           enddo
8564         enddo
8565       enddo
8566 cd      eij=1.0d0
8567 cd      ekl=1.0d0
8568 cd      ekont=1.0d0
8569       eello6_5=eello6_graph4(l,k,j,i,kk,jj,2,.true.)
8570 cd      eello6_5=0.0d0
8571 cd      write (2,*) 'eello6_5',eello6_5
8572 #ifdef MOMENT
8573       call transpose2(AEA(1,1,1),auxmat(1,1))
8574       call matmat2(EUg(1,1,i+1),auxmat(1,1),auxmat(1,1))
8575       ss1=scalar2(Ub2(1,i+2),b1(1,itl))
8576       s1 = (auxmat(1,1)+auxmat(2,2))*ss1
8577 #endif
8578       call matvec2(EUg(1,1,i+2),b1(1,itl),vtemp1(1))
8579       call matvec2(AEA(1,1,1),vtemp1(1),vtemp1(1))
8580       s2 = scalar2(b1(1,itk),vtemp1(1))
8581 #ifdef MOMENT
8582       call transpose2(AEA(1,1,2),atemp(1,1))
8583       call matmat2(atemp(1,1),EUg(1,1,i+4),atemp(1,1))
8584       call matvec2(Ug2(1,1,i+2),dd(1,1,itk1),vtemp2(1))
8585       s8 = -(atemp(1,1)+atemp(2,2))*scalar2(cc(1,1,itl),vtemp2(1))
8586 #endif
8587       call matmat2(EUg(1,1,i+3),AEA(1,1,2),auxmat(1,1))
8588       call matvec2(auxmat(1,1),Ub2(1,i+4),vtemp3(1))
8589       s12 = scalar2(Ub2(1,i+2),vtemp3(1))
8590 #ifdef MOMENT
8591       call transpose2(a_chuj(1,1,kk,i+1),achuj_temp(1,1))
8592       call matmat2(achuj_temp(1,1),EUg(1,1,i+2),gtemp(1,1))
8593       call matmat2(gtemp(1,1),EUg(1,1,i+3),gtemp(1,1)) 
8594       call matvec2(a_chuj(1,1,jj,i),Ub2(1,i+4),vtemp4(1)) 
8595       ss13 = scalar2(b1(1,itk),vtemp4(1))
8596       s13 = (gtemp(1,1)+gtemp(2,2))*ss13
8597 #endif
8598 c      write (2,*) 's1,s2,s8,s12,s13',s1,s2,s8,s12,s13
8599 c      s1=0.0d0
8600 c      s2=0.0d0
8601 c      s8=0.0d0
8602 c      s12=0.0d0
8603 c      s13=0.0d0
8604       eel_turn6 = eello6_5 - 0.5d0*(s1+s2+s12+s8+s13)
8605 C Derivatives in gamma(i+2)
8606       s1d =0.0d0
8607       s8d =0.0d0
8608 #ifdef MOMENT
8609       call transpose2(AEA(1,1,1),auxmatd(1,1))
8610       call matmat2(EUgder(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
8611       s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
8612       call transpose2(AEAderg(1,1,2),atempd(1,1))
8613       call matmat2(atempd(1,1),EUg(1,1,i+4),atempd(1,1))
8614       s8d = -(atempd(1,1)+atempd(2,2))*scalar2(cc(1,1,itl),vtemp2(1))
8615 #endif
8616       call matmat2(EUg(1,1,i+3),AEAderg(1,1,2),auxmatd(1,1))
8617       call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
8618       s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
8619 c      s1d=0.0d0
8620 c      s2d=0.0d0
8621 c      s8d=0.0d0
8622 c      s12d=0.0d0
8623 c      s13d=0.0d0
8624       gel_loc_turn6(i)=gel_loc_turn6(i)-0.5d0*ekont*(s1d+s8d+s12d)
8625 C Derivatives in gamma(i+3)
8626 #ifdef MOMENT
8627       call transpose2(AEA(1,1,1),auxmatd(1,1))
8628       call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
8629       ss1d=scalar2(Ub2der(1,i+2),b1(1,itl))
8630       s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1d
8631 #endif
8632       call matvec2(EUgder(1,1,i+2),b1(1,itl),vtemp1d(1))
8633       call matvec2(AEA(1,1,1),vtemp1d(1),vtemp1d(1))
8634       s2d = scalar2(b1(1,itk),vtemp1d(1))
8635 #ifdef MOMENT
8636       call matvec2(Ug2der(1,1,i+2),dd(1,1,itk1),vtemp2d(1))
8637       s8d = -(atemp(1,1)+atemp(2,2))*scalar2(cc(1,1,itl),vtemp2d(1))
8638 #endif
8639       s12d = scalar2(Ub2der(1,i+2),vtemp3(1))
8640 #ifdef MOMENT
8641       call matmat2(achuj_temp(1,1),EUgder(1,1,i+2),gtempd(1,1))
8642       call matmat2(gtempd(1,1),EUg(1,1,i+3),gtempd(1,1)) 
8643       s13d = (gtempd(1,1)+gtempd(2,2))*ss13
8644 #endif
8645 c      s1d=0.0d0
8646 c      s2d=0.0d0
8647 c      s8d=0.0d0
8648 c      s12d=0.0d0
8649 c      s13d=0.0d0
8650 #ifdef MOMENT
8651       gel_loc_turn6(i+1)=gel_loc_turn6(i+1)
8652      &               -0.5d0*ekont*(s1d+s2d+s8d+s12d+s13d)
8653 #else
8654       gel_loc_turn6(i+1)=gel_loc_turn6(i+1)
8655      &               -0.5d0*ekont*(s2d+s12d)
8656 #endif
8657 C Derivatives in gamma(i+4)
8658       call matmat2(EUgder(1,1,i+3),AEA(1,1,2),auxmatd(1,1))
8659       call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
8660       s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
8661 #ifdef MOMENT
8662       call matmat2(achuj_temp(1,1),EUg(1,1,i+2),gtempd(1,1))
8663       call matmat2(gtempd(1,1),EUgder(1,1,i+3),gtempd(1,1)) 
8664       s13d = (gtempd(1,1)+gtempd(2,2))*ss13
8665 #endif
8666 c      s1d=0.0d0
8667 c      s2d=0.0d0
8668 c      s8d=0.0d0
8669 C      s12d=0.0d0
8670 c      s13d=0.0d0
8671 #ifdef MOMENT
8672       gel_loc_turn6(i+2)=gel_loc_turn6(i+2)-0.5d0*ekont*(s12d+s13d)
8673 #else
8674       gel_loc_turn6(i+2)=gel_loc_turn6(i+2)-0.5d0*ekont*(s12d)
8675 #endif
8676 C Derivatives in gamma(i+5)
8677 #ifdef MOMENT
8678       call transpose2(AEAderg(1,1,1),auxmatd(1,1))
8679       call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
8680       s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
8681 #endif
8682       call matvec2(EUg(1,1,i+2),b1(1,itl),vtemp1d(1))
8683       call matvec2(AEAderg(1,1,1),vtemp1d(1),vtemp1d(1))
8684       s2d = scalar2(b1(1,itk),vtemp1d(1))
8685 #ifdef MOMENT
8686       call transpose2(AEA(1,1,2),atempd(1,1))
8687       call matmat2(atempd(1,1),EUgder(1,1,i+4),atempd(1,1))
8688       s8d = -(atempd(1,1)+atempd(2,2))*scalar2(cc(1,1,itl),vtemp2(1))
8689 #endif
8690       call matvec2(auxmat(1,1),Ub2der(1,i+4),vtemp3d(1))
8691       s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
8692 #ifdef MOMENT
8693       call matvec2(a_chuj(1,1,jj,i),Ub2der(1,i+4),vtemp4d(1)) 
8694       ss13d = scalar2(b1(1,itk),vtemp4d(1))
8695       s13d = (gtemp(1,1)+gtemp(2,2))*ss13d
8696 #endif
8697 c      s1d=0.0d0
8698 c      s2d=0.0d0
8699 c      s8d=0.0d0
8700 c      s12d=0.0d0
8701 c      s13d=0.0d0
8702 #ifdef MOMENT
8703       gel_loc_turn6(i+3)=gel_loc_turn6(i+3)
8704      &               -0.5d0*ekont*(s1d+s2d+s8d+s12d+s13d)
8705 #else
8706       gel_loc_turn6(i+3)=gel_loc_turn6(i+3)
8707      &               -0.5d0*ekont*(s2d+s12d)
8708 #endif
8709 C Cartesian derivatives
8710       do iii=1,2
8711         do kkk=1,5
8712           do lll=1,3
8713 #ifdef MOMENT
8714             call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmatd(1,1))
8715             call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
8716             s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
8717 #endif
8718             call matvec2(EUg(1,1,i+2),b1(1,itl),vtemp1(1))
8719             call matvec2(AEAderx(1,1,lll,kkk,iii,1),vtemp1(1),
8720      &          vtemp1d(1))
8721             s2d = scalar2(b1(1,itk),vtemp1d(1))
8722 #ifdef MOMENT
8723             call transpose2(AEAderx(1,1,lll,kkk,iii,2),atempd(1,1))
8724             call matmat2(atempd(1,1),EUg(1,1,i+4),atempd(1,1))
8725             s8d = -(atempd(1,1)+atempd(2,2))*
8726      &           scalar2(cc(1,1,itl),vtemp2(1))
8727 #endif
8728             call matmat2(EUg(1,1,i+3),AEAderx(1,1,lll,kkk,iii,2),
8729      &           auxmatd(1,1))
8730             call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
8731             s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
8732 c      s1d=0.0d0
8733 c      s2d=0.0d0
8734 c      s8d=0.0d0
8735 c      s12d=0.0d0
8736 c      s13d=0.0d0
8737 #ifdef MOMENT
8738             derx_turn(lll,kkk,iii) = derx_turn(lll,kkk,iii) 
8739      &        - 0.5d0*(s1d+s2d)
8740 #else
8741             derx_turn(lll,kkk,iii) = derx_turn(lll,kkk,iii) 
8742      &        - 0.5d0*s2d
8743 #endif
8744 #ifdef MOMENT
8745             derx_turn(lll,kkk,3-iii) = derx_turn(lll,kkk,3-iii) 
8746      &        - 0.5d0*(s8d+s12d)
8747 #else
8748             derx_turn(lll,kkk,3-iii) = derx_turn(lll,kkk,3-iii) 
8749      &        - 0.5d0*s12d
8750 #endif
8751           enddo
8752         enddo
8753       enddo
8754 #ifdef MOMENT
8755       do kkk=1,5
8756         do lll=1,3
8757           call transpose2(a_chuj_der(1,1,lll,kkk,kk,i+1),
8758      &      achuj_tempd(1,1))
8759           call matmat2(achuj_tempd(1,1),EUg(1,1,i+2),gtempd(1,1))
8760           call matmat2(gtempd(1,1),EUg(1,1,i+3),gtempd(1,1)) 
8761           s13d=(gtempd(1,1)+gtempd(2,2))*ss13
8762           derx_turn(lll,kkk,2) = derx_turn(lll,kkk,2)-0.5d0*s13d
8763           call matvec2(a_chuj_der(1,1,lll,kkk,jj,i),Ub2(1,i+4),
8764      &      vtemp4d(1)) 
8765           ss13d = scalar2(b1(1,itk),vtemp4d(1))
8766           s13d = (gtemp(1,1)+gtemp(2,2))*ss13d
8767           derx_turn(lll,kkk,1) = derx_turn(lll,kkk,1)-0.5d0*s13d
8768         enddo
8769       enddo
8770 #endif
8771 cd      write(iout,*) 'eel6_turn6',eel_turn6,' eel_turn6_num',
8772 cd     &  16*eel_turn6_num
8773 cd      goto 1112
8774       if (j.lt.nres-1) then
8775         j1=j+1
8776         j2=j-1
8777       else
8778         j1=j-1
8779         j2=j-2
8780       endif
8781       if (l.lt.nres-1) then
8782         l1=l+1
8783         l2=l-1
8784       else
8785         l1=l-1
8786         l2=l-2
8787       endif
8788       do ll=1,3
8789 cgrad        ggg1(ll)=eel_turn6*g_contij(ll,1)
8790 cgrad        ggg2(ll)=eel_turn6*g_contij(ll,2)
8791 cgrad        ghalf=0.5d0*ggg1(ll)
8792 cd        ghalf=0.0d0
8793         gturn6ij=eel_turn6*g_contij(ll,1)+ekont*derx_turn(ll,1,1)
8794         gturn6kl=eel_turn6*g_contij(ll,2)+ekont*derx_turn(ll,1,2)
8795         gcorr6_turn(ll,i)=gcorr6_turn(ll,i)!+ghalf
8796      &    +ekont*derx_turn(ll,2,1)
8797         gcorr6_turn(ll,i+1)=gcorr6_turn(ll,i+1)+ekont*derx_turn(ll,3,1)
8798         gcorr6_turn(ll,j)=gcorr6_turn(ll,j)!+ghalf
8799      &    +ekont*derx_turn(ll,4,1)
8800         gcorr6_turn(ll,j1)=gcorr6_turn(ll,j1)+ekont*derx_turn(ll,5,1)
8801         gcorr6_turn_long(ll,j)=gcorr6_turn_long(ll,j)+gturn6ij
8802         gcorr6_turn_long(ll,i)=gcorr6_turn_long(ll,i)-gturn6ij
8803 cgrad        ghalf=0.5d0*ggg2(ll)
8804 cd        ghalf=0.0d0
8805         gcorr6_turn(ll,k)=gcorr6_turn(ll,k)!+ghalf
8806      &    +ekont*derx_turn(ll,2,2)
8807         gcorr6_turn(ll,k+1)=gcorr6_turn(ll,k+1)+ekont*derx_turn(ll,3,2)
8808         gcorr6_turn(ll,l)=gcorr6_turn(ll,l)!+ghalf
8809      &    +ekont*derx_turn(ll,4,2)
8810         gcorr6_turn(ll,l1)=gcorr6_turn(ll,l1)+ekont*derx_turn(ll,5,2)
8811         gcorr6_turn_long(ll,l)=gcorr6_turn_long(ll,l)+gturn6kl
8812         gcorr6_turn_long(ll,k)=gcorr6_turn_long(ll,k)-gturn6kl
8813       enddo
8814 cd      goto 1112
8815 cgrad      do m=i+1,j-1
8816 cgrad        do ll=1,3
8817 cgrad          gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ggg1(ll)
8818 cgrad        enddo
8819 cgrad      enddo
8820 cgrad      do m=k+1,l-1
8821 cgrad        do ll=1,3
8822 cgrad          gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ggg2(ll)
8823 cgrad        enddo
8824 cgrad      enddo
8825 cgrad1112  continue
8826 cgrad      do m=i+2,j2
8827 cgrad        do ll=1,3
8828 cgrad          gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ekont*derx_turn(ll,1,1)
8829 cgrad        enddo
8830 cgrad      enddo
8831 cgrad      do m=k+2,l2
8832 cgrad        do ll=1,3
8833 cgrad          gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ekont*derx_turn(ll,1,2)
8834 cgrad        enddo
8835 cgrad      enddo 
8836 cd      do iii=1,nres-3
8837 cd        write (2,*) iii,g_corr6_loc(iii)
8838 cd      enddo
8839       eello_turn6=ekont*eel_turn6
8840 cd      write (2,*) 'ekont',ekont
8841 cd      write (2,*) 'eel_turn6',ekont*eel_turn6
8842       return
8843       end
8844
8845 C-----------------------------------------------------------------------------
8846       double precision function scalar(u,v)
8847 !DIR$ INLINEALWAYS scalar
8848 #ifndef OSF
8849 cDEC$ ATTRIBUTES FORCEINLINE::scalar
8850 #endif
8851       implicit none
8852       double precision u(3),v(3)
8853 cd      double precision sc
8854 cd      integer i
8855 cd      sc=0.0d0
8856 cd      do i=1,3
8857 cd        sc=sc+u(i)*v(i)
8858 cd      enddo
8859 cd      scalar=sc
8860
8861       scalar=u(1)*v(1)+u(2)*v(2)+u(3)*v(3)
8862       return
8863       end
8864 crc-------------------------------------------------
8865       SUBROUTINE MATVEC2(A1,V1,V2)
8866 !DIR$ INLINEALWAYS MATVEC2
8867 #ifndef OSF
8868 cDEC$ ATTRIBUTES FORCEINLINE::MATVEC2
8869 #endif
8870       implicit real*8 (a-h,o-z)
8871       include 'DIMENSIONS'
8872       DIMENSION A1(2,2),V1(2),V2(2)
8873 c      DO 1 I=1,2
8874 c        VI=0.0
8875 c        DO 3 K=1,2
8876 c    3     VI=VI+A1(I,K)*V1(K)
8877 c        Vaux(I)=VI
8878 c    1 CONTINUE
8879
8880       vaux1=a1(1,1)*v1(1)+a1(1,2)*v1(2)
8881       vaux2=a1(2,1)*v1(1)+a1(2,2)*v1(2)
8882
8883       v2(1)=vaux1
8884       v2(2)=vaux2
8885       END
8886 C---------------------------------------
8887       SUBROUTINE MATMAT2(A1,A2,A3)
8888 #ifndef OSF
8889 cDEC$ ATTRIBUTES FORCEINLINE::MATMAT2  
8890 #endif
8891       implicit real*8 (a-h,o-z)
8892       include 'DIMENSIONS'
8893       DIMENSION A1(2,2),A2(2,2),A3(2,2)
8894 c      DIMENSION AI3(2,2)
8895 c        DO  J=1,2
8896 c          A3IJ=0.0
8897 c          DO K=1,2
8898 c           A3IJ=A3IJ+A1(I,K)*A2(K,J)
8899 c          enddo
8900 c          A3(I,J)=A3IJ
8901 c       enddo
8902 c      enddo
8903
8904       ai3_11=a1(1,1)*a2(1,1)+a1(1,2)*a2(2,1)
8905       ai3_12=a1(1,1)*a2(1,2)+a1(1,2)*a2(2,2)
8906       ai3_21=a1(2,1)*a2(1,1)+a1(2,2)*a2(2,1)
8907       ai3_22=a1(2,1)*a2(1,2)+a1(2,2)*a2(2,2)
8908
8909       A3(1,1)=AI3_11
8910       A3(2,1)=AI3_21
8911       A3(1,2)=AI3_12
8912       A3(2,2)=AI3_22
8913       END
8914
8915 c-------------------------------------------------------------------------
8916       double precision function scalar2(u,v)
8917 !DIR$ INLINEALWAYS scalar2
8918       implicit none
8919       double precision u(2),v(2)
8920       double precision sc
8921       integer i
8922       scalar2=u(1)*v(1)+u(2)*v(2)
8923       return
8924       end
8925
8926 C-----------------------------------------------------------------------------
8927
8928       subroutine transpose2(a,at)
8929 !DIR$ INLINEALWAYS transpose2
8930 #ifndef OSF
8931 cDEC$ ATTRIBUTES FORCEINLINE::transpose2
8932 #endif
8933       implicit none
8934       double precision a(2,2),at(2,2)
8935       at(1,1)=a(1,1)
8936       at(1,2)=a(2,1)
8937       at(2,1)=a(1,2)
8938       at(2,2)=a(2,2)
8939       return
8940       end
8941 c--------------------------------------------------------------------------
8942       subroutine transpose(n,a,at)
8943       implicit none
8944       integer n,i,j
8945       double precision a(n,n),at(n,n)
8946       do i=1,n
8947         do j=1,n
8948           at(j,i)=a(i,j)
8949         enddo
8950       enddo
8951       return
8952       end
8953 C---------------------------------------------------------------------------
8954       subroutine prodmat3(a1,a2,kk,transp,prod)
8955 !DIR$ INLINEALWAYS prodmat3
8956 #ifndef OSF
8957 cDEC$ ATTRIBUTES FORCEINLINE::prodmat3
8958 #endif
8959       implicit none
8960       integer i,j
8961       double precision a1(2,2),a2(2,2),a2t(2,2),kk(2,2),prod(2,2)
8962       logical transp
8963 crc      double precision auxmat(2,2),prod_(2,2)
8964
8965       if (transp) then
8966 crc        call transpose2(kk(1,1),auxmat(1,1))
8967 crc        call matmat2(a1(1,1),auxmat(1,1),auxmat(1,1))
8968 crc        call matmat2(auxmat(1,1),a2(1,1),prod_(1,1)) 
8969         
8970            prod(1,1)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(1,2))*a2(1,1)
8971      & +(a1(1,1)*kk(2,1)+a1(1,2)*kk(2,2))*a2(2,1)
8972            prod(1,2)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(1,2))*a2(1,2)
8973      & +(a1(1,1)*kk(2,1)+a1(1,2)*kk(2,2))*a2(2,2)
8974            prod(2,1)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(1,2))*a2(1,1)
8975      & +(a1(2,1)*kk(2,1)+a1(2,2)*kk(2,2))*a2(2,1)
8976            prod(2,2)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(1,2))*a2(1,2)
8977      & +(a1(2,1)*kk(2,1)+a1(2,2)*kk(2,2))*a2(2,2)
8978
8979       else
8980 crc        call matmat2(a1(1,1),kk(1,1),auxmat(1,1))
8981 crc        call matmat2(auxmat(1,1),a2(1,1),prod_(1,1))
8982
8983            prod(1,1)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(2,1))*a2(1,1)
8984      &  +(a1(1,1)*kk(1,2)+a1(1,2)*kk(2,2))*a2(2,1)
8985            prod(1,2)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(2,1))*a2(1,2)
8986      &  +(a1(1,1)*kk(1,2)+a1(1,2)*kk(2,2))*a2(2,2)
8987            prod(2,1)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(2,1))*a2(1,1)
8988      &  +(a1(2,1)*kk(1,2)+a1(2,2)*kk(2,2))*a2(2,1)
8989            prod(2,2)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(2,1))*a2(1,2)
8990      &  +(a1(2,1)*kk(1,2)+a1(2,2)*kk(2,2))*a2(2,2)
8991
8992       endif
8993 c      call transpose2(a2(1,1),a2t(1,1))
8994
8995 crc      print *,transp
8996 crc      print *,((prod_(i,j),i=1,2),j=1,2)
8997 crc      print *,((prod(i,j),i=1,2),j=1,2)
8998
8999       return
9000       end
9001