1 subroutine define_fragments
2 implicit real*8 (a-h,o-z)
4 include 'DIMENSIONS.ZSCOPT'
5 include 'DIMENSIONS.FREE'
6 include 'DIMENSIONS.COMPAR'
7 include 'COMMON.IOUNITS'
10 include 'COMMON.SBRIDGE'
11 include 'COMMON.CONTROL'
12 include 'COMMON.COMPAR'
13 include 'COMMON.CHAIN'
14 include 'COMMON.HEADER'
16 include 'COMMON.CONTACTS'
17 include 'COMMON.PEPTCONT'
18 include 'COMMON.INTERACT'
19 include 'COMMON.NAMES'
20 integer nstrand,istrand(2,maxres/2)
21 integer nhairp,ihairp(2,maxres/5)
22 character*16 strstr(4) /'helix','hairpin','strand','strand pair'/
23 write (iout,*) 'NC_FRAC_HEL',ncfrac_hel,' NC_REQ_HEL',ncreq_hel,
24 & 'NC_FRAC_BET',ncfrac_bet,' NC_REQ_BET',ncreq_bet,
25 & 'NC_FRAC_PAIR',ncfrac_pair,' NC_REQ_PAIR',ncreq_pair,
26 & ' RMS_PAIR',irms_pair,' SPLIT_BET',isplit_bet
27 write (iout,*) 'NSHIFT_HEL',nshift_hel,' NSHIFT_BET',nshift_bet,
28 & ' NSHIFT_STRAND',nshift_strand,' NSHIFT_PAIR',nshift_pair
29 write (iout,*) 'ANGCUT_HEL',angcut_hel*rad2deg,
30 & ' MAXANG_HEL',angcut1_hel*rad2deg
31 write (iout,*) 'ANGCUT_BET',angcut_bet*rad2deg,
32 & ' MAXANG_BET',angcut1_bet*rad2deg
33 write (iout,*) 'ANGCUT_STRAND',angcut_strand*rad2deg,
34 & ' MAXANG_STRAND',angcut1_strand*rad2deg
35 write (iout,*) 'FRAC_MIN',frac_min_set
36 c Find secondary structure elements (helices and beta-sheets)
37 call secondary2(.true.,.false.,ncont_pept_ref,icont_pept_ref,
39 c Define primary fragments. First include the helices.
43 c AL 12/23/03 - to avoid splitting helices into very small fragments
44 if (merge_helices) then
45 write (iout,*) "Before merging helices: nhfrag",nhfrag
47 write (2,*) hfrag(1,i),hfrag(2,i)
50 do while (i.lt.nhfrag)
51 if (hfrag(1,i+1)-hfrag(2,i).le.1) then
53 hfrag(2,i)=hfrag(2,i+1)
55 hfrag(1,j)=hfrag(1,j+1)
56 hfrag(2,j)=hfrag(2,j+1)
61 write (iout,*) "After merging helices: nhfrag",nhfrag
63 write (2,*) hfrag(1,i),hfrag(2,i)
69 ifrag(1,1,i)=hfrag(1,i)
70 ifrag(2,1,i)=hfrag(2,i)
72 n_shift(2,i,1)=nshift_hel
74 ang_cut1(i)=angcut1_hel
75 frac_min(i)=frac_min_set
76 nc_fragm(i,1)=ncfrac_hel
77 nc_req_setf(i,1)=ncreq_hel
80 write (iout,*) "isplit_bet",isplit_bet
81 if (isplit_bet.gt.1) then
82 c Split beta-sheets into strands and store strands as primary fragments.
83 call split_beta(nbfrag,bfrag,nstrand,istrand,nhairp,ihairp)
87 ifrag(1,1,ii)=istrand(1,i)
88 ifrag(2,1,ii)=istrand(2,i)
89 n_shift(1,ii,1)=nshift_strand
90 n_shift(2,ii,1)=nshift_strand
91 ang_cut(ii)=angcut_strand
92 ang_cut1(ii)=angcut1_strand
93 frac_min(ii)=frac_min_set
98 nfrag(1)=nfrag(1)+nstrand
99 else if (isplit_bet.eq.1) then
100 c Split only far beta-sheets; does not split hairpins.
101 call find_and_remove_hairpins(nbfrag,bfrag,nhairp,ihairp)
102 call split_beta(nbfrag,bfrag,nstrand,istrand,nhairp,ihairp)
106 ifrag(1,1,ii)=ihairp(1,i)
107 ifrag(2,1,ii)=ihairp(2,i)
108 n_shift(1,ii,1)=nshift_bet
109 n_shift(2,ii,1)=nshift_bet
110 ang_cut(ii)=angcut_bet
111 ang_cut1(ii)=angcut1_bet
112 frac_min(ii)=frac_min_set
113 nc_fragm(ii,1)=ncfrac_bet
114 nc_req_setf(ii,1)=ncreq_bet
117 nfrag(1)=nfrag(1)+nhairp
121 ifrag(1,1,ii)=istrand(1,i)
122 ifrag(2,1,ii)=istrand(2,i)
123 n_shift(1,ii,1)=nshift_strand
124 n_shift(2,ii,1)=nshift_strand
125 ang_cut(ii)=angcut_strand
126 ang_cut1(ii)=angcut1_strand
127 frac_min(ii)=frac_min_set
132 nfrag(1)=nfrag(1)+nstrand
134 c Do not split beta-sheets; each pair of strands is a primary element.
135 call find_and_remove_hairpins(nbfrag,bfrag,nhairp,ihairp)
139 ifrag(1,1,ii)=ihairp(1,i)
140 ifrag(2,1,ii)=ihairp(2,i)
141 n_shift(1,ii,1)=nshift_bet
142 n_shift(2,ii,1)=nshift_bet
143 ang_cut(ii)=angcut_bet
144 ang_cut1(ii)=angcut1_bet
145 frac_min(ii)=frac_min_set
146 nc_fragm(ii,1)=ncfrac_bet
147 nc_req_setf(ii,1)=ncreq_bet
150 nfrag(1)=nfrag(1)+nhairp
154 ifrag(1,1,ii)=bfrag(1,i)
155 ifrag(2,1,ii)=bfrag(2,i)
156 if (bfrag(3,i).lt.bfrag(4,i)) then
157 ifrag(1,2,ii)=bfrag(3,i)
158 ifrag(2,2,ii)=bfrag(4,i)
160 ifrag(1,2,ii)=bfrag(4,i)
161 ifrag(2,2,ii)=bfrag(3,i)
163 n_shift(1,ii,1)=nshift_bet
164 n_shift(2,ii,1)=nshift_bet
165 ang_cut(ii)=angcut_bet
166 ang_cut1(ii)=angcut1_bet
167 frac_min(ii)=frac_min_set
168 nc_fragm(ii,1)=ncfrac_bet
169 nc_req_setf(ii,1)=ncreq_bet
172 nfrag(1)=nfrag(1)+nbfrag
174 write (iout,*) "The following primary fragments were found:"
175 write (iout,*) "Helices:",nhfrag
181 write (iout,'(i3,2x,a,i4,2x,a,i4)')
182 & i,restyp(it1),i1,restyp(it2),i2
184 write (iout,*) "Hairpins:",nhairp
185 do i=nhfrag+1,nhfrag+nhairp
190 write (iout,'(i3,2x,a,i4,2x,a,i4,2x)')
191 & i,restyp(it1),i1,restyp(it2),i2
193 write (iout,*) "Far strand pairs:",nbfrag
194 do i=nhfrag+nhairp+1,nhfrag+nhairp+nbfrag
203 write (iout,'(i3,2x,a,i4,2x,a,i4," and ",a,i4,2x,a,i4)')
204 & i,restyp(it1),i1,restyp(it2),i2,
205 & restyp(it3),i3,restyp(it4),i4
207 write (iout,*) "Strands:",nstrand
208 do i=nhfrag+nhairp+nbfrag+1,nfrag(1)
213 write (iout,'(i3,2x,a,i4,2x,a,i4)')
214 & i,restyp(it1),i1,restyp(it2),i2
216 call imysort(nfrag(1),2,maxpiece,ifrag(1,1,1),npiece(1,1),
217 & istruct(1),n_shift(1,1,1),ang_cut(1),ang_cut1(1),frac_min(1),
218 & nc_fragm(1,1),nc_req_setf(1,1))
219 write (iout,*) "Fragments after sorting:"
225 write (iout,'(i3,2x,a,i4,2x,a,i4,$)')
226 & i,restyp(it1),i1,restyp(it2),i2
227 if (npiece(i,1).eq.1) then
228 write (iout,'(2x,a)') strstr(istruct(i))
234 write (iout,'(2x,a,i4,2x,a,i4,2x,a)')
235 & restyp(it1),i1,restyp(it2),i2,strstr(istruct(i))
240 c------------------------------------------------------------------------------
241 subroutine find_and_remove_hairpins(nbfrag,bfrag,nhairp,ihairp)
242 implicit real*8 (a-h,o-z)
244 include 'DIMENSIONS.ZSCOPT'
245 include 'DIMENSIONS.COMPAR'
246 include 'COMMON.IOUNITS'
247 integer nbfrag,bfrag(4,maxres/3)
248 integer nhairp,ihairp(2,maxres/5)
249 write (iout,*) "Entered find_and_remove_hairpins"
250 write (iout,*) "nbfrag",nbfrag
252 write (iout,*) i,(bfrag(k,i),k=1,4)
256 do while (i.le.nbfrag)
257 write (iout,*) "check hairpin:",i,(bfrag(j,i),j=1,4)
258 if (bfrag(3,i).gt.bfrag(4,i) .and. bfrag(4,i)-bfrag(2,i).lt.5)
260 write (iout,*) "Found hairpin:",i,bfrag(1,i),bfrag(3,i)
262 ihairp(1,nhairp)=bfrag(1,i)
263 ihairp(2,nhairp)=bfrag(3,i)
267 bfrag(k,j)=bfrag(k,j+1)
274 write (iout,*) "After finding hairpins:"
275 write (iout,*) "nhairp",nhairp
277 write (iout,*) i,ihairp(1,i),ihairp(2,i)
279 write (iout,*) "nbfrag",nbfrag
281 write (iout,*) i,(bfrag(k,i),k=1,4)
285 c------------------------------------------------------------------------------
286 subroutine split_beta(nbfrag,bfrag,nstrand,istrand,nhairp,ihairp)
287 implicit real*8 (a-h,o-z)
289 include 'DIMENSIONS.ZSCOPT'
290 include 'DIMENSIONS.COMPAR'
291 include 'COMMON.IOUNITS'
292 integer nbfrag,bfrag(4,maxres/3)
293 integer nstrand,istrand(2,maxres/2)
294 integer nhairp,ihairp(2,maxres/5)
296 write (iout,*) "Entered split_beta"
297 write (iout,*) "nbfrag",nbfrag
299 write (iout,*) i,(bfrag(k,i),k=1,4)
303 write (iout,*) "calling add_strand:",i,bfrag(1,i),bfrag(2,i)
304 call add_strand(nstrand,istrand,nhairp,ihairp,
305 & bfrag(1,i),bfrag(2,i),found)
306 if (bfrag(3,i).lt.bfrag(4,i)) then
307 write (iout,*) "calling add_strand:",i,bfrag(3,i),bfrag(4,i)
308 call add_strand(nstrand,istrand,nhairp,ihairp,
309 & bfrag(3,i),bfrag(4,i),found)
311 write (iout,*) "calling add_strand:",i,bfrag(4,i),bfrag(3,i)
312 call add_strand(nstrand,istrand,nhairp,ihairp,
313 & bfrag(4,i),bfrag(3,i),found)
317 write (iout,*) "Strands found:",nstrand
319 write (iout,*) i,istrand(1,i),istrand(2,i)
323 c------------------------------------------------------------------------------
324 subroutine add_strand(nstrand,istrand,nhairp,ihairp,is1,is2,found)
325 implicit real*8 (a-h,o-z)
327 include 'DIMENSIONS.ZSCOPT'
328 include 'DIMENSIONS.COMPAR'
329 include 'COMMON.IOUNITS'
330 integer nstrand,istrand(2,maxres/2)
331 integer nhairp,ihairp(2,maxres/5)
335 idelt=(ihairp(2,j)-ihairp(1,j))/6
336 if (is1.lt.ihairp(2,j)-idelt.and.is2.gt.ihairp(1,j)+idelt) then
337 write (iout,*) "strand",is1,is2," is part of hairpin",
338 & ihairp(1,j),ihairp(2,j)
343 idelt=(istrand(2,j)-istrand(1,j))/3
344 if (is1.lt.istrand(2,j)-idelt.and.is2.gt.istrand(1,j)+idelt)
346 c The strand already exists in the array; update its ends if necessary.
347 write (iout,*) "strand",is1,is2," found at position",j,
348 & ":",istrand(1,j),istrand(2,j)
349 istrand(1,j)=min0(istrand(1,j),is1)
350 istrand(2,j)=max0(istrand(2,j),is2)
354 c The strand has not been found; add it to the array.
355 write (iout,*) "strand",is1,is2," added to the array."
358 istrand(1,nstrand)=is1
359 istrand(2,nstrand)=is2
362 c------------------------------------------------------------------------------
363 subroutine secondary2(lprint,lprint_sec,ncont,icont,isecstr)
364 implicit real*8 (a-h,o-z)
366 include 'DIMENSIONS.ZSCOPT'
367 include 'COMMON.IOUNITS'
368 include 'COMMON.FRAG'
371 include 'COMMON.CHAIN'
372 include 'COMMON.NAMES'
373 include 'COMMON.INTERACT'
374 integer ncont,icont(2,maxcont),isec(maxres,4),nsec(maxres),
376 logical lprint,lprint_sec,not_done,freeres
377 double precision p1,p2
379 character*1 csec(0:2) /'-','E','H'/
381 write (iout,*) "entered secondary2",ncont
382 write (iout,*) "nstart_sup",nstart_sup," nend_sup",nend_sup
384 write (iout,*) icont(1,i),icont(2,i)
398 c finding parallel beta
399 cd write (iout,*) '------- looking for parallel beta -----------'
405 if (i1.ge.nstart_sup .and. i1.le.nend_sup
406 & .and. j1.gt.nstart_sup .and. j1.le.nend_sup) then
407 cd write (iout,*) "parallel",i1,j1
408 if(j1-i1.gt.5 .and. freeres(i1,j1,nsec,isec)) then
411 cd write (iout,*) i1,j1
417 if (i1.eq.icont(1,j) .and. j1.eq.icont(2,j) .and.
418 & freeres(i1,j1,nsec,isec)) goto 5
422 cd write (iout,*) i1,j1,not_done
426 if (i1-ii1.gt.1) then
430 if(lprint)write(iout,'(a,i3,4i4)')'parallel beta',
431 & nbeta,ii1,i1,jj1,j1
434 bfrag(1,nbfrag)=ii1+1
436 bfrag(3,nbfrag)=jj1+1
437 bfrag(4,nbfrag)=min0(j1+1,nres)
441 isec(ij,nsec(ij))=nbeta
445 isec(ij,nsec(ij))=nbeta
451 write(12,'(a18,i1,a9,i3,a2,i3,a1)')
452 & "DefPropRes 'strand",nstrand,
453 & "' 'num = ",ii1-1,"..",i1-1,"'"
455 write(12,'(a18,i2,a9,i3,a2,i3,a1)')
456 & "DefPropRes 'strand",nstrand,
457 & "' 'num = ",ii1-1,"..",i1-1,"'"
461 write(12,'(a18,i1,a9,i3,a2,i3,a1)')
462 & "DefPropRes 'strand",nstrand,
463 & "' 'num = ",jj1-1,"..",j1-1,"'"
465 write(12,'(a18,i2,a9,i3,a2,i3,a1)')
466 & "DefPropRes 'strand",nstrand,
467 & "' 'num = ",jj1-1,"..",j1-1,"'"
470 & "SetNeigh",ii1-1,i1-1,jj1-1,j1-1
474 endif ! i1.ge.nstart_sup .and. i1.le.nend_sup .and. i2.gt.nstart_sup .and. i2.le.nend_sup
477 c finding antiparallel beta
478 cd write (iout,*) '--------- looking for antiparallel beta ---------'
483 if (freeres(i1,j1,nsec,isec)) then
486 cd write (iout,*) i1,j1
493 if (i1.eq.icont(1,j).and.j1.eq.icont(2,j) .and.
494 & freeres(i1,j1,nsec,isec)) goto 6
498 cd write (iout,*) i1,j1,not_done
502 if (i1-ii1.gt.1) then
506 bfrag(2,nbfrag)=min0(i1+1,nres)
507 bfrag(3,nbfrag)=min0(jj1+1,nres)
514 if (nsec(ij).le.2) then
515 isec(ij,nsec(ij))=nbeta
521 if (nsec(ij).le.2) then
522 isec(ij,nsec(ij))=nbeta
528 write (iout,'(a,i3,4i4)')'antiparallel beta',
529 & nbeta,ii1-1,i1,jj1,j1-1
531 if (nstrand.le.9) then
532 write(12,'(a18,i1,a9,i3,a2,i3,a1)')
533 & "DefPropRes 'strand",nstrand,
534 & "' 'num = ",ii1-2,"..",i1-1,"'"
536 write(12,'(a18,i2,a9,i3,a2,i3,a1)')
537 & "DefPropRes 'strand",nstrand,
538 & "' 'num = ",ii1-2,"..",i1-1,"'"
541 if (nstrand.le.9) then
542 write(12,'(a18,i1,a9,i3,a2,i3,a1)')
543 & "DefPropRes 'strand",nstrand,
544 & "' 'num = ",j1-2,"..",jj1-1,"'"
546 write(12,'(a18,i2,a9,i3,a2,i3,a1)')
547 & "DefPropRes 'strand",nstrand,
548 & "' 'num = ",j1-2,"..",jj1-1,"'"
551 & "SetNeigh",ii1-2,i1-1,jj1-1,j1-2
557 cd write (iout,*) "After beta:",nbfrag
559 cd write (iout,*) (bfrag(j,i),j=1,4)
562 if (nstrand.gt.0.and.lprint_sec) then
563 write(12,'(a27,$)') "DefPropRes 'sheet' 'strand1"
566 write(12,'(a9,i1,$)') " | strand",i
568 write(12,'(a9,i2,$)') " | strand",i
575 c finding alpha or 310 helix
583 if (j1+2.le.nres) p2=phi(j1+2)*rad2deg
587 & ((p1.ge.10.and.p1.le.80).or.i1.le.2).and.
588 & ((p2.ge.10.and.p2.le.80).or.j1.le.2.or.j1.ge.nres-3) )then
589 cd if (j1.eq.i1+3) write (iout,*) "found 1-4 ",i1,j1,p1,p2
590 co if (j1.eq.i1+4) write (iout,*) "found 1-5 ",i1,j1,p1,p2
593 if (nsec(ii1).eq.0) then
602 if (i1.eq.icont(1,j) .and. j1.eq.icont(2,j)) goto 10
608 if (p1.lt.10.or.p1.gt.80.or.p2.lt.10.or.p2.gt.80)
611 cd write (iout,*) i1,j1,not_done,p1,p2
614 if (j1-ii1.gt.4) then
616 cd write (iout,*)'helix',nhelix,ii1,j1
626 write (iout,'(a,i3,2i4)') "Helix",nhelix,ii1-1,j1-1
627 if (nhelix.le.9) then
628 write(12,'(a17,i1,a9,i3,a2,i3,a1)')
629 & "DefPropRes 'helix",nhelix,
630 & "' 'num = ",ii1-1,"..",j1-2,"'"
632 write(12,'(a17,i2,a9,i3,a2,i3,a1)')
633 & "DefPropRes 'helix",nhelix,
634 & "' 'num = ",ii1-1,"..",j1-2,"'"
641 if (nhelix.gt.0.and.lprint_sec) then
642 write(12,'(a26,$)') "DefPropRes 'helix' 'helix1"
644 if (nhelix.le.9) then
645 write(12,'(a8,i1,$)') " | helix",i
647 write(12,'(a8,i2,$)') " | helix",i
654 write(12,'(a37)') "DefPropRes 'coil' '! (helix | sheet)'"
655 write(12,'(a20)') "XMacStand ribbon.mac"
660 write(iout,*) 'UNRES seq:'
662 write(iout,*) 'beta ',(bfrag(i,j),i=1,4)
666 write(iout,*) 'helix ',(hfrag(i,j),i=1,2)
672 do k=min0(bfrag(1,j),bfrag(2,j)),max0(bfrag(1,j),bfrag(2,j))
675 do k=min0(bfrag(3,j),bfrag(4,j)),max0(bfrag(3,j),bfrag(4,j))
680 do k=hfrag(1,j),hfrag(2,j)
686 write (iout,*) "Secondary structure"
691 write (iout,'(8(7x,i3))') (k,k=ist+9,ien,10)
692 write (iout,'(80a1)') (onelet(itype(k)),k=ist,ien)
693 write (iout,'(80a1)') (csec(isecstr(k)),k=ist,ien)
699 c-------------------------------------------------
700 logical function freeres(i,j,nsec,isec)
702 integer isec(maxres,4),nsec(maxres)
705 if (nsec(i).gt.1.or.nsec(j).gt.1) return
708 if (isec(i,k).eq.isec(j,l)) return