2 C Read the PDB file and convert the peptide geometry into virtual-chain
4 implicit real*8 (a-h,o-z)
10 include 'COMMON.INTERACT'
11 include 'COMMON.IOUNITS'
13 include 'COMMON.NAMES'
14 include 'COMMON.CONTROL'
15 integer i,j,ibeg,ishift1,ires,iii,ires_old,ishift,ity
16 logical lprn /.false./,fail,sccalc
17 double precision e1(3),e2(3),e3(3)
18 double precision dcj,efree_temp
22 double precision sccor(3,50)
24 integer iterter(maxres)
29 c write (2,*) "UNRES_PDB",unres_pdb
38 read (ipdbin,'(a80)',end=10) card
39 ! write (iout,'(a)') card
40 if (card(:5).eq.'HELIX') then
43 read(card(22:25),*) hfrag(1,nhfrag)
44 read(card(34:37),*) hfrag(2,nhfrag)
46 if (card(:5).eq.'SHEET') then
49 read(card(24:26),*) bfrag(1,nbfrag)
50 read(card(35:37),*) bfrag(2,nbfrag)
51 !rc----------------------------------------
52 !rc to be corrected !!!
53 bfrag(3,nbfrag)=bfrag(1,nbfrag)
54 bfrag(4,nbfrag)=bfrag(2,nbfrag)
55 !rc----------------------------------------
57 if (card(:3).eq.'END') then
59 else if (card(:3).eq.'TER') then
62 itype(ires_old-1)=ntyp1
68 ! write (iout,*) "Chain ended",ires,ishift,ires_old
71 dc(j,ires)=sccor(j,iii)
74 call sccenter(ires,iii,sccor)
80 c if (index(card,"FREE ENERGY").gt.0) read(card(35:),*) efree_temp
81 ! Fish out the ATOM cards.
82 if (index(card(1:4),'ATOM').gt.0) then
84 read (card(12:16),*) atom
85 c write (2,'(a)') card
86 ! write (iout,*) "! ",atom," !",ires
87 ! if (atom.eq.'CA' .or. atom.eq.'CH3') then
88 read (card(23:26),*) ires
89 read (card(18:20),'(a3)') res
90 ! write (iout,*) "ires",ires,ires-ishift+ishift1,
91 ! & " ires_old",ires_old
92 ! write (iout,*) "ishift",ishift," ishift1",ishift1
93 ! write (iout,*) "IRES",ires-ishift+ishift1,ires_old
94 if (ires-ishift+ishift1.ne.ires_old) then
95 ! Calculate the CM of the preceding residue.
96 ! if (ibeg.eq.0) call sccenter(ires,iii,sccor)
98 ! write (iout,*) "Calculating sidechain center iii",iii
101 dc(j,ires_old)=sccor(j,iii)
104 call sccenter(ires_old,iii,sccor)
110 if (res.eq.'Cl-' .or. res.eq.'Na+') then
113 else if (ibeg.eq.1) then
114 c write (iout,*) "BEG ires",ires
116 if (res.ne.'GLY' .and. res.ne. 'ACE') then
120 ires=ires-ishift+ishift1
122 ! write (iout,*) "ishift",ishift," ires",ires,&
123 ! " ires_old",ires_old
125 else if (ibeg.eq.2) then
127 ishift=-ires_old+ires-1 !!!!!
128 ishift1=ishift1-1 !!!!!
129 ! write (iout,*) "New chain started",ires,ishift,ishift1,"!"
130 ires=ires-ishift+ishift1
134 ishift=ishift-(ires-ishift+ishift1-ires_old-1)
135 ires=ires-ishift+ishift1
138 if (res.eq.'ACE' .or. res.eq.'NHE') then
141 itype(ires)=rescode(ires,res,0)
144 ires=ires-ishift+ishift1
146 ! write (iout,*) "ires_old",ires_old," ires",ires
147 if (card(27:27).eq."A" .or. card(27:27).eq."B") then
150 ! write (2,*) "ires",ires," res ",res!," ity"!,ity
151 if (atom.eq.'CA' .or. atom.eq.'CH3' .or.
152 & res.eq.'NHE'.and.atom(:2).eq.'HN') then
153 read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
154 ! write (iout,*) "backbone ",atom
156 write (iout,'(2i3,2x,a,3f8.3)')
157 & ires,itype(ires),res,(c(j,ires),j=1,3)
161 sccor(j,iii)=c(j,ires)
163 c write (2,*) card(23:27),ires,itype(ires),iii
164 else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
165 & atom.ne.'N' .and. atom.ne.'C' .and.
166 & atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
167 & atom.ne.'OXT' .and. atom(:2).ne.'3H') then
168 ! write (iout,*) "sidechain ",atom
170 read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
171 c write (2,*) "iii",iii
175 10 write (iout,'(a,i5)') ' Nres: ',ires
176 C Calculate dummy residue coordinates inside the "chain" of a multichain
180 c write (iout,*) i,itype(i)
182 if (itype(i).eq.ntyp1) then
183 if (itype(i+1).eq.ntyp1) then
184 C 16/01/2014 by Adasko: Adding to dummy atoms in the chain
185 C first is connected prevous chain (itype(i+1).eq.ntyp1)=true
186 C second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
187 C if (unres_pdb) then
188 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
189 C call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
196 C c(j,i)=c(j,i-1)-1.9d0*e2(j)
200 dcj=(c(j,i-2)-c(j,i-3))/2.0
205 else !itype(i+1).eq.ntyp1
206 C if (unres_pdb) then
207 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
208 C call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
215 C c(j,i)=c(j,i+1)-1.9d0*e2(j)
219 dcj=(c(j,i+3)-c(j,i+2))/2.0
224 endif !itype(i+1).eq.ntyp1
225 endif !itype.eq.ntyp1
227 C Calculate the CM of the last side chain.
228 if (.not.sccalc) call sccenter(ires,iii,sccor)
231 if (itype(nres).ne.10) then
235 dcj=(c(j,nres-2)-c(j,nres-3))/2.0
236 c(j,nres)=c(j,nres-1)+dcj
237 c(j,2*nres)=c(j,nres)
247 c(j,2*nres)=c(j,nres)
249 if (itype(1).eq.ntyp1) then
253 dcj=(c(j,4)-c(j,3))/2.0
258 C Calculate internal coordinates.
261 & "Cartesian coordinates of the reference structure"
262 write (iout,'(a,3(3x,a5),5x,3(3x,a5))')
263 & "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
265 write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)')
266 & restyp(itype(ires)),ires,(c(j,ires),j=1,3),
267 & (c(j,ires+nres),j=1,3)
270 C Calculate internal coordinates.
272 & "Backbone and SC coordinates as read from the PDB"
274 write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)')
275 & ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
276 & (c(j,nres+ires),j=1,3)
278 call int_from_cart(.true.,.false.)
279 call sc_loc_geom(.false.)
286 dc(j,i)=c(j,i+1)-c(j,i)
287 dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
292 dc(j,i+nres)=c(j,i+nres)-c(j,i)
293 dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
295 c write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
299 C Copy the coordinates to reference coordinates
309 bfrag(i,j)=bfrag(i,j)-ishift
315 hfrag(i,j)=hfrag(i,j)-ishift
321 c---------------------------------------------------------------------------
322 subroutine int_from_cart(lside,lprn)
323 implicit real*8 (a-h,o-z)
325 include 'COMMON.LOCAL'
327 include 'COMMON.CHAIN'
328 include 'COMMON.INTERACT'
329 include 'COMMON.IOUNITS'
331 include 'COMMON.NAMES'
335 dimension sccor(3,50)
340 & 'Internal coordinates calculated from crystal structure.'
342 write (iout,'(8a)') ' Res ',' dvb',' Theta',
343 & ' Gamma',' Dsc_id',' Dsc',' Alpha',
346 write (iout,'(4a)') ' Res ',' dvb',' Theta',
352 c write (iout,*) i,i-1,(c(j,i),j=1,3),(c(j,i-1),j=1,3),dist(i,i-1)
353 if (itype(i-1).ne.ntyp1 .and. itype(i).ne.ntyp1 .and.
354 & (dist(i,i-1).lt.1.0D0 .or. dist(i,i-1).gt.6.0D0)) then
355 write (iout,'(a,i4)') 'Bad Cartesians for residue',i
359 vbld_inv(i)=1.0d0/vbld(i)
360 theta(i+1)=alpha(i-1,i,i+1)
361 if (i.gt.2) phi(i+1)=beta(i-2,i-1,i,i+1)
364 c if (unres_pdb) then
365 c if (itype(1).eq.ntyp1) then
366 c theta(3)=90.0d0*deg2rad
367 c phi(4)=180.0d0*deg2rad
369 c vbld_inv(2)=1.0d0/vbld(2)
371 c if (itype(nres).eq.ntyp1) then
372 c theta(nres)=90.0d0*deg2rad
373 c phi(nres)=180.0d0*deg2rad
375 c vbld_inv(nres)=1.0d0/vbld(2)
381 c(j,maxres2)=0.5D0*(2*c(j,i)+(c(j,i-1)-c(j,i))*vbld_inv(i)
382 & +(c(j,i+1)-c(j,i))*vbld_inv(i+1))
386 C 10/03/12 Adam: Correction for zero SC-SC bond length
387 if (itype(i).ne.10 .and. itype(i).ne.ntyp1. and. di.eq.0.0d0)
390 if (itype(i).ne.10) then
391 vbld_inv(i+nres)=1.0d0/di
393 vbld_inv(i+nres)=0.0d0
396 alph(i)=alpha(nres+i,i,maxres2)
397 omeg(i)=beta(nres+i,i,maxres2,i+1)
400 & write (iout,'(a3,i4,7f10.3)') restyp(iti),i,vbld(i),
401 & rad2deg*theta(i),rad2deg*phi(i),dsc(iti),vbld(nres+i),
402 & rad2deg*alph(i),rad2deg*omeg(i)
407 write (iout,'(a3,i4,7f10.3)') restyp(iti),i,dist(i,i-1),
408 & rad2deg*theta(i),rad2deg*phi(i)
413 c-------------------------------------------------------------------------------
414 subroutine sc_loc_geom(lprn)
415 implicit real*8 (a-h,o-z)
417 include 'COMMON.LOCAL'
419 include 'COMMON.CHAIN'
420 include 'COMMON.INTERACT'
421 include 'COMMON.IOUNITS'
423 include 'COMMON.NAMES'
424 include 'COMMON.CONTROL'
425 double precision x_prime(3),y_prime(3),z_prime(3)
429 dc_norm(j,i)=vbld_inv(i+1)*(c(j,i+1)-c(j,i))
433 if (itype(i).ne.10) then
435 dc_norm(j,i+nres)=vbld_inv(i+nres)*(c(j,i+nres)-c(j,i))
439 dc_norm(j,i+nres)=0.0d0
444 costtab(i+1) =dcos(theta(i+1))
445 sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
446 cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
447 sint2tab(i+1)=dsqrt(0.5d0*(1.0d0-costtab(i+1)))
448 cosfac2=0.5d0/(1.0d0+costtab(i+1))
449 cosfac=dsqrt(cosfac2)
450 sinfac2=0.5d0/(1.0d0-costtab(i+1))
451 sinfac=dsqrt(sinfac2)
455 C Compute the axes of tghe local cartesian coordinates system; store in
456 c x_prime, y_prime and z_prime
464 x_prime(j) = (dc_norm(j,i) - dc_norm(j,i-1))*cosfac
465 y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
467 call vecpr(x_prime,y_prime,z_prime)
469 C Transform the unit vector of the ith side-chain centroid, dC_norm(*,i),
470 C to local coordinate system. Store in xx, yy, zz.
476 xx = xx + x_prime(j)*dc_norm(j,i+nres)
477 yy = yy + y_prime(j)*dc_norm(j,i+nres)
478 zz = zz + z_prime(j)*dc_norm(j,i+nres)
493 write (iout,'(a3,i4,3f10.5)') restyp(iti),i,xxref(i),
499 c---------------------------------------------------------------------------
500 subroutine sccenter(ires,nscat,sccor)
501 implicit real*8 (a-h,o-z)
503 include 'COMMON.CHAIN'
504 dimension sccor(3,50)
508 sccmj=sccmj+sccor(j,i)
510 dc(j,ires)=sccmj/nscat
514 c---------------------------------------------------------------------------
515 subroutine bond_regular
519 include 'COMMON.LOCAL'
520 include 'COMMON.INTERACT'
521 include 'COMMON.CHAIN'
526 vbld(i+1+nres)=dsc(iabs(itype(i+1)))
527 vbld_inv(i+1+nres)=dsc_inv(iabs(itype(i+1)))
528 c print *,vbld(i+1),vbld(i+1+nres)
530 c Adam 2/26/20 Alter virtual bonds for non-blocking end groups of each chain
536 vbld_inv(i1)=vbld_inv(i1)*2
539 vbld(i2+1)=vbld(i2+1)/2
540 vbld_inv(i2+1)=vbld_inv(i2+1)*2
545 c---------------------------------------------------------------------------
546 subroutine readpdb_template(k)
547 C Read the PDB file with gaps for read_constr_homology with read2sigma
548 C and convert the peptide geometry into virtual-chain geometry.
549 implicit real*8 (a-h,o-z)
551 include 'COMMON.LOCAL'
553 include 'COMMON.CHAIN'
554 include 'COMMON.INTERACT'
555 include 'COMMON.IOUNITS'
557 include 'COMMON.NAMES'
558 include 'COMMON.CONTROL'
559 integer i,j,ibeg,ishift1,ires,iii,ires_old,ishift,ity
560 logical lprn /.false./,fail
561 double precision e1(3),e2(3),e3(3)
562 double precision dcj,efree_temp
566 double precision sccor(3,50)
567 integer rescode,iterter(maxres)
574 c write (2,*) "UNRES_PDB",unres_pdb
582 read (ipdbin,'(a80)',end=10) card
583 if (card(:3).eq.'END') then
585 else if (card(:3).eq.'TER') then
588 itype(ires_old-1)=ntyp1
589 iterter(ires_old-1)=1
590 itype(ires_old)=ntyp1
593 c write (iout,*) "Chain ended",ires,ishift,ires_old
596 dc(j,ires)=sccor(j,iii)
599 call sccenter(ires,iii,sccor)
602 C Fish out the ATOM cards.
603 if (index(card(1:4),'ATOM').gt.0) then
604 read (card(12:16),*) atom
605 c write (iout,*) "! ",atom," !",ires
606 c if (atom.eq.'CA' .or. atom.eq.'CH3') then
607 read (card(23:26),*) ires
608 read (card(18:20),'(a3)') res
609 c write (iout,*) "ires",ires,ires-ishift+ishift1,
610 c & " ires_old",ires_old
611 c write (iout,*) "ishift",ishift," ishift1",ishift1
612 c write (iout,*) "IRES",ires-ishift+ishift1,ires_old
613 if (ires-ishift+ishift1.ne.ires_old) then
614 C Calculate the CM of the preceding residue.
618 dc(j,ires)=sccor(j,iii)
621 call sccenter(ires_old,iii,sccor)
626 if (res.eq.'Cl-' .or. res.eq.'Na+') then
629 else if (ibeg.eq.1) then
630 c write (iout,*) "BEG ires",ires
632 if (res.ne.'GLY' .and. res.ne. 'ACE') then
636 ires=ires-ishift+ishift1
638 c write (iout,*) "ishift",ishift," ires",ires,
639 c & " ires_old",ires_old
640 c write (iout,*) "ires",ires," ibeg",ibeg," ishift",ishift
642 else if (ibeg.eq.2) then
644 ishift=-ires_old+ires-1
646 c write (iout,*) "New chain started",ires,ishift
649 ishift=ishift-(ires-ishift+ishift1-ires_old-1)
650 ires=ires-ishift+ishift1
653 if (res.eq.'ACE' .or. res.eq.'NHE') then
656 itype(ires)=rescode(ires,res,0)
659 ires=ires-ishift+ishift1
661 c write (iout,*) "ires_old",ires_old," ires",ires
662 c if (card(27:27).eq."A" .or. card(27:27).eq."B") then
665 c write (2,*) "ires",ires," res ",res," ity",ity
666 if (atom.eq.'CA' .or. atom.eq.'CH3' .or.
667 & res.eq.'NHE'.and.atom(:2).eq.'HN') then
668 read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
669 c write (iout,*) "backbone ",atom ,ires,res, (c(j,ires),j=1,3)
671 write (iout,'(2i3,2x,a,3f8.3)')
672 & ires,itype(ires),res,(c(j,ires),j=1,3)
676 sccor(j,iii)=c(j,ires)
678 if (ishift.ne.0) then
679 ires_ca=ires+ishift-ishift1
683 c write (*,*) card(23:27),ires,itype(ires)
684 else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
685 & atom.ne.'N' .and. atom.ne.'C' .and.
686 & atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
687 & atom.ne.'OXT' .and. atom(:2).ne.'3H') then
688 c write (iout,*) "sidechain ",atom
690 read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
694 10 write (iout,'(a,i5)') ' Nres: ',ires
695 C Calculate dummy residue coordinates inside the "chain" of a multichain
699 c write (iout,*) i,itype(i),itype(i+1)
700 if (itype(i).eq.ntyp1.and.iterter(i).eq.1) then
701 if (itype(i+1).eq.ntyp1.and.iterter(i+1).eq.1 ) then
702 C 16/01/2014 by Adasko: Adding to dummy atoms in the chain
703 C first is connected prevous chain (itype(i+1).eq.ntyp1)=true
704 C second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
706 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
707 call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
714 c(j,i)=c(j,i-1)-1.9d0*e2(j)
718 dcj=(c(j,i-2)-c(j,i-3))/2.0
719 if (dcj.eq.0) dcj=1.23591524223
724 else !itype(i+1).eq.ntyp1
726 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
727 call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
734 c(j,i)=c(j,i+1)-1.9d0*e2(j)
738 dcj=(c(j,i+3)-c(j,i+2))/2.0
739 if (dcj.eq.0) dcj=1.23591524223
744 endif !itype(i+1).eq.ntyp1
745 endif !itype.eq.ntyp1
747 C Calculate the CM of the last side chain.
750 dc(j,ires)=sccor(j,iii)
753 call sccenter(ires,iii,sccor)
757 if (itype(nres).ne.10) then
761 C 2/15/2013 by Adam: corrected insertion of the last dummy residue
762 call refsys(nres-3,nres-2,nres-1,e1,e2,e3,fail)
769 c(j,nres)=c(j,nres-1)-1.9d0*e2(j)
773 dcj=(c(j,nres-2)-c(j,nres-3))/2.0
774 if (dcj.eq.0) dcj=1.23591524223
775 c(j,nres)=c(j,nres-1)+dcj
776 c(j,2*nres)=c(j,nres)
787 c(j,2*nres)=c(j,nres)
789 if (itype(1).eq.ntyp1) then
793 C 2/15/2013 by Adam: corrected insertion of the first dummy residue
794 call refsys(2,3,4,e1,e2,e3,fail)
801 c(j,1)=c(j,2)-1.9d0*e2(j)
805 dcj=(c(j,4)-c(j,3))/2.0
811 C Calculate internal coordinates.
812 if (out_template_coord) then
814 & "Cartesian coordinates of the reference structure"
815 write (iout,'(a,3(3x,a5),5x,3(3x,a5))')
816 & "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
818 write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)')
819 & restyp(itype(ires)),ires,(c(j,ires),j=1,3),
820 & (c(j,ires+nres),j=1,3)
823 C Calculate internal coordinates.
826 & "Backbone and SC coordinates as read from the PDB"
828 write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)')
829 & ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
830 & (c(j,nres+ires),j=1,3)
833 call int_from_cart(.true.,out_template_coord)
834 call sc_loc_geom(.false.)
841 dc(j,i)=c(j,i+1)-c(j,i)
842 dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
847 dc(j,i+nres)=c(j,i+nres)-c(j,i)
848 dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
850 c write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
856 cref(j,i+nres)=c(j,i+nres)