character*80 card
double precision sccor(3,20)
integer rescode
+ integer iterter(maxres)
efree_temp=0.0d0
ibeg=1
ishift1=0
nbfrag=0
do
read (ipdbin,'(a80)',end=10) card
-c write (iout,'(a)') card
+! write (iout,'(a)') card
if (card(:5).eq.'HELIX') then
- nhfrag=nhfrag+1
- lsecondary=.true.
- read(card(22:25),*) hfrag(1,nhfrag)
- read(card(34:37),*) hfrag(2,nhfrag)
+ nhfrag=nhfrag+1
+ lsecondary=.true.
+ read(card(22:25),*) hfrag(1,nhfrag)
+ read(card(34:37),*) hfrag(2,nhfrag)
endif
if (card(:5).eq.'SHEET') then
- nbfrag=nbfrag+1
- lsecondary=.true.
- read(card(24:26),*) bfrag(1,nbfrag)
- read(card(35:37),*) bfrag(2,nbfrag)
-crc----------------------------------------
-crc to be corrected !!!
- bfrag(3,nbfrag)=bfrag(1,nbfrag)
- bfrag(4,nbfrag)=bfrag(2,nbfrag)
-crc----------------------------------------
+ nbfrag=nbfrag+1
+ lsecondary=.true.
+ read(card(24:26),*) bfrag(1,nbfrag)
+ read(card(35:37),*) bfrag(2,nbfrag)
+!rc----------------------------------------
+!rc to be corrected !!!
+ bfrag(3,nbfrag)=bfrag(1,nbfrag)
+ bfrag(4,nbfrag)=bfrag(2,nbfrag)
+!rc----------------------------------------
endif
- if (card(:3).eq.'END' .or. card(:3).eq.'TER') goto 10
-c Read free energy
+ if (card(:3).eq.'END') then
+ goto 10
+ else if (card(:3).eq.'TER') then
+! End current chain
+ ires_old=ires+2
+ itype(ires_old-1)=ntyp1
+ iterter(ires_old-1)=1
+ itype(ires_old)=ntyp1
+ ishift1=ishift1+1
+ ibeg=2
+! write (iout,*) "Chain ended",ires,ishift,ires_old
+ if (unres_pdb) then
+ do j=1,3
+ dc(j,ires)=sccor(j,iii)
+ enddo
+ else
+ call sccenter(ires,iii,sccor)
+ endif
+c iii=0
+ endif
+! Read free energy
if (index(card,"FREE ENERGY").gt.0) read(card(35:),*) efree_temp
-C Fish out the ATOM cards.
+! Fish out the ATOM cards.
if (index(card(1:4),'ATOM').gt.0) then
read (card(12:16),*) atom
-c write (iout,*) "! ",atom," !",ires
-c if (atom.eq.'CA' .or. atom.eq.'CH3') then
+c write (2,'(a)') card
+! write (iout,*) "! ",atom," !",ires
+! if (atom.eq.'CA' .or. atom.eq.'CH3') then
read (card(23:26),*) ires
read (card(18:20),'(a3)') res
-c write (iout,*) "ires",ires,ires-ishift+ishift1,
-c & " ires_old",ires_old
-c write (iout,*) "ishift",ishift," ishift1",ishift1
-c write (iout,*) "IRES",ires-ishift+ishift1,ires_old
+! write (iout,*) "ires",ires,ires-ishift+ishift1,
+! & " ires_old",ires_old
+! write (iout,*) "ishift",ishift," ishift1",ishift1
+! write (iout,*) "IRES",ires-ishift+ishift1,ires_old
if (ires-ishift+ishift1.ne.ires_old) then
-C Calculate the CM of the preceding residue.
-c if (ibeg.eq.0) call sccenter(ires,iii,sccor)
+! Calculate the CM of the preceding residue.
+! if (ibeg.eq.0) call sccenter(ires,iii,sccor)
if (ibeg.eq.0) then
-c write (iout,*) "Calculating sidechain center iii",iii
+! write (iout,*) "Calculating sidechain center iii",iii
if (unres_pdb) then
do j=1,3
- dc(j,ires)=sccor(j,iii)
+ dc(j,ires+nres)=sccor(j,iii)
enddo
else
call sccenter(ires_old,iii,sccor)
endif
iii=0
endif
-C Start new residue.
+! Start new residue.
if (res.eq.'Cl-' .or. res.eq.'Na+') then
ires=ires_old
cycle
endif
ires=ires-ishift+ishift1
ires_old=ires
-c write (iout,*) "ishift",ishift," ires",ires,
-c & " ires_old",ires_old
- ibeg=0
+! write (iout,*) "ishift",ishift," ires",ires,&
+! " ires_old",ires_old
+ ibeg=0
+ else if (ibeg.eq.2) then
+! Start a new chain
+ ishift=-ires_old+ires-1 !!!!!
+ ishift1=ishift1-1 !!!!!
+! write (iout,*) "New chain started",ires,ishift,ishift1,"!"
+ ires=ires-ishift+ishift1
+ ires_old=ires
+ ibeg=0
else
ishift=ishift-(ires-ishift+ishift1-ires_old-1)
ires=ires-ishift+ishift1
else
ires=ires-ishift+ishift1
endif
-c write (iout,*) "ires_old",ires_old," ires",ires
+! write (iout,*) "ires_old",ires_old," ires",ires
if (card(27:27).eq."A" .or. card(27:27).eq."B") then
-c ishift1=ishift1+1
+! ishift1=ishift1+1
endif
-c write (2,*) "ires",ires," res ",res," ity",ity
+! write (2,*) "ires",ires," res ",res!," ity"!,ity
if (atom.eq.'CA' .or. atom.eq.'CH3' .or.
& res.eq.'NHE'.and.atom(:2).eq.'HN') then
read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
-c write (iout,*) "backbone ",atom
+! write (iout,*) "backbone ",atom
#ifdef DEBUG
write (iout,'(2i3,2x,a,3f8.3)')
& ires,itype(ires),res,(c(j,ires),j=1,3)
do j=1,3
sccor(j,iii)=c(j,ires)
enddo
- if (ishift.ne.0) then
- ires_ca=ires+ishift-ishift1
- else
- ires_ca=ires
- endif
-c write (*,*) card(23:27),ires,itype(ires)
- else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
- & atom.ne.'N' .and. atom.ne.'C' .and.
- & atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
+c write (2,*) card(23:27),ires,itype(ires),iii
+ else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
+ & atom.ne.'N' .and. atom.ne.'C' .and.
+ & atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
& atom.ne.'OXT' .and. atom(:2).ne.'3H') then
-c write (iout,*) "sidechain ",atom
+! write (iout,*) "sidechain ",atom
iii=iii+1
read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
+c write (2,*) "iii",iii
endif
endif
enddo
end
c---------------------------------------------------------------------------
subroutine bond_regular
- implicit real*8 (a-h,o-z)
- include 'DIMENSIONS'
+ implicit none
+ include 'DIMENSIONS'
include 'COMMON.VAR'
- include 'COMMON.LOCAL'
- include 'COMMON.CALC'
+ include 'COMMON.LOCAL'
include 'COMMON.INTERACT'
include 'COMMON.CHAIN'
+ integer i,i1,i2
do i=1,nres-1
vbld(i+1)=vbl
- vbld_inv(i+1)=1.0d0/vbld(i+1)
- vbld(i+1+nres)=dsc(itype(i+1))
- vbld_inv(i+1+nres)=dsc_inv(itype(i+1))
+ vbld_inv(i+1)=vblinv
+ vbld(i+1+nres)=dsc(iabs(itype(i+1)))
+ vbld_inv(i+1+nres)=dsc_inv(iabs(itype(i+1)))
c print *,vbld(i+1),vbld(i+1+nres)
enddo
+c Adam 2/26/20 Alter virtual bonds for non-blocking end groups of each chain
+ do i=1,nchain
+ i1=chain_border(1,i)
+ i2=chain_border(2,i)
+ if (i1.gt.1) then
+ vbld(i1)=vbld(i1)/2
+ vbld_inv(i1)=vbld_inv(i1)*2
+ endif
+ if (i2.lt.nres) then
+ vbld(i2+1)=vbld(i2+1)/2
+ vbld_inv(i2+1)=vbld_inv(i2+1)*2
+ endif
+ enddo
return
end
+c---------------------------------------------------------------------------
subroutine readpdb_template(k)
C Read the PDB file with gaps for read_constr_homology with read2sigma
C and convert the peptide geometry into virtual-chain geometry.
integer rescode,iterter(maxres),cou
logical fail
integer i,j,iii,ires,ires_old,ishift,ishift1,ibeg
- double precision dcj
+ double precision dcj,efree_temp
bfac=0.0d0
do i=1,maxres
iterter(i)=0
nbfrag=0
do
read (ipdbin,'(a80)',end=10) card
+! write (iout,'(a)') card
if (card(:5).eq.'HELIX') then
- nhfrag=nhfrag+1
- lsecondary=.true.
- read(card(22:25),*) hfrag(1,nhfrag)
- read(card(34:37),*) hfrag(2,nhfrag)
+ nhfrag=nhfrag+1
+ lsecondary=.true.
+ read(card(22:25),*) hfrag(1,nhfrag)
+ read(card(34:37),*) hfrag(2,nhfrag)
endif
if (card(:5).eq.'SHEET') then
- nbfrag=nbfrag+1
- lsecondary=.true.
- read(card(24:26),*) bfrag(1,nbfrag)
- read(card(35:37),*) bfrag(2,nbfrag)
-crc----------------------------------------
-crc to be corrected !!!
- bfrag(3,nbfrag)=bfrag(1,nbfrag)
- bfrag(4,nbfrag)=bfrag(2,nbfrag)
-crc----------------------------------------
+ nbfrag=nbfrag+1
+ lsecondary=.true.
+ read(card(24:26),*) bfrag(1,nbfrag)
+ read(card(35:37),*) bfrag(2,nbfrag)
+!rc----------------------------------------
+!rc to be corrected !!!
+ bfrag(3,nbfrag)=bfrag(1,nbfrag)
+ bfrag(4,nbfrag)=bfrag(2,nbfrag)
+!rc----------------------------------------
endif
if (card(:3).eq.'END') then
goto 10
else if (card(:3).eq.'TER') then
-C End current chain
+! End current chain
ires_old=ires+2
- itype(ires_old-1)=ntyp1
+ itype(ires_old-1)=ntyp1
iterter(ires_old-1)=1
itype(ires_old)=ntyp1
- iterter(ires_old)=1
+ ishift1=ishift1+1
ibeg=2
- write (iout,*) "Chain ended",ires,ishift,ires_old
+! write (iout,*) "Chain ended",ires,ishift,ires_old
if (unres_pdb) then
do j=1,3
dc(j,ires)=sccor(j,iii)
enddo
- else
+ else
call sccenter(ires,iii,sccor)
endif
+c iii=0
endif
-C Fish out the ATOM cards.
-c if (index(card(1:4),'ATOM').gt.0) then
-c read (card(14:16),'(a3)') atom
-c if (atom.eq.'CA' .or. atom.eq.'CH3') then
-C Calculate the CM of the preceding residue.
- read (card(23:26),*) ires
- read (card(18:20),'(a3)') res
- if (ires-ishift+ishift1.ne.ires_old) then
- if (ibeg.eq.0) then
- if (unres_pdb) then
- do j=1,3
- dc(j,ires+nres)=sccor(j,iii)
- enddo
+! Read free energy
+ if (index(card,"FREE ENERGY").gt.0) read(card(35:),*) efree_temp
+! Fish out the ATOM cards.
+ if (index(card(1:4),'ATOM').gt.0) then
+ read (card(12:16),*) atom
+c write (2,'(a)') card
+! write (iout,*) "! ",atom," !",ires
+! if (atom.eq.'CA' .or. atom.eq.'CH3') then
+ read (card(23:26),*) ires
+ read (card(18:20),'(a3)') res
+! write (iout,*) "ires",ires,ires-ishift+ishift1,
+! & " ires_old",ires_old
+! write (iout,*) "ishift",ishift," ishift1",ishift1
+! write (iout,*) "IRES",ires-ishift+ishift1,ires_old
+ if (ires-ishift+ishift1.ne.ires_old) then
+! Calculate the CM of the preceding residue.
+! if (ibeg.eq.0) call sccenter(ires,iii,sccor)
+ if (ibeg.eq.0) then
+! write (iout,*) "Calculating sidechain center iii",iii
+ if (unres_pdb) then
+ do j=1,3
+ dc(j,ires+nres)=sccor(j,iii)
+ enddo
+ else
+ call sccenter(ires_old,iii,sccor)
+ endif
+ iii=0
+ endif
+! Start new residue.
+ if (res.eq.'Cl-' .or. res.eq.'Na+') then
+ ires=ires_old
+ cycle
+ else if (ibeg.eq.1) then
+c write (iout,*) "BEG ires",ires
+ ishift=ires-1
+ if (res.ne.'GLY' .and. res.ne. 'ACE') then
+ ishift=ishift-1
+ itype(1)=ntyp1
+ endif
+ ires=ires-ishift+ishift1
+ ires_old=ires
+! write (iout,*) "ishift",ishift," ires",ires,&
+! " ires_old",ires_old
+ ibeg=0
+ else if (ibeg.eq.2) then
+! Start a new chain
+ ishift=-ires_old+ires-1 !!!!!
+ ishift1=ishift1-1 !!!!!
+! write (iout,*) "New chain started",ires,ishift,ishift1,"!"
+ ires=ires-ishift+ishift1
+ ires_old=ires
+ ibeg=0
else
- call sccenter(ires,iii,sccor)
+ ishift=ishift-(ires-ishift+ishift1-ires_old-1)
+ ires=ires-ishift+ishift1
+ ires_old=ires
endif
- endif
-C Start new residue.
-c write (iout,'(a80)') card
- if (ibeg.eq.1) then
- ishift=ires-1
- if (res.ne.'GLY' .and. res.ne. 'ACE') then
- ishift=ishift-1
- itype(1)=ntyp1
+ if (res.eq.'ACE' .or. res.eq.'NHE') then
+ itype(ires)=10
+ else
+ itype(ires)=rescode(ires,res,0)
endif
-c write (iout,*) "ires",ires," ibeg",ibeg," ishift",ishift
- ibeg=0
- else if (ibeg.eq.2) then
-c Start a new chain
- ishift=-ires_old+ires-1
-c write (iout,*) "New chain started",ires,ishift
- ibeg=0
- endif
- else
- ires=ires-ishift
-c write (2,*) "ires",ires," ishift",ish
- endif
- if (atom.eq.'CA' .or. atom.eq.'CH3' .or.
- & res.eq.'NHE'.and.atom(:2).eq.'HN') then
- if (res.eq.'ACE') then
- itype(ires)=10
else
- itype(ires)=rescode(ires,res,0)
+ ires=ires-ishift+ishift1
endif
- read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
- read(card(61:66),*) bfac(ires)
-c if(me.eq.king.or..not.out1file)
-c & write (iout,'(2i3,2x,a,3f8.3)')
-c & ires,itype(ires),res,(c(j,ires),j=1,3)
- iii=1
- do j=1,3
- sccor(j,iii)=c(j,ires)
- enddo
- else if (atom.ne.'O '.and.atom(1:1).ne.'H' .and.
- & atom.ne.'N ' .and. atom.ne.'C ') then
+! write (iout,*) "ires_old",ires_old," ires",ires
+ if (card(27:27).eq."A" .or. card(27:27).eq."B") then
+! ishift1=ishift1+1
+ endif
+! write (2,*) "ires",ires," res ",res!," ity"!,ity
+ if (atom.eq.'CA' .or. atom.eq.'CH3' .or.
+ & res.eq.'NHE'.and.atom(:2).eq.'HN') then
+ read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
+! write (iout,*) "backbone ",atom
+#ifdef DEBUG
+ write (iout,'(2i3,2x,a,3f8.3)')
+ & ires,itype(ires),res,(c(j,ires),j=1,3)
+#endif
iii=iii+1
- read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
+ do j=1,3
+ sccor(j,iii)=c(j,ires)
+ enddo
+c write (2,*) card(23:27),ires,itype(ires),iii
+ else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
+ & atom.ne.'N' .and. atom.ne.'C' .and.
+ & atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
+ & atom.ne.'OXT' .and. atom(:2).ne.'3H') then
+! write (iout,*) "sidechain ",atom
+ iii=iii+1
+ read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
+c write (2,*) "iii",iii
+ endif
endif
enddo
10 if(me.eq.king.or..not.out1file)
& write (iout,'(a,i5)') ' Nres: ',ires
+c write (iout,*) "iii",iii
C Calculate dummy residue coordinates inside the "chain" of a multichain
C system
nres=ires
dc(j,ires)=sccor(j,iii)
enddo
else
+c write (iout,*) "Calling sccenter iii",iii
call sccenter(ires,iii,sccor)
endif
nsup=nres
endif
C Calculate internal coordinates.
if(me.eq.king.or..not.out1file)then
- do ires=1,nres
- write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)')
- & ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
- & (c(j,nres+ires),j=1,3)
- enddo
+ write (iout,'(/a)')
+ & "Cartesian coordinates of the reference structure"
+ write (iout,'(a,3(3x,a5),5x,3(3x,a5))')
+ & "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
+ do ires=1,nres
+ write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)')
+ & restyp(itype(ires)),ires,(c(j,ires),j=1,3),
+ & (c(j,ires+nres),j=1,3)
+ enddo
endif
call flush(iout)
c write(iout,*)"before int_from_cart nres",nres
subroutine readpdb
C Read the PDB file and convert the peptide geometry into virtual-chain
C geometry.
- implicit real*8 (a-h,o-z)
+ implicit none
include 'DIMENSIONS'
include 'DIMENSIONS.ZSCOPT'
- include 'DIMENSIONS.FREE'
- include 'COMMON.FRAG'
+ include 'COMMON.CONTROL'
include 'COMMON.LOCAL'
include 'COMMON.VAR'
include 'COMMON.CHAIN'
include 'COMMON.IOUNITS'
include 'COMMON.GEO'
include 'COMMON.NAMES'
- include 'COMMON.CONTROL'
- integer i,j,ibeg,ishift1,ires,iii,ires_old,ishift,ity
- logical lprn /.false./,fail
- double precision e1(3),e2(3),e3(3)
- double precision dcj,efree_temp
- character*3 seq,res
- character*5 atom
+ include 'COMMON.SBRIDGE'
+ include 'COMMON.FRAG'
+ character*3 seq,atom,res
character*80 card
- double precision sccor(3,20)
- integer rescode
- efree_temp=0.0d0
+ double precision sccor(3,50)
+ integer i,j,iii,ibeg,ishift,ishift1,ity,ires,ires_old
+ double precision dcj
+ integer rescode,kkk,lll,icha,cou,kupa,iprzes
+ logical lsecondary
+ integer iterter(maxres)
+ double precision efree_temp
ibeg=1
ishift1=0
- ishift=0
-c write (2,*) "UNRES_PDB",unres_pdb
- ires=0
- ires_old=0
- iii=0
- lsecondary=.false.
- nhfrag=0
- nbfrag=0
do
read (ipdbin,'(a80)',end=10) card
-c write (iout,'(a)') card
+! write (iout,'(a)') card
if (card(:5).eq.'HELIX') then
- nhfrag=nhfrag+1
- lsecondary=.true.
- read(card(22:25),*) hfrag(1,nhfrag)
- read(card(34:37),*) hfrag(2,nhfrag)
+ nhfrag=nhfrag+1
+ lsecondary=.true.
+ read(card(22:25),*) hfrag(1,nhfrag)
+ read(card(34:37),*) hfrag(2,nhfrag)
endif
if (card(:5).eq.'SHEET') then
- nbfrag=nbfrag+1
- lsecondary=.true.
- read(card(24:26),*) bfrag(1,nbfrag)
- read(card(35:37),*) bfrag(2,nbfrag)
-crc----------------------------------------
-crc to be corrected !!!
- bfrag(3,nbfrag)=bfrag(1,nbfrag)
- bfrag(4,nbfrag)=bfrag(2,nbfrag)
-crc----------------------------------------
+ nbfrag=nbfrag+1
+ lsecondary=.true.
+ read(card(24:26),*) bfrag(1,nbfrag)
+ read(card(35:37),*) bfrag(2,nbfrag)
+!rc----------------------------------------
+!rc to be corrected !!!
+ bfrag(3,nbfrag)=bfrag(1,nbfrag)
+ bfrag(4,nbfrag)=bfrag(2,nbfrag)
+!rc----------------------------------------
+ endif
+ if (card(:3).eq.'END') then
+ goto 10
+ else if (card(:3).eq.'TER') then
+! End current chain
+ ires_old=ires+2
+ itype(ires_old-1)=ntyp1
+ iterter(ires_old-1)=1
+ itype(ires_old)=ntyp1
+ ishift1=ishift1+1
+ ibeg=2
+! write (iout,*) "Chain ended",ires,ishift,ires_old
+ if (unres_pdb) then
+ do j=1,3
+ dc(j,ires)=sccor(j,iii)
+ enddo
+ else
+ call sccenter(ires,iii,sccor)
+ endif
+c iii=0
endif
- if (card(:3).eq.'END' .or. card(:3).eq.'TER') goto 10
-c Read free energy
+! Read free energy
if (index(card,"FREE ENERGY").gt.0) read(card(35:),*) efree_temp
-C Fish out the ATOM cards.
+! Fish out the ATOM cards.
if (index(card(1:4),'ATOM').gt.0) then
read (card(12:16),*) atom
-c write (iout,*) "! ",atom," !",ires
-c if (atom.eq.'CA' .or. atom.eq.'CH3') then
+c write (2,'(a)') card
+! write (iout,*) "! ",atom," !",ires
+! if (atom.eq.'CA' .or. atom.eq.'CH3') then
read (card(23:26),*) ires
read (card(18:20),'(a3)') res
-c write (iout,*) "ires",ires,ires-ishift+ishift1,
-c & " ires_old",ires_old
-c write (iout,*) "ishift",ishift," ishift1",ishift1
-c write (iout,*) "IRES",ires-ishift+ishift1,ires_old
+! write (iout,*) "ires",ires,ires-ishift+ishift1,
+! & " ires_old",ires_old
+! write (iout,*) "ishift",ishift," ishift1",ishift1
+! write (iout,*) "IRES",ires-ishift+ishift1,ires_old
if (ires-ishift+ishift1.ne.ires_old) then
-C Calculate the CM of the preceding residue.
-c if (ibeg.eq.0) call sccenter(ires,iii,sccor)
+! Calculate the CM of the preceding residue.
+! if (ibeg.eq.0) call sccenter(ires,iii,sccor)
if (ibeg.eq.0) then
-c write (iout,*) "Calculating sidechain center iii",iii
+! write (iout,*) "Calculating sidechain center iii",iii
if (unres_pdb) then
do j=1,3
- dc(j,ires)=sccor(j,iii)
+ dc(j,ires+nres)=sccor(j,iii)
enddo
else
call sccenter(ires_old,iii,sccor)
endif
iii=0
endif
-C Start new residue.
+! Start new residue.
if (res.eq.'Cl-' .or. res.eq.'Na+') then
ires=ires_old
cycle
endif
ires=ires-ishift+ishift1
ires_old=ires
-c write (iout,*) "ishift",ishift," ires",ires,
-c & " ires_old",ires_old
- ibeg=0
+! write (iout,*) "ishift",ishift," ires",ires,&
+! " ires_old",ires_old
+ ibeg=0
+ else if (ibeg.eq.2) then
+! Start a new chain
+ ishift=-ires_old+ires-1 !!!!!
+ ishift1=ishift1-1 !!!!!
+! write (iout,*) "New chain started",ires,ishift,ishift1,"!"
+ ires=ires-ishift+ishift1
+ ires_old=ires
+ ibeg=0
else
ishift=ishift-(ires-ishift+ishift1-ires_old-1)
ires=ires-ishift+ishift1
else
ires=ires-ishift+ishift1
endif
-c write (iout,*) "ires_old",ires_old," ires",ires
+! write (iout,*) "ires_old",ires_old," ires",ires
if (card(27:27).eq."A" .or. card(27:27).eq."B") then
-c ishift1=ishift1+1
+! ishift1=ishift1+1
endif
-c write (2,*) "ires",ires," res ",res," ity",ity
+! write (2,*) "ires",ires," res ",res!," ity"!,ity
if (atom.eq.'CA' .or. atom.eq.'CH3' .or.
& res.eq.'NHE'.and.atom(:2).eq.'HN') then
read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
-c write (iout,*) "backbone ",atom
+! write (iout,*) "backbone ",atom
#ifdef DEBUG
write (iout,'(2i3,2x,a,3f8.3)')
& ires,itype(ires),res,(c(j,ires),j=1,3)
do j=1,3
sccor(j,iii)=c(j,ires)
enddo
- if (ishift.ne.0) then
- ires_ca=ires+ishift-ishift1
- else
- ires_ca=ires
- endif
-c write (*,*) card(23:27),ires,itype(ires)
- else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
- & atom.ne.'N' .and. atom.ne.'C' .and.
- & atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
+c write (2,*) card(23:27),ires,itype(ires),iii
+ else if (atom.ne.'O'.and.atom(1:1).ne.'H' .and.
+ & atom.ne.'N' .and. atom.ne.'C' .and.
+ & atom(:2).ne.'1H' .and. atom(:2).ne.'2H' .and.
& atom.ne.'OXT' .and. atom(:2).ne.'3H') then
-c write (iout,*) "sidechain ",atom
+! write (iout,*) "sidechain ",atom
iii=iii+1
read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
+c write (2,*) "iii",iii
endif
endif
enddo
- 10 continue
-#ifdef DEBUG
- write (iout,'(a,i5)') ' Number of residues found: ',ires
-#endif
- if (ires.eq.0) return
-C Calculate the CM of the last side chain.
- if (iii.gt.0) then
- if (unres_pdb) then
- do j=1,3
- dc(j,ires)=sccor(j,iii)
- enddo
- else
- call sccenter(ires,iii,sccor)
- endif
- endif
+ 10 write (iout,'(a,i5)') ' Nres: ',ires
+C Calculate dummy residue coordinates inside the "chain" of a multichain
+C system
nres=ires
+ do i=2,nres-1
+c write (iout,*) i,itype(i)
+
+ if (itype(i).eq.ntyp1) then
+ if (itype(i+1).eq.ntyp1) then
+C 16/01/2014 by Adasko: Adding to dummy atoms in the chain
+C first is connected prevous chain (itype(i+1).eq.ntyp1)=true
+C second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
+C if (unres_pdb) then
+C 2/15/2013 by Adam: corrected insertion of the last dummy residue
+C call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
+C if (fail) then
+C e2(1)=0.0d0
+C e2(2)=1.0d0
+C e2(3)=0.0d0
+C endif !fail
+C do j=1,3
+C c(j,i)=c(j,i-1)-1.9d0*e2(j)
+C enddo
+C else !unres_pdb
+ do j=1,3
+ dcj=(c(j,i-2)-c(j,i-3))/2.0
+ c(j,i)=c(j,i-1)+dcj
+ c(j,nres+i)=c(j,i)
+ enddo
+C endif !unres_pdb
+ else !itype(i+1).eq.ntyp1
+C if (unres_pdb) then
+C 2/15/2013 by Adam: corrected insertion of the first dummy residue
+C call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
+C if (fail) then
+C e2(1)=0.0d0
+C e2(2)=1.0d0
+C e2(3)=0.0d0
+C endif
+C do j=1,3
+C c(j,i)=c(j,i+1)-1.9d0*e2(j)
+C enddo
+C else !unres_pdb
+ do j=1,3
+ dcj=(c(j,i+3)-c(j,i+2))/2.0
+ c(j,i)=c(j,i+1)-dcj
+ c(j,nres+i)=c(j,i)
+ enddo
+C endif !unres_pdb
+ endif !itype(i+1).eq.ntyp1
+ endif !itype.eq.ntyp1
+ enddo
+C Calculate the CM of the last side chain.
+ call sccenter(ires,iii,sccor)
nsup=nres
nstart_sup=1
if (itype(nres).ne.10) then
nres=nres+1
itype(nres)=ntyp1
- if (unres_pdb) then
-C 2/15/2013 by Adam: corrected insertion of the last dummy residue
- call refsys(nres-3,nres-2,nres-1,e1,e2,e3,fail)
- if (fail) then
- e2(1)=0.0d0
- e2(2)=1.0d0
- e2(3)=0.0d0
- endif
- do j=1,3
- c(j,nres)=c(j,nres-1)-3.8d0*e2(j)
- enddo
- else
do j=1,3
- dcj=c(j,nres-2)-c(j,nres-3)
+ dcj=(c(j,nres-2)-c(j,nres-3))/2.0
c(j,nres)=c(j,nres-1)+dcj
c(j,2*nres)=c(j,nres)
enddo
- endif
endif
do i=2,nres-1
do j=1,3
if (itype(1).eq.ntyp1) then
nsup=nsup-1
nstart_sup=2
- if (unres_pdb) then
-C 2/15/2013 by Adam: corrected insertion of the first dummy residue
- call refsys(2,3,4,e1,e2,e3,fail)
- if (fail) then
- e2(1)=0.0d0
- e2(2)=1.0d0
- e2(3)=0.0d0
- endif
- do j=1,3
- c(j,1)=c(j,2)-3.8d0*e2(j)
- enddo
- else
do j=1,3
- dcj=c(j,4)-c(j,3)
+ dcj=(c(j,4)-c(j,3))/2.0
c(j,1)=c(j,2)-dcj
c(j,nres+1)=c(j,1)
enddo
- endif
endif
-C Copy the coordinates to reference coordinates
-c do i=1,2*nres
-c do j=1,3
-c cref(j,i)=c(j,i)
-c enddo
-c enddo
C Calculate internal coordinates.
- if (lprn) then
- write (iout,'(/a)')
- & "Cartesian coordinates of the reference structure"
- write (iout,'(a,3(3x,a5),5x,3(3x,a5))')
- & "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
+ write (iout,100)
do ires=1,nres
- write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)')
- & restyp(itype(ires)),ires,(c(j,ires),j=1,3),
- & (c(j,ires+nres),j=1,3)
- enddo
- endif
-C Calculate internal coordinates.
- write (iout,'(a)')
- & "Backbone and SC coordinates as read from the PDB"
- do ires=1,nres
write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)')
& ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
& (c(j,nres+ires),j=1,3)
- enddo
- call int_from_cart(.true.,.false.)
- call sc_loc_geom(.false.)
- do i=1,nres
- thetaref(i)=theta(i)
- phiref(i)=phi(i)
enddo
+ call int_from_cart(.true.,.false.)
+ call flush(iout)
do i=1,nres-1
do j=1,3
dc(j,i)=c(j,i+1)-c(j,i)
enddo
c call chainbuild
C Copy the coordinates to reference coordinates
- do i=1,2*nres
+ do i=1,nres
do j=1,3
cref(j,i)=c(j,i)
+ cref(j,i+nres)=c(j,i+nres)
enddo
enddo
+ 100 format ('Residue alpha-carbon coordinates ',
+ & ' centroid coordinates'/
+ 1 ' ', 6X,'X',7X,'Y',7X,'Z',
+ & 12X,'X',7X,'Y',7X,'Z')
+ 110 format (a,'(',i3,')',6f12.5)
-
- do j=1,nbfrag
- do i=1,4
- bfrag(i,j)=bfrag(i,j)-ishift
- enddo
- enddo
-
- do j=1,nhfrag
- do i=1,2
- hfrag(i,j)=hfrag(i,j)-ishift
- enddo
- enddo
ishift_pdb=ishift
return
end
c---------------------------------------------------------------------------
subroutine int_from_cart(lside,lprn)
- implicit real*8 (a-h,o-z)
+ implicit none
include 'DIMENSIONS'
include 'DIMENSIONS.ZSCOPT'
include 'COMMON.LOCAL'
include 'COMMON.IOUNITS'
include 'COMMON.GEO'
include 'COMMON.NAMES'
- include 'COMMON.CONTROL'
- character*3 seq,res
-c character*5 atom
+ character*3 seq,atom,res
character*80 card
- dimension sccor(3,20)
+ double precision sccor(3,50)
integer rescode
+ double precision dist,alpha,beta,di
+ integer i,j,iti
logical lside,lprn
- if (lprn) then
+ if (lprn) then
write (iout,'(/a)')
& 'Internal coordinates calculated from crystal structure.'
if (lside) then
write (iout,'(8a)') ' Res ',' dvb',' Theta',
- & ' Gamma',' Dsc_id',' Dsc',' Alpha',
- & ' Beta '
+ & ' Phi',' Dsc_id',' Dsc',' Alpha',
+ & ' Omega'
else
write (iout,'(4a)') ' Res ',' dvb',' Theta',
- & ' Gamma'
+ & ' Phi'
endif
- endif
- do i=1,nres-1
+ endif
+ do i=2,nres
iti=itype(i)
- if (dist(i,i+1).lt.2.0D0 .or. dist(i,i+1).gt.5.0D0) then
+c write (iout,*) i,i-1,(c(j,i),j=1,3),(c(j,i-1),j=1,3),dist(i,i-1)
+ if (itype(i-1).ne.ntyp1 .and. itype(i).ne.ntyp1 .and.
+ & (dist(i,i-1).lt.1.0D0 .or. dist(i,i-1).gt.6.0D0)) then
write (iout,'(a,i4)') 'Bad Cartesians for residue',i
-ctest stop
+ stop
endif
- vbld(i+1)=dist(i,i+1)
- vbld_inv(i+1)=1.0d0/vbld(i+1)
- if (i.gt.1) theta(i+1)=alpha(i-1,i,i+1)
+ vbld(i)=dist(i-1,i)
+ vbld_inv(i)=1.0d0/vbld(i)
+ theta(i+1)=alpha(i-1,i,i+1)
if (i.gt.2) phi(i+1)=beta(i-2,i-1,i,i+1)
enddo
-c if (unres_pdb) then
-c if (itype(1).eq.ntyp1) then
-c theta(3)=90.0d0*deg2rad
-c phi(4)=180.0d0*deg2rad
-c vbld(2)=3.8d0
-c vbld_inv(2)=1.0d0/vbld(2)
-c endif
-c if (itype(nres).eq.ntyp1) then
-c theta(nres)=90.0d0*deg2rad
-c phi(nres)=180.0d0*deg2rad
-c vbld(nres)=3.8d0
-c vbld_inv(nres)=1.0d0/vbld(2)
-c endif
+c if (itype(1).eq.ntyp1) then
+c do j=1,3
+c c(j,1)=c(j,2)+(c(j,3)-c(j,4))
+c enddo
+c endif
+c if (itype(nres).eq.ntyp1) then
+c do j=1,3
+c c(j,nres)=c(j,nres-1)+(c(j,nres-2)-c(j,nres-3))
+c enddo
c endif
if (lside) then
do i=2,nres-1
do j=1,3
- c(j,maxres2)=0.5D0*(2*c(j,i)+(c(j,i-1)-c(j,i))*vbld_inv(i)
- & +(c(j,i+1)-c(j,i))*vbld_inv(i+1))
+ c(j,maxres2)=0.5D0*(c(j,i-1)+c(j,i+1))
enddo
iti=itype(i)
di=dist(i,nres+i)
-C 10/03/12 Adam: Correction for zero SC-SC bond length
- if (itype(i).ne.10 .and. itype(i).ne.ntyp1. and. di.eq.0.0d0)
- & di=dsc(itype(i))
- vbld(i+nres)=di
+ vbld(i+nres)=di
if (itype(i).ne.10) then
vbld_inv(i+nres)=1.0d0/di
else
alph(i)=alpha(nres+i,i,maxres2)
omeg(i)=beta(nres+i,i,maxres2,i+1)
endif
- if (lprn)
- & write (iout,'(a3,i4,7f10.3)') restyp(iti),i,vbld(i),
- & rad2deg*theta(i),rad2deg*phi(i),dsc(iti),vbld(nres+i),
- & rad2deg*alph(i),rad2deg*omeg(i)
+ if (iti.ne.10) then
+ alph(i)=alpha(nres+i,i,maxres2)
+ omeg(i)=beta(nres+i,i,maxres2,i+1)
+ endif
+ if (lprn)
+ & write (iout,'(a3,i4,7f10.3)') restyp(iti),i,dist(i,i-1),
+ & rad2deg*theta(i),rad2deg*phi(i),dsc(iti),di,
+ & rad2deg*alph(i),rad2deg*omeg(i)
enddo
else if (lprn) then
do i=2,nres
iti=itype(i)
write (iout,'(a3,i4,7f10.3)') restyp(iti),i,dist(i,i-1),
- & rad2deg*theta(i),rad2deg*phi(i)
+ & rad2deg*theta(i),rad2deg*phi(i)
enddo
endif
return
end
-c-------------------------------------------------------------------------------
+c---------------------------------------------------------------------------
+ subroutine sccenter(ires,nscat,sccor)
+ implicit none
+ include 'DIMENSIONS'
+ include 'COMMON.CHAIN'
+ integer ires,nscat,i,j
+ double precision sccor(3,50),sccmj
+ do j=1,3
+ sccmj=0.0D0
+ do i=1,nscat
+ sccmj=sccmj+sccor(j,i)
+ enddo
+ dc(j,ires)=sccmj/nscat
+ enddo
+ return
+ end
+c---------------------------------------------------------------------------
subroutine sc_loc_geom(lprn)
implicit real*8 (a-h,o-z)
include 'DIMENSIONS'
include 'COMMON.GEO'
include 'COMMON.NAMES'
include 'COMMON.CONTROL'
+ include 'COMMON.SETUP'
double precision x_prime(3),y_prime(3),z_prime(3)
logical lprn
do i=1,nres-1
enddo
enddo
do i=2,nres-1
- if (itype(i).ne.10) then
+ if (itype(i).ne.10 .and. itype(i).ne.ntyp1) then
do j=1,3
dc_norm(j,i+nres)=vbld_inv(i+nres)*(c(j,i+nres)-c(j,i))
enddo
sinfac2=0.5d0/(1.0d0-costtab(i+1))
sinfac=dsqrt(sinfac2)
it=itype(i)
- if (it.ne.10) then
+ if (it.ne.10 .and. itype(i).ne.ntyp1) then
c
C Compute the axes of tghe local cartesian coordinates system; store in
c x_prime, y_prime and z_prime
x_prime(j) = (dc_norm(j,i) - dc_norm(j,i-1))*cosfac
y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
enddo
+c write (iout,*) "x_prime",(x_prime(j),j=1,3)
+c write (iout,*) "y_prime",(y_prime(j),j=1,3)
call vecpr(x_prime,y_prime,z_prime)
+c write (iout,*) "z_prime",(z_prime(j),j=1,3)
c
C Transform the unit vector of the ith side-chain centroid, dC_norm(*,i),
C to local coordinate system. Store in xx, yy, zz.
endif
enddo
if (lprn) then
+ write (iout,*) "xxref,yyref,zzref"
do i=2,nres
iti=itype(i)
- write (iout,'(a3,i4,3f10.5)') restyp(iti),i,xxref(i),
- & yyref(i),zzref(i)
+ write (iout,'(a3,i4,3f10.5)') restyp(iti),i,xxref(i),yyref(i),
+ & zzref(i)
enddo
endif
return
end
c---------------------------------------------------------------------------
- subroutine sccenter(ires,nscat,sccor)
- implicit real*8 (a-h,o-z)
- include 'DIMENSIONS'
- include 'COMMON.CHAIN'
- dimension sccor(3,20)
- do j=1,3
- sccmj=0.0D0
- do i=1,nscat
- sccmj=sccmj+sccor(j,i)
- enddo
- dc(j,ires)=sccmj/nscat
- enddo
- return
- end
-c---------------------------------------------------------------------------
subroutine bond_regular
- implicit real*8 (a-h,o-z)
- include 'DIMENSIONS'
+ implicit none
+ include 'DIMENSIONS'
include 'COMMON.VAR'
- include 'COMMON.LOCAL'
- include 'COMMON.CALC'
+ include 'COMMON.LOCAL'
include 'COMMON.INTERACT'
include 'COMMON.CHAIN'
+ integer i,i1,i2
do i=1,nres-1
vbld(i+1)=vbl
- vbld_inv(i+1)=1.0d0/vbld(i+1)
- vbld(i+1+nres)=dsc(itype(i+1))
- vbld_inv(i+1+nres)=dsc_inv(itype(i+1))
+ vbld_inv(i+1)=vblinv
+ vbld(i+1+nres)=dsc(iabs(itype(i+1)))
+ vbld_inv(i+1+nres)=dsc_inv(iabs(itype(i+1)))
c print *,vbld(i+1),vbld(i+1+nres)
enddo
+c Adam 2/26/20 Alter virtual bonds for non-blocking end groups of each chain
+ do i=1,nchain
+ i1=chain_border(1,i)
+ i2=chain_border(2,i)
+ if (i1.gt.1) then
+ vbld(i1)=vbld(i1)/2
+ vbld_inv(i1)=vbld_inv(i1)*2
+ endif
+ if (i2.lt.nres) then
+ vbld(i2+1)=vbld(i2+1)/2
+ vbld_inv(i2+1)=vbld_inv(i2+1)*2
+ endif
+ enddo
return
end
+c---------------------------------------------------------------------------
subroutine readpdb_template(k)
-C Read the PDB file with gaps for read_constr_homology with read2sigma
+C Read the PDB file for read_constr_homology with read2sigma
C and convert the peptide geometry into virtual-chain geometry.
implicit real*8 (a-h,o-z)
include 'DIMENSIONS'
include 'DIMENSIONS.ZSCOPT'
- include 'DIMENSIONS.FREE'
include 'COMMON.LOCAL'
include 'COMMON.VAR'
include 'COMMON.CHAIN'
include 'COMMON.GEO'
include 'COMMON.NAMES'
include 'COMMON.CONTROL'
+ include 'COMMON.SETUP'
integer i,j,ibeg,ishift1,ires,iii,ires_old,ishift,ity
logical lprn /.false./,fail
double precision e1(3),e2(3),e3(3)
character*5 atom
character*80 card
double precision sccor(3,20)
- integer rescode
- efree_temp=0.0d0
+ integer rescode,iterter(maxres)
+ do i=1,maxres
+ iterter(i)=0
+ enddo
ibeg=1
ishift1=0
ishift=0
lsecondary=.false.
nhfrag=0
nbfrag=0
- do
+ do
read (ipdbin,'(a80)',end=10) card
-c write (iout,'(a)') card
- if (card(:3).eq.'END' .or. card(:3).eq.'TER') goto 10
+ if (card(:3).eq.'END') then
+ goto 10
+ else if (card(:3).eq.'TER') then
+C End current chain
+ ires_old=ires+2
+ itype(ires_old-1)=ntyp1
+ iterter(ires_old-1)=1
+ itype(ires_old)=ntyp1
+ iterter(ires_old)=1
+ ibeg=2
+c write (iout,*) "Chain ended",ires,ishift,ires_old
+ if (unres_pdb) then
+ do j=1,3
+ dc(j,ires)=sccor(j,iii)
+ enddo
+ else
+ call sccenter(ires,iii,sccor)
+ endif
+ endif
C Fish out the ATOM cards.
if (index(card(1:4),'ATOM').gt.0) then
read (card(12:16),*) atom
c write (iout,*) "IRES",ires-ishift+ishift1,ires_old
if (ires-ishift+ishift1.ne.ires_old) then
C Calculate the CM of the preceding residue.
-c if (ibeg.eq.0) call sccenter(ires,iii,sccor)
if (ibeg.eq.0) then
-c write (iout,*) "Calculating sidechain center iii",iii
if (unres_pdb) then
do j=1,3
dc(j,ires)=sccor(j,iii)
ires_old=ires
c write (iout,*) "ishift",ishift," ires",ires,
c & " ires_old",ires_old
+c write (iout,*) "ires",ires," ibeg",ibeg," ishift",ishift
+ ibeg=0
+ else if (ibeg.eq.2) then
+c Start a new chain
+ ishift=-ires_old+ires-1
+ ires=ires_old+1
+c write (iout,*) "New chain started",ires,ishift
ibeg=0
else
ishift=ishift-(ires-ishift+ishift1-ires_old-1)
ires=ires-ishift+ishift1
endif
c write (iout,*) "ires_old",ires_old," ires",ires
- if (card(27:27).eq."A" .or. card(27:27).eq."B") then
+c if (card(27:27).eq."A" .or. card(27:27).eq."B") then
c ishift1=ishift1+1
- endif
+c endif
c write (2,*) "ires",ires," res ",res," ity",ity
if (atom.eq.'CA' .or. atom.eq.'CH3' .or.
& res.eq.'NHE'.and.atom(:2).eq.'HN') then
read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3)
-c write (iout,*) "backbone ",atom
+c write (iout,*) "backbone ",atom ,ires,res, (c(j,ires),j=1,3)
#ifdef DEBUG
write (iout,'(2i3,2x,a,3f8.3)')
& ires,itype(ires),res,(c(j,ires),j=1,3)
endif
endif
enddo
- 10 continue
-#ifdef DEBUG
- write (iout,'(a,i5)') ' Number of residues found: ',ires
-#endif
- if (ires.eq.0) return
+ 10 write (iout,'(a,i5)') ' Nres: ',ires
+C Calculate dummy residue coordinates inside the "chain" of a multichain
+C system
+ nres=ires
+ do i=2,nres-1
+c write (iout,*) i,itype(i),itype(i+1)
+ if (itype(i).eq.ntyp1.and.iterter(i).eq.1) then
+ if (itype(i+1).eq.ntyp1.and.iterter(i+1).eq.1 ) then
+C 16/01/2014 by Adasko: Adding to dummy atoms in the chain
+C first is connected prevous chain (itype(i+1).eq.ntyp1)=true
+C second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
+ if (unres_pdb) then
+C 2/15/2013 by Adam: corrected insertion of the last dummy residue
+ call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
+ if (fail) then
+ e2(1)=0.0d0
+ e2(2)=1.0d0
+ e2(3)=0.0d0
+ endif !fail
+ do j=1,3
+ c(j,i)=c(j,i-1)-1.9d0*e2(j)
+ enddo
+ else !unres_pdb
+ do j=1,3
+ dcj=(c(j,i-2)-c(j,i-3))/2.0
+ if (dcj.eq.0) dcj=1.23591524223
+ c(j,i)=c(j,i-1)+dcj
+ c(j,nres+i)=c(j,i)
+ enddo
+ endif !unres_pdb
+ else !itype(i+1).eq.ntyp1
+ if (unres_pdb) then
+C 2/15/2013 by Adam: corrected insertion of the first dummy residue
+ call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
+ if (fail) then
+ e2(1)=0.0d0
+ e2(2)=1.0d0
+ e2(3)=0.0d0
+ endif
+ do j=1,3
+ c(j,i)=c(j,i+1)-1.9d0*e2(j)
+ enddo
+ else !unres_pdb
+ do j=1,3
+ dcj=(c(j,i+3)-c(j,i+2))/2.0
+ if (dcj.eq.0) dcj=1.23591524223
+ c(j,i)=c(j,i+1)-dcj
+ c(j,nres+i)=c(j,i)
+ enddo
+ endif !unres_pdb
+ endif !itype(i+1).eq.ntyp1
+ endif !itype.eq.ntyp1
+ enddo
C Calculate the CM of the last side chain.
- if (iii.gt.0) then
if (unres_pdb) then
do j=1,3
dc(j,ires)=sccor(j,iii)
else
call sccenter(ires,iii,sccor)
endif
- endif
- nres=ires
nsup=nres
nstart_sup=1
if (itype(nres).ne.10) then
nres=nres+1
itype(nres)=ntyp1
+ if (unres_pdb) then
+C 2/15/2013 by Adam: corrected insertion of the last dummy residue
+ call refsys(nres-3,nres-2,nres-1,e1,e2,e3,fail)
+ if (fail) then
+ e2(1)=0.0d0
+ e2(2)=1.0d0
+ e2(3)=0.0d0
+ endif
+ do j=1,3
+ c(j,nres)=c(j,nres-1)-1.9d0*e2(j)
+ enddo
+ else
do j=1,3
- dcj=c(j,nres-2)-c(j,nres-3)
+ dcj=(c(j,nres-2)-c(j,nres-3))/2.0
+ if (dcj.eq.0) dcj=1.23591524223
c(j,nres)=c(j,nres-1)+dcj
c(j,2*nres)=c(j,nres)
enddo
endif
+ endif
do i=2,nres-1
do j=1,3
c(j,i+nres)=dc(j,i)
e2(3)=0.0d0
endif
do j=1,3
- c(j,1)=c(j,2)-3.8d0*e2(j)
+ c(j,1)=c(j,2)-1.9d0*e2(j)
enddo
else
do j=1,3
- dcj=c(j,4)-c(j,3)
+ dcj=(c(j,4)-c(j,3))/2.0
c(j,1)=c(j,2)-dcj
c(j,nres+1)=c(j,1)
enddo
endif
endif
+C Copy the coordinates to reference coordinates
+c do i=1,2*nres
+c do j=1,3
+c cref(j,i)=c(j,i)
+c enddo
+c enddo
C Calculate internal coordinates.
- if (lprn) then
+ if (out_template_coord) then
write (iout,'(/a)')
& "Cartesian coordinates of the reference structure"
write (iout,'(a,3(3x,a5),5x,3(3x,a5))')
enddo
endif
C Calculate internal coordinates.
- write (iout,'(a)')
- & "Backbone and SC coordinates as read from the PDB"
- do ires=1,nres
- write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)')
- & ires,itype(ires),restyp(itype(ires)),(c(j,ires),j=1,3),
- & (c(j,nres+ires),j=1,3)
- enddo
- call int_from_cart(.true.,.false.)
- call sc_loc_geom(.false.)
+c call int_from_cart1(.false.)
+ call int_from_cart(.true.,.true.)
+ call sc_loc_geom(.true.)
do i=1,nres
thetaref(i)=theta(i)
phiref(i)=phi(i)
c write (iout,*) i,(dc(j,i+nres),j=1,3),(dc_norm(j,i+nres),j=1,3),
c & vbld_inv(i+nres)
enddo
-c call chainbuild
-C Copy the coordinates to reference coordinates
- do i=1,2*nres
+ do i=1,nres
do j=1,3
cref(j,i)=c(j,i)
+ cref(j,i+nres)=c(j,i+nres)
+ enddo
+ enddo
+ do i=1,2*nres
+ do j=1,3
chomo(j,i,k)=c(j,i)
enddo
enddo
-
- ishift_pdb=ishift
return
end
+
+