1 subroutine elecont(lprint,ncont,icont)
2 implicit real*8 (a-h,o-z)
4 include 'COMMON.IOUNITS'
6 include 'COMMON.INTERACT'
8 include 'COMMON.FFIELD'
11 double precision elpp_6(2,2),elpp_3(2,2),ael6_(2,2),ael3_(2,2)
12 double precision app_(2,2),bpp_(2,2),rpp_(2,2)
13 integer ncont,icont(2,maxcont)
14 double precision econt(maxcont)
16 * Load the constants of peptide bond - peptide bond interactions.
17 * Type 1 - ordinary peptide bond, type 2 - alkylated peptide bond (e.g.
18 * proline) - determined by averaging ECEPP energy.
22 c data epp / 0.3045d0, 0.3649d0, 0.3649d0, 0.5743d0/
23 data rpp_ / 4.5088d0, 4.5395d0, 4.5395d0, 4.4846d0/
24 data elpp_6 /-0.2379d0,-0.2056d0,-0.2056d0,-0.0610d0/
25 data elpp_3 / 0.0503d0, 0.0000d0, 0.0000d0, 0.0692d0/
26 data elcutoff /-0.3d0/,elecutoff_14 /-0.5d0/
27 if (lprint) write (iout,'(a)')
28 & "Constants of electrostatic interaction energy expression."
32 app_(i,j)=epp(i,j)*rri*rri
33 bpp_(i,j)=-2.0*epp(i,j)*rri
34 ael6_(i,j)=elpp_6(i,j)*4.2**6
35 ael3_(i,j)=elpp_3(i,j)*4.2**3
37 & write (iout,'(2i2,4e15.4)') i,j,app_(i,j),bpp_(i,j),ael6_(i,j),
58 if (j.eq.i+2 .and. itelj.eq.2) iteli=2
59 if (iteli.eq.2 .and. itelj.eq.2) goto 4
62 ael6_i=ael6_(iteli,itelj)
63 ael3_i=ael3_(iteli,itelj)
67 xj=c(1,j)+0.5*dxj-xmedi
68 yj=c(2,j)+0.5*dyj-ymedi
69 zj=c(3,j)+0.5*dzj-zmedi
70 rrmij=1.0/(xj*xj+yj*yj+zj*zj)
75 cosa=(dxi*dxj+dyi*dyj+dzi*dzj)*vblinv2
76 cosb=(xj*dxi+yj*dyi+zj*dzi)*vrmij
77 cosg=(xj*dxj+yj*dyj+zj*dzj)*vrmij
78 fac=cosa-3.0*cosb*cosg
84 el1=fac3*(4.0+fac*fac-3.0*(cosb*cosb+cosg*cosg))
87 if (j.gt.i+2 .and. eesij.le.elcutoff .or.
88 & j.eq.i+2 .and. eesij.le.elecutoff_14) then
99 write (iout,*) 'Total average electrostatic energy: ',ees
100 write (iout,*) 'VDW energy between peptide-group centers: ',evdw
102 write (iout,*) 'Electrostatic contacts before pruning: '
108 write (iout,'(i3,2x,a,i4,2x,a,i4,f10.5)')
109 & i,restyp(it1),i1,restyp(it2),i2,econt(i)
112 c For given residues keep only the contacts with the greatest energy.
114 do while (i.lt.ncont)
120 do while (j.lt.ncont)
122 if (ic1.eq.icont(1,j).and.iabs(icont(2,j)-ic2).le.2 .or.
123 & ic2.eq.icont(2,j).and.iabs(icont(1,j)-ic1).le.2) then
124 c write (iout,*) "i",i," j",j," ic1",ic1," ic2",ic2,
125 c & " jc1",icont(1,j)," jc2",icont(2,j)," ncont",ncont
126 if (econt(j).lt.ene .and. icont(2,j).ne.icont(1,j)+2) then
127 if (ic1.eq.icont(1,j)) then
129 if (k.ne.i .and. k.ne.j .and. icont(2,k).eq.icont(2,j)
130 & .and. iabs(icont(1,k)-ic1).le.2 .and.
131 & econt(k).lt.econt(j) ) goto 21
133 else if (ic2.eq.icont(2,j) ) then
135 if (k.ne.i .and. k.ne.j .and. icont(1,k).eq.icont(1,j)
136 & .and. iabs(icont(2,k)-ic2).le.2 .and.
137 & econt(k).lt.econt(j) ) goto 21
142 icont(1,k-1)=icont(1,k)
143 icont(2,k-1)=icont(2,k)
148 c write (iout,*) "ncont",ncont
150 c write (iout,*) icont(1,k),icont(2,k)
153 else if (econt(j).gt.ene .and. ic2.ne.ic1+2)
155 if (ic1.eq.icont(1,j)) then
157 if (k.ne.i .and. k.ne.j .and. icont(2,k).eq.ic2
158 & .and. iabs(icont(1,k)-icont(1,j)).le.2 .and.
159 & econt(k).lt.econt(i) ) goto 21
161 else if (ic2.eq.icont(2,j) ) then
163 if (k.ne.i .and. k.ne.j .and. icont(1,k).eq.ic1
164 & .and. iabs(icont(2,k)-icont(2,j)).le.2 .and.
165 & econt(k).lt.econt(i) ) goto 21
170 icont(1,k-1)=icont(1,k)
171 icont(2,k-1)=icont(2,k)
175 c write (iout,*) "ncont",ncont
177 c write (iout,*) icont(1,k),icont(2,k)
188 write (iout,*) 'Electrostatic contacts after pruning: '
194 write (iout,'(i3,2x,a,i4,2x,a,i4,f10.5)')
195 & i,restyp(it1),i1,restyp(it2),i2,econt(i)
200 c--------------------------------------------
201 subroutine secondary2(lprint)
202 implicit real*8 (a-h,o-z)
204 include 'COMMON.CHAIN'
205 include 'COMMON.IOUNITS'
206 include 'COMMON.DISTFIT'
209 include 'COMMON.CONTROL'
210 integer ncont,icont(2,maxcont),isec(maxres,4),nsec(maxres)
211 logical lprint,not_done,freeres
212 double precision p1,p2
215 if(.not.dccart) call chainbuild
216 cd call write_pdb(99,'sec structure',0d0)
226 call elecont(lprint,ncont,icont)
228 c finding parallel beta
229 cd write (iout,*) '------- looking for parallel beta -----------'
235 if(j1-i1.gt.5 .and. freeres(i1,j1,nsec,isec)) then
238 cd write (iout,*) i1,j1
244 if (i1.eq.icont(1,j) .and. j1.eq.icont(2,j) .and.
245 & freeres(i1,j1,nsec,isec)) goto 5
249 cd write (iout,*) i1,j1,not_done
253 if (i1-ii1.gt.1) then
257 if(lprint)write(iout,'(a,i3,4i4)')'parallel beta',
258 & nbeta,ii1,i1,jj1,j1
261 bfrag(1,nbfrag)=ii1+1
263 bfrag(3,nbfrag)=jj1+1
264 bfrag(4,nbfrag)=min0(j1+1,nres)
268 isec(ij,nsec(ij))=nbeta
272 isec(ij,nsec(ij))=nbeta
278 write(12,'(a18,i1,a9,i3,a2,i3,a1)')
279 & "DefPropRes 'strand",nstrand,
280 & "' 'num = ",ii1-1,"..",i1-1,"'"
282 write(12,'(a18,i2,a9,i3,a2,i3,a1)')
283 & "DefPropRes 'strand",nstrand,
284 & "' 'num = ",ii1-1,"..",i1-1,"'"
288 write(12,'(a18,i1,a9,i3,a2,i3,a1)')
289 & "DefPropRes 'strand",nstrand,
290 & "' 'num = ",jj1-1,"..",j1-1,"'"
292 write(12,'(a18,i2,a9,i3,a2,i3,a1)')
293 & "DefPropRes 'strand",nstrand,
294 & "' 'num = ",jj1-1,"..",j1-1,"'"
297 & "SetNeigh",ii1-1,i1-1,jj1-1,j1-1
303 c finding alpha or 310 helix
311 if (j1+2.le.nres) p2=phi(j1+2)*rad2deg
315 & ((p1.ge.10.and.p1.le.80).or.i1.le.2).and.
316 & ((p2.ge.10.and.p2.le.80).or.j1.le.2.or.j1.ge.nres-3) )then
317 cd if (j1.eq.i1+3) write (iout,*) "found 1-4 ",i1,j1,p1,p2
318 co if (j1.eq.i1+4) write (iout,*) "found 1-5 ",i1,j1,p1,p2
321 if (nsec(ii1).eq.0) then
330 if (i1.eq.icont(1,j) .and. j1.eq.icont(2,j)) goto 10
336 if (p1.lt.10.or.p1.gt.80.or.p2.lt.10.or.p2.gt.80)
338 cd write (iout,*) i1,j1,not_done,p1,p2
341 if (j1-ii1.gt.5) then
343 cd write (iout,*)'helix',nhelix,ii1,j1
353 write (iout,'(a,i3,2i4)') "Helix",nhelix,ii1-1,j1-1
354 if (nhelix.le.9) then
355 write(12,'(a17,i1,a9,i3,a2,i3,a1)')
356 & "DefPropRes 'helix",nhelix,
357 & "' 'num = ",ii1-1,"..",j1-2,"'"
359 write(12,'(a17,i2,a9,i3,a2,i3,a1)')
360 & "DefPropRes 'helix",nhelix,
361 & "' 'num = ",ii1-1,"..",j1-2,"'"
368 if (nhelix.gt.0.and.lprint) then
369 write(12,'(a26,$)') "DefPropRes 'helix' 'helix1"
371 if (nhelix.le.9) then
372 write(12,'(a8,i1,$)') " | helix",i
374 write(12,'(a8,i2,$)') " | helix",i
381 c finding antiparallel beta
382 cd write (iout,*) '--------- looking for antiparallel beta ---------'
387 if (freeres(i1,j1,nsec,isec)) then
390 cd write (iout,*) i1,j1
397 if (i1.eq.icont(1,j).and.j1.eq.icont(2,j) .and.
398 & freeres(i1,j1,nsec,isec)) goto 6
402 cd write (iout,*) i1,j1,not_done
406 if (i1-ii1.gt.1) then
410 bfrag(2,nbfrag)=min0(i1+1,nres)
411 bfrag(3,nbfrag)=min0(jj1+1,nres)
418 if (nsec(ij).le.2) then
419 isec(ij,nsec(ij))=nbeta
425 if (nsec(ij).le.2 .and. nsec(ij).gt.0) then
426 isec(ij,nsec(ij))=nbeta
432 write (iout,'(a,i3,4i4)')'antiparallel beta',
433 & nbeta,ii1-1,i1,jj1,j1-1
435 if (nstrand.le.9) then
436 write(12,'(a18,i1,a9,i3,a2,i3,a1)')
437 & "DefPropRes 'strand",nstrand,
438 & "' 'num = ",ii1-2,"..",i1-1,"'"
440 write(12,'(a18,i2,a9,i3,a2,i3,a1)')
441 & "DefPropRes 'strand",nstrand,
442 & "' 'num = ",ii1-2,"..",i1-1,"'"
445 if (nstrand.le.9) then
446 write(12,'(a18,i1,a9,i3,a2,i3,a1)')
447 & "DefPropRes 'strand",nstrand,
448 & "' 'num = ",j1-2,"..",jj1-1,"'"
450 write(12,'(a18,i2,a9,i3,a2,i3,a1)')
451 & "DefPropRes 'strand",nstrand,
452 & "' 'num = ",j1-2,"..",jj1-1,"'"
455 & "SetNeigh",ii1-2,i1-1,jj1-1,j1-2
461 if (nstrand.gt.0.and.lprint) then
462 write(12,'(a27,$)') "DefPropRes 'sheet' 'strand1"
465 write(12,'(a9,i1,$)') " | strand",i
467 write(12,'(a9,i2,$)') " | strand",i
476 write(12,'(a37)') "DefPropRes 'coil' '! (helix | sheet)'"
477 write(12,'(a20)') "XMacStand ribbon.mac"
480 write(iout,*) 'UNRES seq:'
482 write(iout,*) 'beta ',(bfrag(i,j),i=1,4)
486 write(iout,*) 'helix ',(hfrag(i,j),i=1,2)
492 c-------------------------------------------------
493 logical function freeres(i,j,nsec,isec)
494 implicit real*8 (a-h,o-z)
496 integer isec(maxres,4),nsec(maxres)
499 if (nsec(i).lt.0.or.nsec(j).lt.0) return
500 if (nsec(i).gt.1.or.nsec(j).gt.1) return
503 if (isec(i,k).eq.isec(j,l)) return