c7c2c2fc2ecc6a22d63bf95679950ec88a4c3aab
[unres.git] / source / cluster / wham / src-M / energy_p_new.F
1       subroutine etotal(energia,fact)
2       implicit real*8 (a-h,o-z)
3       include 'DIMENSIONS'
4       include 'sizesclu.dat'
5
6 #ifndef ISNAN
7       external proc_proc
8 #endif
9 #ifdef WINPGI
10 cMS$ATTRIBUTES C ::  proc_proc
11 #endif
12
13       include 'COMMON.IOUNITS'
14       double precision energia(0:max_ene),energia1(0:max_ene+1)
15 #ifdef MPL
16       include 'COMMON.INFO'
17       external d_vadd
18       integer ready
19 #endif
20       include 'COMMON.FFIELD'
21       include 'COMMON.DERIV'
22       include 'COMMON.INTERACT'
23       include 'COMMON.SBRIDGE'
24       include 'COMMON.CHAIN'
25       double precision fact(6)
26 cd      write(iout, '(a,i2)')'Calling etotal ipot=',ipot
27 cd    print *,'nnt=',nnt,' nct=',nct
28 C
29 C Compute the side-chain and electrostatic interaction energy
30 C
31       goto (101,102,103,104,105) ipot
32 C Lennard-Jones potential.
33   101 call elj(evdw,evdw_t)
34 cd    print '(a)','Exit ELJ'
35       goto 106
36 C Lennard-Jones-Kihara potential (shifted).
37   102 call eljk(evdw,evdw_t)
38       goto 106
39 C Berne-Pechukas potential (dilated LJ, angular dependence).
40   103 call ebp(evdw,evdw_t)
41       goto 106
42 C Gay-Berne potential (shifted LJ, angular dependence).
43   104 call egb(evdw,evdw_t)
44       goto 106
45 C Gay-Berne-Vorobjev potential (shifted LJ, angular dependence).
46   105 call egbv(evdw,evdw_t)
47 C
48 C Calculate electrostatic (H-bonding) energy of the main chain.
49 C
50   106 call eelec(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
51 C
52 C Calculate excluded-volume interaction energy between peptide groups
53 C and side chains.
54 C
55       call escp(evdw2,evdw2_14)
56 c
57 c Calculate the bond-stretching energy
58 c
59       call ebond(estr)
60 c      write (iout,*) "estr",estr
61
62 C Calculate the disulfide-bridge and other energy and the contributions
63 C from other distance constraints.
64 cd    print *,'Calling EHPB'
65       call edis(ehpb)
66 cd    print *,'EHPB exitted succesfully.'
67 C
68 C Calculate the virtual-bond-angle energy.
69 C
70       call ebend(ebe)
71 cd    print *,'Bend energy finished.'
72 C
73 C Calculate the SC local energy.
74 C
75       call esc(escloc)
76 cd    print *,'SCLOC energy finished.'
77 C
78 C Calculate the virtual-bond torsional energy.
79 C
80 cd    print *,'nterm=',nterm
81       call etor(etors,edihcnstr,fact(1))
82 C
83 C 6/23/01 Calculate double-torsional energy
84 C
85       call etor_d(etors_d,fact(2))
86 C
87 C 21/5/07 Calculate local sicdechain correlation energy
88 C
89       call eback_sc_corr(esccor)
90
91 C 12/1/95 Multi-body terms
92 C
93       n_corr=0
94       n_corr1=0
95       if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0 
96      &    .or. wturn6.gt.0.0d0) then
97 c         print *,"calling multibody_eello"
98          call multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,n_corr1)
99 c         write (*,*) 'n_corr=',n_corr,' n_corr1=',n_corr1
100 c         print *,ecorr,ecorr5,ecorr6,eturn6
101       endif
102       if (wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) then
103          call multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
104       endif
105 c      write (iout,*) "ft(6)",fact(6)," evdw",evdw," evdw_t",evdw_t
106 #ifdef SPLITELE
107       etot=wsc*(evdw+fact(6)*evdw_t)+wscp*evdw2+welec*fact(1)*ees
108      & +wvdwpp*evdw1
109      & +wang*ebe+wtor*fact(1)*etors+wscloc*escloc
110      & +wstrain*ehpb+nss*ebr+wcorr*fact(3)*ecorr+wcorr5*fact(4)*ecorr5
111      & +wcorr6*fact(5)*ecorr6+wturn4*fact(3)*eello_turn4
112      & +wturn3*fact(2)*eello_turn3+wturn6*fact(5)*eturn6
113      & +wel_loc*fact(2)*eel_loc+edihcnstr+wtor_d*fact(2)*etors_d
114      & +wbond*estr+wsccor*fact(1)*esccor
115 #else
116       etot=wsc*(evdw+fact(6)*evdw_t)+wscp*evdw2
117      & +welec*fact(1)*(ees+evdw1)
118      & +wang*ebe+wtor*fact(1)*etors+wscloc*escloc
119      & +wstrain*ehpb+nss*ebr+wcorr*fact(3)*ecorr+wcorr5*fact(4)*ecorr5
120      & +wcorr6*fact(5)*ecorr6+wturn4*fact(3)*eello_turn4
121      & +wturn3*fact(2)*eello_turn3+wturn6*fact(5)*eturn6
122      & +wel_loc*fact(2)*eel_loc+edihcnstr+wtor_d*fact(2)*etors_d
123      & +wbond*estr+wsccor*fact(1)*esccor
124 #endif
125       energia(0)=etot
126       energia(1)=evdw
127 c      call enerprint(energia(0),frac)
128 #ifdef SCP14
129       energia(2)=evdw2-evdw2_14
130       energia(17)=evdw2_14
131 #else
132       energia(2)=evdw2
133       energia(17)=0.0d0
134 #endif
135 #ifdef SPLITELE
136       energia(3)=ees
137       energia(16)=evdw1
138 #else
139       energia(3)=ees+evdw1
140       energia(16)=0.0d0
141 #endif
142       energia(4)=ecorr
143       energia(5)=ecorr5
144       energia(6)=ecorr6
145       energia(7)=eel_loc
146       energia(8)=eello_turn3
147       energia(9)=eello_turn4
148       energia(10)=eturn6
149       energia(11)=ebe
150       energia(12)=escloc
151       energia(13)=etors
152       energia(14)=etors_d
153       energia(15)=ehpb
154       energia(18)=estr
155       energia(19)=esccor
156       energia(20)=edihcnstr
157       energia(21)=evdw_t
158 c detecting NaNQ
159 #ifdef ISNAN
160 #ifdef AIX
161       if (isnan(etot).ne.0) energia(0)=1.0d+99
162 #else
163       if (isnan(etot)) energia(0)=1.0d+99
164 #endif
165 #else
166       i=0
167 #ifdef WINPGI
168       idumm=proc_proc(etot,i)
169 #else
170       call proc_proc(etot,i)
171 #endif
172       if(i.eq.1)energia(0)=1.0d+99
173 #endif
174 #ifdef MPL
175 c     endif
176 #endif
177       if (calc_grad) then
178 C
179 C Sum up the components of the Cartesian gradient.
180 C
181 #ifdef SPLITELE
182       do i=1,nct
183         do j=1,3
184           gradc(j,i,icg)=wsc*gvdwc(j,i)+wscp*gvdwc_scp(j,i)+
185      &                welec*fact(1)*gelc(j,i)+wvdwpp*gvdwpp(j,i)+
186      &                wbond*gradb(j,i)+
187      &                wstrain*ghpbc(j,i)+
188      &                wcorr*fact(3)*gradcorr(j,i)+
189      &                wel_loc*fact(2)*gel_loc(j,i)+
190      &                wturn3*fact(2)*gcorr3_turn(j,i)+
191      &                wturn4*fact(3)*gcorr4_turn(j,i)+
192      &                wcorr5*fact(4)*gradcorr5(j,i)+
193      &                wcorr6*fact(5)*gradcorr6(j,i)+
194      &                wturn6*fact(5)*gcorr6_turn(j,i)+
195      &                wsccor*fact(2)*gsccorc(j,i)
196           gradx(j,i,icg)=wsc*gvdwx(j,i)+wscp*gradx_scp(j,i)+
197      &                  wbond*gradbx(j,i)+
198      &                  wstrain*ghpbx(j,i)+wcorr*gradxorr(j,i)+
199      &                  wsccor*fact(2)*gsccorx(j,i)
200         enddo
201 #else
202       do i=1,nct
203         do j=1,3
204           gradc(j,i,icg)=wsc*gvdwc(j,i)+wscp*gvdwc_scp(j,i)+
205      &                welec*fact(1)*gelc(j,i)+wstrain*ghpbc(j,i)+
206      &                wbond*gradb(j,i)+
207      &                wcorr*fact(3)*gradcorr(j,i)+
208      &                wel_loc*fact(2)*gel_loc(j,i)+
209      &                wturn3*fact(2)*gcorr3_turn(j,i)+
210      &                wturn4*fact(3)*gcorr4_turn(j,i)+
211      &                wcorr5*fact(4)*gradcorr5(j,i)+
212      &                wcorr6*fact(5)*gradcorr6(j,i)+
213      &                wturn6*fact(5)*gcorr6_turn(j,i)+
214      &                wsccor*fact(2)*gsccorc(j,i)
215           gradx(j,i,icg)=wsc*gvdwx(j,i)+wscp*gradx_scp(j,i)+
216      &                  wbond*gradbx(j,i)+
217      &                  wstrain*ghpbx(j,i)+wcorr*gradxorr(j,i)+
218      &                  wsccor*fact(1)*gsccorx(j,i)
219         enddo
220 #endif
221       enddo
222
223
224       do i=1,nres-3
225         gloc(i,icg)=gloc(i,icg)+wcorr*fact(3)*gcorr_loc(i)
226      &   +wcorr5*fact(4)*g_corr5_loc(i)
227      &   +wcorr6*fact(5)*g_corr6_loc(i)
228      &   +wturn4*fact(3)*gel_loc_turn4(i)
229      &   +wturn3*fact(2)*gel_loc_turn3(i)
230      &   +wturn6*fact(5)*gel_loc_turn6(i)
231      &   +wel_loc*fact(2)*gel_loc_loc(i)
232      &   +wsccor*fact(1)*gsccor_loc(i)
233       enddo
234       endif
235       return
236       end
237 C------------------------------------------------------------------------
238       subroutine enerprint(energia,fact)
239       implicit real*8 (a-h,o-z)
240       include 'DIMENSIONS'
241       include 'sizesclu.dat'
242       include 'COMMON.IOUNITS'
243       include 'COMMON.FFIELD'
244       include 'COMMON.SBRIDGE'
245       double precision energia(0:max_ene),fact(6)
246       etot=energia(0)
247       evdw=energia(1)+fact(6)*energia(21)
248 #ifdef SCP14
249       evdw2=energia(2)+energia(17)
250 #else
251       evdw2=energia(2)
252 #endif
253       ees=energia(3)
254 #ifdef SPLITELE
255       evdw1=energia(16)
256 #endif
257       ecorr=energia(4)
258       ecorr5=energia(5)
259       ecorr6=energia(6)
260       eel_loc=energia(7)
261       eello_turn3=energia(8)
262       eello_turn4=energia(9)
263       eello_turn6=energia(10)
264       ebe=energia(11)
265       escloc=energia(12)
266       etors=energia(13)
267       etors_d=energia(14)
268       ehpb=energia(15)
269       esccor=energia(19)
270       edihcnstr=energia(20)
271       estr=energia(18)
272 #ifdef SPLITELE
273       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec*fact(1),evdw1,
274      &  wvdwpp,
275      &  estr,wbond,ebe,wang,escloc,wscloc,etors,wtor*fact(1),
276      &  etors_d,wtor_d*fact(2),ehpb,wstrain,
277      &  ecorr,wcorr*fact(3),ecorr5,wcorr5*fact(4),ecorr6,wcorr6*fact(5),
278      &  eel_loc,wel_loc*fact(2),eello_turn3,wturn3*fact(2),
279      &  eello_turn4,wturn4*fact(3),eello_turn6,wturn6*fact(5),
280      &  esccor,wsccor*fact(1),edihcnstr,ebr*nss,etot
281    10 format (/'Virtual-chain energies:'//
282      & 'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/
283      & 'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/
284      & 'EES=   ',1pE16.6,' WEIGHT=',1pD16.6,' (p-p elec)'/
285      & 'EVDWPP=',1pE16.6,' WEIGHT=',1pD16.6,' (p-p VDW)'/
286      & 'ESTR=  ',1pE16.6,' WEIGHT=',1pD16.6,' (stretching)'/
287      & 'EBE=   ',1pE16.6,' WEIGHT=',1pD16.6,' (bending)'/
288      & 'ESC=   ',1pE16.6,' WEIGHT=',1pD16.6,' (SC local)'/
289      & 'ETORS= ',1pE16.6,' WEIGHT=',1pD16.6,' (torsional)'/
290      & 'ETORSD=',1pE16.6,' WEIGHT=',1pD16.6,' (double torsional)'/
291      & 'EHBP=  ',1pE16.6,' WEIGHT=',1pD16.6,
292      & ' (SS bridges & dist. cnstr.)'/
293      & 'ECORR4=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
294      & 'ECORR5=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
295      & 'ECORR6=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
296      & 'EELLO= ',1pE16.6,' WEIGHT=',1pD16.6,' (electrostatic-local)'/
297      & 'ETURN3=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 3rd order)'/
298      & 'ETURN4=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 4th order)'/
299      & 'ETURN6=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 6th order)'/
300      & 'ESCCOR=',1pE16.6,' WEIGHT=',1pD16.6,' (backbone-rotamer corr)'/
301      & 'EDIHC= ',1pE16.6,' (dihedral angle constraints)'/
302      & 'ESS=   ',1pE16.6,' (disulfide-bridge intrinsic energy)'/ 
303      & 'ETOT=  ',1pE16.6,' (total)')
304 #else
305       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec*fact(1),estr,wbond,
306      &  ebe,wang,escloc,wscloc,etors,wtor*fact(1),etors_d,wtor_d*fact2,
307      &  ehpb,wstrain,ecorr,wcorr*fact(3),ecorr5,wcorr5*fact(4),
308      &  ecorr6,wcorr6*fact(5),eel_loc,wel_loc*fact(2),
309      &  eello_turn3,wturn3*fact(2),eello_turn4,wturn4*fact(3),
310      &  eello_turn6,wturn6*fact(5),esccor*fact(1),wsccor,
311      &  edihcnstr,ebr*nss,etot
312    10 format (/'Virtual-chain energies:'//
313      & 'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/
314      & 'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/
315      & 'EES=   ',1pE16.6,' WEIGHT=',1pD16.6,' (p-p)'/
316      & 'ESTR=  ',1pE16.6,' WEIGHT=',1pD16.6,' (stretching)'/
317      & 'EBE=   ',1pE16.6,' WEIGHT=',1pD16.6,' (bending)'/
318      & 'ESC=   ',1pE16.6,' WEIGHT=',1pD16.6,' (SC local)'/
319      & 'ETORS= ',1pE16.6,' WEIGHT=',1pD16.6,' (torsional)'/
320      & 'ETORSD=',1pE16.6,' WEIGHT=',1pD16.6,' (double torsional)'/
321      & 'EHBP=  ',1pE16.6,' WEIGHT=',1pD16.6,
322      & ' (SS bridges & dist. cnstr.)'/
323      & 'ECORR4=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
324      & 'ECORR5=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
325      & 'ECORR6=',1pE16.6,' WEIGHT=',1pD16.6,' (multi-body)'/
326      & 'EELLO= ',1pE16.6,' WEIGHT=',1pD16.6,' (electrostatic-local)'/
327      & 'ETURN3=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 3rd order)'/
328      & 'ETURN4=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 4th order)'/
329      & 'ETURN6=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 6th order)'/
330      & 'ESCCOR=',1pE16.6,' WEIGHT=',1pD16.6,' (backbone-rotamer corr)'/
331      & 'EDIHC= ',1pE16.6,' (dihedral angle constraints)'/
332      & 'ESS=   ',1pE16.6,' (disulfide-bridge intrinsic energy)'/ 
333      & 'ETOT=  ',1pE16.6,' (total)')
334 #endif
335       return
336       end
337 C-----------------------------------------------------------------------
338       subroutine elj(evdw,evdw_t)
339 C
340 C This subroutine calculates the interaction energy of nonbonded side chains
341 C assuming the LJ potential of interaction.
342 C
343       implicit real*8 (a-h,o-z)
344       include 'DIMENSIONS'
345       include 'sizesclu.dat'
346       include "DIMENSIONS.COMPAR"
347       parameter (accur=1.0d-10)
348       include 'COMMON.GEO'
349       include 'COMMON.VAR'
350       include 'COMMON.LOCAL'
351       include 'COMMON.CHAIN'
352       include 'COMMON.DERIV'
353       include 'COMMON.INTERACT'
354       include 'COMMON.TORSION'
355       include 'COMMON.SBRIDGE'
356       include 'COMMON.NAMES'
357       include 'COMMON.IOUNITS'
358       include 'COMMON.CONTACTS'
359       dimension gg(3)
360       integer icant
361       external icant
362 cd    print *,'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
363       evdw=0.0D0
364       evdw_t=0.0d0
365       do i=iatsc_s,iatsc_e
366         itypi=itype(i)
367         if (itypi.eq.21) cycle
368         itypi1=itype(i+1)
369         xi=c(1,nres+i)
370         yi=c(2,nres+i)
371         zi=c(3,nres+i)
372 C Change 12/1/95
373         num_conti=0
374 C
375 C Calculate SC interaction energy.
376 C
377         do iint=1,nint_gr(i)
378 cd        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
379 cd   &                  'iend=',iend(i,iint)
380           do j=istart(i,iint),iend(i,iint)
381             itypj=itype(j)
382             if (itypj.eq.21) cycle
383             xj=c(1,nres+j)-xi
384             yj=c(2,nres+j)-yi
385             zj=c(3,nres+j)-zi
386 C Change 12/1/95 to calculate four-body interactions
387             rij=xj*xj+yj*yj+zj*zj
388             rrij=1.0D0/rij
389 c           write (iout,*)'i=',i,' j=',j,' itypi=',itypi,' itypj=',itypj
390             eps0ij=eps(itypi,itypj)
391             fac=rrij**expon2
392             e1=fac*fac*aa(itypi,itypj)
393             e2=fac*bb(itypi,itypj)
394             evdwij=e1+e2
395             ij=icant(itypi,itypj)
396 cd          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
397 cd          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
398 cd          write (iout,'(2(a3,i3,2x),6(1pd12.4)/2(3(1pd12.4),5x)/)')
399 cd   &        restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
400 cd   &        bb(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,epsi,sigm,
401 cd   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
402             if (bb(itypi,itypj).gt.0.0d0) then
403               evdw=evdw+evdwij
404             else
405               evdw_t=evdw_t+evdwij
406             endif
407             if (calc_grad) then
408
409 C Calculate the components of the gradient in DC and X
410 C
411             fac=-rrij*(e1+evdwij)
412             gg(1)=xj*fac
413             gg(2)=yj*fac
414             gg(3)=zj*fac
415             do k=1,3
416               gvdwx(k,i)=gvdwx(k,i)-gg(k)
417               gvdwx(k,j)=gvdwx(k,j)+gg(k)
418             enddo
419             do k=i,j-1
420               do l=1,3
421                 gvdwc(l,k)=gvdwc(l,k)+gg(l)
422               enddo
423             enddo
424             endif
425 C
426 C 12/1/95, revised on 5/20/97
427 C
428 C Calculate the contact function. The ith column of the array JCONT will 
429 C contain the numbers of atoms that make contacts with the atom I (of numbers
430 C greater than I). The arrays FACONT and GACONT will contain the values of
431 C the contact function and its derivative.
432 C
433 C Uncomment next line, if the correlation interactions include EVDW explicitly.
434 c           if (j.gt.i+1 .and. evdwij.le.0.0D0) then
435 C Uncomment next line, if the correlation interactions are contact function only
436             if (j.gt.i+1.and. eps0ij.gt.0.0D0) then
437               rij=dsqrt(rij)
438               sigij=sigma(itypi,itypj)
439               r0ij=rs0(itypi,itypj)
440 C
441 C Check whether the SC's are not too far to make a contact.
442 C
443               rcut=1.5d0*r0ij
444               call gcont(rij,rcut,1.0d0,0.2d0*rcut,fcont,fprimcont)
445 C Add a new contact, if the SC's are close enough, but not too close (r<sigma).
446 C
447               if (fcont.gt.0.0D0) then
448 C If the SC-SC distance if close to sigma, apply spline.
449 cAdam           call gcont(-rij,-1.03d0*sigij,2.0d0*sigij,1.0d0,
450 cAdam &             fcont1,fprimcont1)
451 cAdam           fcont1=1.0d0-fcont1
452 cAdam           if (fcont1.gt.0.0d0) then
453 cAdam             fprimcont=fprimcont*fcont1+fcont*fprimcont1
454 cAdam             fcont=fcont*fcont1
455 cAdam           endif
456 C Uncomment following 4 lines to have the geometric average of the epsilon0's
457 cga             eps0ij=1.0d0/dsqrt(eps0ij)
458 cga             do k=1,3
459 cga               gg(k)=gg(k)*eps0ij
460 cga             enddo
461 cga             eps0ij=-evdwij*eps0ij
462 C Uncomment for AL's type of SC correlation interactions.
463 cadam           eps0ij=-evdwij
464                 num_conti=num_conti+1
465                 jcont(num_conti,i)=j
466                 facont(num_conti,i)=fcont*eps0ij
467                 fprimcont=eps0ij*fprimcont/rij
468                 fcont=expon*fcont
469 cAdam           gacont(1,num_conti,i)=-fprimcont*xj+fcont*gg(1)
470 cAdam           gacont(2,num_conti,i)=-fprimcont*yj+fcont*gg(2)
471 cAdam           gacont(3,num_conti,i)=-fprimcont*zj+fcont*gg(3)
472 C Uncomment following 3 lines for Skolnick's type of SC correlation.
473                 gacont(1,num_conti,i)=-fprimcont*xj
474                 gacont(2,num_conti,i)=-fprimcont*yj
475                 gacont(3,num_conti,i)=-fprimcont*zj
476 cd              write (iout,'(2i5,2f10.5)') i,j,rij,facont(num_conti,i)
477 cd              write (iout,'(2i3,3f10.5)') 
478 cd   &           i,j,(gacont(kk,num_conti,i),kk=1,3)
479               endif
480             endif
481           enddo      ! j
482         enddo        ! iint
483 C Change 12/1/95
484         num_cont(i)=num_conti
485       enddo          ! i
486       if (calc_grad) then
487       do i=1,nct
488         do j=1,3
489           gvdwc(j,i)=expon*gvdwc(j,i)
490           gvdwx(j,i)=expon*gvdwx(j,i)
491         enddo
492       enddo
493       endif
494 C******************************************************************************
495 C
496 C                              N O T E !!!
497 C
498 C To save time, the factor of EXPON has been extracted from ALL components
499 C of GVDWC and GRADX. Remember to multiply them by this factor before further 
500 C use!
501 C
502 C******************************************************************************
503       return
504       end
505 C-----------------------------------------------------------------------------
506       subroutine eljk(evdw,evdw_t)
507 C
508 C This subroutine calculates the interaction energy of nonbonded side chains
509 C assuming the LJK potential of interaction.
510 C
511       implicit real*8 (a-h,o-z)
512       include 'DIMENSIONS'
513       include 'sizesclu.dat'
514       include "DIMENSIONS.COMPAR"
515       include 'COMMON.GEO'
516       include 'COMMON.VAR'
517       include 'COMMON.LOCAL'
518       include 'COMMON.CHAIN'
519       include 'COMMON.DERIV'
520       include 'COMMON.INTERACT'
521       include 'COMMON.IOUNITS'
522       include 'COMMON.NAMES'
523       dimension gg(3)
524       logical scheck
525       integer icant
526       external icant
527 c     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
528       evdw=0.0D0
529       evdw_t=0.0d0
530       do i=iatsc_s,iatsc_e
531         itypi=itype(i)
532         if (itypi.eq.21) cycle
533         itypi1=itype(i+1)
534         xi=c(1,nres+i)
535         yi=c(2,nres+i)
536         zi=c(3,nres+i)
537 C
538 C Calculate SC interaction energy.
539 C
540         do iint=1,nint_gr(i)
541           do j=istart(i,iint),iend(i,iint)
542             itypj=itype(j)
543             if (itypj.eq.21) cycle
544             xj=c(1,nres+j)-xi
545             yj=c(2,nres+j)-yi
546             zj=c(3,nres+j)-zi
547             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
548             fac_augm=rrij**expon
549             e_augm=augm(itypi,itypj)*fac_augm
550             r_inv_ij=dsqrt(rrij)
551             rij=1.0D0/r_inv_ij 
552             r_shift_inv=1.0D0/(rij+r0(itypi,itypj)-sigma(itypi,itypj))
553             fac=r_shift_inv**expon
554             e1=fac*fac*aa(itypi,itypj)
555             e2=fac*bb(itypi,itypj)
556             evdwij=e_augm+e1+e2
557             ij=icant(itypi,itypj)
558 cd          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
559 cd          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
560 cd          write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
561 cd   &        restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
562 cd   &        bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
563 cd   &        sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
564 cd   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
565             if (bb(itypi,itypj).gt.0.0d0) then
566               evdw=evdw+evdwij
567             else 
568               evdw_t=evdw_t+evdwij
569             endif
570             if (calc_grad) then
571
572 C Calculate the components of the gradient in DC and X
573 C
574             fac=-2.0D0*rrij*e_augm-r_inv_ij*r_shift_inv*(e1+e1+e2)
575             gg(1)=xj*fac
576             gg(2)=yj*fac
577             gg(3)=zj*fac
578             do k=1,3
579               gvdwx(k,i)=gvdwx(k,i)-gg(k)
580               gvdwx(k,j)=gvdwx(k,j)+gg(k)
581             enddo
582             do k=i,j-1
583               do l=1,3
584                 gvdwc(l,k)=gvdwc(l,k)+gg(l)
585               enddo
586             enddo
587             endif
588           enddo      ! j
589         enddo        ! iint
590       enddo          ! i
591       if (calc_grad) then
592       do i=1,nct
593         do j=1,3
594           gvdwc(j,i)=expon*gvdwc(j,i)
595           gvdwx(j,i)=expon*gvdwx(j,i)
596         enddo
597       enddo
598       endif
599       return
600       end
601 C-----------------------------------------------------------------------------
602       subroutine ebp(evdw,evdw_t)
603 C
604 C This subroutine calculates the interaction energy of nonbonded side chains
605 C assuming the Berne-Pechukas potential of interaction.
606 C
607       implicit real*8 (a-h,o-z)
608       include 'DIMENSIONS'
609       include 'sizesclu.dat'
610       include "DIMENSIONS.COMPAR"
611       include 'COMMON.GEO'
612       include 'COMMON.VAR'
613       include 'COMMON.LOCAL'
614       include 'COMMON.CHAIN'
615       include 'COMMON.DERIV'
616       include 'COMMON.NAMES'
617       include 'COMMON.INTERACT'
618       include 'COMMON.IOUNITS'
619       include 'COMMON.CALC'
620       common /srutu/ icall
621 c     double precision rrsave(maxdim)
622       logical lprn
623       integer icant
624       external icant
625       evdw=0.0D0
626       evdw_t=0.0d0
627 c     print *,'Entering EBP nnt=',nnt,' nct=',nct,' expon=',expon
628 c     if (icall.eq.0) then
629 c       lprn=.true.
630 c     else
631         lprn=.false.
632 c     endif
633       ind=0
634       do i=iatsc_s,iatsc_e
635         itypi=itype(i)
636         if (itypi.eq.21) cycle
637         itypi1=itype(i+1)
638         xi=c(1,nres+i)
639         yi=c(2,nres+i)
640         zi=c(3,nres+i)
641         dxi=dc_norm(1,nres+i)
642         dyi=dc_norm(2,nres+i)
643         dzi=dc_norm(3,nres+i)
644         dsci_inv=vbld_inv(i+nres)
645 C
646 C Calculate SC interaction energy.
647 C
648         do iint=1,nint_gr(i)
649           do j=istart(i,iint),iend(i,iint)
650             ind=ind+1
651             itypj=itype(j)
652             if (itypj.eq.21) cycle
653             dscj_inv=vbld_inv(j+nres)
654             chi1=chi(itypi,itypj)
655             chi2=chi(itypj,itypi)
656             chi12=chi1*chi2
657             chip1=chip(itypi)
658             chip2=chip(itypj)
659             chip12=chip1*chip2
660             alf1=alp(itypi)
661             alf2=alp(itypj)
662             alf12=0.5D0*(alf1+alf2)
663 C For diagnostics only!!!
664 c           chi1=0.0D0
665 c           chi2=0.0D0
666 c           chi12=0.0D0
667 c           chip1=0.0D0
668 c           chip2=0.0D0
669 c           chip12=0.0D0
670 c           alf1=0.0D0
671 c           alf2=0.0D0
672 c           alf12=0.0D0
673             xj=c(1,nres+j)-xi
674             yj=c(2,nres+j)-yi
675             zj=c(3,nres+j)-zi
676             dxj=dc_norm(1,nres+j)
677             dyj=dc_norm(2,nres+j)
678             dzj=dc_norm(3,nres+j)
679             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
680 cd          if (icall.eq.0) then
681 cd            rrsave(ind)=rrij
682 cd          else
683 cd            rrij=rrsave(ind)
684 cd          endif
685             rij=dsqrt(rrij)
686 C Calculate the angle-dependent terms of energy & contributions to derivatives.
687             call sc_angular
688 C Calculate whole angle-dependent part of epsilon and contributions
689 C to its derivatives
690             fac=(rrij*sigsq)**expon2
691             e1=fac*fac*aa(itypi,itypj)
692             e2=fac*bb(itypi,itypj)
693             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
694             eps2der=evdwij*eps3rt
695             eps3der=evdwij*eps2rt
696             evdwij=evdwij*eps2rt*eps3rt
697             ij=icant(itypi,itypj)
698             aux=eps1*eps2rt**2*eps3rt**2
699             if (bb(itypi,itypj).gt.0.0d0) then
700               evdw=evdw+evdwij
701             else
702               evdw_t=evdw_t+evdwij
703             endif
704             if (calc_grad) then
705             if (lprn) then
706             sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
707             epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
708 cd            write (iout,'(2(a3,i3,2x),15(0pf7.3))')
709 cd     &        restyp(itypi),i,restyp(itypj),j,
710 cd     &        epsi,sigm,chi1,chi2,chip1,chip2,
711 cd     &        eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
712 cd     &        om1,om2,om12,1.0D0/dsqrt(rrij),
713 cd     &        evdwij
714             endif
715 C Calculate gradient components.
716             e1=e1*eps1*eps2rt**2*eps3rt**2
717             fac=-expon*(e1+evdwij)
718             sigder=fac/sigsq
719             fac=rrij*fac
720 C Calculate radial part of the gradient
721             gg(1)=xj*fac
722             gg(2)=yj*fac
723             gg(3)=zj*fac
724 C Calculate the angular part of the gradient and sum add the contributions
725 C to the appropriate components of the Cartesian gradient.
726             call sc_grad
727             endif
728           enddo      ! j
729         enddo        ! iint
730       enddo          ! i
731 c     stop
732       return
733       end
734 C-----------------------------------------------------------------------------
735       subroutine egb(evdw,evdw_t)
736 C
737 C This subroutine calculates the interaction energy of nonbonded side chains
738 C assuming the Gay-Berne potential of interaction.
739 C
740       implicit real*8 (a-h,o-z)
741       include 'DIMENSIONS'
742       include 'sizesclu.dat'
743       include "DIMENSIONS.COMPAR"
744       include 'COMMON.GEO'
745       include 'COMMON.VAR'
746       include 'COMMON.LOCAL'
747       include 'COMMON.CHAIN'
748       include 'COMMON.DERIV'
749       include 'COMMON.NAMES'
750       include 'COMMON.INTERACT'
751       include 'COMMON.IOUNITS'
752       include 'COMMON.CALC'
753       logical lprn
754       common /srutu/icall
755       integer icant
756       external icant
757 c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
758       evdw=0.0D0
759       evdw_t=0.0d0
760       lprn=.false.
761 c      if (icall.gt.0) lprn=.true.
762       ind=0
763       do i=iatsc_s,iatsc_e
764         itypi=itype(i)
765         if (itypi.eq.21) cycle
766         itypi1=itype(i+1)
767         xi=c(1,nres+i)
768         yi=c(2,nres+i)
769         zi=c(3,nres+i)
770         dxi=dc_norm(1,nres+i)
771         dyi=dc_norm(2,nres+i)
772         dzi=dc_norm(3,nres+i)
773         dsci_inv=vbld_inv(i+nres)
774 C
775 C Calculate SC interaction energy.
776 C
777         do iint=1,nint_gr(i)
778           do j=istart(i,iint),iend(i,iint)
779             ind=ind+1
780             itypj=itype(j)
781             if (itypj.eq.21) cycle
782             dscj_inv=vbld_inv(j+nres)
783             sig0ij=sigma(itypi,itypj)
784             chi1=chi(itypi,itypj)
785             chi2=chi(itypj,itypi)
786             chi12=chi1*chi2
787             chip1=chip(itypi)
788             chip2=chip(itypj)
789             chip12=chip1*chip2
790             alf1=alp(itypi)
791             alf2=alp(itypj)
792             alf12=0.5D0*(alf1+alf2)
793 C For diagnostics only!!!
794 c           chi1=0.0D0
795 c           chi2=0.0D0
796 c           chi12=0.0D0
797 c           chip1=0.0D0
798 c           chip2=0.0D0
799 c           chip12=0.0D0
800 c           alf1=0.0D0
801 c           alf2=0.0D0
802 c           alf12=0.0D0
803             xj=c(1,nres+j)-xi
804             yj=c(2,nres+j)-yi
805             zj=c(3,nres+j)-zi
806             dxj=dc_norm(1,nres+j)
807             dyj=dc_norm(2,nres+j)
808             dzj=dc_norm(3,nres+j)
809 c            write (iout,*) i,j,xj,yj,zj
810             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
811             rij=dsqrt(rrij)
812 C Calculate angle-dependent terms of energy and contributions to their
813 C derivatives.
814             call sc_angular
815             sigsq=1.0D0/sigsq
816             sig=sig0ij*dsqrt(sigsq)
817             rij_shift=1.0D0/rij-sig+sig0ij
818 C I hate to put IF's in the loops, but here don't have another choice!!!!
819             if (rij_shift.le.0.0D0) then
820               evdw=1.0D20
821               return
822             endif
823             sigder=-sig*sigsq
824 c---------------------------------------------------------------
825             rij_shift=1.0D0/rij_shift 
826             fac=rij_shift**expon
827             e1=fac*fac*aa(itypi,itypj)
828             e2=fac*bb(itypi,itypj)
829             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
830             eps2der=evdwij*eps3rt
831             eps3der=evdwij*eps2rt
832             evdwij=evdwij*eps2rt*eps3rt
833             if (bb(itypi,itypj).gt.0) then
834               evdw=evdw+evdwij
835             else
836               evdw_t=evdw_t+evdwij
837             endif
838             ij=icant(itypi,itypj)
839             aux=eps1*eps2rt**2*eps3rt**2
840 c            write (iout,*) "i",i," j",j," itypi",itypi," itypj",itypj,
841 c     &         " ij",ij," eneps",aux*e1/dabs(eps(itypi,itypj)),
842 c     &         aux*e2/eps(itypi,itypj)
843 c            if (lprn) then
844             sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
845             epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
846 c            write (iout,'(2(a3,i3,2x),17(0pf7.3))')
847 c     &        restyp(itypi),i,restyp(itypj),j,
848 c     &        epsi,sigm,chi1,chi2,chip1,chip2,
849 c     &        eps1,eps2rt**2,eps3rt**2,sig,sig0ij,
850 c     &        om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,
851 c     &        evdwij
852 c             write (iout,*) "pratial sum", evdw,evdw_t
853 c            endif
854             if (calc_grad) then
855 C Calculate gradient components.
856             e1=e1*eps1*eps2rt**2*eps3rt**2
857             fac=-expon*(e1+evdwij)*rij_shift
858             sigder=fac*sigder
859             fac=rij*fac
860 C Calculate the radial part of the gradient
861             gg(1)=xj*fac
862             gg(2)=yj*fac
863             gg(3)=zj*fac
864 C Calculate angular part of the gradient.
865             call sc_grad
866             endif
867           enddo      ! j
868         enddo        ! iint
869       enddo          ! i
870       return
871       end
872 C-----------------------------------------------------------------------------
873       subroutine egbv(evdw,evdw_t)
874 C
875 C This subroutine calculates the interaction energy of nonbonded side chains
876 C assuming the Gay-Berne-Vorobjev potential of interaction.
877 C
878       implicit real*8 (a-h,o-z)
879       include 'DIMENSIONS'
880       include 'sizesclu.dat'
881       include "DIMENSIONS.COMPAR"
882       include 'COMMON.GEO'
883       include 'COMMON.VAR'
884       include 'COMMON.LOCAL'
885       include 'COMMON.CHAIN'
886       include 'COMMON.DERIV'
887       include 'COMMON.NAMES'
888       include 'COMMON.INTERACT'
889       include 'COMMON.IOUNITS'
890       include 'COMMON.CALC'
891       common /srutu/ icall
892       logical lprn
893       integer icant
894       external icant
895       evdw=0.0D0
896       evdw_t=0.0d0
897 c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
898       evdw=0.0D0
899       lprn=.false.
900 c      if (icall.gt.0) lprn=.true.
901       ind=0
902       do i=iatsc_s,iatsc_e
903         itypi=itype(i)
904         if (itypi.eq.21) cycle
905         itypi1=itype(i+1)
906         xi=c(1,nres+i)
907         yi=c(2,nres+i)
908         zi=c(3,nres+i)
909         dxi=dc_norm(1,nres+i)
910         dyi=dc_norm(2,nres+i)
911         dzi=dc_norm(3,nres+i)
912         dsci_inv=vbld_inv(i+nres)
913 C
914 C Calculate SC interaction energy.
915 C
916         do iint=1,nint_gr(i)
917           do j=istart(i,iint),iend(i,iint)
918             ind=ind+1
919             itypj=itype(j)
920             if (itypj.eq.21) cycle
921             dscj_inv=vbld_inv(j+nres)
922             sig0ij=sigma(itypi,itypj)
923             r0ij=r0(itypi,itypj)
924             chi1=chi(itypi,itypj)
925             chi2=chi(itypj,itypi)
926             chi12=chi1*chi2
927             chip1=chip(itypi)
928             chip2=chip(itypj)
929             chip12=chip1*chip2
930             alf1=alp(itypi)
931             alf2=alp(itypj)
932             alf12=0.5D0*(alf1+alf2)
933 C For diagnostics only!!!
934 c           chi1=0.0D0
935 c           chi2=0.0D0
936 c           chi12=0.0D0
937 c           chip1=0.0D0
938 c           chip2=0.0D0
939 c           chip12=0.0D0
940 c           alf1=0.0D0
941 c           alf2=0.0D0
942 c           alf12=0.0D0
943             xj=c(1,nres+j)-xi
944             yj=c(2,nres+j)-yi
945             zj=c(3,nres+j)-zi
946             dxj=dc_norm(1,nres+j)
947             dyj=dc_norm(2,nres+j)
948             dzj=dc_norm(3,nres+j)
949             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
950             rij=dsqrt(rrij)
951 C Calculate angle-dependent terms of energy and contributions to their
952 C derivatives.
953             call sc_angular
954             sigsq=1.0D0/sigsq
955             sig=sig0ij*dsqrt(sigsq)
956             rij_shift=1.0D0/rij-sig+r0ij
957 C I hate to put IF's in the loops, but here don't have another choice!!!!
958             if (rij_shift.le.0.0D0) then
959               evdw=1.0D20
960               return
961             endif
962             sigder=-sig*sigsq
963 c---------------------------------------------------------------
964             rij_shift=1.0D0/rij_shift 
965             fac=rij_shift**expon
966             e1=fac*fac*aa(itypi,itypj)
967             e2=fac*bb(itypi,itypj)
968             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
969             eps2der=evdwij*eps3rt
970             eps3der=evdwij*eps2rt
971             fac_augm=rrij**expon
972             e_augm=augm(itypi,itypj)*fac_augm
973             evdwij=evdwij*eps2rt*eps3rt
974             if (bb(itypi,itypj).gt.0.0d0) then
975               evdw=evdw+evdwij+e_augm
976             else
977               evdw_t=evdw_t+evdwij+e_augm
978             endif
979             ij=icant(itypi,itypj)
980             aux=eps1*eps2rt**2*eps3rt**2
981 c            if (lprn) then
982 c            sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
983 c            epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
984 c            write (iout,'(2(a3,i3,2x),17(0pf7.3))')
985 c     &        restyp(itypi),i,restyp(itypj),j,
986 c     &        epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),
987 c     &        chi1,chi2,chip1,chip2,
988 c     &        eps1,eps2rt**2,eps3rt**2,
989 c     &        om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,
990 c     &        evdwij+e_augm
991 c            endif
992             if (calc_grad) then
993 C Calculate gradient components.
994             e1=e1*eps1*eps2rt**2*eps3rt**2
995             fac=-expon*(e1+evdwij)*rij_shift
996             sigder=fac*sigder
997             fac=rij*fac-2*expon*rrij*e_augm
998 C Calculate the radial part of the gradient
999             gg(1)=xj*fac
1000             gg(2)=yj*fac
1001             gg(3)=zj*fac
1002 C Calculate angular part of the gradient.
1003             call sc_grad
1004             endif
1005           enddo      ! j
1006         enddo        ! iint
1007       enddo          ! i
1008       return
1009       end
1010 C-----------------------------------------------------------------------------
1011       subroutine sc_angular
1012 C Calculate eps1,eps2,eps3,sigma, and parts of their derivatives in om1,om2,
1013 C om12. Called by ebp, egb, and egbv.
1014       implicit none
1015       include 'COMMON.CALC'
1016       erij(1)=xj*rij
1017       erij(2)=yj*rij
1018       erij(3)=zj*rij
1019       om1=dxi*erij(1)+dyi*erij(2)+dzi*erij(3)
1020       om2=dxj*erij(1)+dyj*erij(2)+dzj*erij(3)
1021       om12=dxi*dxj+dyi*dyj+dzi*dzj
1022       chiom12=chi12*om12
1023 C Calculate eps1(om12) and its derivative in om12
1024       faceps1=1.0D0-om12*chiom12
1025       faceps1_inv=1.0D0/faceps1
1026       eps1=dsqrt(faceps1_inv)
1027 C Following variable is eps1*deps1/dom12
1028       eps1_om12=faceps1_inv*chiom12
1029 C Calculate sigma(om1,om2,om12) and the derivatives of sigma**2 in om1,om2,
1030 C and om12.
1031       om1om2=om1*om2
1032       chiom1=chi1*om1
1033       chiom2=chi2*om2
1034       facsig=om1*chiom1+om2*chiom2-2.0D0*om1om2*chiom12
1035       sigsq=1.0D0-facsig*faceps1_inv
1036       sigsq_om1=(chiom1-chiom12*om2)*faceps1_inv
1037       sigsq_om2=(chiom2-chiom12*om1)*faceps1_inv
1038       sigsq_om12=-chi12*(om1om2*faceps1-om12*facsig)*faceps1_inv**2
1039 C Calculate eps2 and its derivatives in om1, om2, and om12.
1040       chipom1=chip1*om1
1041       chipom2=chip2*om2
1042       chipom12=chip12*om12
1043       facp=1.0D0-om12*chipom12
1044       facp_inv=1.0D0/facp
1045       facp1=om1*chipom1+om2*chipom2-2.0D0*om1om2*chipom12
1046 C Following variable is the square root of eps2
1047       eps2rt=1.0D0-facp1*facp_inv
1048 C Following three variables are the derivatives of the square root of eps
1049 C in om1, om2, and om12.
1050       eps2rt_om1=-4.0D0*(chipom1-chipom12*om2)*facp_inv
1051       eps2rt_om2=-4.0D0*(chipom2-chipom12*om1)*facp_inv
1052       eps2rt_om12=4.0D0*chip12*(om1om2*facp-om12*facp1)*facp_inv**2 
1053 C Evaluate the "asymmetric" factor in the VDW constant, eps3
1054       eps3rt=1.0D0-alf1*om1+alf2*om2-alf12*om12 
1055 C Calculate whole angle-dependent part of epsilon and contributions
1056 C to its derivatives
1057       return
1058       end
1059 C----------------------------------------------------------------------------
1060       subroutine sc_grad
1061       implicit real*8 (a-h,o-z)
1062       include 'DIMENSIONS'
1063       include 'sizesclu.dat'
1064       include 'COMMON.CHAIN'
1065       include 'COMMON.DERIV'
1066       include 'COMMON.CALC'
1067       double precision dcosom1(3),dcosom2(3)
1068       eom1=eps2der*eps2rt_om1-2.0D0*alf1*eps3der+sigder*sigsq_om1
1069       eom2=eps2der*eps2rt_om2+2.0D0*alf2*eps3der+sigder*sigsq_om2
1070       eom12=evdwij*eps1_om12+eps2der*eps2rt_om12
1071      &     -2.0D0*alf12*eps3der+sigder*sigsq_om12
1072       do k=1,3
1073         dcosom1(k)=rij*(dc_norm(k,nres+i)-om1*erij(k))
1074         dcosom2(k)=rij*(dc_norm(k,nres+j)-om2*erij(k))
1075       enddo
1076       do k=1,3
1077         gg(k)=gg(k)+eom1*dcosom1(k)+eom2*dcosom2(k)
1078       enddo 
1079       do k=1,3
1080         gvdwx(k,i)=gvdwx(k,i)-gg(k)
1081      &            +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i))
1082      &            +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
1083         gvdwx(k,j)=gvdwx(k,j)+gg(k)
1084      &            +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j))
1085      &            +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
1086       enddo
1087
1088 C Calculate the components of the gradient in DC and X
1089 C
1090       do k=i,j-1
1091         do l=1,3
1092           gvdwc(l,k)=gvdwc(l,k)+gg(l)
1093         enddo
1094       enddo
1095       return
1096       end
1097 c------------------------------------------------------------------------------
1098       subroutine vec_and_deriv
1099       implicit real*8 (a-h,o-z)
1100       include 'DIMENSIONS'
1101       include 'sizesclu.dat'
1102       include 'COMMON.IOUNITS'
1103       include 'COMMON.GEO'
1104       include 'COMMON.VAR'
1105       include 'COMMON.LOCAL'
1106       include 'COMMON.CHAIN'
1107       include 'COMMON.VECTORS'
1108       include 'COMMON.DERIV'
1109       include 'COMMON.INTERACT'
1110       dimension uyder(3,3,2),uzder(3,3,2),vbld_inv_temp(2)
1111 C Compute the local reference systems. For reference system (i), the
1112 C X-axis points from CA(i) to CA(i+1), the Y axis is in the 
1113 C CA(i)-CA(i+1)-CA(i+2) plane, and the Z axis is perpendicular to this plane.
1114       do i=1,nres-1
1115 c          if (i.eq.nres-1 .or. itel(i+1).eq.0) then
1116           if (i.eq.nres-1) then
1117 C Case of the last full residue
1118 C Compute the Z-axis
1119             call vecpr(dc_norm(1,i),dc_norm(1,i-1),uz(1,i))
1120             costh=dcos(pi-theta(nres))
1121             fac=1.0d0/dsqrt(1.0d0-costh*costh)
1122             do k=1,3
1123               uz(k,i)=fac*uz(k,i)
1124             enddo
1125             if (calc_grad) then
1126 C Compute the derivatives of uz
1127             uzder(1,1,1)= 0.0d0
1128             uzder(2,1,1)=-dc_norm(3,i-1)
1129             uzder(3,1,1)= dc_norm(2,i-1) 
1130             uzder(1,2,1)= dc_norm(3,i-1)
1131             uzder(2,2,1)= 0.0d0
1132             uzder(3,2,1)=-dc_norm(1,i-1)
1133             uzder(1,3,1)=-dc_norm(2,i-1)
1134             uzder(2,3,1)= dc_norm(1,i-1)
1135             uzder(3,3,1)= 0.0d0
1136             uzder(1,1,2)= 0.0d0
1137             uzder(2,1,2)= dc_norm(3,i)
1138             uzder(3,1,2)=-dc_norm(2,i) 
1139             uzder(1,2,2)=-dc_norm(3,i)
1140             uzder(2,2,2)= 0.0d0
1141             uzder(3,2,2)= dc_norm(1,i)
1142             uzder(1,3,2)= dc_norm(2,i)
1143             uzder(2,3,2)=-dc_norm(1,i)
1144             uzder(3,3,2)= 0.0d0
1145             endif
1146 C Compute the Y-axis
1147             facy=fac
1148             do k=1,3
1149               uy(k,i)=fac*(dc_norm(k,i-1)-costh*dc_norm(k,i))
1150             enddo
1151             if (calc_grad) then
1152 C Compute the derivatives of uy
1153             do j=1,3
1154               do k=1,3
1155                 uyder(k,j,1)=2*dc_norm(k,i-1)*dc_norm(j,i)
1156      &                        -dc_norm(k,i)*dc_norm(j,i-1)
1157                 uyder(k,j,2)=-dc_norm(j,i)*dc_norm(k,i)
1158               enddo
1159               uyder(j,j,1)=uyder(j,j,1)-costh
1160               uyder(j,j,2)=1.0d0+uyder(j,j,2)
1161             enddo
1162             do j=1,2
1163               do k=1,3
1164                 do l=1,3
1165                   uygrad(l,k,j,i)=uyder(l,k,j)
1166                   uzgrad(l,k,j,i)=uzder(l,k,j)
1167                 enddo
1168               enddo
1169             enddo 
1170             call unormderiv(uy(1,i),uyder(1,1,1),facy,uygrad(1,1,1,i))
1171             call unormderiv(uy(1,i),uyder(1,1,2),facy,uygrad(1,1,2,i))
1172             call unormderiv(uz(1,i),uzder(1,1,1),fac,uzgrad(1,1,1,i))
1173             call unormderiv(uz(1,i),uzder(1,1,2),fac,uzgrad(1,1,2,i))
1174             endif
1175           else
1176 C Other residues
1177 C Compute the Z-axis
1178             call vecpr(dc_norm(1,i),dc_norm(1,i+1),uz(1,i))
1179             costh=dcos(pi-theta(i+2))
1180             fac=1.0d0/dsqrt(1.0d0-costh*costh)
1181             do k=1,3
1182               uz(k,i)=fac*uz(k,i)
1183             enddo
1184             if (calc_grad) then
1185 C Compute the derivatives of uz
1186             uzder(1,1,1)= 0.0d0
1187             uzder(2,1,1)=-dc_norm(3,i+1)
1188             uzder(3,1,1)= dc_norm(2,i+1) 
1189             uzder(1,2,1)= dc_norm(3,i+1)
1190             uzder(2,2,1)= 0.0d0
1191             uzder(3,2,1)=-dc_norm(1,i+1)
1192             uzder(1,3,1)=-dc_norm(2,i+1)
1193             uzder(2,3,1)= dc_norm(1,i+1)
1194             uzder(3,3,1)= 0.0d0
1195             uzder(1,1,2)= 0.0d0
1196             uzder(2,1,2)= dc_norm(3,i)
1197             uzder(3,1,2)=-dc_norm(2,i) 
1198             uzder(1,2,2)=-dc_norm(3,i)
1199             uzder(2,2,2)= 0.0d0
1200             uzder(3,2,2)= dc_norm(1,i)
1201             uzder(1,3,2)= dc_norm(2,i)
1202             uzder(2,3,2)=-dc_norm(1,i)
1203             uzder(3,3,2)= 0.0d0
1204             endif
1205 C Compute the Y-axis
1206             facy=fac
1207             do k=1,3
1208               uy(k,i)=facy*(dc_norm(k,i+1)-costh*dc_norm(k,i))
1209             enddo
1210             if (calc_grad) then
1211 C Compute the derivatives of uy
1212             do j=1,3
1213               do k=1,3
1214                 uyder(k,j,1)=2*dc_norm(k,i+1)*dc_norm(j,i)
1215      &                        -dc_norm(k,i)*dc_norm(j,i+1)
1216                 uyder(k,j,2)=-dc_norm(j,i)*dc_norm(k,i)
1217               enddo
1218               uyder(j,j,1)=uyder(j,j,1)-costh
1219               uyder(j,j,2)=1.0d0+uyder(j,j,2)
1220             enddo
1221             do j=1,2
1222               do k=1,3
1223                 do l=1,3
1224                   uygrad(l,k,j,i)=uyder(l,k,j)
1225                   uzgrad(l,k,j,i)=uzder(l,k,j)
1226                 enddo
1227               enddo
1228             enddo 
1229             call unormderiv(uy(1,i),uyder(1,1,1),facy,uygrad(1,1,1,i))
1230             call unormderiv(uy(1,i),uyder(1,1,2),facy,uygrad(1,1,2,i))
1231             call unormderiv(uz(1,i),uzder(1,1,1),fac,uzgrad(1,1,1,i))
1232             call unormderiv(uz(1,i),uzder(1,1,2),fac,uzgrad(1,1,2,i))
1233           endif
1234           endif
1235       enddo
1236       if (calc_grad) then
1237       do i=1,nres-1
1238         vbld_inv_temp(1)=vbld_inv(i+1)
1239         if (i.lt.nres-1) then
1240           vbld_inv_temp(2)=vbld_inv(i+2)
1241         else
1242           vbld_inv_temp(2)=vbld_inv(i)
1243         endif
1244         do j=1,2
1245           do k=1,3
1246             do l=1,3
1247               uygrad(l,k,j,i)=vbld_inv_temp(j)*uygrad(l,k,j,i)
1248               uzgrad(l,k,j,i)=vbld_inv_temp(j)*uzgrad(l,k,j,i)
1249             enddo
1250           enddo
1251         enddo
1252       enddo
1253       endif
1254       return
1255       end
1256 C-----------------------------------------------------------------------------
1257       subroutine vec_and_deriv_test
1258       implicit real*8 (a-h,o-z)
1259       include 'DIMENSIONS'
1260       include 'sizesclu.dat'
1261       include 'COMMON.IOUNITS'
1262       include 'COMMON.GEO'
1263       include 'COMMON.VAR'
1264       include 'COMMON.LOCAL'
1265       include 'COMMON.CHAIN'
1266       include 'COMMON.VECTORS'
1267       dimension uyder(3,3,2),uzder(3,3,2)
1268 C Compute the local reference systems. For reference system (i), the
1269 C X-axis points from CA(i) to CA(i+1), the Y axis is in the 
1270 C CA(i)-CA(i+1)-CA(i+2) plane, and the Z axis is perpendicular to this plane.
1271       do i=1,nres-1
1272           if (i.eq.nres-1) then
1273 C Case of the last full residue
1274 C Compute the Z-axis
1275             call vecpr(dc_norm(1,i),dc_norm(1,i-1),uz(1,i))
1276             costh=dcos(pi-theta(nres))
1277             fac=1.0d0/dsqrt(1.0d0-costh*costh)
1278 c            write (iout,*) 'fac',fac,
1279 c     &        1.0d0/dsqrt(scalar(uz(1,i),uz(1,i)))
1280             fac=1.0d0/dsqrt(scalar(uz(1,i),uz(1,i)))
1281             do k=1,3
1282               uz(k,i)=fac*uz(k,i)
1283             enddo
1284 C Compute the derivatives of uz
1285             uzder(1,1,1)= 0.0d0
1286             uzder(2,1,1)=-dc_norm(3,i-1)
1287             uzder(3,1,1)= dc_norm(2,i-1) 
1288             uzder(1,2,1)= dc_norm(3,i-1)
1289             uzder(2,2,1)= 0.0d0
1290             uzder(3,2,1)=-dc_norm(1,i-1)
1291             uzder(1,3,1)=-dc_norm(2,i-1)
1292             uzder(2,3,1)= dc_norm(1,i-1)
1293             uzder(3,3,1)= 0.0d0
1294             uzder(1,1,2)= 0.0d0
1295             uzder(2,1,2)= dc_norm(3,i)
1296             uzder(3,1,2)=-dc_norm(2,i) 
1297             uzder(1,2,2)=-dc_norm(3,i)
1298             uzder(2,2,2)= 0.0d0
1299             uzder(3,2,2)= dc_norm(1,i)
1300             uzder(1,3,2)= dc_norm(2,i)
1301             uzder(2,3,2)=-dc_norm(1,i)
1302             uzder(3,3,2)= 0.0d0
1303 C Compute the Y-axis
1304             do k=1,3
1305               uy(k,i)=fac*(dc_norm(k,i-1)-costh*dc_norm(k,i))
1306             enddo
1307             facy=fac
1308             facy=1.0d0/dsqrt(scalar(dc_norm(1,i),dc_norm(1,i))*
1309      &       (scalar(dc_norm(1,i-1),dc_norm(1,i-1))**2-
1310      &        scalar(dc_norm(1,i),dc_norm(1,i-1))**2))
1311             do k=1,3
1312 c              uy(k,i)=facy*(dc_norm(k,i+1)-costh*dc_norm(k,i))
1313               uy(k,i)=
1314 c     &        facy*(
1315      &        dc_norm(k,i-1)*scalar(dc_norm(1,i),dc_norm(1,i))
1316      &        -scalar(dc_norm(1,i),dc_norm(1,i-1))*dc_norm(k,i)
1317 c     &        )
1318             enddo
1319 c            write (iout,*) 'facy',facy,
1320 c     &       1.0d0/dsqrt(scalar(uy(1,i),uy(1,i)))
1321             facy=1.0d0/dsqrt(scalar(uy(1,i),uy(1,i)))
1322             do k=1,3
1323               uy(k,i)=facy*uy(k,i)
1324             enddo
1325 C Compute the derivatives of uy
1326             do j=1,3
1327               do k=1,3
1328                 uyder(k,j,1)=2*dc_norm(k,i-1)*dc_norm(j,i)
1329      &                        -dc_norm(k,i)*dc_norm(j,i-1)
1330                 uyder(k,j,2)=-dc_norm(j,i)*dc_norm(k,i)
1331               enddo
1332 c              uyder(j,j,1)=uyder(j,j,1)-costh
1333 c              uyder(j,j,2)=1.0d0+uyder(j,j,2)
1334               uyder(j,j,1)=uyder(j,j,1)
1335      &          -scalar(dc_norm(1,i),dc_norm(1,i-1))
1336               uyder(j,j,2)=scalar(dc_norm(1,i),dc_norm(1,i))
1337      &          +uyder(j,j,2)
1338             enddo
1339             do j=1,2
1340               do k=1,3
1341                 do l=1,3
1342                   uygrad(l,k,j,i)=uyder(l,k,j)
1343                   uzgrad(l,k,j,i)=uzder(l,k,j)
1344                 enddo
1345               enddo
1346             enddo 
1347             call unormderiv(uy(1,i),uyder(1,1,1),facy,uygrad(1,1,1,i))
1348             call unormderiv(uy(1,i),uyder(1,1,2),facy,uygrad(1,1,2,i))
1349             call unormderiv(uz(1,i),uzder(1,1,1),fac,uzgrad(1,1,1,i))
1350             call unormderiv(uz(1,i),uzder(1,1,2),fac,uzgrad(1,1,2,i))
1351           else
1352 C Other residues
1353 C Compute the Z-axis
1354             call vecpr(dc_norm(1,i),dc_norm(1,i+1),uz(1,i))
1355             costh=dcos(pi-theta(i+2))
1356             fac=1.0d0/dsqrt(1.0d0-costh*costh)
1357             fac=1.0d0/dsqrt(scalar(uz(1,i),uz(1,i)))
1358             do k=1,3
1359               uz(k,i)=fac*uz(k,i)
1360             enddo
1361 C Compute the derivatives of uz
1362             uzder(1,1,1)= 0.0d0
1363             uzder(2,1,1)=-dc_norm(3,i+1)
1364             uzder(3,1,1)= dc_norm(2,i+1) 
1365             uzder(1,2,1)= dc_norm(3,i+1)
1366             uzder(2,2,1)= 0.0d0
1367             uzder(3,2,1)=-dc_norm(1,i+1)
1368             uzder(1,3,1)=-dc_norm(2,i+1)
1369             uzder(2,3,1)= dc_norm(1,i+1)
1370             uzder(3,3,1)= 0.0d0
1371             uzder(1,1,2)= 0.0d0
1372             uzder(2,1,2)= dc_norm(3,i)
1373             uzder(3,1,2)=-dc_norm(2,i) 
1374             uzder(1,2,2)=-dc_norm(3,i)
1375             uzder(2,2,2)= 0.0d0
1376             uzder(3,2,2)= dc_norm(1,i)
1377             uzder(1,3,2)= dc_norm(2,i)
1378             uzder(2,3,2)=-dc_norm(1,i)
1379             uzder(3,3,2)= 0.0d0
1380 C Compute the Y-axis
1381             facy=fac
1382             facy=1.0d0/dsqrt(scalar(dc_norm(1,i),dc_norm(1,i))*
1383      &       (scalar(dc_norm(1,i+1),dc_norm(1,i+1))**2-
1384      &        scalar(dc_norm(1,i),dc_norm(1,i+1))**2))
1385             do k=1,3
1386 c              uy(k,i)=facy*(dc_norm(k,i+1)-costh*dc_norm(k,i))
1387               uy(k,i)=
1388 c     &        facy*(
1389      &        dc_norm(k,i+1)*scalar(dc_norm(1,i),dc_norm(1,i))
1390      &        -scalar(dc_norm(1,i),dc_norm(1,i+1))*dc_norm(k,i)
1391 c     &        )
1392             enddo
1393 c            write (iout,*) 'facy',facy,
1394 c     &       1.0d0/dsqrt(scalar(uy(1,i),uy(1,i)))
1395             facy=1.0d0/dsqrt(scalar(uy(1,i),uy(1,i)))
1396             do k=1,3
1397               uy(k,i)=facy*uy(k,i)
1398             enddo
1399 C Compute the derivatives of uy
1400             do j=1,3
1401               do k=1,3
1402                 uyder(k,j,1)=2*dc_norm(k,i+1)*dc_norm(j,i)
1403      &                        -dc_norm(k,i)*dc_norm(j,i+1)
1404                 uyder(k,j,2)=-dc_norm(j,i)*dc_norm(k,i)
1405               enddo
1406 c              uyder(j,j,1)=uyder(j,j,1)-costh
1407 c              uyder(j,j,2)=1.0d0+uyder(j,j,2)
1408               uyder(j,j,1)=uyder(j,j,1)
1409      &          -scalar(dc_norm(1,i),dc_norm(1,i+1))
1410               uyder(j,j,2)=scalar(dc_norm(1,i),dc_norm(1,i))
1411      &          +uyder(j,j,2)
1412             enddo
1413             do j=1,2
1414               do k=1,3
1415                 do l=1,3
1416                   uygrad(l,k,j,i)=uyder(l,k,j)
1417                   uzgrad(l,k,j,i)=uzder(l,k,j)
1418                 enddo
1419               enddo
1420             enddo 
1421             call unormderiv(uy(1,i),uyder(1,1,1),facy,uygrad(1,1,1,i))
1422             call unormderiv(uy(1,i),uyder(1,1,2),facy,uygrad(1,1,2,i))
1423             call unormderiv(uz(1,i),uzder(1,1,1),fac,uzgrad(1,1,1,i))
1424             call unormderiv(uz(1,i),uzder(1,1,2),fac,uzgrad(1,1,2,i))
1425           endif
1426       enddo
1427       do i=1,nres-1
1428         do j=1,2
1429           do k=1,3
1430             do l=1,3
1431               uygrad(l,k,j,i)=vblinv*uygrad(l,k,j,i)
1432               uzgrad(l,k,j,i)=vblinv*uzgrad(l,k,j,i)
1433             enddo
1434           enddo
1435         enddo
1436       enddo
1437       return
1438       end
1439 C-----------------------------------------------------------------------------
1440       subroutine check_vecgrad
1441       implicit real*8 (a-h,o-z)
1442       include 'DIMENSIONS'
1443       include 'sizesclu.dat'
1444       include 'COMMON.IOUNITS'
1445       include 'COMMON.GEO'
1446       include 'COMMON.VAR'
1447       include 'COMMON.LOCAL'
1448       include 'COMMON.CHAIN'
1449       include 'COMMON.VECTORS'
1450       dimension uygradt(3,3,2,maxres),uzgradt(3,3,2,maxres)
1451       dimension uyt(3,maxres),uzt(3,maxres)
1452       dimension uygradn(3,3,2),uzgradn(3,3,2),erij(3)
1453       double precision delta /1.0d-7/
1454       call vec_and_deriv
1455 cd      do i=1,nres
1456 crc          write(iout,'(2i5,2(3f10.5,5x))') i,1,dc_norm(:,i)
1457 crc          write(iout,'(2i5,2(3f10.5,5x))') i,2,uy(:,i)
1458 crc          write(iout,'(2i5,2(3f10.5,5x)/)')i,3,uz(:,i)
1459 cd          write(iout,'(2i5,2(3f10.5,5x))') i,1,
1460 cd     &     (dc_norm(if90,i),if90=1,3)
1461 cd          write(iout,'(2i5,2(3f10.5,5x))') i,2,(uy(if90,i),if90=1,3)
1462 cd          write(iout,'(2i5,2(3f10.5,5x)/)')i,3,(uz(if90,i),if90=1,3)
1463 cd          write(iout,'(a)')
1464 cd      enddo
1465       do i=1,nres
1466         do j=1,2
1467           do k=1,3
1468             do l=1,3
1469               uygradt(l,k,j,i)=uygrad(l,k,j,i)
1470               uzgradt(l,k,j,i)=uzgrad(l,k,j,i)
1471             enddo
1472           enddo
1473         enddo
1474       enddo
1475       call vec_and_deriv
1476       do i=1,nres
1477         do j=1,3
1478           uyt(j,i)=uy(j,i)
1479           uzt(j,i)=uz(j,i)
1480         enddo
1481       enddo
1482       do i=1,nres
1483 cd        write (iout,*) 'i=',i
1484         do k=1,3
1485           erij(k)=dc_norm(k,i)
1486         enddo
1487         do j=1,3
1488           do k=1,3
1489             dc_norm(k,i)=erij(k)
1490           enddo
1491           dc_norm(j,i)=dc_norm(j,i)+delta
1492 c          fac=dsqrt(scalar(dc_norm(1,i),dc_norm(1,i)))
1493 c          do k=1,3
1494 c            dc_norm(k,i)=dc_norm(k,i)/fac
1495 c          enddo
1496 c          write (iout,*) (dc_norm(k,i),k=1,3)
1497 c          write (iout,*) (erij(k),k=1,3)
1498           call vec_and_deriv
1499           do k=1,3
1500             uygradn(k,j,1)=(uy(k,i)-uyt(k,i))/delta
1501             uygradn(k,j,2)=(uy(k,i-1)-uyt(k,i-1))/delta
1502             uzgradn(k,j,1)=(uz(k,i)-uzt(k,i))/delta
1503             uzgradn(k,j,2)=(uz(k,i-1)-uzt(k,i-1))/delta
1504           enddo 
1505 c          write (iout,'(i5,3f8.5,3x,3f8.5,5x,3f8.5,3x,3f8.5)') 
1506 c     &      j,(uzgradt(k,j,1,i),k=1,3),(uzgradn(k,j,1),k=1,3),
1507 c     &      (uzgradt(k,j,2,i-1),k=1,3),(uzgradn(k,j,2),k=1,3)
1508         enddo
1509         do k=1,3
1510           dc_norm(k,i)=erij(k)
1511         enddo
1512 cd        do k=1,3
1513 cd          write (iout,'(i5,3f8.5,3x,3f8.5,5x,3f8.5,3x,3f8.5)') 
1514 cd     &      k,(uygradt(k,l,1,i),l=1,3),(uygradn(k,l,1),l=1,3),
1515 cd     &      (uygradt(k,l,2,i-1),l=1,3),(uygradn(k,l,2),l=1,3)
1516 cd          write (iout,'(i5,3f8.5,3x,3f8.5,5x,3f8.5,3x,3f8.5)') 
1517 cd     &      k,(uzgradt(k,l,1,i),l=1,3),(uzgradn(k,l,1),l=1,3),
1518 cd     &      (uzgradt(k,l,2,i-1),l=1,3),(uzgradn(k,l,2),l=1,3)
1519 cd          write (iout,'(a)')
1520 cd        enddo
1521       enddo
1522       return
1523       end
1524 C--------------------------------------------------------------------------
1525       subroutine set_matrices
1526       implicit real*8 (a-h,o-z)
1527       include 'DIMENSIONS'
1528       include 'sizesclu.dat'
1529       include 'COMMON.IOUNITS'
1530       include 'COMMON.GEO'
1531       include 'COMMON.VAR'
1532       include 'COMMON.LOCAL'
1533       include 'COMMON.CHAIN'
1534       include 'COMMON.DERIV'
1535       include 'COMMON.INTERACT'
1536       include 'COMMON.CONTACTS'
1537       include 'COMMON.TORSION'
1538       include 'COMMON.VECTORS'
1539       include 'COMMON.FFIELD'
1540       double precision auxvec(2),auxmat(2,2)
1541 C
1542 C Compute the virtual-bond-torsional-angle dependent quantities needed
1543 C to calculate the el-loc multibody terms of various order.
1544 C
1545       do i=3,nres+1
1546         if (i .lt. nres+1) then
1547           sin1=dsin(phi(i))
1548           cos1=dcos(phi(i))
1549           sintab(i-2)=sin1
1550           costab(i-2)=cos1
1551           obrot(1,i-2)=cos1
1552           obrot(2,i-2)=sin1
1553           sin2=dsin(2*phi(i))
1554           cos2=dcos(2*phi(i))
1555           sintab2(i-2)=sin2
1556           costab2(i-2)=cos2
1557           obrot2(1,i-2)=cos2
1558           obrot2(2,i-2)=sin2
1559           Ug(1,1,i-2)=-cos1
1560           Ug(1,2,i-2)=-sin1
1561           Ug(2,1,i-2)=-sin1
1562           Ug(2,2,i-2)= cos1
1563           Ug2(1,1,i-2)=-cos2
1564           Ug2(1,2,i-2)=-sin2
1565           Ug2(2,1,i-2)=-sin2
1566           Ug2(2,2,i-2)= cos2
1567         else
1568           costab(i-2)=1.0d0
1569           sintab(i-2)=0.0d0
1570           obrot(1,i-2)=1.0d0
1571           obrot(2,i-2)=0.0d0
1572           obrot2(1,i-2)=0.0d0
1573           obrot2(2,i-2)=0.0d0
1574           Ug(1,1,i-2)=1.0d0
1575           Ug(1,2,i-2)=0.0d0
1576           Ug(2,1,i-2)=0.0d0
1577           Ug(2,2,i-2)=1.0d0
1578           Ug2(1,1,i-2)=0.0d0
1579           Ug2(1,2,i-2)=0.0d0
1580           Ug2(2,1,i-2)=0.0d0
1581           Ug2(2,2,i-2)=0.0d0
1582         endif
1583         if (i .gt. 3 .and. i .lt. nres+1) then
1584           obrot_der(1,i-2)=-sin1
1585           obrot_der(2,i-2)= cos1
1586           Ugder(1,1,i-2)= sin1
1587           Ugder(1,2,i-2)=-cos1
1588           Ugder(2,1,i-2)=-cos1
1589           Ugder(2,2,i-2)=-sin1
1590           dwacos2=cos2+cos2
1591           dwasin2=sin2+sin2
1592           obrot2_der(1,i-2)=-dwasin2
1593           obrot2_der(2,i-2)= dwacos2
1594           Ug2der(1,1,i-2)= dwasin2
1595           Ug2der(1,2,i-2)=-dwacos2
1596           Ug2der(2,1,i-2)=-dwacos2
1597           Ug2der(2,2,i-2)=-dwasin2
1598         else
1599           obrot_der(1,i-2)=0.0d0
1600           obrot_der(2,i-2)=0.0d0
1601           Ugder(1,1,i-2)=0.0d0
1602           Ugder(1,2,i-2)=0.0d0
1603           Ugder(2,1,i-2)=0.0d0
1604           Ugder(2,2,i-2)=0.0d0
1605           obrot2_der(1,i-2)=0.0d0
1606           obrot2_der(2,i-2)=0.0d0
1607           Ug2der(1,1,i-2)=0.0d0
1608           Ug2der(1,2,i-2)=0.0d0
1609           Ug2der(2,1,i-2)=0.0d0
1610           Ug2der(2,2,i-2)=0.0d0
1611         endif
1612         if (i.gt. nnt+2 .and. i.lt.nct+2) then
1613           if (itype(i-2).le.ntyp) then
1614             iti = itortyp(itype(i-2))
1615           else 
1616             iti=ntortyp+1
1617           endif
1618         else
1619           iti=ntortyp+1
1620         endif
1621         if (i.gt. nnt+1 .and. i.lt.nct+1) then
1622           if (itype(i-1).le.ntyp) then
1623             iti1 = itortyp(itype(i-1))
1624           else
1625             iti1=ntortyp+1
1626           endif
1627         else
1628           iti1=ntortyp+1
1629         endif
1630 cd        write (iout,*) '*******i',i,' iti1',iti
1631 cd        write (iout,*) 'b1',b1(:,iti)
1632 cd        write (iout,*) 'b2',b2(:,iti)
1633 cd        write (iout,*) 'Ug',Ug(:,:,i-2)
1634 c        print *,"itilde1 i iti iti1",i,iti,iti1
1635         if (i .gt. iatel_s+2) then
1636           call matvec2(Ug(1,1,i-2),b2(1,iti),Ub2(1,i-2))
1637           call matmat2(EE(1,1,iti),Ug(1,1,i-2),EUg(1,1,i-2))
1638           call matmat2(CC(1,1,iti),Ug(1,1,i-2),CUg(1,1,i-2))
1639           call matmat2(DD(1,1,iti),Ug(1,1,i-2),DUg(1,1,i-2))
1640           call matmat2(Dtilde(1,1,iti),Ug2(1,1,i-2),DtUg2(1,1,i-2))
1641           call matvec2(Ctilde(1,1,iti1),obrot(1,i-2),Ctobr(1,i-2))
1642           call matvec2(Dtilde(1,1,iti),obrot2(1,i-2),Dtobr2(1,i-2))
1643         else
1644           do k=1,2
1645             Ub2(k,i-2)=0.0d0
1646             Ctobr(k,i-2)=0.0d0 
1647             Dtobr2(k,i-2)=0.0d0
1648             do l=1,2
1649               EUg(l,k,i-2)=0.0d0
1650               CUg(l,k,i-2)=0.0d0
1651               DUg(l,k,i-2)=0.0d0
1652               DtUg2(l,k,i-2)=0.0d0
1653             enddo
1654           enddo
1655         endif
1656 c        print *,"itilde2 i iti iti1",i,iti,iti1
1657         call matvec2(Ugder(1,1,i-2),b2(1,iti),Ub2der(1,i-2))
1658         call matmat2(EE(1,1,iti),Ugder(1,1,i-2),EUgder(1,1,i-2))
1659         call matmat2(CC(1,1,iti1),Ugder(1,1,i-2),CUgder(1,1,i-2))
1660         call matmat2(DD(1,1,iti),Ugder(1,1,i-2),DUgder(1,1,i-2))
1661         call matmat2(Dtilde(1,1,iti),Ug2der(1,1,i-2),DtUg2der(1,1,i-2))
1662         call matvec2(Ctilde(1,1,iti1),obrot_der(1,i-2),Ctobrder(1,i-2))
1663         call matvec2(Dtilde(1,1,iti),obrot2_der(1,i-2),Dtobr2der(1,i-2))
1664 c        print *,"itilde3 i iti iti1",i,iti,iti1
1665         do k=1,2
1666           muder(k,i-2)=Ub2der(k,i-2)
1667         enddo
1668         if (i.gt. nnt+1 .and. i.lt.nct+1) then
1669           if (itype(i-1).le.ntyp) then
1670             iti1 = itortyp(itype(i-1))
1671           else
1672             iti1=ntortyp+1
1673           endif
1674         else
1675           iti1=ntortyp+1
1676         endif
1677         do k=1,2
1678           mu(k,i-2)=Ub2(k,i-2)+b1(k,iti1)
1679         enddo
1680 C Vectors and matrices dependent on a single virtual-bond dihedral.
1681         call matvec2(DD(1,1,iti),b1tilde(1,iti1),auxvec(1))
1682         call matvec2(Ug2(1,1,i-2),auxvec(1),Ug2Db1t(1,i-2)) 
1683         call matvec2(Ug2der(1,1,i-2),auxvec(1),Ug2Db1tder(1,i-2)) 
1684         call matvec2(CC(1,1,iti1),Ub2(1,i-2),CUgb2(1,i-2))
1685         call matvec2(CC(1,1,iti1),Ub2der(1,i-2),CUgb2der(1,i-2))
1686         call matmat2(EUg(1,1,i-2),CC(1,1,iti1),EUgC(1,1,i-2))
1687         call matmat2(EUgder(1,1,i-2),CC(1,1,iti1),EUgCder(1,1,i-2))
1688         call matmat2(EUg(1,1,i-2),DD(1,1,iti1),EUgD(1,1,i-2))
1689         call matmat2(EUgder(1,1,i-2),DD(1,1,iti1),EUgDder(1,1,i-2))
1690 cd        write (iout,*) 'i',i,' mu ',(mu(k,i-2),k=1,2),
1691 cd     &  ' mu1',(b1(k,i-2),k=1,2),' mu2',(Ub2(k,i-2),k=1,2)
1692       enddo
1693 C Matrices dependent on two consecutive virtual-bond dihedrals.
1694 C The order of matrices is from left to right.
1695       do i=2,nres-1
1696         call matmat2(DtUg2(1,1,i-1),EUg(1,1,i),DtUg2EUg(1,1,i))
1697         call matmat2(DtUg2der(1,1,i-1),EUg(1,1,i),DtUg2EUgder(1,1,1,i))
1698         call matmat2(DtUg2(1,1,i-1),EUgder(1,1,i),DtUg2EUgder(1,1,2,i))
1699         call transpose2(DtUg2(1,1,i-1),auxmat(1,1))
1700         call matmat2(auxmat(1,1),EUg(1,1,i),Ug2DtEUg(1,1,i))
1701         call matmat2(auxmat(1,1),EUgder(1,1,i),Ug2DtEUgder(1,1,2,i))
1702         call transpose2(DtUg2der(1,1,i-1),auxmat(1,1))
1703         call matmat2(auxmat(1,1),EUg(1,1,i),Ug2DtEUgder(1,1,1,i))
1704       enddo
1705 cd      do i=1,nres
1706 cd        iti = itortyp(itype(i))
1707 cd        write (iout,*) i
1708 cd        do j=1,2
1709 cd        write (iout,'(2f10.5,5x,2f10.5,5x,2f10.5)') 
1710 cd     &  (EE(j,k,iti),k=1,2),(Ug(j,k,i),k=1,2),(EUg(j,k,i),k=1,2)
1711 cd        enddo
1712 cd      enddo
1713       return
1714       end
1715 C--------------------------------------------------------------------------
1716       subroutine eelec(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
1717 C
1718 C This subroutine calculates the average interaction energy and its gradient
1719 C in the virtual-bond vectors between non-adjacent peptide groups, based on 
1720 C the potential described in Liwo et al., Protein Sci., 1993, 2, 1715. 
1721 C The potential depends both on the distance of peptide-group centers and on 
1722 C the orientation of the CA-CA virtual bonds.
1723
1724       implicit real*8 (a-h,o-z)
1725       include 'DIMENSIONS'
1726       include 'sizesclu.dat'
1727       include 'COMMON.CONTROL'
1728       include 'COMMON.IOUNITS'
1729       include 'COMMON.GEO'
1730       include 'COMMON.VAR'
1731       include 'COMMON.LOCAL'
1732       include 'COMMON.CHAIN'
1733       include 'COMMON.DERIV'
1734       include 'COMMON.INTERACT'
1735       include 'COMMON.CONTACTS'
1736       include 'COMMON.TORSION'
1737       include 'COMMON.VECTORS'
1738       include 'COMMON.FFIELD'
1739       dimension ggg(3),gggp(3),gggm(3),erij(3),dcosb(3),dcosg(3),
1740      &          erder(3,3),uryg(3,3),urzg(3,3),vryg(3,3),vrzg(3,3)
1741       double precision acipa(2,2),agg(3,4),aggi(3,4),aggi1(3,4),
1742      &    aggj(3,4),aggj1(3,4),a_temp(2,2),muij(4)
1743       common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,j1
1744 c 4/26/02 - AL scaling factor for 1,4 repulsive VDW interactions
1745       double precision scal_el /0.5d0/
1746 C 12/13/98 
1747 C 13-go grudnia roku pamietnego... 
1748       double precision unmat(3,3) /1.0d0,0.0d0,0.0d0,
1749      &                   0.0d0,1.0d0,0.0d0,
1750      &                   0.0d0,0.0d0,1.0d0/
1751 cd      write(iout,*) 'In EELEC'
1752 cd      do i=1,nloctyp
1753 cd        write(iout,*) 'Type',i
1754 cd        write(iout,*) 'B1',B1(:,i)
1755 cd        write(iout,*) 'B2',B2(:,i)
1756 cd        write(iout,*) 'CC',CC(:,:,i)
1757 cd        write(iout,*) 'DD',DD(:,:,i)
1758 cd        write(iout,*) 'EE',EE(:,:,i)
1759 cd      enddo
1760 cd      call check_vecgrad
1761 cd      stop
1762       if (icheckgrad.eq.1) then
1763         do i=1,nres-1
1764           fac=1.0d0/dsqrt(scalar(dc(1,i),dc(1,i)))
1765           do k=1,3
1766             dc_norm(k,i)=dc(k,i)*fac
1767           enddo
1768 c          write (iout,*) 'i',i,' fac',fac
1769         enddo
1770       endif
1771       if (wel_loc.gt.0.0d0 .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 
1772      &    .or. wcorr6.gt.0.0d0 .or. wturn3.gt.0.0d0 .or. 
1773      &    wturn4.gt.0.0d0 .or. wturn6.gt.0.0d0) then
1774 cd      if (wel_loc.gt.0.0d0) then
1775         if (icheckgrad.eq.1) then
1776         call vec_and_deriv_test
1777         else
1778         call vec_and_deriv
1779         endif
1780         call set_matrices
1781       endif
1782 cd      do i=1,nres-1
1783 cd        write (iout,*) 'i=',i
1784 cd        do k=1,3
1785 cd          write (iout,'(i5,2f10.5)') k,uy(k,i),uz(k,i)
1786 cd        enddo
1787 cd        do k=1,3
1788 cd          write (iout,'(f10.5,2x,3f10.5,2x,3f10.5)') 
1789 cd     &     uz(k,i),(uzgrad(k,l,1,i),l=1,3),(uzgrad(k,l,2,i),l=1,3)
1790 cd        enddo
1791 cd      enddo
1792       num_conti_hb=0
1793       ees=0.0D0
1794       evdw1=0.0D0
1795       eel_loc=0.0d0 
1796       eello_turn3=0.0d0
1797       eello_turn4=0.0d0
1798       ind=0
1799       do i=1,nres
1800         num_cont_hb(i)=0
1801       enddo
1802 cd      print '(a)','Enter EELEC'
1803 cd      write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
1804       do i=1,nres
1805         gel_loc_loc(i)=0.0d0
1806         gcorr_loc(i)=0.0d0
1807       enddo
1808       do i=iatel_s,iatel_e
1809         if (itype(i).eq.21 .or. itype(i+1).eq.21) cycle
1810         if (itel(i).eq.0) goto 1215
1811         dxi=dc(1,i)
1812         dyi=dc(2,i)
1813         dzi=dc(3,i)
1814         dx_normi=dc_norm(1,i)
1815         dy_normi=dc_norm(2,i)
1816         dz_normi=dc_norm(3,i)
1817         xmedi=c(1,i)+0.5d0*dxi
1818         ymedi=c(2,i)+0.5d0*dyi
1819         zmedi=c(3,i)+0.5d0*dzi
1820         num_conti=0
1821 c        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
1822         do j=ielstart(i),ielend(i)
1823           if (itype(j).eq.21 .or. itype(j+1).eq.21) cycle
1824           if (itel(j).eq.0) goto 1216
1825           ind=ind+1
1826           iteli=itel(i)
1827           itelj=itel(j)
1828           if (j.eq.i+2 .and. itelj.eq.2) iteli=2
1829           aaa=app(iteli,itelj)
1830           bbb=bpp(iteli,itelj)
1831 C Diagnostics only!!!
1832 c         aaa=0.0D0
1833 c         bbb=0.0D0
1834 c         ael6i=0.0D0
1835 c         ael3i=0.0D0
1836 C End diagnostics
1837           ael6i=ael6(iteli,itelj)
1838           ael3i=ael3(iteli,itelj) 
1839           dxj=dc(1,j)
1840           dyj=dc(2,j)
1841           dzj=dc(3,j)
1842           dx_normj=dc_norm(1,j)
1843           dy_normj=dc_norm(2,j)
1844           dz_normj=dc_norm(3,j)
1845           xj=c(1,j)+0.5D0*dxj-xmedi
1846           yj=c(2,j)+0.5D0*dyj-ymedi
1847           zj=c(3,j)+0.5D0*dzj-zmedi
1848           rij=xj*xj+yj*yj+zj*zj
1849           rrmij=1.0D0/rij
1850           rij=dsqrt(rij)
1851           rmij=1.0D0/rij
1852           r3ij=rrmij*rmij
1853           r6ij=r3ij*r3ij  
1854           cosa=dx_normi*dx_normj+dy_normi*dy_normj+dz_normi*dz_normj
1855           cosb=(xj*dx_normi+yj*dy_normi+zj*dz_normi)*rmij
1856           cosg=(xj*dx_normj+yj*dy_normj+zj*dz_normj)*rmij
1857           fac=cosa-3.0D0*cosb*cosg
1858           ev1=aaa*r6ij*r6ij
1859 c 4/26/02 - AL scaling down 1,4 repulsive VDW interactions
1860           if (j.eq.i+2) ev1=scal_el*ev1
1861           ev2=bbb*r6ij
1862           fac3=ael6i*r6ij
1863           fac4=ael3i*r3ij
1864           evdwij=ev1+ev2
1865           el1=fac3*(4.0D0+fac*fac-3.0D0*(cosb*cosb+cosg*cosg))
1866           el2=fac4*fac       
1867           eesij=el1+el2
1868 c          write (iout,*) "i",i,iteli," j",j,itelj," eesij",eesij
1869 C 12/26/95 - for the evaluation of multi-body H-bonding interactions
1870           ees0ij=4.0D0+fac*fac-3.0D0*(cosb*cosb+cosg*cosg)
1871           ees=ees+eesij
1872           evdw1=evdw1+evdwij
1873 cd          write(iout,'(2(2i3,2x),7(1pd12.4)/2(3(1pd12.4),5x)/)')
1874 cd     &      iteli,i,itelj,j,aaa,bbb,ael6i,ael3i,
1875 cd     &      1.0D0/dsqrt(rrmij),evdwij,eesij,
1876 cd     &      xmedi,ymedi,zmedi,xj,yj,zj
1877 C
1878 C Calculate contributions to the Cartesian gradient.
1879 C
1880 #ifdef SPLITELE
1881           facvdw=-6*rrmij*(ev1+evdwij) 
1882           facel=-3*rrmij*(el1+eesij)
1883           fac1=fac
1884           erij(1)=xj*rmij
1885           erij(2)=yj*rmij
1886           erij(3)=zj*rmij
1887           if (calc_grad) then
1888 *
1889 * Radial derivatives. First process both termini of the fragment (i,j)
1890
1891           ggg(1)=facel*xj
1892           ggg(2)=facel*yj
1893           ggg(3)=facel*zj
1894           do k=1,3
1895             ghalf=0.5D0*ggg(k)
1896             gelc(k,i)=gelc(k,i)+ghalf
1897             gelc(k,j)=gelc(k,j)+ghalf
1898           enddo
1899 *
1900 * Loop over residues i+1 thru j-1.
1901 *
1902           do k=i+1,j-1
1903             do l=1,3
1904               gelc(l,k)=gelc(l,k)+ggg(l)
1905             enddo
1906           enddo
1907           ggg(1)=facvdw*xj
1908           ggg(2)=facvdw*yj
1909           ggg(3)=facvdw*zj
1910           do k=1,3
1911             ghalf=0.5D0*ggg(k)
1912             gvdwpp(k,i)=gvdwpp(k,i)+ghalf
1913             gvdwpp(k,j)=gvdwpp(k,j)+ghalf
1914           enddo
1915 *
1916 * Loop over residues i+1 thru j-1.
1917 *
1918           do k=i+1,j-1
1919             do l=1,3
1920               gvdwpp(l,k)=gvdwpp(l,k)+ggg(l)
1921             enddo
1922           enddo
1923 #else
1924           facvdw=ev1+evdwij 
1925           facel=el1+eesij  
1926           fac1=fac
1927           fac=-3*rrmij*(facvdw+facvdw+facel)
1928           erij(1)=xj*rmij
1929           erij(2)=yj*rmij
1930           erij(3)=zj*rmij
1931           if (calc_grad) then
1932 *
1933 * Radial derivatives. First process both termini of the fragment (i,j)
1934
1935           ggg(1)=fac*xj
1936           ggg(2)=fac*yj
1937           ggg(3)=fac*zj
1938           do k=1,3
1939             ghalf=0.5D0*ggg(k)
1940             gelc(k,i)=gelc(k,i)+ghalf
1941             gelc(k,j)=gelc(k,j)+ghalf
1942           enddo
1943 *
1944 * Loop over residues i+1 thru j-1.
1945 *
1946           do k=i+1,j-1
1947             do l=1,3
1948               gelc(l,k)=gelc(l,k)+ggg(l)
1949             enddo
1950           enddo
1951 #endif
1952 *
1953 * Angular part
1954 *          
1955           ecosa=2.0D0*fac3*fac1+fac4
1956           fac4=-3.0D0*fac4
1957           fac3=-6.0D0*fac3
1958           ecosb=(fac3*(fac1*cosg+cosb)+cosg*fac4)
1959           ecosg=(fac3*(fac1*cosb+cosg)+cosb*fac4)
1960           do k=1,3
1961             dcosb(k)=rmij*(dc_norm(k,i)-erij(k)*cosb)
1962             dcosg(k)=rmij*(dc_norm(k,j)-erij(k)*cosg)
1963           enddo
1964 cd        print '(2i3,2(3(1pd14.5),3x))',i,j,(dcosb(k),k=1,3),
1965 cd   &          (dcosg(k),k=1,3)
1966           do k=1,3
1967             ggg(k)=ecosb*dcosb(k)+ecosg*dcosg(k) 
1968           enddo
1969           do k=1,3
1970             ghalf=0.5D0*ggg(k)
1971             gelc(k,i)=gelc(k,i)+ghalf
1972      &               +(ecosa*(dc_norm(k,j)-cosa*dc_norm(k,i))
1973      &               + ecosb*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
1974             gelc(k,j)=gelc(k,j)+ghalf
1975      &               +(ecosa*(dc_norm(k,i)-cosa*dc_norm(k,j))
1976      &               + ecosg*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
1977           enddo
1978           do k=i+1,j-1
1979             do l=1,3
1980               gelc(l,k)=gelc(l,k)+ggg(l)
1981             enddo
1982           enddo
1983           endif
1984
1985           IF (wel_loc.gt.0.0d0 .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0
1986      &        .or. wcorr6.gt.0.0d0 .or. wturn3.gt.0.0d0 
1987      &        .or. wturn4.gt.0.0d0 .or. wturn6.gt.0.0d0) THEN
1988 C
1989 C 9/25/99 Mixed third-order local-electrostatic terms. The local-interaction 
1990 C   energy of a peptide unit is assumed in the form of a second-order 
1991 C   Fourier series in the angles lambda1 and lambda2 (see Nishikawa et al.
1992 C   Macromolecules, 1974, 7, 797-806 for definition). This correlation terms
1993 C   are computed for EVERY pair of non-contiguous peptide groups.
1994 C
1995           if (j.lt.nres-1) then
1996             j1=j+1
1997             j2=j-1
1998           else
1999             j1=j-1
2000             j2=j-2
2001           endif
2002           kkk=0
2003           do k=1,2
2004             do l=1,2
2005               kkk=kkk+1
2006               muij(kkk)=mu(k,i)*mu(l,j)
2007             enddo
2008           enddo  
2009 cd         write (iout,*) 'EELEC: i',i,' j',j
2010 cd          write (iout,*) 'j',j,' j1',j1,' j2',j2
2011 cd          write(iout,*) 'muij',muij
2012           ury=scalar(uy(1,i),erij)
2013           urz=scalar(uz(1,i),erij)
2014           vry=scalar(uy(1,j),erij)
2015           vrz=scalar(uz(1,j),erij)
2016           a22=scalar(uy(1,i),uy(1,j))-3*ury*vry
2017           a23=scalar(uy(1,i),uz(1,j))-3*ury*vrz
2018           a32=scalar(uz(1,i),uy(1,j))-3*urz*vry
2019           a33=scalar(uz(1,i),uz(1,j))-3*urz*vrz
2020 C For diagnostics only
2021 cd          a22=1.0d0
2022 cd          a23=1.0d0
2023 cd          a32=1.0d0
2024 cd          a33=1.0d0
2025           fac=dsqrt(-ael6i)*r3ij
2026 cd          write (2,*) 'fac=',fac
2027 C For diagnostics only
2028 cd          fac=1.0d0
2029           a22=a22*fac
2030           a23=a23*fac
2031           a32=a32*fac
2032           a33=a33*fac
2033 cd          write (iout,'(4i5,4f10.5)')
2034 cd     &     i,itortyp(itype(i)),j,itortyp(itype(j)),a22,a23,a32,a33
2035 cd          write (iout,'(6f10.5)') (muij(k),k=1,4),fac,eel_loc_ij
2036 cd          write (iout,'(2(3f10.5,5x)/2(3f10.5,5x))') (uy(k,i),k=1,3),
2037 cd     &      (uz(k,i),k=1,3),(uy(k,j),k=1,3),(uz(k,j),k=1,3)
2038 cd          write (iout,'(4f10.5)') 
2039 cd     &      scalar(uy(1,i),uy(1,j)),scalar(uy(1,i),uz(1,j)),
2040 cd     &      scalar(uz(1,i),uy(1,j)),scalar(uz(1,i),uz(1,j))
2041 cd          write (iout,'(4f10.5)') ury,urz,vry,vrz
2042 cd           write (iout,'(2i3,9f10.5/)') i,j,
2043 cd     &      fac22,a22,fac23,a23,fac32,a32,fac33,a33,eel_loc_ij
2044           if (calc_grad) then
2045 C Derivatives of the elements of A in virtual-bond vectors
2046           call unormderiv(erij(1),unmat(1,1),rmij,erder(1,1))
2047 cd          do k=1,3
2048 cd            do l=1,3
2049 cd              erder(k,l)=0.0d0
2050 cd            enddo
2051 cd          enddo
2052           do k=1,3
2053             uryg(k,1)=scalar(erder(1,k),uy(1,i))
2054             uryg(k,2)=scalar(uygrad(1,k,1,i),erij(1))
2055             uryg(k,3)=scalar(uygrad(1,k,2,i),erij(1))
2056             urzg(k,1)=scalar(erder(1,k),uz(1,i))
2057             urzg(k,2)=scalar(uzgrad(1,k,1,i),erij(1))
2058             urzg(k,3)=scalar(uzgrad(1,k,2,i),erij(1))
2059             vryg(k,1)=scalar(erder(1,k),uy(1,j))
2060             vryg(k,2)=scalar(uygrad(1,k,1,j),erij(1))
2061             vryg(k,3)=scalar(uygrad(1,k,2,j),erij(1))
2062             vrzg(k,1)=scalar(erder(1,k),uz(1,j))
2063             vrzg(k,2)=scalar(uzgrad(1,k,1,j),erij(1))
2064             vrzg(k,3)=scalar(uzgrad(1,k,2,j),erij(1))
2065           enddo
2066 cd          do k=1,3
2067 cd            do l=1,3
2068 cd              uryg(k,l)=0.0d0
2069 cd              urzg(k,l)=0.0d0
2070 cd              vryg(k,l)=0.0d0
2071 cd              vrzg(k,l)=0.0d0
2072 cd            enddo
2073 cd          enddo
2074 C Compute radial contributions to the gradient
2075           facr=-3.0d0*rrmij
2076           a22der=a22*facr
2077           a23der=a23*facr
2078           a32der=a32*facr
2079           a33der=a33*facr
2080 cd          a22der=0.0d0
2081 cd          a23der=0.0d0
2082 cd          a32der=0.0d0
2083 cd          a33der=0.0d0
2084           agg(1,1)=a22der*xj
2085           agg(2,1)=a22der*yj
2086           agg(3,1)=a22der*zj
2087           agg(1,2)=a23der*xj
2088           agg(2,2)=a23der*yj
2089           agg(3,2)=a23der*zj
2090           agg(1,3)=a32der*xj
2091           agg(2,3)=a32der*yj
2092           agg(3,3)=a32der*zj
2093           agg(1,4)=a33der*xj
2094           agg(2,4)=a33der*yj
2095           agg(3,4)=a33der*zj
2096 C Add the contributions coming from er
2097           fac3=-3.0d0*fac
2098           do k=1,3
2099             agg(k,1)=agg(k,1)+fac3*(uryg(k,1)*vry+vryg(k,1)*ury)
2100             agg(k,2)=agg(k,2)+fac3*(uryg(k,1)*vrz+vrzg(k,1)*ury)
2101             agg(k,3)=agg(k,3)+fac3*(urzg(k,1)*vry+vryg(k,1)*urz)
2102             agg(k,4)=agg(k,4)+fac3*(urzg(k,1)*vrz+vrzg(k,1)*urz)
2103           enddo
2104           do k=1,3
2105 C Derivatives in DC(i) 
2106             ghalf1=0.5d0*agg(k,1)
2107             ghalf2=0.5d0*agg(k,2)
2108             ghalf3=0.5d0*agg(k,3)
2109             ghalf4=0.5d0*agg(k,4)
2110             aggi(k,1)=fac*(scalar(uygrad(1,k,1,i),uy(1,j))
2111      &      -3.0d0*uryg(k,2)*vry)+ghalf1
2112             aggi(k,2)=fac*(scalar(uygrad(1,k,1,i),uz(1,j))
2113      &      -3.0d0*uryg(k,2)*vrz)+ghalf2
2114             aggi(k,3)=fac*(scalar(uzgrad(1,k,1,i),uy(1,j))
2115      &      -3.0d0*urzg(k,2)*vry)+ghalf3
2116             aggi(k,4)=fac*(scalar(uzgrad(1,k,1,i),uz(1,j))
2117      &      -3.0d0*urzg(k,2)*vrz)+ghalf4
2118 C Derivatives in DC(i+1)
2119             aggi1(k,1)=fac*(scalar(uygrad(1,k,2,i),uy(1,j))
2120      &      -3.0d0*uryg(k,3)*vry)+agg(k,1)
2121             aggi1(k,2)=fac*(scalar(uygrad(1,k,2,i),uz(1,j))
2122      &      -3.0d0*uryg(k,3)*vrz)+agg(k,2)
2123             aggi1(k,3)=fac*(scalar(uzgrad(1,k,2,i),uy(1,j))
2124      &      -3.0d0*urzg(k,3)*vry)+agg(k,3)
2125             aggi1(k,4)=fac*(scalar(uzgrad(1,k,2,i),uz(1,j))
2126      &      -3.0d0*urzg(k,3)*vrz)+agg(k,4)
2127 C Derivatives in DC(j)
2128             aggj(k,1)=fac*(scalar(uygrad(1,k,1,j),uy(1,i))
2129      &      -3.0d0*vryg(k,2)*ury)+ghalf1
2130             aggj(k,2)=fac*(scalar(uzgrad(1,k,1,j),uy(1,i))
2131      &      -3.0d0*vrzg(k,2)*ury)+ghalf2
2132             aggj(k,3)=fac*(scalar(uygrad(1,k,1,j),uz(1,i))
2133      &      -3.0d0*vryg(k,2)*urz)+ghalf3
2134             aggj(k,4)=fac*(scalar(uzgrad(1,k,1,j),uz(1,i)) 
2135      &      -3.0d0*vrzg(k,2)*urz)+ghalf4
2136 C Derivatives in DC(j+1) or DC(nres-1)
2137             aggj1(k,1)=fac*(scalar(uygrad(1,k,2,j),uy(1,i))
2138      &      -3.0d0*vryg(k,3)*ury)
2139             aggj1(k,2)=fac*(scalar(uzgrad(1,k,2,j),uy(1,i))
2140      &      -3.0d0*vrzg(k,3)*ury)
2141             aggj1(k,3)=fac*(scalar(uygrad(1,k,2,j),uz(1,i))
2142      &      -3.0d0*vryg(k,3)*urz)
2143             aggj1(k,4)=fac*(scalar(uzgrad(1,k,2,j),uz(1,i)) 
2144      &      -3.0d0*vrzg(k,3)*urz)
2145 cd            aggi(k,1)=ghalf1
2146 cd            aggi(k,2)=ghalf2
2147 cd            aggi(k,3)=ghalf3
2148 cd            aggi(k,4)=ghalf4
2149 C Derivatives in DC(i+1)
2150 cd            aggi1(k,1)=agg(k,1)
2151 cd            aggi1(k,2)=agg(k,2)
2152 cd            aggi1(k,3)=agg(k,3)
2153 cd            aggi1(k,4)=agg(k,4)
2154 C Derivatives in DC(j)
2155 cd            aggj(k,1)=ghalf1
2156 cd            aggj(k,2)=ghalf2
2157 cd            aggj(k,3)=ghalf3
2158 cd            aggj(k,4)=ghalf4
2159 C Derivatives in DC(j+1)
2160 cd            aggj1(k,1)=0.0d0
2161 cd            aggj1(k,2)=0.0d0
2162 cd            aggj1(k,3)=0.0d0
2163 cd            aggj1(k,4)=0.0d0
2164             if (j.eq.nres-1 .and. i.lt.j-2) then
2165               do l=1,4
2166                 aggj1(k,l)=aggj1(k,l)+agg(k,l)
2167 cd                aggj1(k,l)=agg(k,l)
2168               enddo
2169             endif
2170           enddo
2171           endif
2172 c          goto 11111
2173 C Check the loc-el terms by numerical integration
2174           acipa(1,1)=a22
2175           acipa(1,2)=a23
2176           acipa(2,1)=a32
2177           acipa(2,2)=a33
2178           a22=-a22
2179           a23=-a23
2180           do l=1,2
2181             do k=1,3
2182               agg(k,l)=-agg(k,l)
2183               aggi(k,l)=-aggi(k,l)
2184               aggi1(k,l)=-aggi1(k,l)
2185               aggj(k,l)=-aggj(k,l)
2186               aggj1(k,l)=-aggj1(k,l)
2187             enddo
2188           enddo
2189           if (j.lt.nres-1) then
2190             a22=-a22
2191             a32=-a32
2192             do l=1,3,2
2193               do k=1,3
2194                 agg(k,l)=-agg(k,l)
2195                 aggi(k,l)=-aggi(k,l)
2196                 aggi1(k,l)=-aggi1(k,l)
2197                 aggj(k,l)=-aggj(k,l)
2198                 aggj1(k,l)=-aggj1(k,l)
2199               enddo
2200             enddo
2201           else
2202             a22=-a22
2203             a23=-a23
2204             a32=-a32
2205             a33=-a33
2206             do l=1,4
2207               do k=1,3
2208                 agg(k,l)=-agg(k,l)
2209                 aggi(k,l)=-aggi(k,l)
2210                 aggi1(k,l)=-aggi1(k,l)
2211                 aggj(k,l)=-aggj(k,l)
2212                 aggj1(k,l)=-aggj1(k,l)
2213               enddo
2214             enddo 
2215           endif    
2216           ENDIF ! WCORR
2217 11111     continue
2218           IF (wel_loc.gt.0.0d0) THEN
2219 C Contribution to the local-electrostatic energy coming from the i-j pair
2220           eel_loc_ij=a22*muij(1)+a23*muij(2)+a32*muij(3)
2221      &     +a33*muij(4)
2222 cd          write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
2223 cd          write (iout,*) a22,muij(1),a23,muij(2),a32,muij(3)
2224           eel_loc=eel_loc+eel_loc_ij
2225 C Partial derivatives in virtual-bond dihedral angles gamma
2226           if (calc_grad) then
2227           if (i.gt.1)
2228      &    gel_loc_loc(i-1)=gel_loc_loc(i-1)+ 
2229      &            a22*muder(1,i)*mu(1,j)+a23*muder(1,i)*mu(2,j)
2230      &           +a32*muder(2,i)*mu(1,j)+a33*muder(2,i)*mu(2,j)
2231           gel_loc_loc(j-1)=gel_loc_loc(j-1)+ 
2232      &            a22*mu(1,i)*muder(1,j)+a23*mu(1,i)*muder(2,j)
2233      &           +a32*mu(2,i)*muder(1,j)+a33*mu(2,i)*muder(2,j)
2234 cd          call checkint3(i,j,mu1,mu2,a22,a23,a32,a33,acipa,eel_loc_ij)
2235 cd          write(iout,*) 'agg  ',agg
2236 cd          write(iout,*) 'aggi ',aggi
2237 cd          write(iout,*) 'aggi1',aggi1
2238 cd          write(iout,*) 'aggj ',aggj
2239 cd          write(iout,*) 'aggj1',aggj1
2240
2241 C Derivatives of eello in DC(i+1) thru DC(j-1) or DC(nres-2)
2242           do l=1,3
2243             ggg(l)=agg(l,1)*muij(1)+
2244      &          agg(l,2)*muij(2)+agg(l,3)*muij(3)+agg(l,4)*muij(4)
2245           enddo
2246           do k=i+2,j2
2247             do l=1,3
2248               gel_loc(l,k)=gel_loc(l,k)+ggg(l)
2249             enddo
2250           enddo
2251 C Remaining derivatives of eello
2252           do l=1,3
2253             gel_loc(l,i)=gel_loc(l,i)+aggi(l,1)*muij(1)+
2254      &          aggi(l,2)*muij(2)+aggi(l,3)*muij(3)+aggi(l,4)*muij(4)
2255             gel_loc(l,i+1)=gel_loc(l,i+1)+aggi1(l,1)*muij(1)+
2256      &          aggi1(l,2)*muij(2)+aggi1(l,3)*muij(3)+aggi1(l,4)*muij(4)
2257             gel_loc(l,j)=gel_loc(l,j)+aggj(l,1)*muij(1)+
2258      &          aggj(l,2)*muij(2)+aggj(l,3)*muij(3)+aggj(l,4)*muij(4)
2259             gel_loc(l,j1)=gel_loc(l,j1)+aggj1(l,1)*muij(1)+
2260      &          aggj1(l,2)*muij(2)+aggj1(l,3)*muij(3)+aggj1(l,4)*muij(4)
2261           enddo
2262           endif
2263           ENDIF
2264           if (wturn3.gt.0.0d0 .or. wturn4.gt.0.0d0) then
2265 C Contributions from turns
2266             a_temp(1,1)=a22
2267             a_temp(1,2)=a23
2268             a_temp(2,1)=a32
2269             a_temp(2,2)=a33
2270             call eturn34(i,j,eello_turn3,eello_turn4)
2271           endif
2272 C Change 12/26/95 to calculate four-body contributions to H-bonding energy
2273           if (j.gt.i+1 .and. num_conti.le.maxconts) then
2274 C
2275 C Calculate the contact function. The ith column of the array JCONT will 
2276 C contain the numbers of atoms that make contacts with the atom I (of numbers
2277 C greater than I). The arrays FACONT and GACONT will contain the values of
2278 C the contact function and its derivative.
2279 c           r0ij=1.02D0*rpp(iteli,itelj)
2280 c           r0ij=1.11D0*rpp(iteli,itelj)
2281             r0ij=2.20D0*rpp(iteli,itelj)
2282 c           r0ij=1.55D0*rpp(iteli,itelj)
2283             call gcont(rij,r0ij,1.0D0,0.2d0*r0ij,fcont,fprimcont)
2284             if (fcont.gt.0.0D0) then
2285               num_conti=num_conti+1
2286               if (num_conti.gt.maxconts) then
2287                 write (iout,*) 'WARNING - max. # of contacts exceeded;',
2288      &                         ' will skip next contacts for this conf.'
2289               else
2290                 jcont_hb(num_conti,i)=j
2291                 IF (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. 
2292      &          wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0) THEN
2293 C 9/30/99 (AL) - store components necessary to evaluate higher-order loc-el
2294 C  terms.
2295                 d_cont(num_conti,i)=rij
2296 cd                write (2,'(3e15.5)') rij,r0ij+0.2d0*r0ij,rij
2297 C     --- Electrostatic-interaction matrix --- 
2298                 a_chuj(1,1,num_conti,i)=a22
2299                 a_chuj(1,2,num_conti,i)=a23
2300                 a_chuj(2,1,num_conti,i)=a32
2301                 a_chuj(2,2,num_conti,i)=a33
2302 C     --- Gradient of rij
2303                 do kkk=1,3
2304                   grij_hb_cont(kkk,num_conti,i)=erij(kkk)
2305                 enddo
2306 c             if (i.eq.1) then
2307 c                a_chuj(1,1,num_conti,i)=-0.61d0
2308 c                a_chuj(1,2,num_conti,i)= 0.4d0
2309 c                a_chuj(2,1,num_conti,i)= 0.65d0
2310 c                a_chuj(2,2,num_conti,i)= 0.50d0
2311 c             else if (i.eq.2) then
2312 c                a_chuj(1,1,num_conti,i)= 0.0d0
2313 c                a_chuj(1,2,num_conti,i)= 0.0d0
2314 c                a_chuj(2,1,num_conti,i)= 0.0d0
2315 c                a_chuj(2,2,num_conti,i)= 0.0d0
2316 c             endif
2317 C     --- and its gradients
2318 cd                write (iout,*) 'i',i,' j',j
2319 cd                do kkk=1,3
2320 cd                write (iout,*) 'iii 1 kkk',kkk
2321 cd                write (iout,*) agg(kkk,:)
2322 cd                enddo
2323 cd                do kkk=1,3
2324 cd                write (iout,*) 'iii 2 kkk',kkk
2325 cd                write (iout,*) aggi(kkk,:)
2326 cd                enddo
2327 cd                do kkk=1,3
2328 cd                write (iout,*) 'iii 3 kkk',kkk
2329 cd                write (iout,*) aggi1(kkk,:)
2330 cd                enddo
2331 cd                do kkk=1,3
2332 cd                write (iout,*) 'iii 4 kkk',kkk
2333 cd                write (iout,*) aggj(kkk,:)
2334 cd                enddo
2335 cd                do kkk=1,3
2336 cd                write (iout,*) 'iii 5 kkk',kkk
2337 cd                write (iout,*) aggj1(kkk,:)
2338 cd                enddo
2339                 kkll=0
2340                 do k=1,2
2341                   do l=1,2
2342                     kkll=kkll+1
2343                     do m=1,3
2344                       a_chuj_der(k,l,m,1,num_conti,i)=agg(m,kkll)
2345                       a_chuj_der(k,l,m,2,num_conti,i)=aggi(m,kkll)
2346                       a_chuj_der(k,l,m,3,num_conti,i)=aggi1(m,kkll)
2347                       a_chuj_der(k,l,m,4,num_conti,i)=aggj(m,kkll)
2348                       a_chuj_der(k,l,m,5,num_conti,i)=aggj1(m,kkll)
2349 c                      do mm=1,5
2350 c                      a_chuj_der(k,l,m,mm,num_conti,i)=0.0d0
2351 c                      enddo
2352                     enddo
2353                   enddo
2354                 enddo
2355                 ENDIF
2356                 IF (wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) THEN
2357 C Calculate contact energies
2358                 cosa4=4.0D0*cosa
2359                 wij=cosa-3.0D0*cosb*cosg
2360                 cosbg1=cosb+cosg
2361                 cosbg2=cosb-cosg
2362 c               fac3=dsqrt(-ael6i)/r0ij**3     
2363                 fac3=dsqrt(-ael6i)*r3ij
2364                 ees0pij=dsqrt(4.0D0+cosa4+wij*wij-3.0D0*cosbg1*cosbg1)
2365                 ees0mij=dsqrt(4.0D0-cosa4+wij*wij-3.0D0*cosbg2*cosbg2)
2366 c               ees0mij=0.0D0
2367                 ees0p(num_conti,i)=0.5D0*fac3*(ees0pij+ees0mij)
2368                 ees0m(num_conti,i)=0.5D0*fac3*(ees0pij-ees0mij)
2369 C Diagnostics. Comment out or remove after debugging!
2370 c               ees0p(num_conti,i)=0.5D0*fac3*ees0pij
2371 c               ees0m(num_conti,i)=0.5D0*fac3*ees0mij
2372 c               ees0m(num_conti,i)=0.0D0
2373 C End diagnostics.
2374 c                write (iout,*) 'i=',i,' j=',j,' rij=',rij,' r0ij=',r0ij,
2375 c     & ' ees0ij=',ees0p(num_conti,i),ees0m(num_conti,i),' fcont=',fcont
2376                 facont_hb(num_conti,i)=fcont
2377                 if (calc_grad) then
2378 C Angular derivatives of the contact function
2379                 ees0pij1=fac3/ees0pij 
2380                 ees0mij1=fac3/ees0mij
2381                 fac3p=-3.0D0*fac3*rrmij
2382                 ees0pijp=0.5D0*fac3p*(ees0pij+ees0mij)
2383                 ees0mijp=0.5D0*fac3p*(ees0pij-ees0mij)
2384 c               ees0mij1=0.0D0
2385                 ecosa1=       ees0pij1*( 1.0D0+0.5D0*wij)
2386                 ecosb1=-1.5D0*ees0pij1*(wij*cosg+cosbg1)
2387                 ecosg1=-1.5D0*ees0pij1*(wij*cosb+cosbg1)
2388                 ecosa2=       ees0mij1*(-1.0D0+0.5D0*wij)
2389                 ecosb2=-1.5D0*ees0mij1*(wij*cosg+cosbg2) 
2390                 ecosg2=-1.5D0*ees0mij1*(wij*cosb-cosbg2)
2391                 ecosap=ecosa1+ecosa2
2392                 ecosbp=ecosb1+ecosb2
2393                 ecosgp=ecosg1+ecosg2
2394                 ecosam=ecosa1-ecosa2
2395                 ecosbm=ecosb1-ecosb2
2396                 ecosgm=ecosg1-ecosg2
2397 C Diagnostics
2398 c               ecosap=ecosa1
2399 c               ecosbp=ecosb1
2400 c               ecosgp=ecosg1
2401 c               ecosam=0.0D0
2402 c               ecosbm=0.0D0
2403 c               ecosgm=0.0D0
2404 C End diagnostics
2405                 fprimcont=fprimcont/rij
2406 cd              facont_hb(num_conti,i)=1.0D0
2407 C Following line is for diagnostics.
2408 cd              fprimcont=0.0D0
2409                 do k=1,3
2410                   dcosb(k)=rmij*(dc_norm(k,i)-erij(k)*cosb)
2411                   dcosg(k)=rmij*(dc_norm(k,j)-erij(k)*cosg)
2412                 enddo
2413                 do k=1,3
2414                   gggp(k)=ecosbp*dcosb(k)+ecosgp*dcosg(k)
2415                   gggm(k)=ecosbm*dcosb(k)+ecosgm*dcosg(k)
2416                 enddo
2417                 gggp(1)=gggp(1)+ees0pijp*xj
2418                 gggp(2)=gggp(2)+ees0pijp*yj
2419                 gggp(3)=gggp(3)+ees0pijp*zj
2420                 gggm(1)=gggm(1)+ees0mijp*xj
2421                 gggm(2)=gggm(2)+ees0mijp*yj
2422                 gggm(3)=gggm(3)+ees0mijp*zj
2423 C Derivatives due to the contact function
2424                 gacont_hbr(1,num_conti,i)=fprimcont*xj
2425                 gacont_hbr(2,num_conti,i)=fprimcont*yj
2426                 gacont_hbr(3,num_conti,i)=fprimcont*zj
2427                 do k=1,3
2428                   ghalfp=0.5D0*gggp(k)
2429                   ghalfm=0.5D0*gggm(k)
2430                   gacontp_hb1(k,num_conti,i)=ghalfp
2431      &              +(ecosap*(dc_norm(k,j)-cosa*dc_norm(k,i))
2432      &              + ecosbp*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
2433                   gacontp_hb2(k,num_conti,i)=ghalfp
2434      &              +(ecosap*(dc_norm(k,i)-cosa*dc_norm(k,j))
2435      &              + ecosgp*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
2436                   gacontp_hb3(k,num_conti,i)=gggp(k)
2437                   gacontm_hb1(k,num_conti,i)=ghalfm
2438      &              +(ecosam*(dc_norm(k,j)-cosa*dc_norm(k,i))
2439      &              + ecosbm*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
2440                   gacontm_hb2(k,num_conti,i)=ghalfm
2441      &              +(ecosam*(dc_norm(k,i)-cosa*dc_norm(k,j))
2442      &              + ecosgm*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
2443                   gacontm_hb3(k,num_conti,i)=gggm(k)
2444                 enddo
2445                 endif
2446 C Diagnostics. Comment out or remove after debugging!
2447 cdiag           do k=1,3
2448 cdiag             gacontp_hb1(k,num_conti,i)=0.0D0
2449 cdiag             gacontp_hb2(k,num_conti,i)=0.0D0
2450 cdiag             gacontp_hb3(k,num_conti,i)=0.0D0
2451 cdiag             gacontm_hb1(k,num_conti,i)=0.0D0
2452 cdiag             gacontm_hb2(k,num_conti,i)=0.0D0
2453 cdiag             gacontm_hb3(k,num_conti,i)=0.0D0
2454 cdiag           enddo
2455               ENDIF ! wcorr
2456               endif  ! num_conti.le.maxconts
2457             endif  ! fcont.gt.0
2458           endif    ! j.gt.i+1
2459  1216     continue
2460         enddo ! j
2461         num_cont_hb(i)=num_conti
2462  1215   continue
2463       enddo   ! i
2464 cd      do i=1,nres
2465 cd        write (iout,'(i3,3f10.5,5x,3f10.5)') 
2466 cd     &     i,(gel_loc(k,i),k=1,3),gel_loc_loc(i)
2467 cd      enddo
2468 c 12/7/99 Adam eello_turn3 will be considered as a separate energy term
2469 ccc      eel_loc=eel_loc+eello_turn3
2470       return
2471       end
2472 C-----------------------------------------------------------------------------
2473       subroutine eturn34(i,j,eello_turn3,eello_turn4)
2474 C Third- and fourth-order contributions from turns
2475       implicit real*8 (a-h,o-z)
2476       include 'DIMENSIONS'
2477       include 'sizesclu.dat'
2478       include 'COMMON.IOUNITS'
2479       include 'COMMON.GEO'
2480       include 'COMMON.VAR'
2481       include 'COMMON.LOCAL'
2482       include 'COMMON.CHAIN'
2483       include 'COMMON.DERIV'
2484       include 'COMMON.INTERACT'
2485       include 'COMMON.CONTACTS'
2486       include 'COMMON.TORSION'
2487       include 'COMMON.VECTORS'
2488       include 'COMMON.FFIELD'
2489       dimension ggg(3)
2490       double precision auxmat(2,2),auxmat1(2,2),auxmat2(2,2),pizda(2,2),
2491      &  e1t(2,2),e2t(2,2),e3t(2,2),e1tder(2,2),e2tder(2,2),e3tder(2,2),
2492      &  e1a(2,2),ae3(2,2),ae3e2(2,2),auxvec(2),auxvec1(2)
2493       double precision agg(3,4),aggi(3,4),aggi1(3,4),
2494      &    aggj(3,4),aggj1(3,4),a_temp(2,2)
2495       common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,j1,j2
2496       if (j.eq.i+2) then
2497 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
2498 C
2499 C               Third-order contributions
2500 C        
2501 C                 (i+2)o----(i+3)
2502 C                      | |
2503 C                      | |
2504 C                 (i+1)o----i
2505 C
2506 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC   
2507 cd        call checkint_turn3(i,a_temp,eello_turn3_num)
2508         call matmat2(EUg(1,1,i+1),EUg(1,1,i+2),auxmat(1,1))
2509         call transpose2(auxmat(1,1),auxmat1(1,1))
2510         call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
2511         eello_turn3=eello_turn3+0.5d0*(pizda(1,1)+pizda(2,2))
2512 cd        write (2,*) 'i,',i,' j',j,'eello_turn3',
2513 cd     &    0.5d0*(pizda(1,1)+pizda(2,2)),
2514 cd     &    ' eello_turn3_num',4*eello_turn3_num
2515         if (calc_grad) then
2516 C Derivatives in gamma(i)
2517         call matmat2(EUgder(1,1,i+1),EUg(1,1,i+2),auxmat2(1,1))
2518         call transpose2(auxmat2(1,1),pizda(1,1))
2519         call matmat2(a_temp(1,1),pizda(1,1),pizda(1,1))
2520         gel_loc_turn3(i)=gel_loc_turn3(i)+0.5d0*(pizda(1,1)+pizda(2,2))
2521 C Derivatives in gamma(i+1)
2522         call matmat2(EUg(1,1,i+1),EUgder(1,1,i+2),auxmat2(1,1))
2523         call transpose2(auxmat2(1,1),pizda(1,1))
2524         call matmat2(a_temp(1,1),pizda(1,1),pizda(1,1))
2525         gel_loc_turn3(i+1)=gel_loc_turn3(i+1)
2526      &    +0.5d0*(pizda(1,1)+pizda(2,2))
2527 C Cartesian derivatives
2528         do l=1,3
2529           a_temp(1,1)=aggi(l,1)
2530           a_temp(1,2)=aggi(l,2)
2531           a_temp(2,1)=aggi(l,3)
2532           a_temp(2,2)=aggi(l,4)
2533           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
2534           gcorr3_turn(l,i)=gcorr3_turn(l,i)
2535      &      +0.5d0*(pizda(1,1)+pizda(2,2))
2536           a_temp(1,1)=aggi1(l,1)
2537           a_temp(1,2)=aggi1(l,2)
2538           a_temp(2,1)=aggi1(l,3)
2539           a_temp(2,2)=aggi1(l,4)
2540           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
2541           gcorr3_turn(l,i+1)=gcorr3_turn(l,i+1)
2542      &      +0.5d0*(pizda(1,1)+pizda(2,2))
2543           a_temp(1,1)=aggj(l,1)
2544           a_temp(1,2)=aggj(l,2)
2545           a_temp(2,1)=aggj(l,3)
2546           a_temp(2,2)=aggj(l,4)
2547           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
2548           gcorr3_turn(l,j)=gcorr3_turn(l,j)
2549      &      +0.5d0*(pizda(1,1)+pizda(2,2))
2550           a_temp(1,1)=aggj1(l,1)
2551           a_temp(1,2)=aggj1(l,2)
2552           a_temp(2,1)=aggj1(l,3)
2553           a_temp(2,2)=aggj1(l,4)
2554           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
2555           gcorr3_turn(l,j1)=gcorr3_turn(l,j1)
2556      &      +0.5d0*(pizda(1,1)+pizda(2,2))
2557         enddo
2558         endif
2559       else if (j.eq.i+3 .and. itype(i+2).ne.21) then
2560 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
2561 C
2562 C               Fourth-order contributions
2563 C        
2564 C                 (i+3)o----(i+4)
2565 C                     /  |
2566 C               (i+2)o   |
2567 C                     \  |
2568 C                 (i+1)o----i
2569 C
2570 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC   
2571 cd        call checkint_turn4(i,a_temp,eello_turn4_num)
2572         iti1=itortyp(itype(i+1))
2573         iti2=itortyp(itype(i+2))
2574         iti3=itortyp(itype(i+3))
2575         call transpose2(EUg(1,1,i+1),e1t(1,1))
2576         call transpose2(Eug(1,1,i+2),e2t(1,1))
2577         call transpose2(Eug(1,1,i+3),e3t(1,1))
2578         call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
2579         call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
2580         s1=scalar2(b1(1,iti2),auxvec(1))
2581         call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
2582         call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
2583         s2=scalar2(b1(1,iti1),auxvec(1))
2584         call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
2585         call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
2586         s3=0.5d0*(pizda(1,1)+pizda(2,2))
2587         eello_turn4=eello_turn4-(s1+s2+s3)
2588 cd        write (2,*) 'i,',i,' j',j,'eello_turn4',-(s1+s2+s3),
2589 cd     &    ' eello_turn4_num',8*eello_turn4_num
2590 C Derivatives in gamma(i)
2591         if (calc_grad) then
2592         call transpose2(EUgder(1,1,i+1),e1tder(1,1))
2593         call matmat2(e1tder(1,1),a_temp(1,1),auxmat(1,1))
2594         call matvec2(auxmat(1,1),Ub2(1,i+3),auxvec(1))
2595         s1=scalar2(b1(1,iti2),auxvec(1))
2596         call matmat2(ae3e2(1,1),e1tder(1,1),pizda(1,1))
2597         s3=0.5d0*(pizda(1,1)+pizda(2,2))
2598         gel_loc_turn4(i)=gel_loc_turn4(i)-(s1+s3)
2599 C Derivatives in gamma(i+1)
2600         call transpose2(EUgder(1,1,i+2),e2tder(1,1))
2601         call matvec2(ae3(1,1),Ub2der(1,i+2),auxvec(1)) 
2602         s2=scalar2(b1(1,iti1),auxvec(1))
2603         call matmat2(ae3(1,1),e2tder(1,1),auxmat(1,1))
2604         call matmat2(auxmat(1,1),e1t(1,1),pizda(1,1))
2605         s3=0.5d0*(pizda(1,1)+pizda(2,2))
2606         gel_loc_turn4(i+1)=gel_loc_turn4(i+1)-(s2+s3)
2607 C Derivatives in gamma(i+2)
2608         call transpose2(EUgder(1,1,i+3),e3tder(1,1))
2609         call matvec2(e1a(1,1),Ub2der(1,i+3),auxvec(1))
2610         s1=scalar2(b1(1,iti2),auxvec(1))
2611         call matmat2(a_temp(1,1),e3tder(1,1),auxmat(1,1))
2612         call matvec2(auxmat(1,1),Ub2(1,i+2),auxvec(1)) 
2613         s2=scalar2(b1(1,iti1),auxvec(1))
2614         call matmat2(auxmat(1,1),e2t(1,1),auxmat(1,1))
2615         call matmat2(auxmat(1,1),e1t(1,1),pizda(1,1))
2616         s3=0.5d0*(pizda(1,1)+pizda(2,2))
2617         gel_loc_turn4(i+2)=gel_loc_turn4(i+2)-(s1+s2+s3)
2618 C Cartesian derivatives
2619 C Derivatives of this turn contributions in DC(i+2)
2620         if (j.lt.nres-1) then
2621           do l=1,3
2622             a_temp(1,1)=agg(l,1)
2623             a_temp(1,2)=agg(l,2)
2624             a_temp(2,1)=agg(l,3)
2625             a_temp(2,2)=agg(l,4)
2626             call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
2627             call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
2628             s1=scalar2(b1(1,iti2),auxvec(1))
2629             call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
2630             call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
2631             s2=scalar2(b1(1,iti1),auxvec(1))
2632             call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
2633             call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
2634             s3=0.5d0*(pizda(1,1)+pizda(2,2))
2635             ggg(l)=-(s1+s2+s3)
2636             gcorr4_turn(l,i+2)=gcorr4_turn(l,i+2)-(s1+s2+s3)
2637           enddo
2638         endif
2639 C Remaining derivatives of this turn contribution
2640         do l=1,3
2641           a_temp(1,1)=aggi(l,1)
2642           a_temp(1,2)=aggi(l,2)
2643           a_temp(2,1)=aggi(l,3)
2644           a_temp(2,2)=aggi(l,4)
2645           call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
2646           call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
2647           s1=scalar2(b1(1,iti2),auxvec(1))
2648           call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
2649           call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
2650           s2=scalar2(b1(1,iti1),auxvec(1))
2651           call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
2652           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
2653           s3=0.5d0*(pizda(1,1)+pizda(2,2))
2654           gcorr4_turn(l,i)=gcorr4_turn(l,i)-(s1+s2+s3)
2655           a_temp(1,1)=aggi1(l,1)
2656           a_temp(1,2)=aggi1(l,2)
2657           a_temp(2,1)=aggi1(l,3)
2658           a_temp(2,2)=aggi1(l,4)
2659           call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
2660           call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
2661           s1=scalar2(b1(1,iti2),auxvec(1))
2662           call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
2663           call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
2664           s2=scalar2(b1(1,iti1),auxvec(1))
2665           call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
2666           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
2667           s3=0.5d0*(pizda(1,1)+pizda(2,2))
2668           gcorr4_turn(l,i+1)=gcorr4_turn(l,i+1)-(s1+s2+s3)
2669           a_temp(1,1)=aggj(l,1)
2670           a_temp(1,2)=aggj(l,2)
2671           a_temp(2,1)=aggj(l,3)
2672           a_temp(2,2)=aggj(l,4)
2673           call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
2674           call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
2675           s1=scalar2(b1(1,iti2),auxvec(1))
2676           call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
2677           call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
2678           s2=scalar2(b1(1,iti1),auxvec(1))
2679           call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
2680           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
2681           s3=0.5d0*(pizda(1,1)+pizda(2,2))
2682           gcorr4_turn(l,j)=gcorr4_turn(l,j)-(s1+s2+s3)
2683           a_temp(1,1)=aggj1(l,1)
2684           a_temp(1,2)=aggj1(l,2)
2685           a_temp(2,1)=aggj1(l,3)
2686           a_temp(2,2)=aggj1(l,4)
2687           call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
2688           call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
2689           s1=scalar2(b1(1,iti2),auxvec(1))
2690           call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
2691           call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1)) 
2692           s2=scalar2(b1(1,iti1),auxvec(1))
2693           call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
2694           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
2695           s3=0.5d0*(pizda(1,1)+pizda(2,2))
2696           gcorr4_turn(l,j1)=gcorr4_turn(l,j1)-(s1+s2+s3)
2697         enddo
2698         endif
2699       endif          
2700       return
2701       end
2702 C-----------------------------------------------------------------------------
2703       subroutine vecpr(u,v,w)
2704       implicit real*8(a-h,o-z)
2705       dimension u(3),v(3),w(3)
2706       w(1)=u(2)*v(3)-u(3)*v(2)
2707       w(2)=-u(1)*v(3)+u(3)*v(1)
2708       w(3)=u(1)*v(2)-u(2)*v(1)
2709       return
2710       end
2711 C-----------------------------------------------------------------------------
2712       subroutine unormderiv(u,ugrad,unorm,ungrad)
2713 C This subroutine computes the derivatives of a normalized vector u, given
2714 C the derivatives computed without normalization conditions, ugrad. Returns
2715 C ungrad.
2716       implicit none
2717       double precision u(3),ugrad(3,3),unorm,ungrad(3,3)
2718       double precision vec(3)
2719       double precision scalar
2720       integer i,j
2721 c      write (2,*) 'ugrad',ugrad
2722 c      write (2,*) 'u',u
2723       do i=1,3
2724         vec(i)=scalar(ugrad(1,i),u(1))
2725       enddo
2726 c      write (2,*) 'vec',vec
2727       do i=1,3
2728         do j=1,3
2729           ungrad(j,i)=(ugrad(j,i)-u(j)*vec(i))*unorm
2730         enddo
2731       enddo
2732 c      write (2,*) 'ungrad',ungrad
2733       return
2734       end
2735 C-----------------------------------------------------------------------------
2736       subroutine escp(evdw2,evdw2_14)
2737 C
2738 C This subroutine calculates the excluded-volume interaction energy between
2739 C peptide-group centers and side chains and its gradient in virtual-bond and
2740 C side-chain vectors.
2741 C
2742       implicit real*8 (a-h,o-z)
2743       include 'DIMENSIONS'
2744       include 'sizesclu.dat'
2745       include 'COMMON.GEO'
2746       include 'COMMON.VAR'
2747       include 'COMMON.LOCAL'
2748       include 'COMMON.CHAIN'
2749       include 'COMMON.DERIV'
2750       include 'COMMON.INTERACT'
2751       include 'COMMON.FFIELD'
2752       include 'COMMON.IOUNITS'
2753       dimension ggg(3)
2754       evdw2=0.0D0
2755       evdw2_14=0.0d0
2756 cd    print '(a)','Enter ESCP'
2757 c      write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e,
2758 c     &  ' scal14',scal14
2759       do i=iatscp_s,iatscp_e
2760         if (itype(i).eq.21 .or. itype(i+1).eq.21) cycle
2761         iteli=itel(i)
2762 c        write (iout,*) "i",i," iteli",iteli," nscp_gr",nscp_gr(i),
2763 c     &   " iscp",(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
2764         if (iteli.eq.0) goto 1225
2765         xi=0.5D0*(c(1,i)+c(1,i+1))
2766         yi=0.5D0*(c(2,i)+c(2,i+1))
2767         zi=0.5D0*(c(3,i)+c(3,i+1))
2768
2769         do iint=1,nscp_gr(i)
2770
2771         do j=iscpstart(i,iint),iscpend(i,iint)
2772           itypj=itype(j)
2773           if (itypj.eq.21) cycle
2774 C Uncomment following three lines for SC-p interactions
2775 c         xj=c(1,nres+j)-xi
2776 c         yj=c(2,nres+j)-yi
2777 c         zj=c(3,nres+j)-zi
2778 C Uncomment following three lines for Ca-p interactions
2779           xj=c(1,j)-xi
2780           yj=c(2,j)-yi
2781           zj=c(3,j)-zi
2782           rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
2783           fac=rrij**expon2
2784           e1=fac*fac*aad(itypj,iteli)
2785           e2=fac*bad(itypj,iteli)
2786           if (iabs(j-i) .le. 2) then
2787             e1=scal14*e1
2788             e2=scal14*e2
2789             evdw2_14=evdw2_14+e1+e2
2790           endif
2791           evdwij=e1+e2
2792 c          write (iout,*) i,j,evdwij
2793           evdw2=evdw2+evdwij
2794           if (calc_grad) then
2795 C
2796 C Calculate contributions to the gradient in the virtual-bond and SC vectors.
2797 C
2798           fac=-(evdwij+e1)*rrij
2799           ggg(1)=xj*fac
2800           ggg(2)=yj*fac
2801           ggg(3)=zj*fac
2802           if (j.lt.i) then
2803 cd          write (iout,*) 'j<i'
2804 C Uncomment following three lines for SC-p interactions
2805 c           do k=1,3
2806 c             gradx_scp(k,j)=gradx_scp(k,j)+ggg(k)
2807 c           enddo
2808           else
2809 cd          write (iout,*) 'j>i'
2810             do k=1,3
2811               ggg(k)=-ggg(k)
2812 C Uncomment following line for SC-p interactions
2813 c             gradx_scp(k,j)=gradx_scp(k,j)-ggg(k)
2814             enddo
2815           endif
2816           do k=1,3
2817             gvdwc_scp(k,i)=gvdwc_scp(k,i)-0.5D0*ggg(k)
2818           enddo
2819           kstart=min0(i+1,j)
2820           kend=max0(i-1,j-1)
2821 cd        write (iout,*) 'i=',i,' j=',j,' kstart=',kstart,' kend=',kend
2822 cd        write (iout,*) ggg(1),ggg(2),ggg(3)
2823           do k=kstart,kend
2824             do l=1,3
2825               gvdwc_scp(l,k)=gvdwc_scp(l,k)-ggg(l)
2826             enddo
2827           enddo
2828           endif
2829         enddo
2830         enddo ! iint
2831  1225   continue
2832       enddo ! i
2833       do i=1,nct
2834         do j=1,3
2835           gvdwc_scp(j,i)=expon*gvdwc_scp(j,i)
2836           gradx_scp(j,i)=expon*gradx_scp(j,i)
2837         enddo
2838       enddo
2839 C******************************************************************************
2840 C
2841 C                              N O T E !!!
2842 C
2843 C To save time the factor EXPON has been extracted from ALL components
2844 C of GVDWC and GRADX. Remember to multiply them by this factor before further 
2845 C use!
2846 C
2847 C******************************************************************************
2848       return
2849       end
2850 C--------------------------------------------------------------------------
2851       subroutine edis(ehpb)
2852
2853 C Evaluate bridge-strain energy and its gradient in virtual-bond and SC vectors.
2854 C
2855       implicit real*8 (a-h,o-z)
2856       include 'DIMENSIONS'
2857       include 'sizesclu.dat'
2858       include 'COMMON.SBRIDGE'
2859       include 'COMMON.CHAIN'
2860       include 'COMMON.DERIV'
2861       include 'COMMON.VAR'
2862       include 'COMMON.INTERACT'
2863       dimension ggg(3)
2864       ehpb=0.0D0
2865 cd    print *,'edis: nhpb=',nhpb,' fbr=',fbr
2866 cd    print *,'link_start=',link_start,' link_end=',link_end
2867       if (link_end.eq.0) return
2868       do i=link_start,link_end
2869 C If ihpb(i) and jhpb(i) > NRES, this is a SC-SC distance, otherwise a
2870 C CA-CA distance used in regularization of structure.
2871         ii=ihpb(i)
2872         jj=jhpb(i)
2873 C iii and jjj point to the residues for which the distance is assigned.
2874         if (ii.gt.nres) then
2875           iii=ii-nres
2876           jjj=jj-nres 
2877         else
2878           iii=ii
2879           jjj=jj
2880         endif
2881 C 24/11/03 AL: SS bridges handled separately because of introducing a specific
2882 C    distance and angle dependent SS bond potential.
2883         if (ii.gt.nres .and. itype(iii).eq.1 .and. itype(jjj).eq.1) then
2884           call ssbond_ene(iii,jjj,eij)
2885           ehpb=ehpb+2*eij
2886         else
2887 C Calculate the distance between the two points and its difference from the
2888 C target distance.
2889         dd=dist(ii,jj)
2890         rdis=dd-dhpb(i)
2891 C Get the force constant corresponding to this distance.
2892         waga=forcon(i)
2893 C Calculate the contribution to energy.
2894         ehpb=ehpb+waga*rdis*rdis
2895 C
2896 C Evaluate gradient.
2897 C
2898         fac=waga*rdis/dd
2899 cd      print *,'i=',i,' ii=',ii,' jj=',jj,' dhpb=',dhpb(i),' dd=',dd,
2900 cd   &   ' waga=',waga,' fac=',fac
2901         do j=1,3
2902           ggg(j)=fac*(c(j,jj)-c(j,ii))
2903         enddo
2904 cd      print '(i3,3(1pe14.5))',i,(ggg(j),j=1,3)
2905 C If this is a SC-SC distance, we need to calculate the contributions to the
2906 C Cartesian gradient in the SC vectors (ghpbx).
2907         if (iii.lt.ii) then
2908           do j=1,3
2909             ghpbx(j,iii)=ghpbx(j,iii)-ggg(j)
2910             ghpbx(j,jjj)=ghpbx(j,jjj)+ggg(j)
2911           enddo
2912         endif
2913         do j=iii,jjj-1
2914           do k=1,3
2915             ghpbc(k,j)=ghpbc(k,j)+ggg(k)
2916           enddo
2917         enddo
2918         endif
2919       enddo
2920       ehpb=0.5D0*ehpb
2921       return
2922       end
2923 C--------------------------------------------------------------------------
2924       subroutine ssbond_ene(i,j,eij)
2925
2926 C Calculate the distance and angle dependent SS-bond potential energy
2927 C using a free-energy function derived based on RHF/6-31G** ab initio
2928 C calculations of diethyl disulfide.
2929 C
2930 C A. Liwo and U. Kozlowska, 11/24/03
2931 C
2932       implicit real*8 (a-h,o-z)
2933       include 'DIMENSIONS'
2934       include 'sizesclu.dat'
2935       include 'COMMON.SBRIDGE'
2936       include 'COMMON.CHAIN'
2937       include 'COMMON.DERIV'
2938       include 'COMMON.LOCAL'
2939       include 'COMMON.INTERACT'
2940       include 'COMMON.VAR'
2941       include 'COMMON.IOUNITS'
2942       double precision erij(3),dcosom1(3),dcosom2(3),gg(3)
2943       itypi=itype(i)
2944       xi=c(1,nres+i)
2945       yi=c(2,nres+i)
2946       zi=c(3,nres+i)
2947       dxi=dc_norm(1,nres+i)
2948       dyi=dc_norm(2,nres+i)
2949       dzi=dc_norm(3,nres+i)
2950       dsci_inv=dsc_inv(itypi)
2951       itypj=itype(j)
2952       dscj_inv=dsc_inv(itypj)
2953       xj=c(1,nres+j)-xi
2954       yj=c(2,nres+j)-yi
2955       zj=c(3,nres+j)-zi
2956       dxj=dc_norm(1,nres+j)
2957       dyj=dc_norm(2,nres+j)
2958       dzj=dc_norm(3,nres+j)
2959       rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
2960       rij=dsqrt(rrij)
2961       erij(1)=xj*rij
2962       erij(2)=yj*rij
2963       erij(3)=zj*rij
2964       om1=dxi*erij(1)+dyi*erij(2)+dzi*erij(3)
2965       om2=dxj*erij(1)+dyj*erij(2)+dzj*erij(3)
2966       om12=dxi*dxj+dyi*dyj+dzi*dzj
2967       do k=1,3
2968         dcosom1(k)=rij*(dc_norm(k,nres+i)-om1*erij(k))
2969         dcosom2(k)=rij*(dc_norm(k,nres+j)-om2*erij(k))
2970       enddo
2971       rij=1.0d0/rij
2972       deltad=rij-d0cm
2973       deltat1=1.0d0-om1
2974       deltat2=1.0d0+om2
2975       deltat12=om2-om1+2.0d0
2976       cosphi=om12-om1*om2
2977       eij=akcm*deltad*deltad+akth*(deltat1*deltat1+deltat2*deltat2)
2978      &  +akct*deltad*deltat12
2979      &  +v1ss*cosphi+v2ss*cosphi*cosphi+v3ss*cosphi*cosphi*cosphi
2980 c      write(iout,*) i,j,"rij",rij,"d0cm",d0cm," akcm",akcm," akth",akth,
2981 c     &  " akct",akct," deltad",deltad," deltat",deltat1,deltat2,
2982 c     &  " deltat12",deltat12," eij",eij 
2983       ed=2*akcm*deltad+akct*deltat12
2984       pom1=akct*deltad
2985       pom2=v1ss+2*v2ss*cosphi+3*v3ss*cosphi*cosphi
2986       eom1=-2*akth*deltat1-pom1-om2*pom2
2987       eom2= 2*akth*deltat2+pom1-om1*pom2
2988       eom12=pom2
2989       do k=1,3
2990         gg(k)=ed*erij(k)+eom1*dcosom1(k)+eom2*dcosom2(k)
2991       enddo
2992       do k=1,3
2993         ghpbx(k,i)=ghpbx(k,i)-gg(k)
2994      &            +(eom12*dc_norm(k,nres+j)+eom1*erij(k))*dsci_inv
2995         ghpbx(k,j)=ghpbx(k,j)+gg(k)
2996      &            +(eom12*dc_norm(k,nres+i)+eom2*erij(k))*dscj_inv
2997       enddo
2998 C
2999 C Calculate the components of the gradient in DC and X
3000 C
3001       do k=i,j-1
3002         do l=1,3
3003           ghpbc(l,k)=ghpbc(l,k)+gg(l)
3004         enddo
3005       enddo
3006       return
3007       end
3008 C--------------------------------------------------------------------------
3009       subroutine ebond(estr)
3010 c
3011 c Evaluate the energy of stretching of the CA-CA and CA-SC virtual bonds
3012 c
3013       implicit real*8 (a-h,o-z)
3014       include 'DIMENSIONS'
3015       include 'sizesclu.dat'
3016       include 'COMMON.LOCAL'
3017       include 'COMMON.GEO'
3018       include 'COMMON.INTERACT'
3019       include 'COMMON.DERIV'
3020       include 'COMMON.VAR'
3021       include 'COMMON.CHAIN'
3022       include 'COMMON.IOUNITS'
3023       include 'COMMON.NAMES'
3024       include 'COMMON.FFIELD'
3025       include 'COMMON.CONTROL'
3026       logical energy_dec /.false./
3027       double precision u(3),ud(3)
3028       estr=0.0d0
3029       do i=nnt+1,nct
3030         if (itype(i-1).eq.21 .or. itype(i).eq.21) then
3031           estr1=estr1+gnmr1(vbld(i),-1.0d0,distchainmax)
3032           do j=1,3
3033           gradb(j,i-1)=gnmr1prim(vbld(i),-1.0d0,distchainmax)
3034      &      *dc(j,i-1)/vbld(i)
3035           enddo
3036           if (energy_dec) write(iout,*)
3037      &       "estr1",i,gnmr1(vbld(i),-1.0d0,distchainmax)
3038         else
3039           diff = vbld(i)-vbldp0
3040 c          write (iout,*) i,vbld(i),vbldp0,diff,AKP*diff*diff
3041           estr=estr+diff*diff
3042           do j=1,3
3043             gradb(j,i-1)=AKP*diff*dc(j,i-1)/vbld(i)
3044           enddo
3045         endif
3046
3047       enddo
3048       estr=0.5d0*AKP*estr+estr1
3049 c
3050 c 09/18/07 AL: multimodal bond potential based on AM1 CA-SC PMF's included
3051 c
3052       do i=nnt,nct
3053         iti=itype(i)
3054         if (iti.ne.10 .and. iti.ne.21) then
3055           nbi=nbondterm(iti)
3056           if (nbi.eq.1) then
3057             diff=vbld(i+nres)-vbldsc0(1,iti)
3058 c            write (iout,*) i,iti,vbld(i+nres),vbldsc0(1,iti),diff,
3059 c     &      AKSC(1,iti),AKSC(1,iti)*diff*diff
3060             estr=estr+0.5d0*AKSC(1,iti)*diff*diff
3061             do j=1,3
3062               gradbx(j,i)=AKSC(1,iti)*diff*dc(j,i+nres)/vbld(i+nres)
3063             enddo
3064           else
3065             do j=1,nbi
3066               diff=vbld(i+nres)-vbldsc0(j,iti)
3067               ud(j)=aksc(j,iti)*diff
3068               u(j)=abond0(j,iti)+0.5d0*ud(j)*diff
3069             enddo
3070             uprod=u(1)
3071             do j=2,nbi
3072               uprod=uprod*u(j)
3073             enddo
3074             usum=0.0d0
3075             usumsqder=0.0d0
3076             do j=1,nbi
3077               uprod1=1.0d0
3078               uprod2=1.0d0
3079               do k=1,nbi
3080                 if (k.ne.j) then
3081                   uprod1=uprod1*u(k)
3082                   uprod2=uprod2*u(k)*u(k)
3083                 endif
3084               enddo
3085               usum=usum+uprod1
3086               usumsqder=usumsqder+ud(j)*uprod2
3087             enddo
3088 c            write (iout,*) i,iti,vbld(i+nres),(vbldsc0(j,iti),
3089 c     &      AKSC(j,iti),abond0(j,iti),u(j),j=1,nbi)
3090             estr=estr+uprod/usum
3091             do j=1,3
3092              gradbx(j,i)=usumsqder/(usum*usum)*dc(j,i+nres)/vbld(i+nres)
3093             enddo
3094           endif
3095         endif
3096       enddo
3097       return
3098       end
3099 #ifdef CRYST_THETA
3100 C--------------------------------------------------------------------------
3101       subroutine ebend(etheta)
3102 C
3103 C Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
3104 C angles gamma and its derivatives in consecutive thetas and gammas.
3105 C
3106       implicit real*8 (a-h,o-z)
3107       include 'DIMENSIONS'
3108       include 'sizesclu.dat'
3109       include 'COMMON.LOCAL'
3110       include 'COMMON.GEO'
3111       include 'COMMON.INTERACT'
3112       include 'COMMON.DERIV'
3113       include 'COMMON.VAR'
3114       include 'COMMON.CHAIN'
3115       include 'COMMON.IOUNITS'
3116       include 'COMMON.NAMES'
3117       include 'COMMON.FFIELD'
3118       common /calcthet/ term1,term2,termm,diffak,ratak,
3119      & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
3120      & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
3121       double precision y(2),z(2)
3122       delta=0.02d0*pi
3123       time11=dexp(-2*time)
3124       time12=1.0d0
3125       etheta=0.0D0
3126 c      write (iout,*) "nres",nres
3127 c     write (*,'(a,i2)') 'EBEND ICG=',icg
3128 c      write (iout,*) ithet_start,ithet_end
3129       do i=ithet_start,ithet_end
3130         if (itype(i-1).eq.21) cycle
3131 C Zero the energy function and its derivative at 0 or pi.
3132         call splinthet(theta(i),0.5d0*delta,ss,ssd)
3133         it=itype(i-1)
3134         if (i.gt.3 .and. itype(i-2).ne.21) then
3135 #ifdef OSF
3136           phii=phi(i)
3137           icrc=0
3138           call proc_proc(phii,icrc)
3139           if (icrc.eq.1) phii=150.0
3140 #else
3141           phii=phi(i)
3142 #endif
3143           y(1)=dcos(phii)
3144           y(2)=dsin(phii)
3145         else
3146           y(1)=0.0D0
3147           y(2)=0.0D0
3148         endif
3149         if (i.lt.nres .and. itype(i).ne.21) then
3150 #ifdef OSF
3151           phii1=phi(i+1)
3152           icrc=0
3153           call proc_proc(phii1,icrc)
3154           if (icrc.eq.1) phii1=150.0
3155           phii1=pinorm(phii1)
3156           z(1)=cos(phii1)
3157 #else
3158           phii1=phi(i+1)
3159           z(1)=dcos(phii1)
3160 #endif
3161           z(2)=dsin(phii1)
3162         else
3163           z(1)=0.0D0
3164           z(2)=0.0D0
3165         endif
3166 C Calculate the "mean" value of theta from the part of the distribution
3167 C dependent on the adjacent virtual-bond-valence angles (gamma1 & gamma2).
3168 C In following comments this theta will be referred to as t_c.
3169         thet_pred_mean=0.0d0
3170         do k=1,2
3171           athetk=athet(k,it)
3172           bthetk=bthet(k,it)
3173           thet_pred_mean=thet_pred_mean+athetk*y(k)+bthetk*z(k)
3174         enddo
3175 c        write (iout,*) "thet_pred_mean",thet_pred_mean
3176         dthett=thet_pred_mean*ssd
3177         thet_pred_mean=thet_pred_mean*ss+a0thet(it)
3178 c        write (iout,*) "thet_pred_mean",thet_pred_mean
3179 C Derivatives of the "mean" values in gamma1 and gamma2.
3180         dthetg1=(-athet(1,it)*y(2)+athet(2,it)*y(1))*ss
3181         dthetg2=(-bthet(1,it)*z(2)+bthet(2,it)*z(1))*ss
3182         if (theta(i).gt.pi-delta) then
3183           call theteng(pi-delta,thet_pred_mean,theta0(it),f0,fprim0,
3184      &         E_tc0)
3185           call mixder(pi-delta,thet_pred_mean,theta0(it),fprim_tc0)
3186           call theteng(pi,thet_pred_mean,theta0(it),f1,fprim1,E_tc1)
3187           call spline1(theta(i),pi-delta,delta,f0,f1,fprim0,ethetai,
3188      &        E_theta)
3189           call spline2(theta(i),pi-delta,delta,E_tc0,E_tc1,fprim_tc0,
3190      &        E_tc)
3191         else if (theta(i).lt.delta) then
3192           call theteng(delta,thet_pred_mean,theta0(it),f0,fprim0,E_tc0)
3193           call theteng(0.0d0,thet_pred_mean,theta0(it),f1,fprim1,E_tc1)
3194           call spline1(theta(i),delta,-delta,f0,f1,fprim0,ethetai,
3195      &        E_theta)
3196           call mixder(delta,thet_pred_mean,theta0(it),fprim_tc0)
3197           call spline2(theta(i),delta,-delta,E_tc0,E_tc1,fprim_tc0,
3198      &        E_tc)
3199         else
3200           call theteng(theta(i),thet_pred_mean,theta0(it),ethetai,
3201      &        E_theta,E_tc)
3202         endif
3203         etheta=etheta+ethetai
3204 c        write (iout,'(2i3,3f8.3,f10.5)') i,it,rad2deg*theta(i),
3205 c     &    rad2deg*phii,rad2deg*phii1,ethetai
3206         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*E_tc*dthetg1
3207         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*E_tc*dthetg2
3208         gloc(nphi+i-2,icg)=wang*(E_theta+E_tc*dthett)
3209  1215   continue
3210       enddo
3211 C Ufff.... We've done all this!!! 
3212       return
3213       end
3214 C---------------------------------------------------------------------------
3215       subroutine theteng(thetai,thet_pred_mean,theta0i,ethetai,E_theta,
3216      &     E_tc)
3217       implicit real*8 (a-h,o-z)
3218       include 'DIMENSIONS'
3219       include 'COMMON.LOCAL'
3220       include 'COMMON.IOUNITS'
3221       common /calcthet/ term1,term2,termm,diffak,ratak,
3222      & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
3223      & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
3224 C Calculate the contributions to both Gaussian lobes.
3225 C 6/6/97 - Deform the Gaussians using the factor of 1/(1+time)
3226 C The "polynomial part" of the "standard deviation" of this part of 
3227 C the distribution.
3228         sig=polthet(3,it)
3229         do j=2,0,-1
3230           sig=sig*thet_pred_mean+polthet(j,it)
3231         enddo
3232 C Derivative of the "interior part" of the "standard deviation of the" 
3233 C gamma-dependent Gaussian lobe in t_c.
3234         sigtc=3*polthet(3,it)
3235         do j=2,1,-1
3236           sigtc=sigtc*thet_pred_mean+j*polthet(j,it)
3237         enddo
3238         sigtc=sig*sigtc
3239 C Set the parameters of both Gaussian lobes of the distribution.
3240 C "Standard deviation" of the gamma-dependent Gaussian lobe (sigtc)
3241         fac=sig*sig+sigc0(it)
3242         sigcsq=fac+fac
3243         sigc=1.0D0/sigcsq
3244 C Following variable (sigsqtc) is -(1/2)d[sigma(t_c)**(-2))]/dt_c
3245         sigsqtc=-4.0D0*sigcsq*sigtc
3246 c       print *,i,sig,sigtc,sigsqtc
3247 C Following variable (sigtc) is d[sigma(t_c)]/dt_c
3248         sigtc=-sigtc/(fac*fac)
3249 C Following variable is sigma(t_c)**(-2)
3250         sigcsq=sigcsq*sigcsq
3251         sig0i=sig0(it)
3252         sig0inv=1.0D0/sig0i**2
3253         delthec=thetai-thet_pred_mean
3254         delthe0=thetai-theta0i
3255         term1=-0.5D0*sigcsq*delthec*delthec
3256         term2=-0.5D0*sig0inv*delthe0*delthe0
3257 C Following fuzzy logic is to avoid underflows in dexp and subsequent INFs and
3258 C NaNs in taking the logarithm. We extract the largest exponent which is added
3259 C to the energy (this being the log of the distribution) at the end of energy
3260 C term evaluation for this virtual-bond angle.
3261         if (term1.gt.term2) then
3262           termm=term1
3263           term2=dexp(term2-termm)
3264           term1=1.0d0
3265         else
3266           termm=term2
3267           term1=dexp(term1-termm)
3268           term2=1.0d0
3269         endif
3270 C The ratio between the gamma-independent and gamma-dependent lobes of
3271 C the distribution is a Gaussian function of thet_pred_mean too.
3272         diffak=gthet(2,it)-thet_pred_mean
3273         ratak=diffak/gthet(3,it)**2
3274         ak=dexp(gthet(1,it)-0.5D0*diffak*ratak)
3275 C Let's differentiate it in thet_pred_mean NOW.
3276         aktc=ak*ratak
3277 C Now put together the distribution terms to make complete distribution.
3278         termexp=term1+ak*term2
3279         termpre=sigc+ak*sig0i
3280 C Contribution of the bending energy from this theta is just the -log of
3281 C the sum of the contributions from the two lobes and the pre-exponential
3282 C factor. Simple enough, isn't it?
3283         ethetai=(-dlog(termexp)-termm+dlog(termpre))
3284 C NOW the derivatives!!!
3285 C 6/6/97 Take into account the deformation.
3286         E_theta=(delthec*sigcsq*term1
3287      &       +ak*delthe0*sig0inv*term2)/termexp
3288         E_tc=((sigtc+aktc*sig0i)/termpre
3289      &      -((delthec*sigcsq+delthec*delthec*sigsqtc)*term1+
3290      &       aktc*term2)/termexp)
3291       return
3292       end
3293 c-----------------------------------------------------------------------------
3294       subroutine mixder(thetai,thet_pred_mean,theta0i,E_tc_t)
3295       implicit real*8 (a-h,o-z)
3296       include 'DIMENSIONS'
3297       include 'COMMON.LOCAL'
3298       include 'COMMON.IOUNITS'
3299       common /calcthet/ term1,term2,termm,diffak,ratak,
3300      & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
3301      & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
3302       delthec=thetai-thet_pred_mean
3303       delthe0=thetai-theta0i
3304 C "Thank you" to MAPLE (probably spared one day of hand-differentiation).
3305       t3 = thetai-thet_pred_mean
3306       t6 = t3**2
3307       t9 = term1
3308       t12 = t3*sigcsq
3309       t14 = t12+t6*sigsqtc
3310       t16 = 1.0d0
3311       t21 = thetai-theta0i
3312       t23 = t21**2
3313       t26 = term2
3314       t27 = t21*t26
3315       t32 = termexp
3316       t40 = t32**2
3317       E_tc_t = -((sigcsq+2.D0*t3*sigsqtc)*t9-t14*sigcsq*t3*t16*t9
3318      & -aktc*sig0inv*t27)/t32+(t14*t9+aktc*t26)/t40
3319      & *(-t12*t9-ak*sig0inv*t27)
3320       return
3321       end
3322 #else
3323 C--------------------------------------------------------------------------
3324       subroutine ebend(etheta)
3325 C
3326 C Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
3327 C angles gamma and its derivatives in consecutive thetas and gammas.
3328 C ab initio-derived potentials from 
3329 c Kozlowska et al., J. Phys.: Condens. Matter 19 (2007) 285203
3330 C
3331       implicit real*8 (a-h,o-z)
3332       include 'DIMENSIONS'
3333       include 'sizesclu.dat'
3334       include 'COMMON.LOCAL'
3335       include 'COMMON.GEO'
3336       include 'COMMON.INTERACT'
3337       include 'COMMON.DERIV'
3338       include 'COMMON.VAR'
3339       include 'COMMON.CHAIN'
3340       include 'COMMON.IOUNITS'
3341       include 'COMMON.NAMES'
3342       include 'COMMON.FFIELD'
3343       include 'COMMON.CONTROL'
3344       double precision coskt(mmaxtheterm),sinkt(mmaxtheterm),
3345      & cosph1(maxsingle),sinph1(maxsingle),cosph2(maxsingle),
3346      & sinph2(maxsingle),cosph1ph2(maxdouble,maxdouble),
3347      & sinph1ph2(maxdouble,maxdouble)
3348       logical lprn /.false./, lprn1 /.false./
3349       etheta=0.0D0
3350 c      write (iout,*) "ithetyp",(ithetyp(i),i=1,ntyp1)
3351       do i=ithet_start,ithet_end
3352         if (itype(i-1).eq.21) cycle
3353         dethetai=0.0d0
3354         dephii=0.0d0
3355         dephii1=0.0d0
3356         theti2=0.5d0*theta(i)
3357         ityp2=ithetyp(itype(i-1))
3358         do k=1,nntheterm
3359           coskt(k)=dcos(k*theti2)
3360           sinkt(k)=dsin(k*theti2)
3361         enddo
3362         if (i.gt.3 .and. itype(i-2).ne.21) then
3363 #ifdef OSF
3364           phii=phi(i)
3365           if (phii.ne.phii) phii=150.0
3366 #else
3367           phii=phi(i)
3368 #endif
3369           ityp1=ithetyp(itype(i-2))
3370           do k=1,nsingle
3371             cosph1(k)=dcos(k*phii)
3372             sinph1(k)=dsin(k*phii)
3373           enddo
3374         else
3375           phii=0.0d0
3376           ityp1=nthetyp+1
3377           do k=1,nsingle
3378             cosph1(k)=0.0d0
3379             sinph1(k)=0.0d0
3380           enddo 
3381         endif
3382         if (i.lt.nres .and. itype(i).ne.21) then
3383 #ifdef OSF
3384           phii1=phi(i+1)
3385           if (phii1.ne.phii1) phii1=150.0
3386           phii1=pinorm(phii1)
3387 #else
3388           phii1=phi(i+1)
3389 #endif
3390           ityp3=ithetyp(itype(i))
3391           do k=1,nsingle
3392             cosph2(k)=dcos(k*phii1)
3393             sinph2(k)=dsin(k*phii1)
3394           enddo
3395         else
3396           phii1=0.0d0
3397           ityp3=nthetyp+1
3398           do k=1,nsingle
3399             cosph2(k)=0.0d0
3400             sinph2(k)=0.0d0
3401           enddo
3402         endif  
3403 c        write (iout,*) "i",i," ityp1",itype(i-2),ityp1,
3404 c     &   " ityp2",itype(i-1),ityp2," ityp3",itype(i),ityp3
3405 c        call flush(iout)
3406         ethetai=aa0thet(ityp1,ityp2,ityp3)
3407         do k=1,ndouble
3408           do l=1,k-1
3409             ccl=cosph1(l)*cosph2(k-l)
3410             ssl=sinph1(l)*sinph2(k-l)
3411             scl=sinph1(l)*cosph2(k-l)
3412             csl=cosph1(l)*sinph2(k-l)
3413             cosph1ph2(l,k)=ccl-ssl
3414             cosph1ph2(k,l)=ccl+ssl
3415             sinph1ph2(l,k)=scl+csl
3416             sinph1ph2(k,l)=scl-csl
3417           enddo
3418         enddo
3419         if (lprn) then
3420         write (iout,*) "i",i," ityp1",ityp1," ityp2",ityp2,
3421      &    " ityp3",ityp3," theti2",theti2," phii",phii," phii1",phii1
3422         write (iout,*) "coskt and sinkt"
3423         do k=1,nntheterm
3424           write (iout,*) k,coskt(k),sinkt(k)
3425         enddo
3426         endif
3427         do k=1,ntheterm
3428           ethetai=ethetai+aathet(k,ityp1,ityp2,ityp3)*sinkt(k)
3429           dethetai=dethetai+0.5d0*k*aathet(k,ityp1,ityp2,ityp3)
3430      &      *coskt(k)
3431           if (lprn)
3432      &    write (iout,*) "k",k," aathet",aathet(k,ityp1,ityp2,ityp3),
3433      &     " ethetai",ethetai
3434         enddo
3435         if (lprn) then
3436         write (iout,*) "cosph and sinph"
3437         do k=1,nsingle
3438           write (iout,*) k,cosph1(k),sinph1(k),cosph2(k),sinph2(k)
3439         enddo
3440         write (iout,*) "cosph1ph2 and sinph2ph2"
3441         do k=2,ndouble
3442           do l=1,k-1
3443             write (iout,*) l,k,cosph1ph2(l,k),cosph1ph2(k,l),
3444      &         sinph1ph2(l,k),sinph1ph2(k,l) 
3445           enddo
3446         enddo
3447         write(iout,*) "ethetai",ethetai
3448         endif
3449         do m=1,ntheterm2
3450           do k=1,nsingle
3451             aux=bbthet(k,m,ityp1,ityp2,ityp3)*cosph1(k)
3452      &         +ccthet(k,m,ityp1,ityp2,ityp3)*sinph1(k)
3453      &         +ddthet(k,m,ityp1,ityp2,ityp3)*cosph2(k)
3454      &         +eethet(k,m,ityp1,ityp2,ityp3)*sinph2(k)
3455             ethetai=ethetai+sinkt(m)*aux
3456             dethetai=dethetai+0.5d0*m*aux*coskt(m)
3457             dephii=dephii+k*sinkt(m)*(
3458      &          ccthet(k,m,ityp1,ityp2,ityp3)*cosph1(k)-
3459      &          bbthet(k,m,ityp1,ityp2,ityp3)*sinph1(k))
3460             dephii1=dephii1+k*sinkt(m)*(
3461      &          eethet(k,m,ityp1,ityp2,ityp3)*cosph2(k)-
3462      &          ddthet(k,m,ityp1,ityp2,ityp3)*sinph2(k))
3463             if (lprn)
3464      &      write (iout,*) "m",m," k",k," bbthet",
3465      &         bbthet(k,m,ityp1,ityp2,ityp3)," ccthet",
3466      &         ccthet(k,m,ityp1,ityp2,ityp3)," ddthet",
3467      &         ddthet(k,m,ityp1,ityp2,ityp3)," eethet",
3468      &         eethet(k,m,ityp1,ityp2,ityp3)," ethetai",ethetai
3469           enddo
3470         enddo
3471         if (lprn)
3472      &  write(iout,*) "ethetai",ethetai
3473         do m=1,ntheterm3
3474           do k=2,ndouble
3475             do l=1,k-1
3476               aux=ffthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)+
3477      &            ffthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l)+
3478      &            ggthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)+
3479      &            ggthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)
3480               ethetai=ethetai+sinkt(m)*aux
3481               dethetai=dethetai+0.5d0*m*coskt(m)*aux
3482               dephii=dephii+l*sinkt(m)*(
3483      &           -ffthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)-
3484      &            ffthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)+
3485      &            ggthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)+
3486      &            ggthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l))
3487               dephii1=dephii1+(k-l)*sinkt(m)*(
3488      &           -ffthet(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)+
3489      &            ffthet(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)+
3490      &            ggthet(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)-
3491      &            ggthet(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l))
3492               if (lprn) then
3493               write (iout,*) "m",m," k",k," l",l," ffthet",
3494      &            ffthet(l,k,m,ityp1,ityp2,ityp3),
3495      &            ffthet(k,l,m,ityp1,ityp2,ityp3)," ggthet",
3496      &            ggthet(l,k,m,ityp1,ityp2,ityp3),
3497      &            ggthet(k,l,m,ityp1,ityp2,ityp3)," ethetai",ethetai
3498               write (iout,*) cosph1ph2(l,k)*sinkt(m),
3499      &            cosph1ph2(k,l)*sinkt(m),
3500      &            sinph1ph2(l,k)*sinkt(m),sinph1ph2(k,l)*sinkt(m)
3501               endif
3502             enddo
3503           enddo
3504         enddo
3505 10      continue
3506         if (lprn1) write (iout,'(i2,3f8.1,9h ethetai ,f10.5)') 
3507      &   i,theta(i)*rad2deg,phii*rad2deg,
3508      &   phii1*rad2deg,ethetai
3509         etheta=etheta+ethetai
3510         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*dephii
3511         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*dephii1
3512         gloc(nphi+i-2,icg)=wang*dethetai
3513       enddo
3514       return
3515       end
3516 #endif
3517 #ifdef CRYST_SC
3518 c-----------------------------------------------------------------------------
3519       subroutine esc(escloc)
3520 C Calculate the local energy of a side chain and its derivatives in the
3521 C corresponding virtual-bond valence angles THETA and the spherical angles 
3522 C ALPHA and OMEGA.
3523       implicit real*8 (a-h,o-z)
3524       include 'DIMENSIONS'
3525       include 'sizesclu.dat'
3526       include 'COMMON.GEO'
3527       include 'COMMON.LOCAL'
3528       include 'COMMON.VAR'
3529       include 'COMMON.INTERACT'
3530       include 'COMMON.DERIV'
3531       include 'COMMON.CHAIN'
3532       include 'COMMON.IOUNITS'
3533       include 'COMMON.NAMES'
3534       include 'COMMON.FFIELD'
3535       double precision x(3),dersc(3),xemp(3),dersc0(3),dersc1(3),
3536      &     ddersc0(3),ddummy(3),xtemp(3),temp(3)
3537       common /sccalc/ time11,time12,time112,theti,it,nlobit
3538       delta=0.02d0*pi
3539       escloc=0.0D0
3540 c     write (iout,'(a)') 'ESC'
3541       do i=loc_start,loc_end
3542         it=itype(i)
3543         if (it.eq.21) cycle
3544         if (it.eq.10) goto 1
3545         nlobit=nlob(it)
3546 c       print *,'i=',i,' it=',it,' nlobit=',nlobit
3547 c       write (iout,*) 'i=',i,' ssa=',ssa,' ssad=',ssad
3548         theti=theta(i+1)-pipol
3549         x(1)=dtan(theti)
3550         x(2)=alph(i)
3551         x(3)=omeg(i)
3552 c        write (iout,*) "i",i," x",x(1),x(2),x(3)
3553
3554         if (x(2).gt.pi-delta) then
3555           xtemp(1)=x(1)
3556           xtemp(2)=pi-delta
3557           xtemp(3)=x(3)
3558           call enesc(xtemp,escloci0,dersc0,ddersc0,.true.)
3559           xtemp(2)=pi
3560           call enesc(xtemp,escloci1,dersc1,ddummy,.false.)
3561           call spline1(x(2),pi-delta,delta,escloci0,escloci1,dersc0(2),
3562      &        escloci,dersc(2))
3563           call spline2(x(2),pi-delta,delta,dersc0(1),dersc1(1),
3564      &        ddersc0(1),dersc(1))
3565           call spline2(x(2),pi-delta,delta,dersc0(3),dersc1(3),
3566      &        ddersc0(3),dersc(3))
3567           xtemp(2)=pi-delta
3568           call enesc_bound(xtemp,esclocbi0,dersc0,dersc12,.true.)
3569           xtemp(2)=pi
3570           call enesc_bound(xtemp,esclocbi1,dersc1,chuju,.false.)
3571           call spline1(x(2),pi-delta,delta,esclocbi0,esclocbi1,
3572      &            dersc0(2),esclocbi,dersc02)
3573           call spline2(x(2),pi-delta,delta,dersc0(1),dersc1(1),
3574      &            dersc12,dersc01)
3575           call splinthet(x(2),0.5d0*delta,ss,ssd)
3576           dersc0(1)=dersc01
3577           dersc0(2)=dersc02
3578           dersc0(3)=0.0d0
3579           do k=1,3
3580             dersc(k)=ss*dersc(k)+(1.0d0-ss)*dersc0(k)
3581           enddo
3582           dersc(2)=dersc(2)+ssd*(escloci-esclocbi)
3583 c         write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
3584 c    &             esclocbi,ss,ssd
3585           escloci=ss*escloci+(1.0d0-ss)*esclocbi
3586 c         escloci=esclocbi
3587 c         write (iout,*) escloci
3588         else if (x(2).lt.delta) then
3589           xtemp(1)=x(1)
3590           xtemp(2)=delta
3591           xtemp(3)=x(3)
3592           call enesc(xtemp,escloci0,dersc0,ddersc0,.true.)
3593           xtemp(2)=0.0d0
3594           call enesc(xtemp,escloci1,dersc1,ddummy,.false.)
3595           call spline1(x(2),delta,-delta,escloci0,escloci1,dersc0(2),
3596      &        escloci,dersc(2))
3597           call spline2(x(2),delta,-delta,dersc0(1),dersc1(1),
3598      &        ddersc0(1),dersc(1))
3599           call spline2(x(2),delta,-delta,dersc0(3),dersc1(3),
3600      &        ddersc0(3),dersc(3))
3601           xtemp(2)=delta
3602           call enesc_bound(xtemp,esclocbi0,dersc0,dersc12,.true.)
3603           xtemp(2)=0.0d0
3604           call enesc_bound(xtemp,esclocbi1,dersc1,chuju,.false.)
3605           call spline1(x(2),delta,-delta,esclocbi0,esclocbi1,
3606      &            dersc0(2),esclocbi,dersc02)
3607           call spline2(x(2),delta,-delta,dersc0(1),dersc1(1),
3608      &            dersc12,dersc01)
3609           dersc0(1)=dersc01
3610           dersc0(2)=dersc02
3611           dersc0(3)=0.0d0
3612           call splinthet(x(2),0.5d0*delta,ss,ssd)
3613           do k=1,3
3614             dersc(k)=ss*dersc(k)+(1.0d0-ss)*dersc0(k)
3615           enddo
3616           dersc(2)=dersc(2)+ssd*(escloci-esclocbi)
3617 c         write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
3618 c    &             esclocbi,ss,ssd
3619           escloci=ss*escloci+(1.0d0-ss)*esclocbi
3620 c         write (iout,*) escloci
3621         else
3622           call enesc(x,escloci,dersc,ddummy,.false.)
3623         endif
3624
3625         escloc=escloc+escloci
3626 c        write (iout,*) 'i=',i,' escloci=',escloci,' dersc=',dersc
3627
3628         gloc(nphi+i-1,icg)=gloc(nphi+i-1,icg)+
3629      &   wscloc*dersc(1)
3630         gloc(ialph(i,1),icg)=wscloc*dersc(2)
3631         gloc(ialph(i,1)+nside,icg)=wscloc*dersc(3)
3632     1   continue
3633       enddo
3634       return
3635       end
3636 C---------------------------------------------------------------------------
3637       subroutine enesc(x,escloci,dersc,ddersc,mixed)
3638       implicit real*8 (a-h,o-z)
3639       include 'DIMENSIONS'
3640       include 'COMMON.GEO'
3641       include 'COMMON.LOCAL'
3642       include 'COMMON.IOUNITS'
3643       common /sccalc/ time11,time12,time112,theti,it,nlobit
3644       double precision x(3),z(3),Ax(3,maxlob,-1:1),dersc(3),ddersc(3)
3645       double precision contr(maxlob,-1:1)
3646       logical mixed
3647 c       write (iout,*) 'it=',it,' nlobit=',nlobit
3648         escloc_i=0.0D0
3649         do j=1,3
3650           dersc(j)=0.0D0
3651           if (mixed) ddersc(j)=0.0d0
3652         enddo
3653         x3=x(3)
3654
3655 C Because of periodicity of the dependence of the SC energy in omega we have
3656 C to add up the contributions from x(3)-2*pi, x(3), and x(3+2*pi).
3657 C To avoid underflows, first compute & store the exponents.
3658
3659         do iii=-1,1
3660
3661           x(3)=x3+iii*dwapi
3662  
3663           do j=1,nlobit
3664             do k=1,3
3665               z(k)=x(k)-censc(k,j,it)
3666             enddo
3667             do k=1,3
3668               Axk=0.0D0
3669               do l=1,3
3670                 Axk=Axk+gaussc(l,k,j,it)*z(l)
3671               enddo
3672               Ax(k,j,iii)=Axk
3673             enddo 
3674             expfac=0.0D0 
3675             do k=1,3
3676               expfac=expfac+Ax(k,j,iii)*z(k)
3677             enddo
3678             contr(j,iii)=expfac
3679           enddo ! j
3680
3681         enddo ! iii
3682
3683         x(3)=x3
3684 C As in the case of ebend, we want to avoid underflows in exponentiation and
3685 C subsequent NaNs and INFs in energy calculation.
3686 C Find the largest exponent
3687         emin=contr(1,-1)
3688         do iii=-1,1
3689           do j=1,nlobit
3690             if (emin.gt.contr(j,iii)) emin=contr(j,iii)
3691           enddo 
3692         enddo
3693         emin=0.5D0*emin
3694 cd      print *,'it=',it,' emin=',emin
3695
3696 C Compute the contribution to SC energy and derivatives
3697         do iii=-1,1
3698
3699           do j=1,nlobit
3700             expfac=dexp(bsc(j,it)-0.5D0*contr(j,iii)+emin)
3701 cd          print *,'j=',j,' expfac=',expfac
3702             escloc_i=escloc_i+expfac
3703             do k=1,3
3704               dersc(k)=dersc(k)+Ax(k,j,iii)*expfac
3705             enddo
3706             if (mixed) then
3707               do k=1,3,2
3708                 ddersc(k)=ddersc(k)+(-Ax(2,j,iii)*Ax(k,j,iii)
3709      &            +gaussc(k,2,j,it))*expfac
3710               enddo
3711             endif
3712           enddo
3713
3714         enddo ! iii
3715
3716         dersc(1)=dersc(1)/cos(theti)**2
3717         ddersc(1)=ddersc(1)/cos(theti)**2
3718         ddersc(3)=ddersc(3)
3719
3720         escloci=-(dlog(escloc_i)-emin)
3721         do j=1,3
3722           dersc(j)=dersc(j)/escloc_i
3723         enddo
3724         if (mixed) then
3725           do j=1,3,2
3726             ddersc(j)=(ddersc(j)/escloc_i+dersc(2)*dersc(j))
3727           enddo
3728         endif
3729       return
3730       end
3731 C------------------------------------------------------------------------------
3732       subroutine enesc_bound(x,escloci,dersc,dersc12,mixed)
3733       implicit real*8 (a-h,o-z)
3734       include 'DIMENSIONS'
3735       include 'COMMON.GEO'
3736       include 'COMMON.LOCAL'
3737       include 'COMMON.IOUNITS'
3738       common /sccalc/ time11,time12,time112,theti,it,nlobit
3739       double precision x(3),z(3),Ax(3,maxlob),dersc(3)
3740       double precision contr(maxlob)
3741       logical mixed
3742
3743       escloc_i=0.0D0
3744
3745       do j=1,3
3746         dersc(j)=0.0D0
3747       enddo
3748
3749       do j=1,nlobit
3750         do k=1,2
3751           z(k)=x(k)-censc(k,j,it)
3752         enddo
3753         z(3)=dwapi
3754         do k=1,3
3755           Axk=0.0D0
3756           do l=1,3
3757             Axk=Axk+gaussc(l,k,j,it)*z(l)
3758           enddo
3759           Ax(k,j)=Axk
3760         enddo 
3761         expfac=0.0D0 
3762         do k=1,3
3763           expfac=expfac+Ax(k,j)*z(k)
3764         enddo
3765         contr(j)=expfac
3766       enddo ! j
3767
3768 C As in the case of ebend, we want to avoid underflows in exponentiation and
3769 C subsequent NaNs and INFs in energy calculation.
3770 C Find the largest exponent
3771       emin=contr(1)
3772       do j=1,nlobit
3773         if (emin.gt.contr(j)) emin=contr(j)
3774       enddo 
3775       emin=0.5D0*emin
3776  
3777 C Compute the contribution to SC energy and derivatives
3778
3779       dersc12=0.0d0
3780       do j=1,nlobit
3781         expfac=dexp(bsc(j,it)-0.5D0*contr(j)+emin)
3782         escloc_i=escloc_i+expfac
3783         do k=1,2
3784           dersc(k)=dersc(k)+Ax(k,j)*expfac
3785         enddo
3786         if (mixed) dersc12=dersc12+(-Ax(2,j)*Ax(1,j)
3787      &            +gaussc(1,2,j,it))*expfac
3788         dersc(3)=0.0d0
3789       enddo
3790
3791       dersc(1)=dersc(1)/cos(theti)**2
3792       dersc12=dersc12/cos(theti)**2
3793       escloci=-(dlog(escloc_i)-emin)
3794       do j=1,2
3795         dersc(j)=dersc(j)/escloc_i
3796       enddo
3797       if (mixed) dersc12=(dersc12/escloc_i+dersc(2)*dersc(1))
3798       return
3799       end
3800 #else
3801 c----------------------------------------------------------------------------------
3802       subroutine esc(escloc)
3803 C Calculate the local energy of a side chain and its derivatives in the
3804 C corresponding virtual-bond valence angles THETA and the spherical angles 
3805 C ALPHA and OMEGA derived from AM1 all-atom calculations.
3806 C added by Urszula Kozlowska. 07/11/2007
3807 C
3808       implicit real*8 (a-h,o-z)
3809       include 'DIMENSIONS'
3810       include 'sizesclu.dat'
3811       include 'COMMON.GEO'
3812       include 'COMMON.LOCAL'
3813       include 'COMMON.VAR'
3814       include 'COMMON.SCROT'
3815       include 'COMMON.INTERACT'
3816       include 'COMMON.DERIV'
3817       include 'COMMON.CHAIN'
3818       include 'COMMON.IOUNITS'
3819       include 'COMMON.NAMES'
3820       include 'COMMON.FFIELD'
3821       include 'COMMON.CONTROL'
3822       include 'COMMON.VECTORS'
3823       double precision x_prime(3),y_prime(3),z_prime(3)
3824      &    , sumene,dsc_i,dp2_i,x(65),
3825      &     xx,yy,zz,sumene1,sumene2,sumene3,sumene4,s1,s1_6,s2,s2_6,
3826      &    de_dxx,de_dyy,de_dzz,de_dt
3827       double precision s1_t,s1_6_t,s2_t,s2_6_t
3828       double precision 
3829      & dXX_Ci1(3),dYY_Ci1(3),dZZ_Ci1(3),dXX_Ci(3),
3830      & dYY_Ci(3),dZZ_Ci(3),dXX_XYZ(3),dYY_XYZ(3),dZZ_XYZ(3),
3831      & dt_dCi(3),dt_dCi1(3)
3832       common /sccalc/ time11,time12,time112,theti,it,nlobit
3833       delta=0.02d0*pi
3834       escloc=0.0D0
3835       do i=loc_start,loc_end
3836         if (itype(i).eq.21) cycle
3837         costtab(i+1) =dcos(theta(i+1))
3838         sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
3839         cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
3840         sint2tab(i+1)=dsqrt(0.5d0*(1.0d0-costtab(i+1)))
3841         cosfac2=0.5d0/(1.0d0+costtab(i+1))
3842         cosfac=dsqrt(cosfac2)
3843         sinfac2=0.5d0/(1.0d0-costtab(i+1))
3844         sinfac=dsqrt(sinfac2)
3845         it=itype(i)
3846         if (it.eq.10) goto 1
3847 c
3848 C  Compute the axes of tghe local cartesian coordinates system; store in
3849 c   x_prime, y_prime and z_prime 
3850 c
3851         do j=1,3
3852           x_prime(j) = 0.00
3853           y_prime(j) = 0.00
3854           z_prime(j) = 0.00
3855         enddo
3856 C        write(2,*) "dc_norm", dc_norm(1,i+nres),dc_norm(2,i+nres),
3857 C     &   dc_norm(3,i+nres)
3858         do j = 1,3
3859           x_prime(j) = (dc_norm(j,i) - dc_norm(j,i-1))*cosfac
3860           y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
3861         enddo
3862         do j = 1,3
3863           z_prime(j) = -uz(j,i-1)
3864         enddo     
3865 c       write (2,*) "i",i
3866 c       write (2,*) "x_prime",(x_prime(j),j=1,3)
3867 c       write (2,*) "y_prime",(y_prime(j),j=1,3)
3868 c       write (2,*) "z_prime",(z_prime(j),j=1,3)
3869 c       write (2,*) "xx",scalar(x_prime(1),x_prime(1)),
3870 c      & " xy",scalar(x_prime(1),y_prime(1)),
3871 c      & " xz",scalar(x_prime(1),z_prime(1)),
3872 c      & " yy",scalar(y_prime(1),y_prime(1)),
3873 c      & " yz",scalar(y_prime(1),z_prime(1)),
3874 c      & " zz",scalar(z_prime(1),z_prime(1))
3875 c
3876 C Transform the unit vector of the ith side-chain centroid, dC_norm(*,i),
3877 C to local coordinate system. Store in xx, yy, zz.
3878 c
3879         xx=0.0d0
3880         yy=0.0d0
3881         zz=0.0d0
3882         do j = 1,3
3883           xx = xx + x_prime(j)*dc_norm(j,i+nres)
3884           yy = yy + y_prime(j)*dc_norm(j,i+nres)
3885           zz = zz + z_prime(j)*dc_norm(j,i+nres)
3886         enddo
3887
3888         xxtab(i)=xx
3889         yytab(i)=yy
3890         zztab(i)=zz
3891 C
3892 C Compute the energy of the ith side cbain
3893 C
3894 c        write (2,*) "xx",xx," yy",yy," zz",zz
3895         it=itype(i)
3896         do j = 1,65
3897           x(j) = sc_parmin(j,it) 
3898         enddo
3899 #ifdef CHECK_COORD
3900 Cc diagnostics - remove later
3901         xx1 = dcos(alph(2))
3902         yy1 = dsin(alph(2))*dcos(omeg(2))
3903         zz1 = -dsin(alph(2))*dsin(omeg(2))
3904         write(2,'(3f8.1,3f9.3,1x,3f9.3)') 
3905      &    alph(2)*rad2deg,omeg(2)*rad2deg,theta(3)*rad2deg,xx,yy,zz,
3906      &    xx1,yy1,zz1
3907 C,"  --- ", xx_w,yy_w,zz_w
3908 c end diagnostics
3909 #endif
3910         sumene1= x(1)+  x(2)*xx+  x(3)*yy+  x(4)*zz+  x(5)*xx**2
3911      &   + x(6)*yy**2+  x(7)*zz**2+  x(8)*xx*zz+  x(9)*xx*yy
3912      &   + x(10)*yy*zz
3913         sumene2=  x(11) + x(12)*xx + x(13)*yy + x(14)*zz + x(15)*xx**2
3914      & + x(16)*yy**2 + x(17)*zz**2 + x(18)*xx*zz + x(19)*xx*yy
3915      & + x(20)*yy*zz
3916         sumene3=  x(21) +x(22)*xx +x(23)*yy +x(24)*zz +x(25)*xx**2
3917      &  +x(26)*yy**2 +x(27)*zz**2 +x(28)*xx*zz +x(29)*xx*yy
3918      &  +x(30)*yy*zz +x(31)*xx**3 +x(32)*yy**3 +x(33)*zz**3
3919      &  +x(34)*(xx**2)*yy +x(35)*(xx**2)*zz +x(36)*(yy**2)*xx
3920      &  +x(37)*(yy**2)*zz +x(38)*(zz**2)*xx +x(39)*(zz**2)*yy
3921      &  +x(40)*xx*yy*zz
3922         sumene4= x(41) +x(42)*xx +x(43)*yy +x(44)*zz +x(45)*xx**2
3923      &  +x(46)*yy**2 +x(47)*zz**2 +x(48)*xx*zz +x(49)*xx*yy
3924      &  +x(50)*yy*zz +x(51)*xx**3 +x(52)*yy**3 +x(53)*zz**3
3925      &  +x(54)*(xx**2)*yy +x(55)*(xx**2)*zz +x(56)*(yy**2)*xx
3926      &  +x(57)*(yy**2)*zz +x(58)*(zz**2)*xx +x(59)*(zz**2)*yy
3927      &  +x(60)*xx*yy*zz
3928         dsc_i   = 0.743d0+x(61)
3929         dp2_i   = 1.9d0+x(62)
3930         dscp1=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
3931      &          *(xx*cost2tab(i+1)+yy*sint2tab(i+1)))
3932         dscp2=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
3933      &          *(xx*cost2tab(i+1)-yy*sint2tab(i+1)))
3934         s1=(1+x(63))/(0.1d0 + dscp1)
3935         s1_6=(1+x(64))/(0.1d0 + dscp1**6)
3936         s2=(1+x(65))/(0.1d0 + dscp2)
3937         s2_6=(1+x(65))/(0.1d0 + dscp2**6)
3938         sumene = ( sumene3*sint2tab(i+1) + sumene1)*(s1+s1_6)
3939      & + (sumene4*cost2tab(i+1) +sumene2)*(s2+s2_6)
3940 c        write(2,'(i2," sumene",7f9.3)') i,sumene1,sumene2,sumene3,
3941 c     &   sumene4,
3942 c     &   dscp1,dscp2,sumene
3943 c        sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
3944         escloc = escloc + sumene
3945 c        write (2,*) "escloc",escloc
3946         if (.not. calc_grad) goto 1
3947 #ifdef DEBUG
3948 C
3949 C This section to check the numerical derivatives of the energy of ith side
3950 C chain in xx, yy, zz, and theta. Use the -DDEBUG compiler option or insert
3951 C #define DEBUG in the code to turn it on.
3952 C
3953         write (2,*) "sumene               =",sumene
3954         aincr=1.0d-7
3955         xxsave=xx
3956         xx=xx+aincr
3957         write (2,*) xx,yy,zz
3958         sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
3959         de_dxx_num=(sumenep-sumene)/aincr
3960         xx=xxsave
3961         write (2,*) "xx+ sumene from enesc=",sumenep
3962         yysave=yy
3963         yy=yy+aincr
3964         write (2,*) xx,yy,zz
3965         sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
3966         de_dyy_num=(sumenep-sumene)/aincr
3967         yy=yysave
3968         write (2,*) "yy+ sumene from enesc=",sumenep
3969         zzsave=zz
3970         zz=zz+aincr
3971         write (2,*) xx,yy,zz
3972         sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
3973         de_dzz_num=(sumenep-sumene)/aincr
3974         zz=zzsave
3975         write (2,*) "zz+ sumene from enesc=",sumenep
3976         costsave=cost2tab(i+1)
3977         sintsave=sint2tab(i+1)
3978         cost2tab(i+1)=dcos(0.5d0*(theta(i+1)+aincr))
3979         sint2tab(i+1)=dsin(0.5d0*(theta(i+1)+aincr))
3980         sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
3981         de_dt_num=(sumenep-sumene)/aincr
3982         write (2,*) " t+ sumene from enesc=",sumenep
3983         cost2tab(i+1)=costsave
3984         sint2tab(i+1)=sintsave
3985 C End of diagnostics section.
3986 #endif
3987 C        
3988 C Compute the gradient of esc
3989 C
3990         pom_s1=(1.0d0+x(63))/(0.1d0 + dscp1)**2
3991         pom_s16=6*(1.0d0+x(64))/(0.1d0 + dscp1**6)**2
3992         pom_s2=(1.0d0+x(65))/(0.1d0 + dscp2)**2
3993         pom_s26=6*(1.0d0+x(65))/(0.1d0 + dscp2**6)**2
3994         pom_dx=dsc_i*dp2_i*cost2tab(i+1)
3995         pom_dy=dsc_i*dp2_i*sint2tab(i+1)
3996         pom_dt1=-0.5d0*dsc_i*dp2_i*(xx*sint2tab(i+1)-yy*cost2tab(i+1))
3997         pom_dt2=-0.5d0*dsc_i*dp2_i*(xx*sint2tab(i+1)+yy*cost2tab(i+1))
3998         pom1=(sumene3*sint2tab(i+1)+sumene1)
3999      &     *(pom_s1/dscp1+pom_s16*dscp1**4)
4000         pom2=(sumene4*cost2tab(i+1)+sumene2)
4001      &     *(pom_s2/dscp2+pom_s26*dscp2**4)
4002         sumene1x=x(2)+2*x(5)*xx+x(8)*zz+ x(9)*yy
4003         sumene3x=x(22)+2*x(25)*xx+x(28)*zz+x(29)*yy+3*x(31)*xx**2
4004      &  +2*x(34)*xx*yy +2*x(35)*xx*zz +x(36)*(yy**2) +x(38)*(zz**2)
4005      &  +x(40)*yy*zz
4006         sumene2x=x(12)+2*x(15)*xx+x(18)*zz+ x(19)*yy
4007         sumene4x=x(42)+2*x(45)*xx +x(48)*zz +x(49)*yy +3*x(51)*xx**2
4008      &  +2*x(54)*xx*yy+2*x(55)*xx*zz+x(56)*(yy**2)+x(58)*(zz**2)
4009      &  +x(60)*yy*zz
4010         de_dxx =(sumene1x+sumene3x*sint2tab(i+1))*(s1+s1_6)
4011      &        +(sumene2x+sumene4x*cost2tab(i+1))*(s2+s2_6)
4012      &        +(pom1+pom2)*pom_dx
4013 #ifdef DEBUG
4014         write(2,*), "de_dxx = ", de_dxx,de_dxx_num
4015 #endif
4016 C
4017         sumene1y=x(3) + 2*x(6)*yy + x(9)*xx + x(10)*zz
4018         sumene3y=x(23) +2*x(26)*yy +x(29)*xx +x(30)*zz +3*x(32)*yy**2
4019      &  +x(34)*(xx**2) +2*x(36)*yy*xx +2*x(37)*yy*zz +x(39)*(zz**2)
4020      &  +x(40)*xx*zz
4021         sumene2y=x(13) + 2*x(16)*yy + x(19)*xx + x(20)*zz
4022         sumene4y=x(43)+2*x(46)*yy+x(49)*xx +x(50)*zz
4023      &  +3*x(52)*yy**2+x(54)*xx**2+2*x(56)*yy*xx +2*x(57)*yy*zz
4024      &  +x(59)*zz**2 +x(60)*xx*zz
4025         de_dyy =(sumene1y+sumene3y*sint2tab(i+1))*(s1+s1_6)
4026      &        +(sumene2y+sumene4y*cost2tab(i+1))*(s2+s2_6)
4027      &        +(pom1-pom2)*pom_dy
4028 #ifdef DEBUG
4029         write(2,*), "de_dyy = ", de_dyy,de_dyy_num
4030 #endif
4031 C
4032         de_dzz =(x(24) +2*x(27)*zz +x(28)*xx +x(30)*yy
4033      &  +3*x(33)*zz**2 +x(35)*xx**2 +x(37)*yy**2 +2*x(38)*zz*xx 
4034      &  +2*x(39)*zz*yy +x(40)*xx*yy)*sint2tab(i+1)*(s1+s1_6) 
4035      &  +(x(4) + 2*x(7)*zz+  x(8)*xx + x(10)*yy)*(s1+s1_6) 
4036      &  +(x(44)+2*x(47)*zz +x(48)*xx   +x(50)*yy  +3*x(53)*zz**2   
4037      &  +x(55)*xx**2 +x(57)*(yy**2)+2*x(58)*zz*xx +2*x(59)*zz*yy  
4038      &  +x(60)*xx*yy)*cost2tab(i+1)*(s2+s2_6)
4039      &  + ( x(14) + 2*x(17)*zz+  x(18)*xx + x(20)*yy)*(s2+s2_6)
4040 #ifdef DEBUG
4041         write(2,*), "de_dzz = ", de_dzz,de_dzz_num
4042 #endif
4043 C
4044         de_dt =  0.5d0*sumene3*cost2tab(i+1)*(s1+s1_6) 
4045      &  -0.5d0*sumene4*sint2tab(i+1)*(s2+s2_6)
4046      &  +pom1*pom_dt1+pom2*pom_dt2
4047 #ifdef DEBUG
4048         write(2,*), "de_dt = ", de_dt,de_dt_num
4049 #endif
4050
4051 C
4052        cossc=scalar(dc_norm(1,i),dc_norm(1,i+nres))
4053        cossc1=scalar(dc_norm(1,i-1),dc_norm(1,i+nres))
4054        cosfac2xx=cosfac2*xx
4055        sinfac2yy=sinfac2*yy
4056        do k = 1,3
4057          dt_dCi(k) = -(dc_norm(k,i-1)+costtab(i+1)*dc_norm(k,i))*
4058      &      vbld_inv(i+1)
4059          dt_dCi1(k)= -(dc_norm(k,i)+costtab(i+1)*dc_norm(k,i-1))*
4060      &      vbld_inv(i)
4061          pom=(dC_norm(k,i+nres)-cossc*dC_norm(k,i))*vbld_inv(i+1)
4062          pom1=(dC_norm(k,i+nres)-cossc1*dC_norm(k,i-1))*vbld_inv(i)
4063 c         write (iout,*) "i",i," k",k," pom",pom," pom1",pom1,
4064 c     &    " dt_dCi",dt_dCi(k)," dt_dCi1",dt_dCi1(k)
4065 c         write (iout,*) "dC_norm",(dC_norm(j,i),j=1,3),
4066 c     &   (dC_norm(j,i-1),j=1,3)," vbld_inv",vbld_inv(i+1),vbld_inv(i)
4067          dXX_Ci(k)=pom*cosfac-dt_dCi(k)*cosfac2xx
4068          dXX_Ci1(k)=-pom1*cosfac-dt_dCi1(k)*cosfac2xx
4069          dYY_Ci(k)=pom*sinfac+dt_dCi(k)*sinfac2yy
4070          dYY_Ci1(k)=pom1*sinfac+dt_dCi1(k)*sinfac2yy
4071          dZZ_Ci1(k)=0.0d0
4072          dZZ_Ci(k)=0.0d0
4073          do j=1,3
4074            dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1)*dC_norm(j,i+nres)
4075            dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1)*dC_norm(j,i+nres)
4076          enddo
4077           
4078          dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
4079          dYY_XYZ(k)=vbld_inv(i+nres)*(y_prime(k)-yy*dC_norm(k,i+nres))
4080          dZZ_XYZ(k)=vbld_inv(i+nres)*(z_prime(k)-zz*dC_norm(k,i+nres))
4081 c
4082          dt_dCi(k) = -dt_dCi(k)/sinttab(i+1)
4083          dt_dCi1(k)= -dt_dCi1(k)/sinttab(i+1)
4084        enddo
4085
4086        do k=1,3
4087          dXX_Ctab(k,i)=dXX_Ci(k)
4088          dXX_C1tab(k,i)=dXX_Ci1(k)
4089          dYY_Ctab(k,i)=dYY_Ci(k)
4090          dYY_C1tab(k,i)=dYY_Ci1(k)
4091          dZZ_Ctab(k,i)=dZZ_Ci(k)
4092          dZZ_C1tab(k,i)=dZZ_Ci1(k)
4093          dXX_XYZtab(k,i)=dXX_XYZ(k)
4094          dYY_XYZtab(k,i)=dYY_XYZ(k)
4095          dZZ_XYZtab(k,i)=dZZ_XYZ(k)
4096        enddo
4097
4098        do k = 1,3
4099 c         write (iout,*) "k",k," dxx_ci1",dxx_ci1(k)," dyy_ci1",
4100 c     &    dyy_ci1(k)," dzz_ci1",dzz_ci1(k)
4101 c         write (iout,*) "k",k," dxx_ci",dxx_ci(k)," dyy_ci",
4102 c     &    dyy_ci(k)," dzz_ci",dzz_ci(k)
4103 c         write (iout,*) "k",k," dt_dci",dt_dci(k)," dt_dci",
4104 c     &    dt_dci(k)
4105 c         write (iout,*) "k",k," dxx_XYZ",dxx_XYZ(k)," dyy_XYZ",
4106 c     &    dyy_XYZ(k)," dzz_XYZ",dzz_XYZ(k) 
4107          gscloc(k,i-1)=gscloc(k,i-1)+de_dxx*dxx_ci1(k)
4108      &    +de_dyy*dyy_ci1(k)+de_dzz*dzz_ci1(k)+de_dt*dt_dCi1(k)
4109          gscloc(k,i)=gscloc(k,i)+de_dxx*dxx_Ci(k)
4110      &    +de_dyy*dyy_Ci(k)+de_dzz*dzz_Ci(k)+de_dt*dt_dCi(k)
4111          gsclocx(k,i)=                 de_dxx*dxx_XYZ(k)
4112      &    +de_dyy*dyy_XYZ(k)+de_dzz*dzz_XYZ(k)
4113        enddo
4114 c       write(iout,*) "ENERGY GRAD = ", (gscloc(k,i-1),k=1,3),
4115 c     &  (gscloc(k,i),k=1,3),(gsclocx(k,i),k=1,3)  
4116
4117 C to check gradient call subroutine check_grad
4118
4119     1 continue
4120       enddo
4121       return
4122       end
4123 #endif
4124 c------------------------------------------------------------------------------
4125       subroutine gcont(rij,r0ij,eps0ij,delta,fcont,fprimcont)
4126 C
4127 C This procedure calculates two-body contact function g(rij) and its derivative:
4128 C
4129 C           eps0ij                                     !       x < -1
4130 C g(rij) =  esp0ij*(-0.9375*x+0.625*x**3-0.1875*x**5)  ! -1 =< x =< 1
4131 C            0                                         !       x > 1
4132 C
4133 C where x=(rij-r0ij)/delta
4134 C
4135 C rij - interbody distance, r0ij - contact distance, eps0ij - contact energy
4136 C
4137       implicit none
4138       double precision rij,r0ij,eps0ij,fcont,fprimcont
4139       double precision x,x2,x4,delta
4140 c     delta=0.02D0*r0ij
4141 c      delta=0.2D0*r0ij
4142       x=(rij-r0ij)/delta
4143       if (x.lt.-1.0D0) then
4144         fcont=eps0ij
4145         fprimcont=0.0D0
4146       else if (x.le.1.0D0) then  
4147         x2=x*x
4148         x4=x2*x2
4149         fcont=eps0ij*(x*(-0.9375D0+0.6250D0*x2-0.1875D0*x4)+0.5D0)
4150         fprimcont=eps0ij * (-0.9375D0+1.8750D0*x2-0.9375D0*x4)/delta
4151       else
4152         fcont=0.0D0
4153         fprimcont=0.0D0
4154       endif
4155       return
4156       end
4157 c------------------------------------------------------------------------------
4158       subroutine splinthet(theti,delta,ss,ssder)
4159       implicit real*8 (a-h,o-z)
4160       include 'DIMENSIONS'
4161       include 'sizesclu.dat'
4162       include 'COMMON.VAR'
4163       include 'COMMON.GEO'
4164       thetup=pi-delta
4165       thetlow=delta
4166       if (theti.gt.pipol) then
4167         call gcont(theti,thetup,1.0d0,delta,ss,ssder)
4168       else
4169         call gcont(-theti,-thetlow,1.0d0,delta,ss,ssder)
4170         ssder=-ssder
4171       endif
4172       return
4173       end
4174 c------------------------------------------------------------------------------
4175       subroutine spline1(x,x0,delta,f0,f1,fprim0,f,fprim)
4176       implicit none
4177       double precision x,x0,delta,f0,f1,fprim0,f,fprim
4178       double precision ksi,ksi2,ksi3,a1,a2,a3
4179       a1=fprim0*delta/(f1-f0)
4180       a2=3.0d0-2.0d0*a1
4181       a3=a1-2.0d0
4182       ksi=(x-x0)/delta
4183       ksi2=ksi*ksi
4184       ksi3=ksi2*ksi  
4185       f=f0+(f1-f0)*ksi*(a1+ksi*(a2+a3*ksi))
4186       fprim=(f1-f0)/delta*(a1+ksi*(2*a2+3*ksi*a3))
4187       return
4188       end
4189 c------------------------------------------------------------------------------
4190       subroutine spline2(x,x0,delta,f0x,f1x,fprim0x,fx)
4191       implicit none
4192       double precision x,x0,delta,f0x,f1x,fprim0x,fx
4193       double precision ksi,ksi2,ksi3,a1,a2,a3
4194       ksi=(x-x0)/delta  
4195       ksi2=ksi*ksi
4196       ksi3=ksi2*ksi
4197       a1=fprim0x*delta
4198       a2=3*(f1x-f0x)-2*fprim0x*delta
4199       a3=fprim0x*delta-2*(f1x-f0x)
4200       fx=f0x+a1*ksi+a2*ksi2+a3*ksi3
4201       return
4202       end
4203 C-----------------------------------------------------------------------------
4204 #ifdef CRYST_TOR
4205 C-----------------------------------------------------------------------------
4206       subroutine etor(etors,edihcnstr,fact)
4207       implicit real*8 (a-h,o-z)
4208       include 'DIMENSIONS'
4209       include 'sizesclu.dat'
4210       include 'COMMON.VAR'
4211       include 'COMMON.GEO'
4212       include 'COMMON.LOCAL'
4213       include 'COMMON.TORSION'
4214       include 'COMMON.INTERACT'
4215       include 'COMMON.DERIV'
4216       include 'COMMON.CHAIN'
4217       include 'COMMON.NAMES'
4218       include 'COMMON.IOUNITS'
4219       include 'COMMON.FFIELD'
4220       include 'COMMON.TORCNSTR'
4221       logical lprn
4222 C Set lprn=.true. for debugging
4223       lprn=.false.
4224 c      lprn=.true.
4225       etors=0.0D0
4226       do i=iphi_start,iphi_end
4227         if (itype(i-2).eq.21 .or. itype(i-1).eq.21
4228      &      .or. itype(i).eq.21) cycle
4229         itori=itortyp(itype(i-2))
4230         itori1=itortyp(itype(i-1))
4231         phii=phi(i)
4232         gloci=0.0D0
4233 C Proline-Proline pair is a special case...
4234         if (itori.eq.3 .and. itori1.eq.3) then
4235           if (phii.gt.-dwapi3) then
4236             cosphi=dcos(3*phii)
4237             fac=1.0D0/(1.0D0-cosphi)
4238             etorsi=v1(1,3,3)*fac
4239             etorsi=etorsi+etorsi
4240             etors=etors+etorsi-v1(1,3,3)
4241             gloci=gloci-3*fac*etorsi*dsin(3*phii)
4242           endif
4243           do j=1,3
4244             v1ij=v1(j+1,itori,itori1)
4245             v2ij=v2(j+1,itori,itori1)
4246             cosphi=dcos(j*phii)
4247             sinphi=dsin(j*phii)
4248             etors=etors+v1ij*cosphi+v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
4249             gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
4250           enddo
4251         else 
4252           do j=1,nterm_old
4253             v1ij=v1(j,itori,itori1)
4254             v2ij=v2(j,itori,itori1)
4255             cosphi=dcos(j*phii)
4256             sinphi=dsin(j*phii)
4257             etors=etors+v1ij*cosphi+v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
4258             gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
4259           enddo
4260         endif
4261         if (lprn)
4262      &  write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
4263      &  restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,
4264      &  (v1(j,itori,itori1),j=1,6),(v2(j,itori,itori1),j=1,6)
4265         gloc(i-3,icg)=gloc(i-3,icg)+wtor*fact*gloci
4266 c       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
4267       enddo
4268 ! 6/20/98 - dihedral angle constraints
4269       edihcnstr=0.0d0
4270       do i=1,ndih_constr
4271         itori=idih_constr(i)
4272         phii=phi(itori)
4273         difi=phii-phi0(i)
4274         if (difi.gt.drange(i)) then
4275           difi=difi-drange(i)
4276           edihcnstr=edihcnstr+0.25d0*ftors*difi**4
4277           gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
4278         else if (difi.lt.-drange(i)) then
4279           difi=difi+drange(i)
4280           edihcnstr=edihcnstr+0.25d0*ftors*difi**4
4281           gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
4282         endif
4283 !        write (iout,'(2i5,2f8.3,2e14.5)') i,itori,rad2deg*phii,
4284 !     &    rad2deg*difi,0.25d0*ftors*difi**4,gloc(itori-3,icg)
4285       enddo
4286 !      write (iout,*) 'edihcnstr',edihcnstr
4287       return
4288       end
4289 c------------------------------------------------------------------------------
4290 #else
4291       subroutine etor(etors,edihcnstr,fact)
4292       implicit real*8 (a-h,o-z)
4293       include 'DIMENSIONS'
4294       include 'sizesclu.dat'
4295       include 'COMMON.VAR'
4296       include 'COMMON.GEO'
4297       include 'COMMON.LOCAL'
4298       include 'COMMON.TORSION'
4299       include 'COMMON.INTERACT'
4300       include 'COMMON.DERIV'
4301       include 'COMMON.CHAIN'
4302       include 'COMMON.NAMES'
4303       include 'COMMON.IOUNITS'
4304       include 'COMMON.FFIELD'
4305       include 'COMMON.TORCNSTR'
4306       logical lprn
4307 C Set lprn=.true. for debugging
4308       lprn=.false.
4309 c      lprn=.true.
4310       etors=0.0D0
4311       do i=iphi_start,iphi_end
4312         if (itype(i-2).eq.21 .or. itype(i-1).eq.21
4313      &       .or. itype(i).eq.21) cycle
4314         if (itel(i-2).eq.0 .or. itel(i-1).eq.0) goto 1215
4315         itori=itortyp(itype(i-2))
4316         itori1=itortyp(itype(i-1))
4317         phii=phi(i)
4318         gloci=0.0D0
4319 C Regular cosine and sine terms
4320         do j=1,nterm(itori,itori1)
4321           v1ij=v1(j,itori,itori1)
4322           v2ij=v2(j,itori,itori1)
4323           cosphi=dcos(j*phii)
4324           sinphi=dsin(j*phii)
4325           etors=etors+v1ij*cosphi+v2ij*sinphi
4326           gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
4327         enddo
4328 C Lorentz terms
4329 C                         v1
4330 C  E = SUM ----------------------------------- - v1
4331 C          [v2 cos(phi/2)+v3 sin(phi/2)]^2 + 1
4332 C
4333         cosphi=dcos(0.5d0*phii)
4334         sinphi=dsin(0.5d0*phii)
4335         do j=1,nlor(itori,itori1)
4336           vl1ij=vlor1(j,itori,itori1)
4337           vl2ij=vlor2(j,itori,itori1)
4338           vl3ij=vlor3(j,itori,itori1)
4339           pom=vl2ij*cosphi+vl3ij*sinphi
4340           pom1=1.0d0/(pom*pom+1.0d0)
4341           etors=etors+vl1ij*pom1
4342           pom=-pom*pom1*pom1
4343           gloci=gloci+vl1ij*(vl3ij*cosphi-vl2ij*sinphi)*pom
4344         enddo
4345 C Subtract the constant term
4346         etors=etors-v0(itori,itori1)
4347         if (lprn)
4348      &  write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
4349      &  restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,
4350      &  (v1(j,itori,itori1),j=1,6),(v2(j,itori,itori1),j=1,6)
4351         gloc(i-3,icg)=gloc(i-3,icg)+wtor*fact*gloci
4352 c       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
4353  1215   continue
4354       enddo
4355 ! 6/20/98 - dihedral angle constraints
4356       edihcnstr=0.0d0
4357       do i=1,ndih_constr
4358         itori=idih_constr(i)
4359         phii=phi(itori)
4360         difi=pinorm(phii-phi0(i))
4361         edihi=0.0d0
4362         if (difi.gt.drange(i)) then
4363           difi=difi-drange(i)
4364           edihcnstr=edihcnstr+0.25d0*ftors*difi**4
4365           gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
4366           edihi=0.25d0*ftors*difi**4
4367         else if (difi.lt.-drange(i)) then
4368           difi=difi+drange(i)
4369           edihcnstr=edihcnstr+0.25d0*ftors*difi**4
4370           gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
4371           edihi=0.25d0*ftors*difi**4
4372         else
4373           difi=0.0d0
4374         endif
4375 c        write (iout,'(2i5,4f10.5,e15.5)') i,itori,phii,phi0(i),difi,
4376 c     &    drange(i),edihi
4377 !        write (iout,'(2i5,2f8.3,2e14.5)') i,itori,rad2deg*phii,
4378 !     &    rad2deg*difi,0.25d0*ftors*difi**4,gloc(itori-3,icg)
4379       enddo
4380 !      write (iout,*) 'edihcnstr',edihcnstr
4381       return
4382       end
4383 c----------------------------------------------------------------------------
4384       subroutine etor_d(etors_d,fact2)
4385 C 6/23/01 Compute double torsional energy
4386       implicit real*8 (a-h,o-z)
4387       include 'DIMENSIONS'
4388       include 'sizesclu.dat'
4389       include 'COMMON.VAR'
4390       include 'COMMON.GEO'
4391       include 'COMMON.LOCAL'
4392       include 'COMMON.TORSION'
4393       include 'COMMON.INTERACT'
4394       include 'COMMON.DERIV'
4395       include 'COMMON.CHAIN'
4396       include 'COMMON.NAMES'
4397       include 'COMMON.IOUNITS'
4398       include 'COMMON.FFIELD'
4399       include 'COMMON.TORCNSTR'
4400       logical lprn
4401 C Set lprn=.true. for debugging
4402       lprn=.false.
4403 c     lprn=.true.
4404       etors_d=0.0D0
4405       do i=iphi_start,iphi_end-1
4406         if (itype(i-2).eq.21 .or. itype(i-1).eq.21
4407      &      .or. itype(i).eq.21 .or. itype(i+1).eq.21) cycle
4408         if (itel(i-2).eq.0 .or. itel(i-1).eq.0 .or. itel(i).eq.0) 
4409      &     goto 1215
4410         itori=itortyp(itype(i-2))
4411         itori1=itortyp(itype(i-1))
4412         itori2=itortyp(itype(i))
4413         phii=phi(i)
4414         phii1=phi(i+1)
4415         gloci1=0.0D0
4416         gloci2=0.0D0
4417 C Regular cosine and sine terms
4418         do j=1,ntermd_1(itori,itori1,itori2)
4419           v1cij=v1c(1,j,itori,itori1,itori2)
4420           v1sij=v1s(1,j,itori,itori1,itori2)
4421           v2cij=v1c(2,j,itori,itori1,itori2)
4422           v2sij=v1s(2,j,itori,itori1,itori2)
4423           cosphi1=dcos(j*phii)
4424           sinphi1=dsin(j*phii)
4425           cosphi2=dcos(j*phii1)
4426           sinphi2=dsin(j*phii1)
4427           etors_d=etors_d+v1cij*cosphi1+v1sij*sinphi1+
4428      &     v2cij*cosphi2+v2sij*sinphi2
4429           gloci1=gloci1+j*(v1sij*cosphi1-v1cij*sinphi1)
4430           gloci2=gloci2+j*(v2sij*cosphi2-v2cij*sinphi2)
4431         enddo
4432         do k=2,ntermd_2(itori,itori1,itori2)
4433           do l=1,k-1
4434             v1cdij = v2c(k,l,itori,itori1,itori2)
4435             v2cdij = v2c(l,k,itori,itori1,itori2)
4436             v1sdij = v2s(k,l,itori,itori1,itori2)
4437             v2sdij = v2s(l,k,itori,itori1,itori2)
4438             cosphi1p2=dcos(l*phii+(k-l)*phii1)
4439             cosphi1m2=dcos(l*phii-(k-l)*phii1)
4440             sinphi1p2=dsin(l*phii+(k-l)*phii1)
4441             sinphi1m2=dsin(l*phii-(k-l)*phii1)
4442             etors_d=etors_d+v1cdij*cosphi1p2+v2cdij*cosphi1m2+
4443      &        v1sdij*sinphi1p2+v2sdij*sinphi1m2
4444             gloci1=gloci1+l*(v1sdij*cosphi1p2+v2sdij*cosphi1m2
4445      &        -v1cdij*sinphi1p2-v2cdij*sinphi1m2)
4446             gloci2=gloci2+(k-l)*(v1sdij*cosphi1p2-v2sdij*cosphi1m2
4447      &        -v1cdij*sinphi1p2+v2cdij*sinphi1m2) 
4448           enddo
4449         enddo
4450         gloc(i-3,icg)=gloc(i-3,icg)+wtor_d*fact2*gloci1
4451         gloc(i-2,icg)=gloc(i-2,icg)+wtor_d*fact2*gloci2
4452  1215   continue
4453       enddo
4454       return
4455       end
4456 #endif
4457 c------------------------------------------------------------------------------
4458       subroutine eback_sc_corr(esccor)
4459 c 7/21/2007 Correlations between the backbone-local and side-chain-local
4460 c        conformational states; temporarily implemented as differences
4461 c        between UNRES torsional potentials (dependent on three types of
4462 c        residues) and the torsional potentials dependent on all 20 types
4463 c        of residues computed from AM1 energy surfaces of terminally-blocked
4464 c        amino-acid residues.
4465       implicit real*8 (a-h,o-z)
4466       include 'DIMENSIONS'
4467       include 'sizesclu.dat'
4468       include 'COMMON.VAR'
4469       include 'COMMON.GEO'
4470       include 'COMMON.LOCAL'
4471       include 'COMMON.TORSION'
4472       include 'COMMON.SCCOR'
4473       include 'COMMON.INTERACT'
4474       include 'COMMON.DERIV'
4475       include 'COMMON.CHAIN'
4476       include 'COMMON.NAMES'
4477       include 'COMMON.IOUNITS'
4478       include 'COMMON.FFIELD'
4479       include 'COMMON.CONTROL'
4480       logical lprn
4481 C Set lprn=.true. for debugging
4482       lprn=.false.
4483 c      lprn=.true.
4484 c      write (iout,*) "EBACK_SC_COR",iphi_start,iphi_end,nterm_sccor
4485       esccor=0.0D0
4486       do i=itau_start,itau_end
4487         if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1) cycle
4488         esccor_ii=0.0D0
4489         isccori=isccortyp(itype(i-2))
4490         isccori1=isccortyp(itype(i-1))
4491         phii=phi(i)
4492         do intertyp=1,3 !intertyp
4493 cc Added 09 May 2012 (Adasko)
4494 cc  Intertyp means interaction type of backbone mainchain correlation: 
4495 c   1 = SC...Ca...Ca...Ca
4496 c   2 = Ca...Ca...Ca...SC
4497 c   3 = SC...Ca...Ca...SCi
4498         gloci=0.0D0
4499         if (((intertyp.eq.3).and.((itype(i-2).eq.10).or.
4500      &      (itype(i-1).eq.10).or.(itype(i-2).eq.ntyp1).or.
4501      &      (itype(i-1).eq.ntyp1)))
4502      &    .or. ((intertyp.eq.1).and.((itype(i-2).eq.10)
4503      &     .or.(itype(i-2).eq.ntyp1).or.(itype(i-1).eq.ntyp1)
4504      &     .or.(itype(i).eq.ntyp1)))
4505      &    .or.((intertyp.eq.2).and.((itype(i-1).eq.10).or.
4506      &      (itype(i-1).eq.ntyp1).or.(itype(i-2).eq.ntyp1).or.
4507      &      (itype(i-3).eq.ntyp1)))) cycle
4508         if ((intertyp.eq.2).and.(i.eq.4).and.(itype(1).eq.ntyp1)) cycle
4509         if ((intertyp.eq.1).and.(i.eq.nres).and.(itype(nres).eq.ntyp1))
4510      & cycle
4511        do j=1,nterm_sccor(isccori,isccori1)
4512           v1ij=v1sccor(j,intertyp,isccori,isccori1)
4513           v2ij=v2sccor(j,intertyp,isccori,isccori1)
4514           cosphi=dcos(j*tauangle(intertyp,i))
4515           sinphi=dsin(j*tauangle(intertyp,i))
4516            esccor=esccor+v1ij*cosphi+v2ij*sinphi
4517 c           gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
4518          enddo
4519 c      write (iout,*) "EBACK_SC_COR",i,esccor,intertyp
4520 c      gloc_sc(intertyp,i-3)=gloc_sc(intertyp,i-3)+wsccor*gloci
4521         if (lprn)
4522      &  write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
4523      &  restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,
4524      &  (v1sccor(j,1,itori,itori1),j=1,6),
4525      &  (v2sccor(j,1,itori,itori1),j=1,6)
4526         gsccor_loc(i-3)=gloci
4527        enddo !intertyp
4528       enddo
4529       return
4530       end
4531 c------------------------------------------------------------------------------
4532       subroutine multibody(ecorr)
4533 C This subroutine calculates multi-body contributions to energy following
4534 C the idea of Skolnick et al. If side chains I and J make a contact and
4535 C at the same time side chains I+1 and J+1 make a contact, an extra 
4536 C contribution equal to sqrt(eps(i,j)*eps(i+1,j+1)) is added.
4537       implicit real*8 (a-h,o-z)
4538       include 'DIMENSIONS'
4539       include 'COMMON.IOUNITS'
4540       include 'COMMON.DERIV'
4541       include 'COMMON.INTERACT'
4542       include 'COMMON.CONTACTS'
4543       double precision gx(3),gx1(3)
4544       logical lprn
4545
4546 C Set lprn=.true. for debugging
4547       lprn=.false.
4548
4549       if (lprn) then
4550         write (iout,'(a)') 'Contact function values:'
4551         do i=nnt,nct-2
4552           write (iout,'(i2,20(1x,i2,f10.5))') 
4553      &        i,(jcont(j,i),facont(j,i),j=1,num_cont(i))
4554         enddo
4555       endif
4556       ecorr=0.0D0
4557       do i=nnt,nct
4558         do j=1,3
4559           gradcorr(j,i)=0.0D0
4560           gradxorr(j,i)=0.0D0
4561         enddo
4562       enddo
4563       do i=nnt,nct-2
4564
4565         DO ISHIFT = 3,4
4566
4567         i1=i+ishift
4568         num_conti=num_cont(i)
4569         num_conti1=num_cont(i1)
4570         do jj=1,num_conti
4571           j=jcont(jj,i)
4572           do kk=1,num_conti1
4573             j1=jcont(kk,i1)
4574             if (j1.eq.j+ishift .or. j1.eq.j-ishift) then
4575 cd          write(iout,*)'i=',i,' j=',j,' i1=',i1,' j1=',j1,
4576 cd   &                   ' ishift=',ishift
4577 C Contacts I--J and I+ISHIFT--J+-ISHIFT1 occur simultaneously. 
4578 C The system gains extra energy.
4579               ecorr=ecorr+esccorr(i,j,i1,j1,jj,kk)
4580             endif   ! j1==j+-ishift
4581           enddo     ! kk  
4582         enddo       ! jj
4583
4584         ENDDO ! ISHIFT
4585
4586       enddo         ! i
4587       return
4588       end
4589 c------------------------------------------------------------------------------
4590       double precision function esccorr(i,j,k,l,jj,kk)
4591       implicit real*8 (a-h,o-z)
4592       include 'DIMENSIONS'
4593       include 'COMMON.IOUNITS'
4594       include 'COMMON.DERIV'
4595       include 'COMMON.INTERACT'
4596       include 'COMMON.CONTACTS'
4597       double precision gx(3),gx1(3)
4598       logical lprn
4599       lprn=.false.
4600       eij=facont(jj,i)
4601       ekl=facont(kk,k)
4602 cd    write (iout,'(4i5,3f10.5)') i,j,k,l,eij,ekl,-eij*ekl
4603 C Calculate the multi-body contribution to energy.
4604 C Calculate multi-body contributions to the gradient.
4605 cd    write (iout,'(2(2i3,3f10.5))')i,j,(gacont(m,jj,i),m=1,3),
4606 cd   & k,l,(gacont(m,kk,k),m=1,3)
4607       do m=1,3
4608         gx(m) =ekl*gacont(m,jj,i)
4609         gx1(m)=eij*gacont(m,kk,k)
4610         gradxorr(m,i)=gradxorr(m,i)-gx(m)
4611         gradxorr(m,j)=gradxorr(m,j)+gx(m)
4612         gradxorr(m,k)=gradxorr(m,k)-gx1(m)
4613         gradxorr(m,l)=gradxorr(m,l)+gx1(m)
4614       enddo
4615       do m=i,j-1
4616         do ll=1,3
4617           gradcorr(ll,m)=gradcorr(ll,m)+gx(ll)
4618         enddo
4619       enddo
4620       do m=k,l-1
4621         do ll=1,3
4622           gradcorr(ll,m)=gradcorr(ll,m)+gx1(ll)
4623         enddo
4624       enddo 
4625       esccorr=-eij*ekl
4626       return
4627       end
4628 c------------------------------------------------------------------------------
4629 #ifdef MPL
4630       subroutine pack_buffer(dimen1,dimen2,atom,indx,buffer)
4631       implicit real*8 (a-h,o-z)
4632       include 'DIMENSIONS' 
4633       integer dimen1,dimen2,atom,indx
4634       double precision buffer(dimen1,dimen2)
4635       double precision zapas 
4636       common /contacts_hb/ zapas(3,20,maxres,7),
4637      &   facont_hb(20,maxres),ees0p(20,maxres),ees0m(20,maxres),
4638      &         num_cont_hb(maxres),jcont_hb(20,maxres)
4639       num_kont=num_cont_hb(atom)
4640       do i=1,num_kont
4641         do k=1,7
4642           do j=1,3
4643             buffer(i,indx+(k-1)*3+j)=zapas(j,i,atom,k)
4644           enddo ! j
4645         enddo ! k
4646         buffer(i,indx+22)=facont_hb(i,atom)
4647         buffer(i,indx+23)=ees0p(i,atom)
4648         buffer(i,indx+24)=ees0m(i,atom)
4649         buffer(i,indx+25)=dfloat(jcont_hb(i,atom))
4650       enddo ! i
4651       buffer(1,indx+26)=dfloat(num_kont)
4652       return
4653       end
4654 c------------------------------------------------------------------------------
4655       subroutine unpack_buffer(dimen1,dimen2,atom,indx,buffer)
4656       implicit real*8 (a-h,o-z)
4657       include 'DIMENSIONS' 
4658       integer dimen1,dimen2,atom,indx
4659       double precision buffer(dimen1,dimen2)
4660       double precision zapas 
4661       common /contacts_hb/ zapas(3,20,maxres,7),
4662      &         facont_hb(20,maxres),ees0p(20,maxres),ees0m(20,maxres),
4663      &         num_cont_hb(maxres),jcont_hb(20,maxres)
4664       num_kont=buffer(1,indx+26)
4665       num_kont_old=num_cont_hb(atom)
4666       num_cont_hb(atom)=num_kont+num_kont_old
4667       do i=1,num_kont
4668         ii=i+num_kont_old
4669         do k=1,7    
4670           do j=1,3
4671             zapas(j,ii,atom,k)=buffer(i,indx+(k-1)*3+j)
4672           enddo ! j 
4673         enddo ! k 
4674         facont_hb(ii,atom)=buffer(i,indx+22)
4675         ees0p(ii,atom)=buffer(i,indx+23)
4676         ees0m(ii,atom)=buffer(i,indx+24)
4677         jcont_hb(ii,atom)=buffer(i,indx+25)
4678       enddo ! i
4679       return
4680       end
4681 c------------------------------------------------------------------------------
4682 #endif
4683       subroutine multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
4684 C This subroutine calculates multi-body contributions to hydrogen-bonding 
4685       implicit real*8 (a-h,o-z)
4686       include 'DIMENSIONS'
4687       include 'sizesclu.dat'
4688       include 'COMMON.IOUNITS'
4689 #ifdef MPL
4690       include 'COMMON.INFO'
4691 #endif
4692       include 'COMMON.FFIELD'
4693       include 'COMMON.DERIV'
4694       include 'COMMON.INTERACT'
4695       include 'COMMON.CONTACTS'
4696 #ifdef MPL
4697       parameter (max_cont=maxconts)
4698       parameter (max_dim=2*(8*3+2))
4699       parameter (msglen1=max_cont*max_dim*4)
4700       parameter (msglen2=2*msglen1)
4701       integer source,CorrelType,CorrelID,Error
4702       double precision buffer(max_cont,max_dim)
4703 #endif
4704       double precision gx(3),gx1(3)
4705       logical lprn,ldone
4706
4707 C Set lprn=.true. for debugging
4708       lprn=.false.
4709 #ifdef MPL
4710       n_corr=0
4711       n_corr1=0
4712       if (fgProcs.le.1) goto 30
4713       if (lprn) then
4714         write (iout,'(a)') 'Contact function values:'
4715         do i=nnt,nct-2
4716           write (iout,'(2i3,50(1x,i2,f5.2))') 
4717      &    i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
4718      &    j=1,num_cont_hb(i))
4719         enddo
4720       endif
4721 C Caution! Following code assumes that electrostatic interactions concerning
4722 C a given atom are split among at most two processors!
4723       CorrelType=477
4724       CorrelID=MyID+1
4725       ldone=.false.
4726       do i=1,max_cont
4727         do j=1,max_dim
4728           buffer(i,j)=0.0D0
4729         enddo
4730       enddo
4731       mm=mod(MyRank,2)
4732 cd    write (iout,*) 'MyRank',MyRank,' mm',mm
4733       if (mm) 20,20,10 
4734    10 continue
4735 cd    write (iout,*) 'Sending: MyRank',MyRank,' mm',mm,' ldone',ldone
4736       if (MyRank.gt.0) then
4737 C Send correlation contributions to the preceding processor
4738         msglen=msglen1
4739         nn=num_cont_hb(iatel_s)
4740         call pack_buffer(max_cont,max_dim,iatel_s,0,buffer)
4741 cd      write (iout,*) 'The BUFFER array:'
4742 cd      do i=1,nn
4743 cd        write (iout,'(i2,9(3f8.3,2x))') i,(buffer(i,j),j=1,26)
4744 cd      enddo
4745         if (ielstart(iatel_s).gt.iatel_s+ispp) then
4746           msglen=msglen2
4747             call pack_buffer(max_cont,max_dim,iatel_s+1,26,buffer)
4748 C Clear the contacts of the atom passed to the neighboring processor
4749         nn=num_cont_hb(iatel_s+1)
4750 cd      do i=1,nn
4751 cd        write (iout,'(i2,9(3f8.3,2x))') i,(buffer(i,j+26),j=1,26)
4752 cd      enddo
4753             num_cont_hb(iatel_s)=0
4754         endif 
4755 cd      write (iout,*) 'Processor ',MyID,MyRank,
4756 cd   & ' is sending correlation contribution to processor',MyID-1,
4757 cd   & ' msglen=',msglen
4758 cd      write (*,*) 'Processor ',MyID,MyRank,
4759 cd   & ' is sending correlation contribution to processor',MyID-1,
4760 cd   & ' msglen=',msglen,' CorrelType=',CorrelType
4761         call mp_bsend(buffer,msglen,MyID-1,CorrelType,CorrelID)
4762 cd      write (iout,*) 'Processor ',MyID,
4763 cd   & ' has sent correlation contribution to processor',MyID-1,
4764 cd   & ' msglen=',msglen,' CorrelID=',CorrelID
4765 cd      write (*,*) 'Processor ',MyID,
4766 cd   & ' has sent correlation contribution to processor',MyID-1,
4767 cd   & ' msglen=',msglen,' CorrelID=',CorrelID
4768         msglen=msglen1
4769       endif ! (MyRank.gt.0)
4770       if (ldone) goto 30
4771       ldone=.true.
4772    20 continue
4773 cd    write (iout,*) 'Receiving: MyRank',MyRank,' mm',mm,' ldone',ldone
4774       if (MyRank.lt.fgProcs-1) then
4775 C Receive correlation contributions from the next processor
4776         msglen=msglen1
4777         if (ielend(iatel_e).lt.nct-1) msglen=msglen2
4778 cd      write (iout,*) 'Processor',MyID,
4779 cd   & ' is receiving correlation contribution from processor',MyID+1,
4780 cd   & ' msglen=',msglen,' CorrelType=',CorrelType
4781 cd      write (*,*) 'Processor',MyID,
4782 cd   & ' is receiving correlation contribution from processor',MyID+1,
4783 cd   & ' msglen=',msglen,' CorrelType=',CorrelType
4784         nbytes=-1
4785         do while (nbytes.le.0)
4786           call mp_probe(MyID+1,CorrelType,nbytes)
4787         enddo
4788 cd      print *,'Processor',MyID,' msglen',msglen,' nbytes',nbytes
4789         call mp_brecv(buffer,msglen,MyID+1,CorrelType,nbytes)
4790 cd      write (iout,*) 'Processor',MyID,
4791 cd   & ' has received correlation contribution from processor',MyID+1,
4792 cd   & ' msglen=',msglen,' nbytes=',nbytes
4793 cd      write (iout,*) 'The received BUFFER array:'
4794 cd      do i=1,max_cont
4795 cd        write (iout,'(i2,9(3f8.3,2x))') i,(buffer(i,j),j=1,52)
4796 cd      enddo
4797         if (msglen.eq.msglen1) then
4798           call unpack_buffer(max_cont,max_dim,iatel_e+1,0,buffer)
4799         else if (msglen.eq.msglen2)  then
4800           call unpack_buffer(max_cont,max_dim,iatel_e,0,buffer) 
4801           call unpack_buffer(max_cont,max_dim,iatel_e+1,26,buffer) 
4802         else
4803           write (iout,*) 
4804      & 'ERROR!!!! message length changed while processing correlations.'
4805           write (*,*) 
4806      & 'ERROR!!!! message length changed while processing correlations.'
4807           call mp_stopall(Error)
4808         endif ! msglen.eq.msglen1
4809       endif ! MyRank.lt.fgProcs-1
4810       if (ldone) goto 30
4811       ldone=.true.
4812       goto 10
4813    30 continue
4814 #endif
4815       if (lprn) then
4816         write (iout,'(a)') 'Contact function values:'
4817         do i=nnt,nct-2
4818           write (iout,'(2i3,50(1x,i2,f5.2))') 
4819      &    i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
4820      &    j=1,num_cont_hb(i))
4821         enddo
4822       endif
4823       ecorr=0.0D0
4824 C Remove the loop below after debugging !!!
4825       do i=nnt,nct
4826         do j=1,3
4827           gradcorr(j,i)=0.0D0
4828           gradxorr(j,i)=0.0D0
4829         enddo
4830       enddo
4831 C Calculate the local-electrostatic correlation terms
4832       do i=iatel_s,iatel_e+1
4833         i1=i+1
4834         num_conti=num_cont_hb(i)
4835         num_conti1=num_cont_hb(i+1)
4836         do jj=1,num_conti
4837           j=jcont_hb(jj,i)
4838           do kk=1,num_conti1
4839             j1=jcont_hb(kk,i1)
4840 c            write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
4841 c     &         ' jj=',jj,' kk=',kk
4842             if (j1.eq.j+1 .or. j1.eq.j-1) then
4843 C Contacts I-J and (I+1)-(J+1) or (I+1)-(J-1) occur simultaneously. 
4844 C The system gains extra energy.
4845               ecorr=ecorr+ehbcorr(i,j,i+1,j1,jj,kk,0.72D0,0.32D0)
4846               n_corr=n_corr+1
4847             else if (j1.eq.j) then
4848 C Contacts I-J and I-(J+1) occur simultaneously. 
4849 C The system loses extra energy.
4850 c             ecorr=ecorr+ehbcorr(i,j,i+1,j,jj,kk,0.60D0,-0.40D0) 
4851             endif
4852           enddo ! kk
4853           do kk=1,num_conti
4854             j1=jcont_hb(kk,i)
4855 c           write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
4856 c    &         ' jj=',jj,' kk=',kk
4857             if (j1.eq.j+1) then
4858 C Contacts I-J and (I+1)-J occur simultaneously. 
4859 C The system loses extra energy.
4860 c             ecorr=ecorr+ehbcorr(i,j,i,j+1,jj,kk,0.60D0,-0.40D0)
4861             endif ! j1==j+1
4862           enddo ! kk
4863         enddo ! jj
4864       enddo ! i
4865       return
4866       end
4867 c------------------------------------------------------------------------------
4868       subroutine multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,
4869      &  n_corr1)
4870 C This subroutine calculates multi-body contributions to hydrogen-bonding 
4871       implicit real*8 (a-h,o-z)
4872       include 'DIMENSIONS'
4873       include 'sizesclu.dat'
4874       include 'COMMON.IOUNITS'
4875 #ifdef MPL
4876       include 'COMMON.INFO'
4877 #endif
4878       include 'COMMON.FFIELD'
4879       include 'COMMON.DERIV'
4880       include 'COMMON.INTERACT'
4881       include 'COMMON.CONTACTS'
4882 #ifdef MPL
4883       parameter (max_cont=maxconts)
4884       parameter (max_dim=2*(8*3+2))
4885       parameter (msglen1=max_cont*max_dim*4)
4886       parameter (msglen2=2*msglen1)
4887       integer source,CorrelType,CorrelID,Error
4888       double precision buffer(max_cont,max_dim)
4889 #endif
4890       double precision gx(3),gx1(3)
4891       logical lprn,ldone
4892
4893 C Set lprn=.true. for debugging
4894       lprn=.false.
4895       eturn6=0.0d0
4896 #ifdef MPL
4897       n_corr=0
4898       n_corr1=0
4899       if (fgProcs.le.1) goto 30
4900       if (lprn) then
4901         write (iout,'(a)') 'Contact function values:'
4902         do i=nnt,nct-2
4903           write (iout,'(2i3,50(1x,i2,f5.2))') 
4904      &    i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
4905      &    j=1,num_cont_hb(i))
4906         enddo
4907       endif
4908 C Caution! Following code assumes that electrostatic interactions concerning
4909 C a given atom are split among at most two processors!
4910       CorrelType=477
4911       CorrelID=MyID+1
4912       ldone=.false.
4913       do i=1,max_cont
4914         do j=1,max_dim
4915           buffer(i,j)=0.0D0
4916         enddo
4917       enddo
4918       mm=mod(MyRank,2)
4919 cd    write (iout,*) 'MyRank',MyRank,' mm',mm
4920       if (mm) 20,20,10 
4921    10 continue
4922 cd    write (iout,*) 'Sending: MyRank',MyRank,' mm',mm,' ldone',ldone
4923       if (MyRank.gt.0) then
4924 C Send correlation contributions to the preceding processor
4925         msglen=msglen1
4926         nn=num_cont_hb(iatel_s)
4927         call pack_buffer(max_cont,max_dim,iatel_s,0,buffer)
4928 cd      write (iout,*) 'The BUFFER array:'
4929 cd      do i=1,nn
4930 cd        write (iout,'(i2,9(3f8.3,2x))') i,(buffer(i,j),j=1,26)
4931 cd      enddo
4932         if (ielstart(iatel_s).gt.iatel_s+ispp) then
4933           msglen=msglen2
4934             call pack_buffer(max_cont,max_dim,iatel_s+1,26,buffer)
4935 C Clear the contacts of the atom passed to the neighboring processor
4936         nn=num_cont_hb(iatel_s+1)
4937 cd      do i=1,nn
4938 cd        write (iout,'(i2,9(3f8.3,2x))') i,(buffer(i,j+26),j=1,26)
4939 cd      enddo
4940             num_cont_hb(iatel_s)=0
4941         endif 
4942 cd      write (iout,*) 'Processor ',MyID,MyRank,
4943 cd   & ' is sending correlation contribution to processor',MyID-1,
4944 cd   & ' msglen=',msglen
4945 cd      write (*,*) 'Processor ',MyID,MyRank,
4946 cd   & ' is sending correlation contribution to processor',MyID-1,
4947 cd   & ' msglen=',msglen,' CorrelType=',CorrelType
4948         call mp_bsend(buffer,msglen,MyID-1,CorrelType,CorrelID)
4949 cd      write (iout,*) 'Processor ',MyID,
4950 cd   & ' has sent correlation contribution to processor',MyID-1,
4951 cd   & ' msglen=',msglen,' CorrelID=',CorrelID
4952 cd      write (*,*) 'Processor ',MyID,
4953 cd   & ' has sent correlation contribution to processor',MyID-1,
4954 cd   & ' msglen=',msglen,' CorrelID=',CorrelID
4955         msglen=msglen1
4956       endif ! (MyRank.gt.0)
4957       if (ldone) goto 30
4958       ldone=.true.
4959    20 continue
4960 cd    write (iout,*) 'Receiving: MyRank',MyRank,' mm',mm,' ldone',ldone
4961       if (MyRank.lt.fgProcs-1) then
4962 C Receive correlation contributions from the next processor
4963         msglen=msglen1
4964         if (ielend(iatel_e).lt.nct-1) msglen=msglen2
4965 cd      write (iout,*) 'Processor',MyID,
4966 cd   & ' is receiving correlation contribution from processor',MyID+1,
4967 cd   & ' msglen=',msglen,' CorrelType=',CorrelType
4968 cd      write (*,*) 'Processor',MyID,
4969 cd   & ' is receiving correlation contribution from processor',MyID+1,
4970 cd   & ' msglen=',msglen,' CorrelType=',CorrelType
4971         nbytes=-1
4972         do while (nbytes.le.0)
4973           call mp_probe(MyID+1,CorrelType,nbytes)
4974         enddo
4975 cd      print *,'Processor',MyID,' msglen',msglen,' nbytes',nbytes
4976         call mp_brecv(buffer,msglen,MyID+1,CorrelType,nbytes)
4977 cd      write (iout,*) 'Processor',MyID,
4978 cd   & ' has received correlation contribution from processor',MyID+1,
4979 cd   & ' msglen=',msglen,' nbytes=',nbytes
4980 cd      write (iout,*) 'The received BUFFER array:'
4981 cd      do i=1,max_cont
4982 cd        write (iout,'(i2,9(3f8.3,2x))') i,(buffer(i,j),j=1,52)
4983 cd      enddo
4984         if (msglen.eq.msglen1) then
4985           call unpack_buffer(max_cont,max_dim,iatel_e+1,0,buffer)
4986         else if (msglen.eq.msglen2)  then
4987           call unpack_buffer(max_cont,max_dim,iatel_e,0,buffer) 
4988           call unpack_buffer(max_cont,max_dim,iatel_e+1,26,buffer) 
4989         else
4990           write (iout,*) 
4991      & 'ERROR!!!! message length changed while processing correlations.'
4992           write (*,*) 
4993      & 'ERROR!!!! message length changed while processing correlations.'
4994           call mp_stopall(Error)
4995         endif ! msglen.eq.msglen1
4996       endif ! MyRank.lt.fgProcs-1
4997       if (ldone) goto 30
4998       ldone=.true.
4999       goto 10
5000    30 continue
5001 #endif
5002       if (lprn) then
5003         write (iout,'(a)') 'Contact function values:'
5004         do i=nnt,nct-2
5005           write (iout,'(2i3,50(1x,i2,f5.2))') 
5006      &    i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
5007      &    j=1,num_cont_hb(i))
5008         enddo
5009       endif
5010       ecorr=0.0D0
5011       ecorr5=0.0d0
5012       ecorr6=0.0d0
5013 C Remove the loop below after debugging !!!
5014       do i=nnt,nct
5015         do j=1,3
5016           gradcorr(j,i)=0.0D0
5017           gradxorr(j,i)=0.0D0
5018         enddo
5019       enddo
5020 C Calculate the dipole-dipole interaction energies
5021       if (wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0) then
5022       do i=iatel_s,iatel_e+1
5023         num_conti=num_cont_hb(i)
5024         do jj=1,num_conti
5025           j=jcont_hb(jj,i)
5026           call dipole(i,j,jj)
5027         enddo
5028       enddo
5029       endif
5030 C Calculate the local-electrostatic correlation terms
5031       do i=iatel_s,iatel_e+1
5032         i1=i+1
5033         num_conti=num_cont_hb(i)
5034         num_conti1=num_cont_hb(i+1)
5035         do jj=1,num_conti
5036           j=jcont_hb(jj,i)
5037           do kk=1,num_conti1
5038             j1=jcont_hb(kk,i1)
5039 c            write (*,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
5040 c     &         ' jj=',jj,' kk=',kk
5041             if (j1.eq.j+1 .or. j1.eq.j-1) then
5042 C Contacts I-J and (I+1)-(J+1) or (I+1)-(J-1) occur simultaneously. 
5043 C The system gains extra energy.
5044               n_corr=n_corr+1
5045               sqd1=dsqrt(d_cont(jj,i))
5046               sqd2=dsqrt(d_cont(kk,i1))
5047               sred_geom = sqd1*sqd2
5048               IF (sred_geom.lt.cutoff_corr) THEN
5049                 call gcont(sred_geom,r0_corr,1.0D0,delt_corr,
5050      &            ekont,fprimcont)
5051 c               write (*,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
5052 c     &         ' jj=',jj,' kk=',kk
5053                 fac_prim1=0.5d0*sqd2/sqd1*fprimcont
5054                 fac_prim2=0.5d0*sqd1/sqd2*fprimcont
5055                 do l=1,3
5056                   g_contij(l,1)=fac_prim1*grij_hb_cont(l,jj,i)
5057                   g_contij(l,2)=fac_prim2*grij_hb_cont(l,kk,i1)
5058                 enddo
5059                 n_corr1=n_corr1+1
5060 cd               write (iout,*) 'sred_geom=',sred_geom,
5061 cd     &          ' ekont=',ekont,' fprim=',fprimcont
5062                 call calc_eello(i,j,i+1,j1,jj,kk)
5063                 if (wcorr4.gt.0.0d0) 
5064      &            ecorr=ecorr+eello4(i,j,i+1,j1,jj,kk)
5065                 if (wcorr5.gt.0.0d0)
5066      &            ecorr5=ecorr5+eello5(i,j,i+1,j1,jj,kk)
5067 c                print *,"wcorr5",ecorr5
5068 cd                write(2,*)'wcorr6',wcorr6,' wturn6',wturn6
5069 cd                write(2,*)'ijkl',i,j,i+1,j1 
5070                 if (wcorr6.gt.0.0d0 .and. (j.ne.i+4 .or. j1.ne.i+3
5071      &               .or. wturn6.eq.0.0d0))then
5072 cd                  write (iout,*) '******ecorr6: i,j,i+1,j1',i,j,i+1,j1
5073                   ecorr6=ecorr6+eello6(i,j,i+1,j1,jj,kk)
5074 cd                write (iout,*) 'ecorr',ecorr,' ecorr5=',ecorr5,
5075 cd     &            'ecorr6=',ecorr6
5076 cd                write (iout,'(4e15.5)') sred_geom,
5077 cd     &          dabs(eello4(i,j,i+1,j1,jj,kk)),
5078 cd     &          dabs(eello5(i,j,i+1,j1,jj,kk)),
5079 cd     &          dabs(eello6(i,j,i+1,j1,jj,kk))
5080                 else if (wturn6.gt.0.0d0
5081      &            .and. (j.eq.i+4 .and. j1.eq.i+3)) then
5082 cd                  write (iout,*) '******eturn6: i,j,i+1,j1',i,j,i+1,j1
5083                   eturn6=eturn6+eello_turn6(i,jj,kk)
5084 cd                  write (2,*) 'multibody_eello:eturn6',eturn6
5085                 endif
5086               ENDIF
5087 1111          continue
5088             else if (j1.eq.j) then
5089 C Contacts I-J and I-(J+1) occur simultaneously. 
5090 C The system loses extra energy.
5091 c             ecorr=ecorr+ehbcorr(i,j,i+1,j,jj,kk,0.60D0,-0.40D0) 
5092             endif
5093           enddo ! kk
5094           do kk=1,num_conti
5095             j1=jcont_hb(kk,i)
5096 c           write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
5097 c    &         ' jj=',jj,' kk=',kk
5098             if (j1.eq.j+1) then
5099 C Contacts I-J and (I+1)-J occur simultaneously. 
5100 C The system loses extra energy.
5101 c             ecorr=ecorr+ehbcorr(i,j,i,j+1,jj,kk,0.60D0,-0.40D0)
5102             endif ! j1==j+1
5103           enddo ! kk
5104         enddo ! jj
5105       enddo ! i
5106       return
5107       end
5108 c------------------------------------------------------------------------------
5109       double precision function ehbcorr(i,j,k,l,jj,kk,coeffp,coeffm)
5110       implicit real*8 (a-h,o-z)
5111       include 'DIMENSIONS'
5112       include 'COMMON.IOUNITS'
5113       include 'COMMON.DERIV'
5114       include 'COMMON.INTERACT'
5115       include 'COMMON.CONTACTS'
5116       double precision gx(3),gx1(3)
5117       logical lprn
5118       lprn=.false.
5119       eij=facont_hb(jj,i)
5120       ekl=facont_hb(kk,k)
5121       ees0pij=ees0p(jj,i)
5122       ees0pkl=ees0p(kk,k)
5123       ees0mij=ees0m(jj,i)
5124       ees0mkl=ees0m(kk,k)
5125       ekont=eij*ekl
5126       ees=-(coeffp*ees0pij*ees0pkl+coeffm*ees0mij*ees0mkl)
5127 cd    ees=-(coeffp*ees0pkl+coeffm*ees0mkl)
5128 C Following 4 lines for diagnostics.
5129 cd    ees0pkl=0.0D0
5130 cd    ees0pij=1.0D0
5131 cd    ees0mkl=0.0D0
5132 cd    ees0mij=1.0D0
5133 c     write (iout,*)'Contacts have occurred for peptide groups',i,j,
5134 c    &   ' and',k,l
5135 c     write (iout,*)'Contacts have occurred for peptide groups',
5136 c    &  i,j,' fcont:',eij,' eij',' eesij',ees0pij,ees0mij,' and ',k,l
5137 c    & ,' fcont ',ekl,' eeskl',ees0pkl,ees0mkl,' ees=',ees
5138 C Calculate the multi-body contribution to energy.
5139       ecorr=ecorr+ekont*ees
5140       if (calc_grad) then
5141 C Calculate multi-body contributions to the gradient.
5142       do ll=1,3
5143         ghalf=0.5D0*ees*ekl*gacont_hbr(ll,jj,i)
5144         gradcorr(ll,i)=gradcorr(ll,i)+ghalf
5145      &  -ekont*(coeffp*ees0pkl*gacontp_hb1(ll,jj,i)+
5146      &  coeffm*ees0mkl*gacontm_hb1(ll,jj,i))
5147         gradcorr(ll,j)=gradcorr(ll,j)+ghalf
5148      &  -ekont*(coeffp*ees0pkl*gacontp_hb2(ll,jj,i)+
5149      &  coeffm*ees0mkl*gacontm_hb2(ll,jj,i))
5150         ghalf=0.5D0*ees*eij*gacont_hbr(ll,kk,k)
5151         gradcorr(ll,k)=gradcorr(ll,k)+ghalf
5152      &  -ekont*(coeffp*ees0pij*gacontp_hb1(ll,kk,k)+
5153      &  coeffm*ees0mij*gacontm_hb1(ll,kk,k))
5154         gradcorr(ll,l)=gradcorr(ll,l)+ghalf
5155      &  -ekont*(coeffp*ees0pij*gacontp_hb2(ll,kk,k)+
5156      &  coeffm*ees0mij*gacontm_hb2(ll,kk,k))
5157       enddo
5158       do m=i+1,j-1
5159         do ll=1,3
5160           gradcorr(ll,m)=gradcorr(ll,m)+
5161      &     ees*ekl*gacont_hbr(ll,jj,i)-
5162      &     ekont*(coeffp*ees0pkl*gacontp_hb3(ll,jj,i)+
5163      &     coeffm*ees0mkl*gacontm_hb3(ll,jj,i))
5164         enddo
5165       enddo
5166       do m=k+1,l-1
5167         do ll=1,3
5168           gradcorr(ll,m)=gradcorr(ll,m)+
5169      &     ees*eij*gacont_hbr(ll,kk,k)-
5170      &     ekont*(coeffp*ees0pij*gacontp_hb3(ll,kk,k)+
5171      &     coeffm*ees0mij*gacontm_hb3(ll,kk,k))
5172         enddo
5173       enddo 
5174       endif
5175       ehbcorr=ekont*ees
5176       return
5177       end
5178 C---------------------------------------------------------------------------
5179       subroutine dipole(i,j,jj)
5180       implicit real*8 (a-h,o-z)
5181       include 'DIMENSIONS'
5182       include 'sizesclu.dat'
5183       include 'COMMON.IOUNITS'
5184       include 'COMMON.CHAIN'
5185       include 'COMMON.FFIELD'
5186       include 'COMMON.DERIV'
5187       include 'COMMON.INTERACT'
5188       include 'COMMON.CONTACTS'
5189       include 'COMMON.TORSION'
5190       include 'COMMON.VAR'
5191       include 'COMMON.GEO'
5192       dimension dipi(2,2),dipj(2,2),dipderi(2),dipderj(2),auxvec(2),
5193      &  auxmat(2,2)
5194       iti1 = itortyp(itype(i+1))
5195       if (j.lt.nres-1) then
5196         itj1 = itortyp(itype(j+1))
5197       else
5198         itj1=ntortyp+1
5199       endif
5200       do iii=1,2
5201         dipi(iii,1)=Ub2(iii,i)
5202         dipderi(iii)=Ub2der(iii,i)
5203         dipi(iii,2)=b1(iii,iti1)
5204         dipj(iii,1)=Ub2(iii,j)
5205         dipderj(iii)=Ub2der(iii,j)
5206         dipj(iii,2)=b1(iii,itj1)
5207       enddo
5208       kkk=0
5209       do iii=1,2
5210         call matvec2(a_chuj(1,1,jj,i),dipj(1,iii),auxvec(1)) 
5211         do jjj=1,2
5212           kkk=kkk+1
5213           dip(kkk,jj,i)=scalar2(dipi(1,jjj),auxvec(1))
5214         enddo
5215       enddo
5216       if (.not.calc_grad) return
5217       do kkk=1,5
5218         do lll=1,3
5219           mmm=0
5220           do iii=1,2
5221             call matvec2(a_chuj_der(1,1,lll,kkk,jj,i),dipj(1,iii),
5222      &        auxvec(1))
5223             do jjj=1,2
5224               mmm=mmm+1
5225               dipderx(lll,kkk,mmm,jj,i)=scalar2(dipi(1,jjj),auxvec(1))
5226             enddo
5227           enddo
5228         enddo
5229       enddo
5230       call transpose2(a_chuj(1,1,jj,i),auxmat(1,1))
5231       call matvec2(auxmat(1,1),dipderi(1),auxvec(1))
5232       do iii=1,2
5233         dipderg(iii,jj,i)=scalar2(auxvec(1),dipj(1,iii))
5234       enddo
5235       call matvec2(a_chuj(1,1,jj,i),dipderj(1),auxvec(1))
5236       do iii=1,2
5237         dipderg(iii+2,jj,i)=scalar2(auxvec(1),dipi(1,iii))
5238       enddo
5239       return
5240       end
5241 C---------------------------------------------------------------------------
5242       subroutine calc_eello(i,j,k,l,jj,kk)
5243
5244 C This subroutine computes matrices and vectors needed to calculate 
5245 C the fourth-, fifth-, and sixth-order local-electrostatic terms.
5246 C
5247       implicit real*8 (a-h,o-z)
5248       include 'DIMENSIONS'
5249       include 'sizesclu.dat'
5250       include 'COMMON.IOUNITS'
5251       include 'COMMON.CHAIN'
5252       include 'COMMON.DERIV'
5253       include 'COMMON.INTERACT'
5254       include 'COMMON.CONTACTS'
5255       include 'COMMON.TORSION'
5256       include 'COMMON.VAR'
5257       include 'COMMON.GEO'
5258       include 'COMMON.FFIELD'
5259       double precision aa1(2,2),aa2(2,2),aa1t(2,2),aa2t(2,2),
5260      &  aa1tder(2,2,3,5),aa2tder(2,2,3,5),auxmat(2,2)
5261       logical lprn
5262       common /kutas/ lprn
5263 cd      write (iout,*) 'calc_eello: i=',i,' j=',j,' k=',k,' l=',l,
5264 cd     & ' jj=',jj,' kk=',kk
5265 cd      if (i.ne.2 .or. j.ne.4 .or. k.ne.3 .or. l.ne.5) return
5266       do iii=1,2
5267         do jjj=1,2
5268           aa1(iii,jjj)=a_chuj(iii,jjj,jj,i)
5269           aa2(iii,jjj)=a_chuj(iii,jjj,kk,k)
5270         enddo
5271       enddo
5272       call transpose2(aa1(1,1),aa1t(1,1))
5273       call transpose2(aa2(1,1),aa2t(1,1))
5274       do kkk=1,5
5275         do lll=1,3
5276           call transpose2(a_chuj_der(1,1,lll,kkk,jj,i),
5277      &      aa1tder(1,1,lll,kkk))
5278           call transpose2(a_chuj_der(1,1,lll,kkk,kk,k),
5279      &      aa2tder(1,1,lll,kkk))
5280         enddo
5281       enddo 
5282       if (l.eq.j+1) then
5283 C parallel orientation of the two CA-CA-CA frames.
5284         if (i.gt.1) then
5285           iti=itortyp(itype(i))
5286         else
5287           iti=ntortyp+1
5288         endif
5289         itk1=itortyp(itype(k+1))
5290         itj=itortyp(itype(j))
5291         if (l.lt.nres-1) then
5292           itl1=itortyp(itype(l+1))
5293         else
5294           itl1=ntortyp+1
5295         endif
5296 C A1 kernel(j+1) A2T
5297 cd        do iii=1,2
5298 cd          write (iout,'(3f10.5,5x,3f10.5)') 
5299 cd     &     (EUg(iii,jjj,k),jjj=1,2),(EUg(iii,jjj,l),jjj=1,2)
5300 cd        enddo
5301         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
5302      &   aa2tder(1,1,1,1),1,.false.,EUg(1,1,l),EUgder(1,1,l),
5303      &   AEA(1,1,1),AEAderg(1,1,1),AEAderx(1,1,1,1,1,1))
5304 C Following matrices are needed only for 6-th order cumulants
5305         IF (wcorr6.gt.0.0d0) THEN
5306         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
5307      &   aa2tder(1,1,1,1),1,.false.,EUgC(1,1,l),EUgCder(1,1,l),
5308      &   AECA(1,1,1),AECAderg(1,1,1),AECAderx(1,1,1,1,1,1))
5309         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
5310      &   aa2tder(1,1,1,1),2,.false.,Ug2DtEUg(1,1,l),
5311      &   Ug2DtEUgder(1,1,1,l),ADtEA(1,1,1),ADtEAderg(1,1,1,1),
5312      &   ADtEAderx(1,1,1,1,1,1))
5313         lprn=.false.
5314         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
5315      &   aa2tder(1,1,1,1),2,.false.,DtUg2EUg(1,1,l),
5316      &   DtUg2EUgder(1,1,1,l),ADtEA1(1,1,1),ADtEA1derg(1,1,1,1),
5317      &   ADtEA1derx(1,1,1,1,1,1))
5318         ENDIF
5319 C End 6-th order cumulants
5320 cd        lprn=.false.
5321 cd        if (lprn) then
5322 cd        write (2,*) 'In calc_eello6'
5323 cd        do iii=1,2
5324 cd          write (2,*) 'iii=',iii
5325 cd          do kkk=1,5
5326 cd            write (2,*) 'kkk=',kkk
5327 cd            do jjj=1,2
5328 cd              write (2,'(3(2f10.5),5x)') 
5329 cd     &        ((ADtEA1derx(jjj,mmm,lll,kkk,iii,1),mmm=1,2),lll=1,3)
5330 cd            enddo
5331 cd          enddo
5332 cd        enddo
5333 cd        endif
5334         call transpose2(EUgder(1,1,k),auxmat(1,1))
5335         call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,1,1))
5336         call transpose2(EUg(1,1,k),auxmat(1,1))
5337         call matmat2(auxmat(1,1),AEA(1,1,1),EAEA(1,1,1))
5338         call matmat2(auxmat(1,1),AEAderg(1,1,1),EAEAderg(1,1,2,1))
5339         do iii=1,2
5340           do kkk=1,5
5341             do lll=1,3
5342               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
5343      &          EAEAderx(1,1,lll,kkk,iii,1))
5344             enddo
5345           enddo
5346         enddo
5347 C A1T kernel(i+1) A2
5348         call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
5349      &   a_chuj_der(1,1,1,1,kk,k),1,.false.,EUg(1,1,k),EUgder(1,1,k),
5350      &   AEA(1,1,2),AEAderg(1,1,2),AEAderx(1,1,1,1,1,2))
5351 C Following matrices are needed only for 6-th order cumulants
5352         IF (wcorr6.gt.0.0d0) THEN
5353         call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
5354      &   a_chuj_der(1,1,1,1,kk,k),1,.false.,EUgC(1,1,k),EUgCder(1,1,k),
5355      &   AECA(1,1,2),AECAderg(1,1,2),AECAderx(1,1,1,1,1,2))
5356         call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
5357      &   a_chuj_der(1,1,1,1,kk,k),2,.false.,Ug2DtEUg(1,1,k),
5358      &   Ug2DtEUgder(1,1,1,k),ADtEA(1,1,2),ADtEAderg(1,1,1,2),
5359      &   ADtEAderx(1,1,1,1,1,2))
5360         call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
5361      &   a_chuj_der(1,1,1,1,kk,k),2,.false.,DtUg2EUg(1,1,k),
5362      &   DtUg2EUgder(1,1,1,k),ADtEA1(1,1,2),ADtEA1derg(1,1,1,2),
5363      &   ADtEA1derx(1,1,1,1,1,2))
5364         ENDIF
5365 C End 6-th order cumulants
5366         call transpose2(EUgder(1,1,l),auxmat(1,1))
5367         call matmat2(auxmat(1,1),AEA(1,1,2),EAEAderg(1,1,1,2))
5368         call transpose2(EUg(1,1,l),auxmat(1,1))
5369         call matmat2(auxmat(1,1),AEA(1,1,2),EAEA(1,1,2))
5370         call matmat2(auxmat(1,1),AEAderg(1,1,2),EAEAderg(1,1,2,2))
5371         do iii=1,2
5372           do kkk=1,5
5373             do lll=1,3
5374               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
5375      &          EAEAderx(1,1,lll,kkk,iii,2))
5376             enddo
5377           enddo
5378         enddo
5379 C AEAb1 and AEAb2
5380 C Calculate the vectors and their derivatives in virtual-bond dihedral angles.
5381 C They are needed only when the fifth- or the sixth-order cumulants are
5382 C indluded.
5383         IF (wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0) THEN
5384         call transpose2(AEA(1,1,1),auxmat(1,1))
5385         call matvec2(auxmat(1,1),b1(1,iti),AEAb1(1,1,1))
5386         call matvec2(auxmat(1,1),Ub2(1,i),AEAb2(1,1,1))
5387         call matvec2(auxmat(1,1),Ub2der(1,i),AEAb2derg(1,2,1,1))
5388         call transpose2(AEAderg(1,1,1),auxmat(1,1))
5389         call matvec2(auxmat(1,1),b1(1,iti),AEAb1derg(1,1,1))
5390         call matvec2(auxmat(1,1),Ub2(1,i),AEAb2derg(1,1,1,1))
5391         call matvec2(AEA(1,1,1),b1(1,itk1),AEAb1(1,2,1))
5392         call matvec2(AEAderg(1,1,1),b1(1,itk1),AEAb1derg(1,2,1))
5393         call matvec2(AEA(1,1,1),Ub2(1,k+1),AEAb2(1,2,1))
5394         call matvec2(AEAderg(1,1,1),Ub2(1,k+1),AEAb2derg(1,1,2,1))
5395         call matvec2(AEA(1,1,1),Ub2der(1,k+1),AEAb2derg(1,2,2,1))
5396         call transpose2(AEA(1,1,2),auxmat(1,1))
5397         call matvec2(auxmat(1,1),b1(1,itj),AEAb1(1,1,2))
5398         call matvec2(auxmat(1,1),Ub2(1,j),AEAb2(1,1,2))
5399         call matvec2(auxmat(1,1),Ub2der(1,j),AEAb2derg(1,2,1,2))
5400         call transpose2(AEAderg(1,1,2),auxmat(1,1))
5401         call matvec2(auxmat(1,1),b1(1,itj),AEAb1derg(1,1,2))
5402         call matvec2(auxmat(1,1),Ub2(1,j),AEAb2derg(1,1,1,2))
5403         call matvec2(AEA(1,1,2),b1(1,itl1),AEAb1(1,2,2))
5404         call matvec2(AEAderg(1,1,2),b1(1,itl1),AEAb1derg(1,2,2))
5405         call matvec2(AEA(1,1,2),Ub2(1,l+1),AEAb2(1,2,2))
5406         call matvec2(AEAderg(1,1,2),Ub2(1,l+1),AEAb2derg(1,1,2,2))
5407         call matvec2(AEA(1,1,2),Ub2der(1,l+1),AEAb2derg(1,2,2,2))
5408 C Calculate the Cartesian derivatives of the vectors.
5409         do iii=1,2
5410           do kkk=1,5
5411             do lll=1,3
5412               call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1))
5413               call matvec2(auxmat(1,1),b1(1,iti),
5414      &          AEAb1derx(1,lll,kkk,iii,1,1))
5415               call matvec2(auxmat(1,1),Ub2(1,i),
5416      &          AEAb2derx(1,lll,kkk,iii,1,1))
5417               call matvec2(AEAderx(1,1,lll,kkk,iii,1),b1(1,itk1),
5418      &          AEAb1derx(1,lll,kkk,iii,2,1))
5419               call matvec2(AEAderx(1,1,lll,kkk,iii,1),Ub2(1,k+1),
5420      &          AEAb2derx(1,lll,kkk,iii,2,1))
5421               call transpose2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1))
5422               call matvec2(auxmat(1,1),b1(1,itj),
5423      &          AEAb1derx(1,lll,kkk,iii,1,2))
5424               call matvec2(auxmat(1,1),Ub2(1,j),
5425      &          AEAb2derx(1,lll,kkk,iii,1,2))
5426               call matvec2(AEAderx(1,1,lll,kkk,iii,2),b1(1,itl1),
5427      &          AEAb1derx(1,lll,kkk,iii,2,2))
5428               call matvec2(AEAderx(1,1,lll,kkk,iii,2),Ub2(1,l+1),
5429      &          AEAb2derx(1,lll,kkk,iii,2,2))
5430             enddo
5431           enddo
5432         enddo
5433         ENDIF
5434 C End vectors
5435       else
5436 C Antiparallel orientation of the two CA-CA-CA frames.
5437         if (i.gt.1) then
5438           iti=itortyp(itype(i))
5439         else
5440           iti=ntortyp+1
5441         endif
5442         itk1=itortyp(itype(k+1))
5443         itl=itortyp(itype(l))
5444         itj=itortyp(itype(j))
5445         if (j.lt.nres-1) then
5446           itj1=itortyp(itype(j+1))
5447         else 
5448           itj1=ntortyp+1
5449         endif
5450 C A2 kernel(j-1)T A1T
5451         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
5452      &   aa2tder(1,1,1,1),1,.true.,EUg(1,1,j),EUgder(1,1,j),
5453      &   AEA(1,1,1),AEAderg(1,1,1),AEAderx(1,1,1,1,1,1))
5454 C Following matrices are needed only for 6-th order cumulants
5455         IF (wcorr6.gt.0.0d0 .or. (wturn6.gt.0.0d0 .and.
5456      &     j.eq.i+4 .and. l.eq.i+3)) THEN
5457         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
5458      &   aa2tder(1,1,1,1),1,.true.,EUgC(1,1,j),EUgCder(1,1,j),
5459      &   AECA(1,1,1),AECAderg(1,1,1),AECAderx(1,1,1,1,1,1))
5460         call kernel(aa2(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
5461      &   aa2tder(1,1,1,1),2,.true.,Ug2DtEUg(1,1,j),
5462      &   Ug2DtEUgder(1,1,1,j),ADtEA(1,1,1),ADtEAderg(1,1,1,1),
5463      &   ADtEAderx(1,1,1,1,1,1))
5464         call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
5465      &   aa2tder(1,1,1,1),2,.true.,DtUg2EUg(1,1,j),
5466      &   DtUg2EUgder(1,1,1,j),ADtEA1(1,1,1),ADtEA1derg(1,1,1,1),
5467      &   ADtEA1derx(1,1,1,1,1,1))
5468         ENDIF
5469 C End 6-th order cumulants
5470         call transpose2(EUgder(1,1,k),auxmat(1,1))
5471         call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,1,1))
5472         call transpose2(EUg(1,1,k),auxmat(1,1))
5473         call matmat2(auxmat(1,1),AEA(1,1,1),EAEA(1,1,1))
5474         call matmat2(auxmat(1,1),AEAderg(1,1,1),EAEAderg(1,1,2,1))
5475         do iii=1,2
5476           do kkk=1,5
5477             do lll=1,3
5478               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
5479      &          EAEAderx(1,1,lll,kkk,iii,1))
5480             enddo
5481           enddo
5482         enddo
5483 C A2T kernel(i+1)T A1
5484         call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
5485      &   a_chuj_der(1,1,1,1,jj,i),1,.true.,EUg(1,1,k),EUgder(1,1,k),
5486      &   AEA(1,1,2),AEAderg(1,1,2),AEAderx(1,1,1,1,1,2))
5487 C Following matrices are needed only for 6-th order cumulants
5488         IF (wcorr6.gt.0.0d0 .or. (wturn6.gt.0.0d0 .and.
5489      &     j.eq.i+4 .and. l.eq.i+3)) THEN
5490         call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
5491      &   a_chuj_der(1,1,1,1,jj,i),1,.true.,EUgC(1,1,k),EUgCder(1,1,k),
5492      &   AECA(1,1,2),AECAderg(1,1,2),AECAderx(1,1,1,1,1,2))
5493         call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
5494      &   a_chuj_der(1,1,1,1,jj,i),2,.true.,Ug2DtEUg(1,1,k),
5495      &   Ug2DtEUgder(1,1,1,k),ADtEA(1,1,2),ADtEAderg(1,1,1,2),
5496      &   ADtEAderx(1,1,1,1,1,2))
5497         call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
5498      &   a_chuj_der(1,1,1,1,jj,i),2,.true.,DtUg2EUg(1,1,k),
5499      &   DtUg2EUgder(1,1,1,k),ADtEA1(1,1,2),ADtEA1derg(1,1,1,2),
5500      &   ADtEA1derx(1,1,1,1,1,2))
5501         ENDIF
5502 C End 6-th order cumulants
5503         call transpose2(EUgder(1,1,j),auxmat(1,1))
5504         call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,2,2))
5505         call transpose2(EUg(1,1,j),auxmat(1,1))
5506         call matmat2(auxmat(1,1),AEA(1,1,2),EAEA(1,1,2))
5507         call matmat2(auxmat(1,1),AEAderg(1,1,2),EAEAderg(1,1,2,2))
5508         do iii=1,2
5509           do kkk=1,5
5510             do lll=1,3
5511               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
5512      &          EAEAderx(1,1,lll,kkk,iii,2))
5513             enddo
5514           enddo
5515         enddo
5516 C AEAb1 and AEAb2
5517 C Calculate the vectors and their derivatives in virtual-bond dihedral angles.
5518 C They are needed only when the fifth- or the sixth-order cumulants are
5519 C indluded.
5520         IF (wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0 .or.
5521      &    (wturn6.gt.0.0d0 .and. j.eq.i+4 .and. l.eq.i+3)) THEN
5522         call transpose2(AEA(1,1,1),auxmat(1,1))
5523         call matvec2(auxmat(1,1),b1(1,iti),AEAb1(1,1,1))
5524         call matvec2(auxmat(1,1),Ub2(1,i),AEAb2(1,1,1))
5525         call matvec2(auxmat(1,1),Ub2der(1,i),AEAb2derg(1,2,1,1))
5526         call transpose2(AEAderg(1,1,1),auxmat(1,1))
5527         call matvec2(auxmat(1,1),b1(1,iti),AEAb1derg(1,1,1))
5528         call matvec2(auxmat(1,1),Ub2(1,i),AEAb2derg(1,1,1,1))
5529         call matvec2(AEA(1,1,1),b1(1,itk1),AEAb1(1,2,1))
5530         call matvec2(AEAderg(1,1,1),b1(1,itk1),AEAb1derg(1,2,1))
5531         call matvec2(AEA(1,1,1),Ub2(1,k+1),AEAb2(1,2,1))
5532         call matvec2(AEAderg(1,1,1),Ub2(1,k+1),AEAb2derg(1,1,2,1))
5533         call matvec2(AEA(1,1,1),Ub2der(1,k+1),AEAb2derg(1,2,2,1))
5534         call transpose2(AEA(1,1,2),auxmat(1,1))
5535         call matvec2(auxmat(1,1),b1(1,itj1),AEAb1(1,1,2))
5536         call matvec2(auxmat(1,1),Ub2(1,l),AEAb2(1,1,2))
5537         call matvec2(auxmat(1,1),Ub2der(1,l),AEAb2derg(1,2,1,2))
5538         call transpose2(AEAderg(1,1,2),auxmat(1,1))
5539         call matvec2(auxmat(1,1),b1(1,itl),AEAb1(1,1,2))
5540         call matvec2(auxmat(1,1),Ub2(1,l),AEAb2derg(1,1,1,2))
5541         call matvec2(AEA(1,1,2),b1(1,itj1),AEAb1(1,2,2))
5542         call matvec2(AEAderg(1,1,2),b1(1,itj1),AEAb1derg(1,2,2))
5543         call matvec2(AEA(1,1,2),Ub2(1,j),AEAb2(1,2,2))
5544         call matvec2(AEAderg(1,1,2),Ub2(1,j),AEAb2derg(1,1,2,2))
5545         call matvec2(AEA(1,1,2),Ub2der(1,j),AEAb2derg(1,2,2,2))
5546 C Calculate the Cartesian derivatives of the vectors.
5547         do iii=1,2
5548           do kkk=1,5
5549             do lll=1,3
5550               call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1))
5551               call matvec2(auxmat(1,1),b1(1,iti),
5552      &          AEAb1derx(1,lll,kkk,iii,1,1))
5553               call matvec2(auxmat(1,1),Ub2(1,i),
5554      &          AEAb2derx(1,lll,kkk,iii,1,1))
5555               call matvec2(AEAderx(1,1,lll,kkk,iii,1),b1(1,itk1),
5556      &          AEAb1derx(1,lll,kkk,iii,2,1))
5557               call matvec2(AEAderx(1,1,lll,kkk,iii,1),Ub2(1,k+1),
5558      &          AEAb2derx(1,lll,kkk,iii,2,1))
5559               call transpose2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1))
5560               call matvec2(auxmat(1,1),b1(1,itl),
5561      &          AEAb1derx(1,lll,kkk,iii,1,2))
5562               call matvec2(auxmat(1,1),Ub2(1,l),
5563      &          AEAb2derx(1,lll,kkk,iii,1,2))
5564               call matvec2(AEAderx(1,1,lll,kkk,iii,2),b1(1,itj1),
5565      &          AEAb1derx(1,lll,kkk,iii,2,2))
5566               call matvec2(AEAderx(1,1,lll,kkk,iii,2),Ub2(1,j),
5567      &          AEAb2derx(1,lll,kkk,iii,2,2))
5568             enddo
5569           enddo
5570         enddo
5571         ENDIF
5572 C End vectors
5573       endif
5574       return
5575       end
5576 C---------------------------------------------------------------------------
5577       subroutine kernel(aa1,aa2t,aa1derx,aa2tderx,nderg,transp,
5578      &  KK,KKderg,AKA,AKAderg,AKAderx)
5579       implicit none
5580       integer nderg
5581       logical transp
5582       double precision aa1(2,2),aa2t(2,2),aa1derx(2,2,3,5),
5583      &  aa2tderx(2,2,3,5),KK(2,2),KKderg(2,2,nderg),AKA(2,2),
5584      &  AKAderg(2,2,nderg),AKAderx(2,2,3,5,2)
5585       integer iii,kkk,lll
5586       integer jjj,mmm
5587       logical lprn
5588       common /kutas/ lprn
5589       call prodmat3(aa1(1,1),aa2t(1,1),KK(1,1),transp,AKA(1,1))
5590       do iii=1,nderg 
5591         call prodmat3(aa1(1,1),aa2t(1,1),KKderg(1,1,iii),transp,
5592      &    AKAderg(1,1,iii))
5593       enddo
5594 cd      if (lprn) write (2,*) 'In kernel'
5595       do kkk=1,5
5596 cd        if (lprn) write (2,*) 'kkk=',kkk
5597         do lll=1,3
5598           call prodmat3(aa1derx(1,1,lll,kkk),aa2t(1,1),
5599      &      KK(1,1),transp,AKAderx(1,1,lll,kkk,1))
5600 cd          if (lprn) then
5601 cd            write (2,*) 'lll=',lll
5602 cd            write (2,*) 'iii=1'
5603 cd            do jjj=1,2
5604 cd              write (2,'(3(2f10.5),5x)') 
5605 cd     &        (AKAderx(jjj,mmm,lll,kkk,1),mmm=1,2)
5606 cd            enddo
5607 cd          endif
5608           call prodmat3(aa1(1,1),aa2tderx(1,1,lll,kkk),
5609      &      KK(1,1),transp,AKAderx(1,1,lll,kkk,2))
5610 cd          if (lprn) then
5611 cd            write (2,*) 'lll=',lll
5612 cd            write (2,*) 'iii=2'
5613 cd            do jjj=1,2
5614 cd              write (2,'(3(2f10.5),5x)') 
5615 cd     &        (AKAderx(jjj,mmm,lll,kkk,2),mmm=1,2)
5616 cd            enddo
5617 cd          endif
5618         enddo
5619       enddo
5620       return
5621       end
5622 C---------------------------------------------------------------------------
5623       double precision function eello4(i,j,k,l,jj,kk)
5624       implicit real*8 (a-h,o-z)
5625       include 'DIMENSIONS'
5626       include 'sizesclu.dat'
5627       include 'COMMON.IOUNITS'
5628       include 'COMMON.CHAIN'
5629       include 'COMMON.DERIV'
5630       include 'COMMON.INTERACT'
5631       include 'COMMON.CONTACTS'
5632       include 'COMMON.TORSION'
5633       include 'COMMON.VAR'
5634       include 'COMMON.GEO'
5635       double precision pizda(2,2),ggg1(3),ggg2(3)
5636 cd      if (i.ne.1 .or. j.ne.5 .or. k.ne.2 .or.l.ne.4) then
5637 cd        eello4=0.0d0
5638 cd        return
5639 cd      endif
5640 cd      print *,'eello4:',i,j,k,l,jj,kk
5641 cd      write (2,*) 'i',i,' j',j,' k',k,' l',l
5642 cd      call checkint4(i,j,k,l,jj,kk,eel4_num)
5643 cold      eij=facont_hb(jj,i)
5644 cold      ekl=facont_hb(kk,k)
5645 cold      ekont=eij*ekl
5646       eel4=-EAEA(1,1,1)-EAEA(2,2,1)
5647       if (calc_grad) then
5648 cd      eel41=-EAEA(1,1,2)-EAEA(2,2,2)
5649       gcorr_loc(k-1)=gcorr_loc(k-1)
5650      &   -ekont*(EAEAderg(1,1,1,1)+EAEAderg(2,2,1,1))
5651       if (l.eq.j+1) then
5652         gcorr_loc(l-1)=gcorr_loc(l-1)
5653      &     -ekont*(EAEAderg(1,1,2,1)+EAEAderg(2,2,2,1))
5654       else
5655         gcorr_loc(j-1)=gcorr_loc(j-1)
5656      &     -ekont*(EAEAderg(1,1,2,1)+EAEAderg(2,2,2,1))
5657       endif
5658       do iii=1,2
5659         do kkk=1,5
5660           do lll=1,3
5661             derx(lll,kkk,iii)=-EAEAderx(1,1,lll,kkk,iii,1)
5662      &                        -EAEAderx(2,2,lll,kkk,iii,1)
5663 cd            derx(lll,kkk,iii)=0.0d0
5664           enddo
5665         enddo
5666       enddo
5667 cd      gcorr_loc(l-1)=0.0d0
5668 cd      gcorr_loc(j-1)=0.0d0
5669 cd      gcorr_loc(k-1)=0.0d0
5670 cd      eel4=1.0d0
5671 cd      write (iout,*)'Contacts have occurred for peptide groups',
5672 cd     &  i,j,' fcont:',eij,' eij',' and ',k,l,
5673 cd     &  ' fcont ',ekl,' eel4=',eel4,' eel4_num',16*eel4_num
5674       if (j.lt.nres-1) then
5675         j1=j+1
5676         j2=j-1
5677       else
5678         j1=j-1
5679         j2=j-2
5680       endif
5681       if (l.lt.nres-1) then
5682         l1=l+1
5683         l2=l-1
5684       else
5685         l1=l-1
5686         l2=l-2
5687       endif
5688       do ll=1,3
5689 cold        ghalf=0.5d0*eel4*ekl*gacont_hbr(ll,jj,i)
5690         ggg1(ll)=eel4*g_contij(ll,1)
5691         ggg2(ll)=eel4*g_contij(ll,2)
5692         ghalf=0.5d0*ggg1(ll)
5693 cd        ghalf=0.0d0
5694         gradcorr(ll,i)=gradcorr(ll,i)+ghalf+ekont*derx(ll,2,1)
5695         gradcorr(ll,i+1)=gradcorr(ll,i+1)+ekont*derx(ll,3,1)
5696         gradcorr(ll,j)=gradcorr(ll,j)+ghalf+ekont*derx(ll,4,1)
5697         gradcorr(ll,j1)=gradcorr(ll,j1)+ekont*derx(ll,5,1)
5698 cold        ghalf=0.5d0*eel4*eij*gacont_hbr(ll,kk,k)
5699         ghalf=0.5d0*ggg2(ll)
5700 cd        ghalf=0.0d0
5701         gradcorr(ll,k)=gradcorr(ll,k)+ghalf+ekont*derx(ll,2,2)
5702         gradcorr(ll,k+1)=gradcorr(ll,k+1)+ekont*derx(ll,3,2)
5703         gradcorr(ll,l)=gradcorr(ll,l)+ghalf+ekont*derx(ll,4,2)
5704         gradcorr(ll,l1)=gradcorr(ll,l1)+ekont*derx(ll,5,2)
5705       enddo
5706 cd      goto 1112
5707       do m=i+1,j-1
5708         do ll=1,3
5709 cold          gradcorr(ll,m)=gradcorr(ll,m)+eel4*ekl*gacont_hbr(ll,jj,i)
5710           gradcorr(ll,m)=gradcorr(ll,m)+ggg1(ll)
5711         enddo
5712       enddo
5713       do m=k+1,l-1
5714         do ll=1,3
5715 cold          gradcorr(ll,m)=gradcorr(ll,m)+eel4*eij*gacont_hbr(ll,kk,k)
5716           gradcorr(ll,m)=gradcorr(ll,m)+ggg2(ll)
5717         enddo
5718       enddo
5719 1112  continue
5720       do m=i+2,j2
5721         do ll=1,3
5722           gradcorr(ll,m)=gradcorr(ll,m)+ekont*derx(ll,1,1)
5723         enddo
5724       enddo
5725       do m=k+2,l2
5726         do ll=1,3
5727           gradcorr(ll,m)=gradcorr(ll,m)+ekont*derx(ll,1,2)
5728         enddo
5729       enddo 
5730 cd      do iii=1,nres-3
5731 cd        write (2,*) iii,gcorr_loc(iii)
5732 cd      enddo
5733       endif
5734       eello4=ekont*eel4
5735 cd      write (2,*) 'ekont',ekont
5736 cd      write (iout,*) 'eello4',ekont*eel4
5737       return
5738       end
5739 C---------------------------------------------------------------------------
5740       double precision function eello5(i,j,k,l,jj,kk)
5741       implicit real*8 (a-h,o-z)
5742       include 'DIMENSIONS'
5743       include 'sizesclu.dat'
5744       include 'COMMON.IOUNITS'
5745       include 'COMMON.CHAIN'
5746       include 'COMMON.DERIV'
5747       include 'COMMON.INTERACT'
5748       include 'COMMON.CONTACTS'
5749       include 'COMMON.TORSION'
5750       include 'COMMON.VAR'
5751       include 'COMMON.GEO'
5752       double precision pizda(2,2),auxmat(2,2),auxmat1(2,2),vv(2)
5753       double precision ggg1(3),ggg2(3)
5754 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
5755 C                                                                              C
5756 C                            Parallel chains                                   C
5757 C                                                                              C
5758 C          o             o                   o             o                   C
5759 C         /l\           / \             \   / \           / \   /              C
5760 C        /   \         /   \             \ /   \         /   \ /               C
5761 C       j| o |l1       | o |              o| o |         | o |o                C
5762 C     \  |/k\|         |/ \|  /            |/ \|         |/ \|                 C
5763 C      \i/   \         /   \ /             /   \         /   \                 C
5764 C       o    k1             o                                                  C
5765 C         (I)          (II)                (III)          (IV)                 C
5766 C                                                                              C
5767 C      eello5_1        eello5_2            eello5_3       eello5_4             C
5768 C                                                                              C
5769 C                            Antiparallel chains                               C
5770 C                                                                              C
5771 C          o             o                   o             o                   C
5772 C         /j\           / \             \   / \           / \   /              C
5773 C        /   \         /   \             \ /   \         /   \ /               C
5774 C      j1| o |l        | o |              o| o |         | o |o                C
5775 C     \  |/k\|         |/ \|  /            |/ \|         |/ \|                 C
5776 C      \i/   \         /   \ /             /   \         /   \                 C
5777 C       o     k1            o                                                  C
5778 C         (I)          (II)                (III)          (IV)                 C
5779 C                                                                              C
5780 C      eello5_1        eello5_2            eello5_3       eello5_4             C
5781 C                                                                              C
5782 C o denotes a local interaction, vertical lines an electrostatic interaction.  C
5783 C                                                                              C
5784 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
5785 cd      if (i.ne.2 .or. j.ne.6 .or. k.ne.3 .or. l.ne.5) then
5786 cd        eello5=0.0d0
5787 cd        return
5788 cd      endif
5789 cd      write (iout,*)
5790 cd     &   'EELLO5: Contacts have occurred for peptide groups',i,j,
5791 cd     &   ' and',k,l
5792       itk=itortyp(itype(k))
5793       itl=itortyp(itype(l))
5794       itj=itortyp(itype(j))
5795       eello5_1=0.0d0
5796       eello5_2=0.0d0
5797       eello5_3=0.0d0
5798       eello5_4=0.0d0
5799 cd      call checkint5(i,j,k,l,jj,kk,eel5_1_num,eel5_2_num,
5800 cd     &   eel5_3_num,eel5_4_num)
5801       do iii=1,2
5802         do kkk=1,5
5803           do lll=1,3
5804             derx(lll,kkk,iii)=0.0d0
5805           enddo
5806         enddo
5807       enddo
5808 cd      eij=facont_hb(jj,i)
5809 cd      ekl=facont_hb(kk,k)
5810 cd      ekont=eij*ekl
5811 cd      write (iout,*)'Contacts have occurred for peptide groups',
5812 cd     &  i,j,' fcont:',eij,' eij',' and ',k,l
5813 cd      goto 1111
5814 C Contribution from the graph I.
5815 cd      write (2,*) 'AEA  ',AEA(1,1,1),AEA(2,1,1),AEA(1,2,1),AEA(2,2,1)
5816 cd      write (2,*) 'AEAb2',AEAb2(1,1,1),AEAb2(2,1,1)
5817       call transpose2(EUg(1,1,k),auxmat(1,1))
5818       call matmat2(AEA(1,1,1),auxmat(1,1),pizda(1,1))
5819       vv(1)=pizda(1,1)-pizda(2,2)
5820       vv(2)=pizda(1,2)+pizda(2,1)
5821       eello5_1=scalar2(AEAb2(1,1,1),Ub2(1,k))
5822      & +0.5d0*scalar2(vv(1),Dtobr2(1,i))
5823       if (calc_grad) then
5824 C Explicit gradient in virtual-dihedral angles.
5825       if (i.gt.1) g_corr5_loc(i-1)=g_corr5_loc(i-1)
5826      & +ekont*(scalar2(AEAb2derg(1,2,1,1),Ub2(1,k))
5827      & +0.5d0*scalar2(vv(1),Dtobr2der(1,i)))
5828       call transpose2(EUgder(1,1,k),auxmat1(1,1))
5829       call matmat2(AEA(1,1,1),auxmat1(1,1),pizda(1,1))
5830       vv(1)=pizda(1,1)-pizda(2,2)
5831       vv(2)=pizda(1,2)+pizda(2,1)
5832       g_corr5_loc(k-1)=g_corr5_loc(k-1)
5833      & +ekont*(scalar2(AEAb2(1,1,1),Ub2der(1,k))
5834      & +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
5835       call matmat2(AEAderg(1,1,1),auxmat(1,1),pizda(1,1))
5836       vv(1)=pizda(1,1)-pizda(2,2)
5837       vv(2)=pizda(1,2)+pizda(2,1)
5838       if (l.eq.j+1) then
5839         if (l.lt.nres-1) g_corr5_loc(l-1)=g_corr5_loc(l-1)
5840      &   +ekont*(scalar2(AEAb2derg(1,1,1,1),Ub2(1,k))
5841      &   +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
5842       else
5843         if (j.lt.nres-1) g_corr5_loc(j-1)=g_corr5_loc(j-1)
5844      &   +ekont*(scalar2(AEAb2derg(1,1,1,1),Ub2(1,k))
5845      &   +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
5846       endif 
5847 C Cartesian gradient
5848       do iii=1,2
5849         do kkk=1,5
5850           do lll=1,3
5851             call matmat2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1),
5852      &        pizda(1,1))
5853             vv(1)=pizda(1,1)-pizda(2,2)
5854             vv(2)=pizda(1,2)+pizda(2,1)
5855             derx(lll,kkk,iii)=derx(lll,kkk,iii)
5856      &       +scalar2(AEAb2derx(1,lll,kkk,iii,1,1),Ub2(1,k))
5857      &       +0.5d0*scalar2(vv(1),Dtobr2(1,i))
5858           enddo
5859         enddo
5860       enddo
5861 c      goto 1112
5862       endif
5863 c1111  continue
5864 C Contribution from graph II 
5865       call transpose2(EE(1,1,itk),auxmat(1,1))
5866       call matmat2(auxmat(1,1),AEA(1,1,1),pizda(1,1))
5867       vv(1)=pizda(1,1)+pizda(2,2)
5868       vv(2)=pizda(2,1)-pizda(1,2)
5869       eello5_2=scalar2(AEAb1(1,2,1),b1(1,itk))
5870      & -0.5d0*scalar2(vv(1),Ctobr(1,k))
5871       if (calc_grad) then
5872 C Explicit gradient in virtual-dihedral angles.
5873       g_corr5_loc(k-1)=g_corr5_loc(k-1)
5874      & -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,k))
5875       call matmat2(auxmat(1,1),AEAderg(1,1,1),pizda(1,1))
5876       vv(1)=pizda(1,1)+pizda(2,2)
5877       vv(2)=pizda(2,1)-pizda(1,2)
5878       if (l.eq.j+1) then
5879         g_corr5_loc(l-1)=g_corr5_loc(l-1)
5880      &   +ekont*(scalar2(AEAb1derg(1,2,1),b1(1,itk))
5881      &   -0.5d0*scalar2(vv(1),Ctobr(1,k)))
5882       else
5883         g_corr5_loc(j-1)=g_corr5_loc(j-1)
5884      &   +ekont*(scalar2(AEAb1derg(1,2,1),b1(1,itk))
5885      &   -0.5d0*scalar2(vv(1),Ctobr(1,k)))
5886       endif
5887 C Cartesian gradient
5888       do iii=1,2
5889         do kkk=1,5
5890           do lll=1,3
5891             call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
5892      &        pizda(1,1))
5893             vv(1)=pizda(1,1)+pizda(2,2)
5894             vv(2)=pizda(2,1)-pizda(1,2)
5895             derx(lll,kkk,iii)=derx(lll,kkk,iii)
5896      &       +scalar2(AEAb1derx(1,lll,kkk,iii,2,1),b1(1,itk))
5897      &       -0.5d0*scalar2(vv(1),Ctobr(1,k))
5898           enddo
5899         enddo
5900       enddo
5901 cd      goto 1112
5902       endif
5903 cd1111  continue
5904       if (l.eq.j+1) then
5905 cd        goto 1110
5906 C Parallel orientation
5907 C Contribution from graph III
5908         call transpose2(EUg(1,1,l),auxmat(1,1))
5909         call matmat2(AEA(1,1,2),auxmat(1,1),pizda(1,1))
5910         vv(1)=pizda(1,1)-pizda(2,2)
5911         vv(2)=pizda(1,2)+pizda(2,1)
5912         eello5_3=scalar2(AEAb2(1,1,2),Ub2(1,l))
5913      &   +0.5d0*scalar2(vv(1),Dtobr2(1,j))
5914         if (calc_grad) then
5915 C Explicit gradient in virtual-dihedral angles.
5916         g_corr5_loc(j-1)=g_corr5_loc(j-1)
5917      &   +ekont*(scalar2(AEAb2derg(1,2,1,2),Ub2(1,l))
5918      &   +0.5d0*scalar2(vv(1),Dtobr2der(1,j)))
5919         call matmat2(AEAderg(1,1,2),auxmat(1,1),pizda(1,1))
5920         vv(1)=pizda(1,1)-pizda(2,2)
5921         vv(2)=pizda(1,2)+pizda(2,1)
5922         g_corr5_loc(k-1)=g_corr5_loc(k-1)
5923      &   +ekont*(scalar2(AEAb2derg(1,1,1,2),Ub2(1,l))
5924      &   +0.5d0*scalar2(vv(1),Dtobr2(1,j)))
5925         call transpose2(EUgder(1,1,l),auxmat1(1,1))
5926         call matmat2(AEA(1,1,2),auxmat1(1,1),pizda(1,1))
5927         vv(1)=pizda(1,1)-pizda(2,2)
5928         vv(2)=pizda(1,2)+pizda(2,1)
5929         g_corr5_loc(l-1)=g_corr5_loc(l-1)
5930      &   +ekont*(scalar2(AEAb2(1,1,2),Ub2der(1,l))
5931      &   +0.5d0*scalar2(vv(1),Dtobr2(1,j)))
5932 C Cartesian gradient
5933         do iii=1,2
5934           do kkk=1,5
5935             do lll=1,3
5936               call matmat2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1),
5937      &          pizda(1,1))
5938               vv(1)=pizda(1,1)-pizda(2,2)
5939               vv(2)=pizda(1,2)+pizda(2,1)
5940               derx(lll,kkk,iii)=derx(lll,kkk,iii)
5941      &         +scalar2(AEAb2derx(1,lll,kkk,iii,1,2),Ub2(1,l))
5942      &         +0.5d0*scalar2(vv(1),Dtobr2(1,j))
5943             enddo
5944           enddo
5945         enddo
5946 cd        goto 1112
5947         endif
5948 C Contribution from graph IV
5949 cd1110    continue
5950         call transpose2(EE(1,1,itl),auxmat(1,1))
5951         call matmat2(auxmat(1,1),AEA(1,1,2),pizda(1,1))
5952         vv(1)=pizda(1,1)+pizda(2,2)
5953         vv(2)=pizda(2,1)-pizda(1,2)
5954         eello5_4=scalar2(AEAb1(1,2,2),b1(1,itl))
5955      &   -0.5d0*scalar2(vv(1),Ctobr(1,l))
5956         if (calc_grad) then
5957 C Explicit gradient in virtual-dihedral angles.
5958         g_corr5_loc(l-1)=g_corr5_loc(l-1)
5959      &   -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,l))
5960         call matmat2(auxmat(1,1),AEAderg(1,1,2),pizda(1,1))
5961         vv(1)=pizda(1,1)+pizda(2,2)
5962         vv(2)=pizda(2,1)-pizda(1,2)
5963         g_corr5_loc(k-1)=g_corr5_loc(k-1)
5964      &   +ekont*(scalar2(AEAb1derg(1,2,2),b1(1,itl))
5965      &   -0.5d0*scalar2(vv(1),Ctobr(1,l)))
5966 C Cartesian gradient
5967         do iii=1,2
5968           do kkk=1,5
5969             do lll=1,3
5970               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
5971      &          pizda(1,1))
5972               vv(1)=pizda(1,1)+pizda(2,2)
5973               vv(2)=pizda(2,1)-pizda(1,2)
5974               derx(lll,kkk,iii)=derx(lll,kkk,iii)
5975      &         +scalar2(AEAb1derx(1,lll,kkk,iii,2,2),b1(1,itl))
5976      &         -0.5d0*scalar2(vv(1),Ctobr(1,l))
5977             enddo
5978           enddo
5979         enddo
5980         endif
5981       else
5982 C Antiparallel orientation
5983 C Contribution from graph III
5984 c        goto 1110
5985         call transpose2(EUg(1,1,j),auxmat(1,1))
5986         call matmat2(AEA(1,1,2),auxmat(1,1),pizda(1,1))
5987         vv(1)=pizda(1,1)-pizda(2,2)
5988         vv(2)=pizda(1,2)+pizda(2,1)
5989         eello5_3=scalar2(AEAb2(1,1,2),Ub2(1,j))
5990      &   +0.5d0*scalar2(vv(1),Dtobr2(1,l))
5991         if (calc_grad) then
5992 C Explicit gradient in virtual-dihedral angles.
5993         g_corr5_loc(l-1)=g_corr5_loc(l-1)
5994      &   +ekont*(scalar2(AEAb2derg(1,2,1,2),Ub2(1,j))
5995      &   +0.5d0*scalar2(vv(1),Dtobr2der(1,l)))
5996         call matmat2(AEAderg(1,1,2),auxmat(1,1),pizda(1,1))
5997         vv(1)=pizda(1,1)-pizda(2,2)
5998         vv(2)=pizda(1,2)+pizda(2,1)
5999         g_corr5_loc(k-1)=g_corr5_loc(k-1)
6000      &   +ekont*(scalar2(AEAb2derg(1,1,1,2),Ub2(1,j))
6001      &   +0.5d0*scalar2(vv(1),Dtobr2(1,l)))
6002         call transpose2(EUgder(1,1,j),auxmat1(1,1))
6003         call matmat2(AEA(1,1,2),auxmat1(1,1),pizda(1,1))
6004         vv(1)=pizda(1,1)-pizda(2,2)
6005         vv(2)=pizda(1,2)+pizda(2,1)
6006         g_corr5_loc(j-1)=g_corr5_loc(j-1)
6007      &   +ekont*(scalar2(AEAb2(1,1,2),Ub2der(1,j))
6008      &   +0.5d0*scalar2(vv(1),Dtobr2(1,l)))
6009 C Cartesian gradient
6010         do iii=1,2
6011           do kkk=1,5
6012             do lll=1,3
6013               call matmat2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1),
6014      &          pizda(1,1))
6015               vv(1)=pizda(1,1)-pizda(2,2)
6016               vv(2)=pizda(1,2)+pizda(2,1)
6017               derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)
6018      &         +scalar2(AEAb2derx(1,lll,kkk,iii,1,2),Ub2(1,j))
6019      &         +0.5d0*scalar2(vv(1),Dtobr2(1,l))
6020             enddo
6021           enddo
6022         enddo
6023 cd        goto 1112
6024         endif
6025 C Contribution from graph IV
6026 1110    continue
6027         call transpose2(EE(1,1,itj),auxmat(1,1))
6028         call matmat2(auxmat(1,1),AEA(1,1,2),pizda(1,1))
6029         vv(1)=pizda(1,1)+pizda(2,2)
6030         vv(2)=pizda(2,1)-pizda(1,2)
6031         eello5_4=scalar2(AEAb1(1,2,2),b1(1,itj))
6032      &   -0.5d0*scalar2(vv(1),Ctobr(1,j))
6033         if (calc_grad) then
6034 C Explicit gradient in virtual-dihedral angles.
6035         g_corr5_loc(j-1)=g_corr5_loc(j-1)
6036      &   -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,j))
6037         call matmat2(auxmat(1,1),AEAderg(1,1,2),pizda(1,1))
6038         vv(1)=pizda(1,1)+pizda(2,2)
6039         vv(2)=pizda(2,1)-pizda(1,2)
6040         g_corr5_loc(k-1)=g_corr5_loc(k-1)
6041      &   +ekont*(scalar2(AEAb1derg(1,2,2),b1(1,itj))
6042      &   -0.5d0*scalar2(vv(1),Ctobr(1,j)))
6043 C Cartesian gradient
6044         do iii=1,2
6045           do kkk=1,5
6046             do lll=1,3
6047               call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
6048      &          pizda(1,1))
6049               vv(1)=pizda(1,1)+pizda(2,2)
6050               vv(2)=pizda(2,1)-pizda(1,2)
6051               derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)
6052      &         +scalar2(AEAb1derx(1,lll,kkk,iii,2,2),b1(1,itj))
6053      &         -0.5d0*scalar2(vv(1),Ctobr(1,j))
6054             enddo
6055           enddo
6056         enddo
6057       endif
6058       endif
6059 1112  continue
6060       eel5=eello5_1+eello5_2+eello5_3+eello5_4
6061 cd      if (i.eq.2 .and. j.eq.8 .and. k.eq.3 .and. l.eq.7) then
6062 cd        write (2,*) 'ijkl',i,j,k,l
6063 cd        write (2,*) 'eello5_1',eello5_1,' eello5_2',eello5_2,
6064 cd     &     ' eello5_3',eello5_3,' eello5_4',eello5_4
6065 cd      endif
6066 cd      write(iout,*) 'eello5_1',eello5_1,' eel5_1_num',16*eel5_1_num
6067 cd      write(iout,*) 'eello5_2',eello5_2,' eel5_2_num',16*eel5_2_num
6068 cd      write(iout,*) 'eello5_3',eello5_3,' eel5_3_num',16*eel5_3_num
6069 cd      write(iout,*) 'eello5_4',eello5_4,' eel5_4_num',16*eel5_4_num
6070       if (calc_grad) then
6071       if (j.lt.nres-1) then
6072         j1=j+1
6073         j2=j-1
6074       else
6075         j1=j-1
6076         j2=j-2
6077       endif
6078       if (l.lt.nres-1) then
6079         l1=l+1
6080         l2=l-1
6081       else
6082         l1=l-1
6083         l2=l-2
6084       endif
6085 cd      eij=1.0d0
6086 cd      ekl=1.0d0
6087 cd      ekont=1.0d0
6088 cd      write (2,*) 'eij',eij,' ekl',ekl,' ekont',ekont
6089       do ll=1,3
6090         ggg1(ll)=eel5*g_contij(ll,1)
6091         ggg2(ll)=eel5*g_contij(ll,2)
6092 cold        ghalf=0.5d0*eel5*ekl*gacont_hbr(ll,jj,i)
6093         ghalf=0.5d0*ggg1(ll)
6094 cd        ghalf=0.0d0
6095         gradcorr5(ll,i)=gradcorr5(ll,i)+ghalf+ekont*derx(ll,2,1)
6096         gradcorr5(ll,i+1)=gradcorr5(ll,i+1)+ekont*derx(ll,3,1)
6097         gradcorr5(ll,j)=gradcorr5(ll,j)+ghalf+ekont*derx(ll,4,1)
6098         gradcorr5(ll,j1)=gradcorr5(ll,j1)+ekont*derx(ll,5,1)
6099 cold        ghalf=0.5d0*eel5*eij*gacont_hbr(ll,kk,k)
6100         ghalf=0.5d0*ggg2(ll)
6101 cd        ghalf=0.0d0
6102         gradcorr5(ll,k)=gradcorr5(ll,k)+ghalf+ekont*derx(ll,2,2)
6103         gradcorr5(ll,k+1)=gradcorr5(ll,k+1)+ekont*derx(ll,3,2)
6104         gradcorr5(ll,l)=gradcorr5(ll,l)+ghalf+ekont*derx(ll,4,2)
6105         gradcorr5(ll,l1)=gradcorr5(ll,l1)+ekont*derx(ll,5,2)
6106       enddo
6107 cd      goto 1112
6108       do m=i+1,j-1
6109         do ll=1,3
6110 cold          gradcorr5(ll,m)=gradcorr5(ll,m)+eel5*ekl*gacont_hbr(ll,jj,i)
6111           gradcorr5(ll,m)=gradcorr5(ll,m)+ggg1(ll)
6112         enddo
6113       enddo
6114       do m=k+1,l-1
6115         do ll=1,3
6116 cold          gradcorr5(ll,m)=gradcorr5(ll,m)+eel5*eij*gacont_hbr(ll,kk,k)
6117           gradcorr5(ll,m)=gradcorr5(ll,m)+ggg2(ll)
6118         enddo
6119       enddo
6120 c1112  continue
6121       do m=i+2,j2
6122         do ll=1,3
6123           gradcorr5(ll,m)=gradcorr5(ll,m)+ekont*derx(ll,1,1)
6124         enddo
6125       enddo
6126       do m=k+2,l2
6127         do ll=1,3
6128           gradcorr5(ll,m)=gradcorr5(ll,m)+ekont*derx(ll,1,2)
6129         enddo
6130       enddo 
6131 cd      do iii=1,nres-3
6132 cd        write (2,*) iii,g_corr5_loc(iii)
6133 cd      enddo
6134       endif
6135       eello5=ekont*eel5
6136 cd      write (2,*) 'ekont',ekont
6137 cd      write (iout,*) 'eello5',ekont*eel5
6138       return
6139       end
6140 c--------------------------------------------------------------------------
6141       double precision function eello6(i,j,k,l,jj,kk)
6142       implicit real*8 (a-h,o-z)
6143       include 'DIMENSIONS'
6144       include 'sizesclu.dat'
6145       include 'COMMON.IOUNITS'
6146       include 'COMMON.CHAIN'
6147       include 'COMMON.DERIV'
6148       include 'COMMON.INTERACT'
6149       include 'COMMON.CONTACTS'
6150       include 'COMMON.TORSION'
6151       include 'COMMON.VAR'
6152       include 'COMMON.GEO'
6153       include 'COMMON.FFIELD'
6154       double precision ggg1(3),ggg2(3)
6155 cd      if (i.ne.1 .or. j.ne.3 .or. k.ne.2 .or. l.ne.4) then
6156 cd        eello6=0.0d0
6157 cd        return
6158 cd      endif
6159 cd      write (iout,*)
6160 cd     &   'EELLO6: Contacts have occurred for peptide groups',i,j,
6161 cd     &   ' and',k,l
6162       eello6_1=0.0d0
6163       eello6_2=0.0d0
6164       eello6_3=0.0d0
6165       eello6_4=0.0d0
6166       eello6_5=0.0d0
6167       eello6_6=0.0d0
6168 cd      call checkint6(i,j,k,l,jj,kk,eel6_1_num,eel6_2_num,
6169 cd     &   eel6_3_num,eel6_4_num,eel6_5_num,eel6_6_num)
6170       do iii=1,2
6171         do kkk=1,5
6172           do lll=1,3
6173             derx(lll,kkk,iii)=0.0d0
6174           enddo
6175         enddo
6176       enddo
6177 cd      eij=facont_hb(jj,i)
6178 cd      ekl=facont_hb(kk,k)
6179 cd      ekont=eij*ekl
6180 cd      eij=1.0d0
6181 cd      ekl=1.0d0
6182 cd      ekont=1.0d0
6183       if (l.eq.j+1) then
6184         eello6_1=eello6_graph1(i,j,k,l,1,.false.)
6185         eello6_2=eello6_graph1(j,i,l,k,2,.false.)
6186         eello6_3=eello6_graph2(i,j,k,l,jj,kk,.false.)
6187         eello6_4=eello6_graph4(i,j,k,l,jj,kk,1,.false.)
6188         eello6_5=eello6_graph4(j,i,l,k,jj,kk,2,.false.)
6189         eello6_6=eello6_graph3(i,j,k,l,jj,kk,.false.)
6190       else
6191         eello6_1=eello6_graph1(i,j,k,l,1,.false.)
6192         eello6_2=eello6_graph1(l,k,j,i,2,.true.)
6193         eello6_3=eello6_graph2(i,l,k,j,jj,kk,.true.)
6194         eello6_4=eello6_graph4(i,j,k,l,jj,kk,1,.false.)
6195         if (wturn6.eq.0.0d0 .or. j.ne.i+4) then
6196           eello6_5=eello6_graph4(l,k,j,i,kk,jj,2,.true.)
6197         else
6198           eello6_5=0.0d0
6199         endif
6200         eello6_6=eello6_graph3(i,l,k,j,jj,kk,.true.)
6201       endif
6202 C If turn contributions are considered, they will be handled separately.
6203       eel6=eello6_1+eello6_2+eello6_3+eello6_4+eello6_5+eello6_6
6204 cd      write(iout,*) 'eello6_1',eello6_1,' eel6_1_num',16*eel6_1_num
6205 cd      write(iout,*) 'eello6_2',eello6_2,' eel6_2_num',16*eel6_2_num
6206 cd      write(iout,*) 'eello6_3',eello6_3,' eel6_3_num',16*eel6_3_num
6207 cd      write(iout,*) 'eello6_4',eello6_4,' eel6_4_num',16*eel6_4_num
6208 cd      write(iout,*) 'eello6_5',eello6_5,' eel6_5_num',16*eel6_5_num
6209 cd      write(iout,*) 'eello6_6',eello6_6,' eel6_6_num',16*eel6_6_num
6210 cd      goto 1112
6211       if (calc_grad) then
6212       if (j.lt.nres-1) then
6213         j1=j+1
6214         j2=j-1
6215       else
6216         j1=j-1
6217         j2=j-2
6218       endif
6219       if (l.lt.nres-1) then
6220         l1=l+1
6221         l2=l-1
6222       else
6223         l1=l-1
6224         l2=l-2
6225       endif
6226       do ll=1,3
6227         ggg1(ll)=eel6*g_contij(ll,1)
6228         ggg2(ll)=eel6*g_contij(ll,2)
6229 cold        ghalf=0.5d0*eel6*ekl*gacont_hbr(ll,jj,i)
6230         ghalf=0.5d0*ggg1(ll)
6231 cd        ghalf=0.0d0
6232         gradcorr6(ll,i)=gradcorr6(ll,i)+ghalf+ekont*derx(ll,2,1)
6233         gradcorr6(ll,i+1)=gradcorr6(ll,i+1)+ekont*derx(ll,3,1)
6234         gradcorr6(ll,j)=gradcorr6(ll,j)+ghalf+ekont*derx(ll,4,1)
6235         gradcorr6(ll,j1)=gradcorr6(ll,j1)+ekont*derx(ll,5,1)
6236         ghalf=0.5d0*ggg2(ll)
6237 cold        ghalf=0.5d0*eel6*eij*gacont_hbr(ll,kk,k)
6238 cd        ghalf=0.0d0
6239         gradcorr6(ll,k)=gradcorr6(ll,k)+ghalf+ekont*derx(ll,2,2)
6240         gradcorr6(ll,k+1)=gradcorr6(ll,k+1)+ekont*derx(ll,3,2)
6241         gradcorr6(ll,l)=gradcorr6(ll,l)+ghalf+ekont*derx(ll,4,2)
6242         gradcorr6(ll,l1)=gradcorr6(ll,l1)+ekont*derx(ll,5,2)
6243       enddo
6244 cd      goto 1112
6245       do m=i+1,j-1
6246         do ll=1,3
6247 cold          gradcorr6(ll,m)=gradcorr6(ll,m)+eel6*ekl*gacont_hbr(ll,jj,i)
6248           gradcorr6(ll,m)=gradcorr6(ll,m)+ggg1(ll)
6249         enddo
6250       enddo
6251       do m=k+1,l-1
6252         do ll=1,3
6253 cold          gradcorr6(ll,m)=gradcorr6(ll,m)+eel6*eij*gacont_hbr(ll,kk,k)
6254           gradcorr6(ll,m)=gradcorr6(ll,m)+ggg2(ll)
6255         enddo
6256       enddo
6257 1112  continue
6258       do m=i+2,j2
6259         do ll=1,3
6260           gradcorr6(ll,m)=gradcorr6(ll,m)+ekont*derx(ll,1,1)
6261         enddo
6262       enddo
6263       do m=k+2,l2
6264         do ll=1,3
6265           gradcorr6(ll,m)=gradcorr6(ll,m)+ekont*derx(ll,1,2)
6266         enddo
6267       enddo 
6268 cd      do iii=1,nres-3
6269 cd        write (2,*) iii,g_corr6_loc(iii)
6270 cd      enddo
6271       endif
6272       eello6=ekont*eel6
6273 cd      write (2,*) 'ekont',ekont
6274 cd      write (iout,*) 'eello6',ekont*eel6
6275       return
6276       end
6277 c--------------------------------------------------------------------------
6278       double precision function eello6_graph1(i,j,k,l,imat,swap)
6279       implicit real*8 (a-h,o-z)
6280       include 'DIMENSIONS'
6281       include 'sizesclu.dat'
6282       include 'COMMON.IOUNITS'
6283       include 'COMMON.CHAIN'
6284       include 'COMMON.DERIV'
6285       include 'COMMON.INTERACT'
6286       include 'COMMON.CONTACTS'
6287       include 'COMMON.TORSION'
6288       include 'COMMON.VAR'
6289       include 'COMMON.GEO'
6290       double precision vv(2),vv1(2),pizda(2,2),auxmat(2,2),pizda1(2,2)
6291       logical swap
6292       logical lprn
6293       common /kutas/ lprn
6294 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
6295 C                                                                              C 
6296 C      Parallel       Antiparallel                                             C
6297 C                                                                              C
6298 C          o             o                                                     C
6299 C         /l\           /j\                                                    C
6300 C        /   \         /   \                                                   C
6301 C       /| o |         | o |\                                                  C
6302 C     \ j|/k\|  /   \  |/k\|l /                                                C
6303 C      \ /   \ /     \ /   \ /                                                 C
6304 C       o     o       o     o                                                  C
6305 C       i             i                                                        C
6306 C                                                                              C
6307 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
6308       itk=itortyp(itype(k))
6309       s1= scalar2(AEAb1(1,2,imat),CUgb2(1,i))
6310       s2=-scalar2(AEAb2(1,1,imat),Ug2Db1t(1,k))
6311       s3= scalar2(AEAb2(1,1,imat),CUgb2(1,k))
6312       call transpose2(EUgC(1,1,k),auxmat(1,1))
6313       call matmat2(AEA(1,1,imat),auxmat(1,1),pizda1(1,1))
6314       vv1(1)=pizda1(1,1)-pizda1(2,2)
6315       vv1(2)=pizda1(1,2)+pizda1(2,1)
6316       s4=0.5d0*scalar2(vv1(1),Dtobr2(1,i))
6317       vv(1)=AEAb1(1,2,imat)*b1(1,itk)-AEAb1(2,2,imat)*b1(2,itk)
6318       vv(2)=AEAb1(1,2,imat)*b1(2,itk)+AEAb1(2,2,imat)*b1(1,itk)
6319       s5=scalar2(vv(1),Dtobr2(1,i))
6320 cd      write (2,*) 's1',s1,' s2',s2,' s3',s3,' s4', s4,' s5',s5
6321       eello6_graph1=-0.5d0*(s1+s2+s3+s4+s5)
6322       if (.not. calc_grad) return
6323       if (i.gt.1) g_corr6_loc(i-1)=g_corr6_loc(i-1)
6324      & -0.5d0*ekont*(scalar2(AEAb1(1,2,imat),CUgb2der(1,i))
6325      & -scalar2(AEAb2derg(1,2,1,imat),Ug2Db1t(1,k))
6326      & +scalar2(AEAb2derg(1,2,1,imat),CUgb2(1,k))
6327      & +0.5d0*scalar2(vv1(1),Dtobr2der(1,i))
6328      & +scalar2(vv(1),Dtobr2der(1,i)))
6329       call matmat2(AEAderg(1,1,imat),auxmat(1,1),pizda1(1,1))
6330       vv1(1)=pizda1(1,1)-pizda1(2,2)
6331       vv1(2)=pizda1(1,2)+pizda1(2,1)
6332       vv(1)=AEAb1derg(1,2,imat)*b1(1,itk)-AEAb1derg(2,2,imat)*b1(2,itk)
6333       vv(2)=AEAb1derg(1,2,imat)*b1(2,itk)+AEAb1derg(2,2,imat)*b1(1,itk)
6334       if (l.eq.j+1) then
6335         g_corr6_loc(l-1)=g_corr6_loc(l-1)
6336      & +ekont*(-0.5d0*(scalar2(AEAb1derg(1,2,imat),CUgb2(1,i))
6337      & -scalar2(AEAb2derg(1,1,1,imat),Ug2Db1t(1,k))
6338      & +scalar2(AEAb2derg(1,1,1,imat),CUgb2(1,k))
6339      & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))+scalar2(vv(1),Dtobr2(1,i))))
6340       else
6341         g_corr6_loc(j-1)=g_corr6_loc(j-1)
6342      & +ekont*(-0.5d0*(scalar2(AEAb1derg(1,2,imat),CUgb2(1,i))
6343      & -scalar2(AEAb2derg(1,1,1,imat),Ug2Db1t(1,k))
6344      & +scalar2(AEAb2derg(1,1,1,imat),CUgb2(1,k))
6345      & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))+scalar2(vv(1),Dtobr2(1,i))))
6346       endif
6347       call transpose2(EUgCder(1,1,k),auxmat(1,1))
6348       call matmat2(AEA(1,1,imat),auxmat(1,1),pizda1(1,1))
6349       vv1(1)=pizda1(1,1)-pizda1(2,2)
6350       vv1(2)=pizda1(1,2)+pizda1(2,1)
6351       if (k.gt.1) g_corr6_loc(k-1)=g_corr6_loc(k-1)
6352      & +ekont*(-0.5d0*(-scalar2(AEAb2(1,1,imat),Ug2Db1tder(1,k))
6353      & +scalar2(AEAb2(1,1,imat),CUgb2der(1,k))
6354      & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))))
6355       do iii=1,2
6356         if (swap) then
6357           ind=3-iii
6358         else
6359           ind=iii
6360         endif
6361         do kkk=1,5
6362           do lll=1,3
6363             s1= scalar2(AEAb1derx(1,lll,kkk,iii,2,imat),CUgb2(1,i))
6364             s2=-scalar2(AEAb2derx(1,lll,kkk,iii,1,imat),Ug2Db1t(1,k))
6365             s3= scalar2(AEAb2derx(1,lll,kkk,iii,1,imat),CUgb2(1,k))
6366             call transpose2(EUgC(1,1,k),auxmat(1,1))
6367             call matmat2(AEAderx(1,1,lll,kkk,iii,imat),auxmat(1,1),
6368      &        pizda1(1,1))
6369             vv1(1)=pizda1(1,1)-pizda1(2,2)
6370             vv1(2)=pizda1(1,2)+pizda1(2,1)
6371             s4=0.5d0*scalar2(vv1(1),Dtobr2(1,i))
6372             vv(1)=AEAb1derx(1,lll,kkk,iii,2,imat)*b1(1,itk)
6373      &       -AEAb1derx(2,lll,kkk,iii,2,imat)*b1(2,itk)
6374             vv(2)=AEAb1derx(1,lll,kkk,iii,2,imat)*b1(2,itk)
6375      &       +AEAb1derx(2,lll,kkk,iii,2,imat)*b1(1,itk)
6376             s5=scalar2(vv(1),Dtobr2(1,i))
6377             derx(lll,kkk,ind)=derx(lll,kkk,ind)-0.5d0*(s1+s2+s3+s4+s5)
6378           enddo
6379         enddo
6380       enddo
6381       return
6382       end
6383 c----------------------------------------------------------------------------
6384       double precision function eello6_graph2(i,j,k,l,jj,kk,swap)
6385       implicit real*8 (a-h,o-z)
6386       include 'DIMENSIONS'
6387       include 'sizesclu.dat'
6388       include 'COMMON.IOUNITS'
6389       include 'COMMON.CHAIN'
6390       include 'COMMON.DERIV'
6391       include 'COMMON.INTERACT'
6392       include 'COMMON.CONTACTS'
6393       include 'COMMON.TORSION'
6394       include 'COMMON.VAR'
6395       include 'COMMON.GEO'
6396       logical swap
6397       double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2),
6398      & auxvec1(2),auxvec2(2),auxmat1(2,2)
6399       logical lprn
6400       common /kutas/ lprn
6401 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
6402 C                                                                              C 
6403 C      Parallel       Antiparallel                                             C
6404 C                                                                              C
6405 C          o             o                                                     C
6406 C     \   /l\           /j\   /                                                C
6407 C      \ /   \         /   \ /                                                 C
6408 C       o| o |         | o |o                                                  C
6409 C     \ j|/k\|      \  |/k\|l                                                  C
6410 C      \ /   \       \ /   \                                                   C
6411 C       o             o                                                        C
6412 C       i             i                                                        C
6413 C                                                                              C
6414 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
6415 cd      write (2,*) 'eello6_graph2: i,',i,' j',j,' k',k,' l',l
6416 C AL 7/4/01 s1 would occur in the sixth-order moment, 
6417 C           but not in a cluster cumulant
6418 #ifdef MOMENT
6419       s1=dip(1,jj,i)*dip(1,kk,k)
6420 #endif
6421       call matvec2(ADtEA1(1,1,1),Ub2(1,k),auxvec(1))
6422       s2=-0.5d0*scalar2(Ub2(1,i),auxvec(1))
6423       call matvec2(ADtEA(1,1,2),Ub2(1,l),auxvec1(1))
6424       s3=-0.5d0*scalar2(Ub2(1,j),auxvec1(1))
6425       call transpose2(EUg(1,1,k),auxmat(1,1))
6426       call matmat2(ADtEA1(1,1,1),auxmat(1,1),pizda(1,1))
6427       vv(1)=pizda(1,1)-pizda(2,2)
6428       vv(2)=pizda(1,2)+pizda(2,1)
6429       s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
6430 cd      write (2,*) 'eello6_graph2:','s1',s1,' s2',s2,' s3',s3,' s4',s4
6431 #ifdef MOMENT
6432       eello6_graph2=-(s1+s2+s3+s4)
6433 #else
6434       eello6_graph2=-(s2+s3+s4)
6435 #endif
6436 c      eello6_graph2=-s3
6437       if (.not. calc_grad) return
6438 C Derivatives in gamma(i-1)
6439       if (i.gt.1) then
6440 #ifdef MOMENT
6441         s1=dipderg(1,jj,i)*dip(1,kk,k)
6442 #endif
6443         s2=-0.5d0*scalar2(Ub2der(1,i),auxvec(1))
6444         call matvec2(ADtEAderg(1,1,1,2),Ub2(1,l),auxvec2(1))
6445         s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
6446         s4=-0.25d0*scalar2(vv(1),Dtobr2der(1,i))
6447 #ifdef MOMENT
6448         g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s1+s2+s3+s4)
6449 #else
6450         g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s2+s3+s4)
6451 #endif
6452 c        g_corr6_loc(i-1)=g_corr6_loc(i-1)-s3
6453       endif
6454 C Derivatives in gamma(k-1)
6455 #ifdef MOMENT
6456       s1=dip(1,jj,i)*dipderg(1,kk,k)
6457 #endif
6458       call matvec2(ADtEA1(1,1,1),Ub2der(1,k),auxvec2(1))
6459       s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
6460       call matvec2(ADtEAderg(1,1,2,2),Ub2(1,l),auxvec2(1))
6461       s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
6462       call transpose2(EUgder(1,1,k),auxmat1(1,1))
6463       call matmat2(ADtEA1(1,1,1),auxmat1(1,1),pizda(1,1))
6464       vv(1)=pizda(1,1)-pizda(2,2)
6465       vv(2)=pizda(1,2)+pizda(2,1)
6466       s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
6467 #ifdef MOMENT
6468       g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s1+s2+s3+s4)
6469 #else
6470       g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s2+s3+s4)
6471 #endif
6472 c      g_corr6_loc(k-1)=g_corr6_loc(k-1)-s3
6473 C Derivatives in gamma(j-1) or gamma(l-1)
6474       if (j.gt.1) then
6475 #ifdef MOMENT
6476         s1=dipderg(3,jj,i)*dip(1,kk,k) 
6477 #endif
6478         call matvec2(ADtEA1derg(1,1,1,1),Ub2(1,k),auxvec2(1))
6479         s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
6480         s3=-0.5d0*scalar2(Ub2der(1,j),auxvec1(1))
6481         call matmat2(ADtEA1derg(1,1,1,1),auxmat(1,1),pizda(1,1))
6482         vv(1)=pizda(1,1)-pizda(2,2)
6483         vv(2)=pizda(1,2)+pizda(2,1)
6484         s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
6485 #ifdef MOMENT
6486         if (swap) then
6487           g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*s1
6488         else
6489           g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*s1
6490         endif
6491 #endif
6492         g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*(s2+s3+s4)
6493 c        g_corr6_loc(j-1)=g_corr6_loc(j-1)-s3
6494       endif
6495 C Derivatives in gamma(l-1) or gamma(j-1)
6496       if (l.gt.1) then 
6497 #ifdef MOMENT
6498         s1=dip(1,jj,i)*dipderg(3,kk,k)
6499 #endif
6500         call matvec2(ADtEA1derg(1,1,2,1),Ub2(1,k),auxvec2(1))
6501         s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
6502         call matvec2(ADtEA(1,1,2),Ub2der(1,l),auxvec2(1))
6503         s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
6504         call matmat2(ADtEA1derg(1,1,2,1),auxmat(1,1),pizda(1,1))
6505         vv(1)=pizda(1,1)-pizda(2,2)
6506         vv(2)=pizda(1,2)+pizda(2,1)
6507         s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
6508 #ifdef MOMENT
6509         if (swap) then
6510           g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*s1
6511         else
6512           g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*s1
6513         endif
6514 #endif
6515         g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s3+s4)
6516 c        g_corr6_loc(l-1)=g_corr6_loc(l-1)-s3
6517       endif
6518 C Cartesian derivatives.
6519       if (lprn) then
6520         write (2,*) 'In eello6_graph2'
6521         do iii=1,2
6522           write (2,*) 'iii=',iii
6523           do kkk=1,5
6524             write (2,*) 'kkk=',kkk
6525             do jjj=1,2
6526               write (2,'(3(2f10.5),5x)') 
6527      &        ((ADtEA1derx(jjj,mmm,lll,kkk,iii,1),mmm=1,2),lll=1,3)
6528             enddo
6529           enddo
6530         enddo
6531       endif
6532       do iii=1,2
6533         do kkk=1,5
6534           do lll=1,3
6535 #ifdef MOMENT
6536             if (iii.eq.1) then
6537               s1=dipderx(lll,kkk,1,jj,i)*dip(1,kk,k)
6538             else
6539               s1=dip(1,jj,i)*dipderx(lll,kkk,1,kk,k)
6540             endif
6541 #endif
6542             call matvec2(ADtEA1derx(1,1,lll,kkk,iii,1),Ub2(1,k),
6543      &        auxvec(1))
6544             s2=-0.5d0*scalar2(Ub2(1,i),auxvec(1))
6545             call matvec2(ADtEAderx(1,1,lll,kkk,iii,2),Ub2(1,l),
6546      &        auxvec(1))
6547             s3=-0.5d0*scalar2(Ub2(1,j),auxvec(1))
6548             call transpose2(EUg(1,1,k),auxmat(1,1))
6549             call matmat2(ADtEA1derx(1,1,lll,kkk,iii,1),auxmat(1,1),
6550      &        pizda(1,1))
6551             vv(1)=pizda(1,1)-pizda(2,2)
6552             vv(2)=pizda(1,2)+pizda(2,1)
6553             s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
6554 cd            write (2,*) 's1',s1,' s2',s2,' s3',s3,' s4',s4
6555 #ifdef MOMENT
6556             derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
6557 #else
6558             derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
6559 #endif
6560             if (swap) then
6561               derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
6562             else
6563               derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
6564             endif
6565           enddo
6566         enddo
6567       enddo
6568       return
6569       end
6570 c----------------------------------------------------------------------------
6571       double precision function eello6_graph3(i,j,k,l,jj,kk,swap)
6572       implicit real*8 (a-h,o-z)
6573       include 'DIMENSIONS'
6574       include 'sizesclu.dat'
6575       include 'COMMON.IOUNITS'
6576       include 'COMMON.CHAIN'
6577       include 'COMMON.DERIV'
6578       include 'COMMON.INTERACT'
6579       include 'COMMON.CONTACTS'
6580       include 'COMMON.TORSION'
6581       include 'COMMON.VAR'
6582       include 'COMMON.GEO'
6583       double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2)
6584       logical swap
6585 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
6586 C                                                                              C
6587 C      Parallel       Antiparallel                                             C
6588 C                                                                              C
6589 C          o             o                                                     C
6590 C         /l\   /   \   /j\                                                    C
6591 C        /   \ /     \ /   \                                                   C
6592 C       /| o |o       o| o |\                                                  C
6593 C       j|/k\|  /      |/k\|l /                                                C
6594 C        /   \ /       /   \ /                                                 C
6595 C       /     o       /     o                                                  C
6596 C       i             i                                                        C
6597 C                                                                              C
6598 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
6599 C
6600 C 4/7/01 AL Component s1 was removed, because it pertains to the respective 
6601 C           energy moment and not to the cluster cumulant.
6602       iti=itortyp(itype(i))
6603       if (j.lt.nres-1) then
6604         itj1=itortyp(itype(j+1))
6605       else
6606         itj1=ntortyp+1
6607       endif
6608       itk=itortyp(itype(k))
6609       itk1=itortyp(itype(k+1))
6610       if (l.lt.nres-1) then
6611         itl1=itortyp(itype(l+1))
6612       else
6613         itl1=ntortyp+1
6614       endif
6615 #ifdef MOMENT
6616       s1=dip(4,jj,i)*dip(4,kk,k)
6617 #endif
6618       call matvec2(AECA(1,1,1),b1(1,itk1),auxvec(1))
6619       s2=0.5d0*scalar2(b1(1,itk),auxvec(1))
6620       call matvec2(AECA(1,1,2),b1(1,itl1),auxvec(1))
6621       s3=0.5d0*scalar2(b1(1,itj1),auxvec(1))
6622       call transpose2(EE(1,1,itk),auxmat(1,1))
6623       call matmat2(auxmat(1,1),AECA(1,1,1),pizda(1,1))
6624       vv(1)=pizda(1,1)+pizda(2,2)
6625       vv(2)=pizda(2,1)-pizda(1,2)
6626       s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
6627 cd      write (2,*) 'eello6_graph3:','s1',s1,' s2',s2,' s3',s3,' s4',s4
6628 #ifdef MOMENT
6629       eello6_graph3=-(s1+s2+s3+s4)
6630 #else
6631       eello6_graph3=-(s2+s3+s4)
6632 #endif
6633 c      eello6_graph3=-s4
6634       if (.not. calc_grad) return
6635 C Derivatives in gamma(k-1)
6636       call matvec2(AECAderg(1,1,2),b1(1,itl1),auxvec(1))
6637       s3=0.5d0*scalar2(b1(1,itj1),auxvec(1))
6638       s4=-0.25d0*scalar2(vv(1),Ctobrder(1,k))
6639       g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s3+s4)
6640 C Derivatives in gamma(l-1)
6641       call matvec2(AECAderg(1,1,1),b1(1,itk1),auxvec(1))
6642       s2=0.5d0*scalar2(b1(1,itk),auxvec(1))
6643       call matmat2(auxmat(1,1),AECAderg(1,1,1),pizda(1,1))
6644       vv(1)=pizda(1,1)+pizda(2,2)
6645       vv(2)=pizda(2,1)-pizda(1,2)
6646       s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
6647       g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s4) 
6648 C Cartesian derivatives.
6649       do iii=1,2
6650         do kkk=1,5
6651           do lll=1,3
6652 #ifdef MOMENT
6653             if (iii.eq.1) then
6654               s1=dipderx(lll,kkk,4,jj,i)*dip(4,kk,k)
6655             else
6656               s1=dip(4,jj,i)*dipderx(lll,kkk,4,kk,k)
6657             endif
6658 #endif
6659             call matvec2(AECAderx(1,1,lll,kkk,iii,1),b1(1,itk1),
6660      &        auxvec(1))
6661             s2=0.5d0*scalar2(b1(1,itk),auxvec(1))
6662             call matvec2(AECAderx(1,1,lll,kkk,iii,2),b1(1,itl1),
6663      &        auxvec(1))
6664             s3=0.5d0*scalar2(b1(1,itj1),auxvec(1))
6665             call matmat2(auxmat(1,1),AECAderx(1,1,lll,kkk,iii,1),
6666      &        pizda(1,1))
6667             vv(1)=pizda(1,1)+pizda(2,2)
6668             vv(2)=pizda(2,1)-pizda(1,2)
6669             s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
6670 #ifdef MOMENT
6671             derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
6672 #else
6673             derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
6674 #endif
6675             if (swap) then
6676               derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
6677             else
6678               derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
6679             endif
6680 c            derx(lll,kkk,iii)=derx(lll,kkk,iii)-s4
6681           enddo
6682         enddo
6683       enddo
6684       return
6685       end
6686 c----------------------------------------------------------------------------
6687       double precision function eello6_graph4(i,j,k,l,jj,kk,imat,swap)
6688       implicit real*8 (a-h,o-z)
6689       include 'DIMENSIONS'
6690       include 'sizesclu.dat'
6691       include 'COMMON.IOUNITS'
6692       include 'COMMON.CHAIN'
6693       include 'COMMON.DERIV'
6694       include 'COMMON.INTERACT'
6695       include 'COMMON.CONTACTS'
6696       include 'COMMON.TORSION'
6697       include 'COMMON.VAR'
6698       include 'COMMON.GEO'
6699       include 'COMMON.FFIELD'
6700       double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2),
6701      & auxvec1(2),auxmat1(2,2)
6702       logical swap
6703 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
6704 C                                                                              C
6705 C      Parallel       Antiparallel                                             C
6706 C                                                                              C
6707 C          o             o                                                     C
6708 C         /l\   /   \   /j\                                                    C
6709 C        /   \ /     \ /   \                                                   C
6710 C       /| o |o       o| o |\                                                  C
6711 C     \ j|/k\|      \  |/k\|l                                                  C
6712 C      \ /   \       \ /   \                                                   C
6713 C       o     \       o     \                                                  C
6714 C       i             i                                                        C
6715 C                                                                              C
6716 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
6717 C
6718 C 4/7/01 AL Component s1 was removed, because it pertains to the respective 
6719 C           energy moment and not to the cluster cumulant.
6720 cd      write (2,*) 'eello_graph4: wturn6',wturn6
6721       iti=itortyp(itype(i))
6722       itj=itortyp(itype(j))
6723       if (j.lt.nres-1) then
6724         itj1=itortyp(itype(j+1))
6725       else
6726         itj1=ntortyp+1
6727       endif
6728       itk=itortyp(itype(k))
6729       if (k.lt.nres-1) then
6730         itk1=itortyp(itype(k+1))
6731       else
6732         itk1=ntortyp+1
6733       endif
6734       itl=itortyp(itype(l))
6735       if (l.lt.nres-1) then
6736         itl1=itortyp(itype(l+1))
6737       else
6738         itl1=ntortyp+1
6739       endif
6740 cd      write (2,*) 'eello6_graph4:','i',i,' j',j,' k',k,' l',l
6741 cd      write (2,*) 'iti',iti,' itj',itj,' itj1',itj1,' itk',itk,
6742 cd     & ' itl',itl,' itl1',itl1
6743 #ifdef MOMENT
6744       if (imat.eq.1) then
6745         s1=dip(3,jj,i)*dip(3,kk,k)
6746       else
6747         s1=dip(2,jj,j)*dip(2,kk,l)
6748       endif
6749 #endif
6750       call matvec2(AECA(1,1,imat),Ub2(1,k),auxvec(1))
6751       s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
6752       if (j.eq.l+1) then
6753         call matvec2(ADtEA1(1,1,3-imat),b1(1,itj1),auxvec1(1))
6754         s3=-0.5d0*scalar2(b1(1,itj),auxvec1(1))
6755       else
6756         call matvec2(ADtEA1(1,1,3-imat),b1(1,itl1),auxvec1(1))
6757         s3=-0.5d0*scalar2(b1(1,itl),auxvec1(1))
6758       endif
6759       call transpose2(EUg(1,1,k),auxmat(1,1))
6760       call matmat2(AECA(1,1,imat),auxmat(1,1),pizda(1,1))
6761       vv(1)=pizda(1,1)-pizda(2,2)
6762       vv(2)=pizda(2,1)+pizda(1,2)
6763       s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
6764 cd      write (2,*) 'eello6_graph4:','s1',s1,' s2',s2,' s3',s3,' s4',s4
6765 #ifdef MOMENT
6766       eello6_graph4=-(s1+s2+s3+s4)
6767 #else
6768       eello6_graph4=-(s2+s3+s4)
6769 #endif
6770       if (.not. calc_grad) return
6771 C Derivatives in gamma(i-1)
6772       if (i.gt.1) then
6773 #ifdef MOMENT
6774         if (imat.eq.1) then
6775           s1=dipderg(2,jj,i)*dip(3,kk,k)
6776         else
6777           s1=dipderg(4,jj,j)*dip(2,kk,l)
6778         endif
6779 #endif
6780         s2=0.5d0*scalar2(Ub2der(1,i),auxvec(1))
6781         if (j.eq.l+1) then
6782           call matvec2(ADtEA1derg(1,1,1,3-imat),b1(1,itj1),auxvec1(1))
6783           s3=-0.5d0*scalar2(b1(1,itj),auxvec1(1))
6784         else
6785           call matvec2(ADtEA1derg(1,1,1,3-imat),b1(1,itl1),auxvec1(1))
6786           s3=-0.5d0*scalar2(b1(1,itl),auxvec1(1))
6787         endif
6788         s4=0.25d0*scalar2(vv(1),Dtobr2der(1,i))
6789         if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
6790 cd          write (2,*) 'turn6 derivatives'
6791 #ifdef MOMENT
6792           gel_loc_turn6(i-1)=gel_loc_turn6(i-1)-ekont*(s1+s2+s3+s4)
6793 #else
6794           gel_loc_turn6(i-1)=gel_loc_turn6(i-1)-ekont*(s2+s3+s4)
6795 #endif
6796         else
6797 #ifdef MOMENT
6798           g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s1+s2+s3+s4)
6799 #else
6800           g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s2+s3+s4)
6801 #endif
6802         endif
6803       endif
6804 C Derivatives in gamma(k-1)
6805 #ifdef MOMENT
6806       if (imat.eq.1) then
6807         s1=dip(3,jj,i)*dipderg(2,kk,k)
6808       else
6809         s1=dip(2,jj,j)*dipderg(4,kk,l)
6810       endif
6811 #endif
6812       call matvec2(AECA(1,1,imat),Ub2der(1,k),auxvec1(1))
6813       s2=0.5d0*scalar2(Ub2(1,i),auxvec1(1))
6814       if (j.eq.l+1) then
6815         call matvec2(ADtEA1derg(1,1,2,3-imat),b1(1,itj1),auxvec1(1))
6816         s3=-0.5d0*scalar2(b1(1,itj),auxvec1(1))
6817       else
6818         call matvec2(ADtEA1derg(1,1,2,3-imat),b1(1,itl1),auxvec1(1))
6819         s3=-0.5d0*scalar2(b1(1,itl),auxvec1(1))
6820       endif
6821       call transpose2(EUgder(1,1,k),auxmat1(1,1))
6822       call matmat2(AECA(1,1,imat),auxmat1(1,1),pizda(1,1))
6823       vv(1)=pizda(1,1)-pizda(2,2)
6824       vv(2)=pizda(2,1)+pizda(1,2)
6825       s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
6826       if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
6827 #ifdef MOMENT
6828         gel_loc_turn6(k-1)=gel_loc_turn6(k-1)-ekont*(s1+s2+s3+s4)
6829 #else
6830         gel_loc_turn6(k-1)=gel_loc_turn6(k-1)-ekont*(s2+s3+s4)
6831 #endif
6832       else
6833 #ifdef MOMENT
6834         g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s1+s2+s3+s4)
6835 #else
6836         g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s2+s3+s4)
6837 #endif
6838       endif
6839 C Derivatives in gamma(j-1) or gamma(l-1)
6840       if (l.eq.j+1 .and. l.gt.1) then
6841         call matvec2(AECAderg(1,1,imat),Ub2(1,k),auxvec(1))
6842         s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
6843         call matmat2(AECAderg(1,1,imat),auxmat(1,1),pizda(1,1))
6844         vv(1)=pizda(1,1)-pizda(2,2)
6845         vv(2)=pizda(2,1)+pizda(1,2)
6846         s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
6847         g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s4)
6848       else if (j.gt.1) then
6849         call matvec2(AECAderg(1,1,imat),Ub2(1,k),auxvec(1))
6850         s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
6851         call matmat2(AECAderg(1,1,imat),auxmat(1,1),pizda(1,1))
6852         vv(1)=pizda(1,1)-pizda(2,2)
6853         vv(2)=pizda(2,1)+pizda(1,2)
6854         s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
6855         if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
6856           gel_loc_turn6(j-1)=gel_loc_turn6(j-1)-ekont*(s2+s4)
6857         else
6858           g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*(s2+s4)
6859         endif
6860       endif
6861 C Cartesian derivatives.
6862       do iii=1,2
6863         do kkk=1,5
6864           do lll=1,3
6865 #ifdef MOMENT
6866             if (iii.eq.1) then
6867               if (imat.eq.1) then
6868                 s1=dipderx(lll,kkk,3,jj,i)*dip(3,kk,k)
6869               else
6870                 s1=dipderx(lll,kkk,2,jj,j)*dip(2,kk,l)
6871               endif
6872             else
6873               if (imat.eq.1) then
6874                 s1=dip(3,jj,i)*dipderx(lll,kkk,3,kk,k)
6875               else
6876                 s1=dip(2,jj,j)*dipderx(lll,kkk,2,kk,l)
6877               endif
6878             endif
6879 #endif
6880             call matvec2(AECAderx(1,1,lll,kkk,iii,imat),Ub2(1,k),
6881      &        auxvec(1))
6882             s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
6883             if (j.eq.l+1) then
6884               call matvec2(ADtEA1derx(1,1,lll,kkk,iii,3-imat),
6885      &          b1(1,itj1),auxvec(1))
6886               s3=-0.5d0*scalar2(b1(1,itj),auxvec(1))
6887             else
6888               call matvec2(ADtEA1derx(1,1,lll,kkk,iii,3-imat),
6889      &          b1(1,itl1),auxvec(1))
6890               s3=-0.5d0*scalar2(b1(1,itl),auxvec(1))
6891             endif
6892             call matmat2(AECAderx(1,1,lll,kkk,iii,imat),auxmat(1,1),
6893      &        pizda(1,1))
6894             vv(1)=pizda(1,1)-pizda(2,2)
6895             vv(2)=pizda(2,1)+pizda(1,2)
6896             s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
6897             if (swap) then
6898               if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
6899 #ifdef MOMENT
6900                 derx_turn(lll,kkk,3-iii)=derx_turn(lll,kkk,3-iii)
6901      &             -(s1+s2+s4)
6902 #else
6903                 derx_turn(lll,kkk,3-iii)=derx_turn(lll,kkk,3-iii)
6904      &             -(s2+s4)
6905 #endif
6906                 derx_turn(lll,kkk,iii)=derx_turn(lll,kkk,iii)-s3
6907               else
6908 #ifdef MOMENT
6909                 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-(s1+s2+s4)
6910 #else
6911                 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-(s2+s4)
6912 #endif
6913                 derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
6914               endif
6915             else
6916 #ifdef MOMENT
6917               derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
6918 #else
6919               derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
6920 #endif
6921               if (l.eq.j+1) then
6922                 derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
6923               else 
6924                 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
6925               endif
6926             endif 
6927           enddo
6928         enddo
6929       enddo
6930       return
6931       end
6932 c----------------------------------------------------------------------------
6933       double precision function eello_turn6(i,jj,kk)
6934       implicit real*8 (a-h,o-z)
6935       include 'DIMENSIONS'
6936       include 'sizesclu.dat'
6937       include 'COMMON.IOUNITS'
6938       include 'COMMON.CHAIN'
6939       include 'COMMON.DERIV'
6940       include 'COMMON.INTERACT'
6941       include 'COMMON.CONTACTS'
6942       include 'COMMON.TORSION'
6943       include 'COMMON.VAR'
6944       include 'COMMON.GEO'
6945       double precision vtemp1(2),vtemp2(2),vtemp3(2),vtemp4(2),
6946      &  atemp(2,2),auxmat(2,2),achuj_temp(2,2),gtemp(2,2),gvec(2),
6947      &  ggg1(3),ggg2(3)
6948       double precision vtemp1d(2),vtemp2d(2),vtemp3d(2),vtemp4d(2),
6949      &  atempd(2,2),auxmatd(2,2),achuj_tempd(2,2),gtempd(2,2),gvecd(2)
6950 C 4/7/01 AL Components s1, s8, and s13 were removed, because they pertain to
6951 C           the respective energy moment and not to the cluster cumulant.
6952       eello_turn6=0.0d0
6953       j=i+4
6954       k=i+1
6955       l=i+3
6956       iti=itortyp(itype(i))
6957       itk=itortyp(itype(k))
6958       itk1=itortyp(itype(k+1))
6959       itl=itortyp(itype(l))
6960       itj=itortyp(itype(j))
6961 cd      write (2,*) 'itk',itk,' itk1',itk1,' itl',itl,' itj',itj
6962 cd      write (2,*) 'i',i,' k',k,' j',j,' l',l
6963 cd      if (i.ne.1 .or. j.ne.3 .or. k.ne.2 .or. l.ne.4) then
6964 cd        eello6=0.0d0
6965 cd        return
6966 cd      endif
6967 cd      write (iout,*)
6968 cd     &   'EELLO6: Contacts have occurred for peptide groups',i,j,
6969 cd     &   ' and',k,l
6970 cd      call checkint_turn6(i,jj,kk,eel_turn6_num)
6971       do iii=1,2
6972         do kkk=1,5
6973           do lll=1,3
6974             derx_turn(lll,kkk,iii)=0.0d0
6975           enddo
6976         enddo
6977       enddo
6978 cd      eij=1.0d0
6979 cd      ekl=1.0d0
6980 cd      ekont=1.0d0
6981       eello6_5=eello6_graph4(l,k,j,i,kk,jj,2,.true.)
6982 cd      eello6_5=0.0d0
6983 cd      write (2,*) 'eello6_5',eello6_5
6984 #ifdef MOMENT
6985       call transpose2(AEA(1,1,1),auxmat(1,1))
6986       call matmat2(EUg(1,1,i+1),auxmat(1,1),auxmat(1,1))
6987       ss1=scalar2(Ub2(1,i+2),b1(1,itl))
6988       s1 = (auxmat(1,1)+auxmat(2,2))*ss1
6989 #else
6990       s1 = 0.0d0
6991 #endif
6992       call matvec2(EUg(1,1,i+2),b1(1,itl),vtemp1(1))
6993       call matvec2(AEA(1,1,1),vtemp1(1),vtemp1(1))
6994       s2 = scalar2(b1(1,itk),vtemp1(1))
6995 #ifdef MOMENT
6996       call transpose2(AEA(1,1,2),atemp(1,1))
6997       call matmat2(atemp(1,1),EUg(1,1,i+4),atemp(1,1))
6998       call matvec2(Ug2(1,1,i+2),dd(1,1,itk1),vtemp2(1))
6999       s8 = -(atemp(1,1)+atemp(2,2))*scalar2(cc(1,1,itl),vtemp2(1))
7000 #else
7001       s8=0.0d0
7002 #endif
7003       call matmat2(EUg(1,1,i+3),AEA(1,1,2),auxmat(1,1))
7004       call matvec2(auxmat(1,1),Ub2(1,i+4),vtemp3(1))
7005       s12 = scalar2(Ub2(1,i+2),vtemp3(1))
7006 #ifdef MOMENT
7007       call transpose2(a_chuj(1,1,kk,i+1),achuj_temp(1,1))
7008       call matmat2(achuj_temp(1,1),EUg(1,1,i+2),gtemp(1,1))
7009       call matmat2(gtemp(1,1),EUg(1,1,i+3),gtemp(1,1)) 
7010       call matvec2(a_chuj(1,1,jj,i),Ub2(1,i+4),vtemp4(1)) 
7011       ss13 = scalar2(b1(1,itk),vtemp4(1))
7012       s13 = (gtemp(1,1)+gtemp(2,2))*ss13
7013 #else
7014       s13=0.0d0
7015 #endif
7016 c      write (2,*) 's1,s2,s8,s12,s13',s1,s2,s8,s12,s13
7017 c      s1=0.0d0
7018 c      s2=0.0d0
7019 c      s8=0.0d0
7020 c      s12=0.0d0
7021 c      s13=0.0d0
7022       eel_turn6 = eello6_5 - 0.5d0*(s1+s2+s12+s8+s13)
7023       if (calc_grad) then
7024 C Derivatives in gamma(i+2)
7025 #ifdef MOMENT
7026       call transpose2(AEA(1,1,1),auxmatd(1,1))
7027       call matmat2(EUgder(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
7028       s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
7029       call transpose2(AEAderg(1,1,2),atempd(1,1))
7030       call matmat2(atempd(1,1),EUg(1,1,i+4),atempd(1,1))
7031       s8d = -(atempd(1,1)+atempd(2,2))*scalar2(cc(1,1,itl),vtemp2(1))
7032 #else
7033       s8d=0.0d0
7034 #endif
7035       call matmat2(EUg(1,1,i+3),AEAderg(1,1,2),auxmatd(1,1))
7036       call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
7037       s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
7038 c      s1d=0.0d0
7039 c      s2d=0.0d0
7040 c      s8d=0.0d0
7041 c      s12d=0.0d0
7042 c      s13d=0.0d0
7043       gel_loc_turn6(i)=gel_loc_turn6(i)-0.5d0*ekont*(s1d+s8d+s12d)
7044 C Derivatives in gamma(i+3)
7045 #ifdef MOMENT
7046       call transpose2(AEA(1,1,1),auxmatd(1,1))
7047       call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
7048       ss1d=scalar2(Ub2der(1,i+2),b1(1,itl))
7049       s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1d
7050 #else
7051       s1d=0.0d0
7052 #endif
7053       call matvec2(EUgder(1,1,i+2),b1(1,itl),vtemp1d(1))
7054       call matvec2(AEA(1,1,1),vtemp1d(1),vtemp1d(1))
7055       s2d = scalar2(b1(1,itk),vtemp1d(1))
7056 #ifdef MOMENT
7057       call matvec2(Ug2der(1,1,i+2),dd(1,1,itk1),vtemp2d(1))
7058       s8d = -(atemp(1,1)+atemp(2,2))*scalar2(cc(1,1,itl),vtemp2d(1))
7059 #endif
7060       s12d = scalar2(Ub2der(1,i+2),vtemp3(1))
7061 #ifdef MOMENT
7062       call matmat2(achuj_temp(1,1),EUgder(1,1,i+2),gtempd(1,1))
7063       call matmat2(gtempd(1,1),EUg(1,1,i+3),gtempd(1,1)) 
7064       s13d = (gtempd(1,1)+gtempd(2,2))*ss13
7065 #else
7066       s13d=0.0d0
7067 #endif
7068 c      s1d=0.0d0
7069 c      s2d=0.0d0
7070 c      s8d=0.0d0
7071 c      s12d=0.0d0
7072 c      s13d=0.0d0
7073 #ifdef MOMENT
7074       gel_loc_turn6(i+1)=gel_loc_turn6(i+1)
7075      &               -0.5d0*ekont*(s1d+s2d+s8d+s12d+s13d)
7076 #else
7077       gel_loc_turn6(i+1)=gel_loc_turn6(i+1)
7078      &               -0.5d0*ekont*(s2d+s12d)
7079 #endif
7080 C Derivatives in gamma(i+4)
7081       call matmat2(EUgder(1,1,i+3),AEA(1,1,2),auxmatd(1,1))
7082       call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
7083       s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
7084 #ifdef MOMENT
7085       call matmat2(achuj_temp(1,1),EUg(1,1,i+2),gtempd(1,1))
7086       call matmat2(gtempd(1,1),EUgder(1,1,i+3),gtempd(1,1)) 
7087       s13d = (gtempd(1,1)+gtempd(2,2))*ss13
7088 #else
7089       s13d = 0.0d0
7090 #endif
7091 c      s1d=0.0d0
7092 c      s2d=0.0d0
7093 c      s8d=0.0d0
7094 C      s12d=0.0d0
7095 c      s13d=0.0d0
7096 #ifdef MOMENT
7097       gel_loc_turn6(i+2)=gel_loc_turn6(i+2)-0.5d0*ekont*(s12d+s13d)
7098 #else
7099       gel_loc_turn6(i+2)=gel_loc_turn6(i+2)-0.5d0*ekont*(s12d)
7100 #endif
7101 C Derivatives in gamma(i+5)
7102 #ifdef MOMENT
7103       call transpose2(AEAderg(1,1,1),auxmatd(1,1))
7104       call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
7105       s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
7106 #else
7107       s1d = 0.0d0
7108 #endif
7109       call matvec2(EUg(1,1,i+2),b1(1,itl),vtemp1d(1))
7110       call matvec2(AEAderg(1,1,1),vtemp1d(1),vtemp1d(1))
7111       s2d = scalar2(b1(1,itk),vtemp1d(1))
7112 #ifdef MOMENT
7113       call transpose2(AEA(1,1,2),atempd(1,1))
7114       call matmat2(atempd(1,1),EUgder(1,1,i+4),atempd(1,1))
7115       s8d = -(atempd(1,1)+atempd(2,2))*scalar2(cc(1,1,itl),vtemp2(1))
7116 #else
7117       s8d = 0.0d0
7118 #endif
7119       call matvec2(auxmat(1,1),Ub2der(1,i+4),vtemp3d(1))
7120       s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
7121 #ifdef MOMENT
7122       call matvec2(a_chuj(1,1,jj,i),Ub2der(1,i+4),vtemp4d(1)) 
7123       ss13d = scalar2(b1(1,itk),vtemp4d(1))
7124       s13d = (gtemp(1,1)+gtemp(2,2))*ss13d
7125 #else
7126       s13d = 0.0d0
7127 #endif
7128 c      s1d=0.0d0
7129 c      s2d=0.0d0
7130 c      s8d=0.0d0
7131 c      s12d=0.0d0
7132 c      s13d=0.0d0
7133 #ifdef MOMENT
7134       gel_loc_turn6(i+3)=gel_loc_turn6(i+3)
7135      &               -0.5d0*ekont*(s1d+s2d+s8d+s12d+s13d)
7136 #else
7137       gel_loc_turn6(i+3)=gel_loc_turn6(i+3)
7138      &               -0.5d0*ekont*(s2d+s12d)
7139 #endif
7140 C Cartesian derivatives
7141       do iii=1,2
7142         do kkk=1,5
7143           do lll=1,3
7144 #ifdef MOMENT
7145             call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmatd(1,1))
7146             call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
7147             s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
7148 #else
7149             s1d = 0.0d0
7150 #endif
7151             call matvec2(EUg(1,1,i+2),b1(1,itl),vtemp1(1))
7152             call matvec2(AEAderx(1,1,lll,kkk,iii,1),vtemp1(1),
7153      &          vtemp1d(1))
7154             s2d = scalar2(b1(1,itk),vtemp1d(1))
7155 #ifdef MOMENT
7156             call transpose2(AEAderx(1,1,lll,kkk,iii,2),atempd(1,1))
7157             call matmat2(atempd(1,1),EUg(1,1,i+4),atempd(1,1))
7158             s8d = -(atempd(1,1)+atempd(2,2))*
7159      &           scalar2(cc(1,1,itl),vtemp2(1))
7160 #else
7161             s8d = 0.0d0
7162 #endif
7163             call matmat2(EUg(1,1,i+3),AEAderx(1,1,lll,kkk,iii,2),
7164      &           auxmatd(1,1))
7165             call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
7166             s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
7167 c      s1d=0.0d0
7168 c      s2d=0.0d0
7169 c      s8d=0.0d0
7170 c      s12d=0.0d0
7171 c      s13d=0.0d0
7172 #ifdef MOMENT
7173             derx_turn(lll,kkk,iii) = derx_turn(lll,kkk,iii) 
7174      &        - 0.5d0*(s1d+s2d)
7175 #else
7176             derx_turn(lll,kkk,iii) = derx_turn(lll,kkk,iii) 
7177      &        - 0.5d0*s2d
7178 #endif
7179 #ifdef MOMENT
7180             derx_turn(lll,kkk,3-iii) = derx_turn(lll,kkk,3-iii) 
7181      &        - 0.5d0*(s8d+s12d)
7182 #else
7183             derx_turn(lll,kkk,3-iii) = derx_turn(lll,kkk,3-iii) 
7184      &        - 0.5d0*s12d
7185 #endif
7186           enddo
7187         enddo
7188       enddo
7189 #ifdef MOMENT
7190       do kkk=1,5
7191         do lll=1,3
7192           call transpose2(a_chuj_der(1,1,lll,kkk,kk,i+1),
7193      &      achuj_tempd(1,1))
7194           call matmat2(achuj_tempd(1,1),EUg(1,1,i+2),gtempd(1,1))
7195           call matmat2(gtempd(1,1),EUg(1,1,i+3),gtempd(1,1)) 
7196           s13d=(gtempd(1,1)+gtempd(2,2))*ss13
7197           derx_turn(lll,kkk,2) = derx_turn(lll,kkk,2)-0.5d0*s13d
7198           call matvec2(a_chuj_der(1,1,lll,kkk,jj,i),Ub2(1,i+4),
7199      &      vtemp4d(1)) 
7200           ss13d = scalar2(b1(1,itk),vtemp4d(1))
7201           s13d = (gtemp(1,1)+gtemp(2,2))*ss13d
7202           derx_turn(lll,kkk,1) = derx_turn(lll,kkk,1)-0.5d0*s13d
7203         enddo
7204       enddo
7205 #endif
7206 cd      write(iout,*) 'eel6_turn6',eel_turn6,' eel_turn6_num',
7207 cd     &  16*eel_turn6_num
7208 cd      goto 1112
7209       if (j.lt.nres-1) then
7210         j1=j+1
7211         j2=j-1
7212       else
7213         j1=j-1
7214         j2=j-2
7215       endif
7216       if (l.lt.nres-1) then
7217         l1=l+1
7218         l2=l-1
7219       else
7220         l1=l-1
7221         l2=l-2
7222       endif
7223       do ll=1,3
7224         ggg1(ll)=eel_turn6*g_contij(ll,1)
7225         ggg2(ll)=eel_turn6*g_contij(ll,2)
7226         ghalf=0.5d0*ggg1(ll)
7227 cd        ghalf=0.0d0
7228         gcorr6_turn(ll,i)=gcorr6_turn(ll,i)+ghalf
7229      &    +ekont*derx_turn(ll,2,1)
7230         gcorr6_turn(ll,i+1)=gcorr6_turn(ll,i+1)+ekont*derx_turn(ll,3,1)
7231         gcorr6_turn(ll,j)=gcorr6_turn(ll,j)+ghalf
7232      &    +ekont*derx_turn(ll,4,1)
7233         gcorr6_turn(ll,j1)=gcorr6_turn(ll,j1)+ekont*derx_turn(ll,5,1)
7234         ghalf=0.5d0*ggg2(ll)
7235 cd        ghalf=0.0d0
7236         gcorr6_turn(ll,k)=gcorr6_turn(ll,k)+ghalf
7237      &    +ekont*derx_turn(ll,2,2)
7238         gcorr6_turn(ll,k+1)=gcorr6_turn(ll,k+1)+ekont*derx_turn(ll,3,2)
7239         gcorr6_turn(ll,l)=gcorr6_turn(ll,l)+ghalf
7240      &    +ekont*derx_turn(ll,4,2)
7241         gcorr6_turn(ll,l1)=gcorr6_turn(ll,l1)+ekont*derx_turn(ll,5,2)
7242       enddo
7243 cd      goto 1112
7244       do m=i+1,j-1
7245         do ll=1,3
7246           gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ggg1(ll)
7247         enddo
7248       enddo
7249       do m=k+1,l-1
7250         do ll=1,3
7251           gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ggg2(ll)
7252         enddo
7253       enddo
7254 1112  continue
7255       do m=i+2,j2
7256         do ll=1,3
7257           gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ekont*derx_turn(ll,1,1)
7258         enddo
7259       enddo
7260       do m=k+2,l2
7261         do ll=1,3
7262           gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ekont*derx_turn(ll,1,2)
7263         enddo
7264       enddo 
7265 cd      do iii=1,nres-3
7266 cd        write (2,*) iii,g_corr6_loc(iii)
7267 cd      enddo
7268       endif
7269       eello_turn6=ekont*eel_turn6
7270 cd      write (2,*) 'ekont',ekont
7271 cd      write (2,*) 'eel_turn6',ekont*eel_turn6
7272       return
7273       end
7274 crc-------------------------------------------------
7275       SUBROUTINE MATVEC2(A1,V1,V2)
7276       implicit real*8 (a-h,o-z)
7277       include 'DIMENSIONS'
7278       DIMENSION A1(2,2),V1(2),V2(2)
7279 c      DO 1 I=1,2
7280 c        VI=0.0
7281 c        DO 3 K=1,2
7282 c    3     VI=VI+A1(I,K)*V1(K)
7283 c        Vaux(I)=VI
7284 c    1 CONTINUE
7285
7286       vaux1=a1(1,1)*v1(1)+a1(1,2)*v1(2)
7287       vaux2=a1(2,1)*v1(1)+a1(2,2)*v1(2)
7288
7289       v2(1)=vaux1
7290       v2(2)=vaux2
7291       END
7292 C---------------------------------------
7293       SUBROUTINE MATMAT2(A1,A2,A3)
7294       implicit real*8 (a-h,o-z)
7295       include 'DIMENSIONS'
7296       DIMENSION A1(2,2),A2(2,2),A3(2,2)
7297 c      DIMENSION AI3(2,2)
7298 c        DO  J=1,2
7299 c          A3IJ=0.0
7300 c          DO K=1,2
7301 c           A3IJ=A3IJ+A1(I,K)*A2(K,J)
7302 c          enddo
7303 c          A3(I,J)=A3IJ
7304 c       enddo
7305 c      enddo
7306
7307       ai3_11=a1(1,1)*a2(1,1)+a1(1,2)*a2(2,1)
7308       ai3_12=a1(1,1)*a2(1,2)+a1(1,2)*a2(2,2)
7309       ai3_21=a1(2,1)*a2(1,1)+a1(2,2)*a2(2,1)
7310       ai3_22=a1(2,1)*a2(1,2)+a1(2,2)*a2(2,2)
7311
7312       A3(1,1)=AI3_11
7313       A3(2,1)=AI3_21
7314       A3(1,2)=AI3_12
7315       A3(2,2)=AI3_22
7316       END
7317
7318 c-------------------------------------------------------------------------
7319       double precision function scalar2(u,v)
7320       implicit none
7321       double precision u(2),v(2)
7322       double precision sc
7323       integer i
7324       scalar2=u(1)*v(1)+u(2)*v(2)
7325       return
7326       end
7327
7328 C-----------------------------------------------------------------------------
7329
7330       subroutine transpose2(a,at)
7331       implicit none
7332       double precision a(2,2),at(2,2)
7333       at(1,1)=a(1,1)
7334       at(1,2)=a(2,1)
7335       at(2,1)=a(1,2)
7336       at(2,2)=a(2,2)
7337       return
7338       end
7339 c--------------------------------------------------------------------------
7340       subroutine transpose(n,a,at)
7341       implicit none
7342       integer n,i,j
7343       double precision a(n,n),at(n,n)
7344       do i=1,n
7345         do j=1,n
7346           at(j,i)=a(i,j)
7347         enddo
7348       enddo
7349       return
7350       end
7351 C---------------------------------------------------------------------------
7352       subroutine prodmat3(a1,a2,kk,transp,prod)
7353       implicit none
7354       integer i,j
7355       double precision a1(2,2),a2(2,2),a2t(2,2),kk(2,2),prod(2,2)
7356       logical transp
7357 crc      double precision auxmat(2,2),prod_(2,2)
7358
7359       if (transp) then
7360 crc        call transpose2(kk(1,1),auxmat(1,1))
7361 crc        call matmat2(a1(1,1),auxmat(1,1),auxmat(1,1))
7362 crc        call matmat2(auxmat(1,1),a2(1,1),prod_(1,1)) 
7363         
7364            prod(1,1)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(1,2))*a2(1,1)
7365      & +(a1(1,1)*kk(2,1)+a1(1,2)*kk(2,2))*a2(2,1)
7366            prod(1,2)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(1,2))*a2(1,2)
7367      & +(a1(1,1)*kk(2,1)+a1(1,2)*kk(2,2))*a2(2,2)
7368            prod(2,1)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(1,2))*a2(1,1)
7369      & +(a1(2,1)*kk(2,1)+a1(2,2)*kk(2,2))*a2(2,1)
7370            prod(2,2)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(1,2))*a2(1,2)
7371      & +(a1(2,1)*kk(2,1)+a1(2,2)*kk(2,2))*a2(2,2)
7372
7373       else
7374 crc        call matmat2(a1(1,1),kk(1,1),auxmat(1,1))
7375 crc        call matmat2(auxmat(1,1),a2(1,1),prod_(1,1))
7376
7377            prod(1,1)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(2,1))*a2(1,1)
7378      &  +(a1(1,1)*kk(1,2)+a1(1,2)*kk(2,2))*a2(2,1)
7379            prod(1,2)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(2,1))*a2(1,2)
7380      &  +(a1(1,1)*kk(1,2)+a1(1,2)*kk(2,2))*a2(2,2)
7381            prod(2,1)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(2,1))*a2(1,1)
7382      &  +(a1(2,1)*kk(1,2)+a1(2,2)*kk(2,2))*a2(2,1)
7383            prod(2,2)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(2,1))*a2(1,2)
7384      &  +(a1(2,1)*kk(1,2)+a1(2,2)*kk(2,2))*a2(2,2)
7385
7386       endif
7387 c      call transpose2(a2(1,1),a2t(1,1))
7388
7389 crc      print *,transp
7390 crc      print *,((prod_(i,j),i=1,2),j=1,2)
7391 crc      print *,((prod(i,j),i=1,2),j=1,2)
7392
7393       return
7394       end
7395 C-----------------------------------------------------------------------------
7396       double precision function scalar(u,v)
7397       implicit none
7398       double precision u(3),v(3)
7399       double precision sc
7400       integer i
7401       sc=0.0d0
7402       do i=1,3
7403         sc=sc+u(i)*v(i)
7404       enddo
7405       scalar=sc
7406       return
7407       end
7408