subroutine readpdb C Read the PDB file and convert the peptide geometry into virtual-chain C geometry. implicit none include 'DIMENSIONS' include 'DIMENSIONS.ZSCOPT' include 'COMMON.CONTROL' include 'COMMON.LOCAL' include 'COMMON.VAR' include 'COMMON.CHAIN' include 'COMMON.INTERACT' include 'COMMON.IOUNITS' include 'COMMON.GEO' include 'COMMON.NAMES' include 'COMMON.SBRIDGE' character*3 seq,atom,res character*80 card 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 ibeg=1 ishift1=0 do read (ipdbin,'(a80)',end=10) card if (card(:3).eq.'END') then goto 10 else if (card(:3).eq.'TER') then C End current chain c ires_old=ires+1 ires_old=ires+2 itype(ires_old-1)=ntyp1 itype(ires_old)=ntyp1 ibeg=2 c write (iout,*) "Chain ended",ires,ishift,ires_old call sccenter(ires,iii,sccor) endif C Fish out the ATOM cards. if (index(card(1:4),'ATOM').gt.0) then read (card(14:16),'(a3)') atom if (atom.eq.'CA' .or. atom.eq.'CH3') then C Calculate the CM of the preceding residue. if (ibeg.eq.0) then call sccenter(ires,iii,sccor) endif C Start new residue. c write (iout,'(a80)') card read (card(23:26),*) ires read (card(18:20),'(a3)') res if (ibeg.eq.1) then ishift=ires-1 if (res.ne.'GLY' .and. res.ne. 'ACE') then ishift=ishift-1 itype(1)=ntyp1 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 ires=ires-ishift c write (2,*) "ires",ires," ishift",ishift if (res.eq.'ACE') then ity=10 else itype(ires)=rescode(ires,res,0) endif read(card(31:54),'(3f8.3)') (c(j,ires),j=1,3) read(card(61:66),*) bfac(ires) write (iout,'(2i3,2x,a,3f8.3,5x,f8.3)') & ires,itype(ires),res,(c(j,ires),j=1,3),bfac(ires) 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(1:1).ne.'Q' .and. atom(1:2).ne.'1H' .and. & atom(1:2).ne.'2H' .and. atom(1:2).ne.'3H' .and. & atom.ne.'N ' .and. atom.ne.'C ') then iii=iii+1 read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3) endif endif enddo 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 do j=1,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 do i=2,nres-1 do j=1,3 c(j,i+nres)=dc(j,i) enddo enddo do j=1,3 c(j,nres+1)=c(j,1) c(j,2*nres)=c(j,nres) enddo if (itype(1).eq.ntyp1) then nsup=nsup-1 nstart_sup=2 do j=1,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 C Calculate internal coordinates. 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.) write (iout,*) "After int_from_cart" call flush(iout) do i=1,nres-1 do j=1,3 dc(j,i)=c(j,i+1)-c(j,i) dc_norm(j,i)=dc(j,i)*vbld_inv(i+1) enddo enddo do i=2,nres-1 do j=1,3 dc(j,i+nres)=c(j,i+nres)-c(j,i) dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres) enddo 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,nres do j=1,3 cref(j,i)=c(j,i) cref(j,i+nres)=c(j,i+nres) enddo enddo 100 format (//' alpha-carbon coordinates ', & ' centroid coordinates'/ 1 ' ', 6X,'X',11X,'Y',11X,'Z', & 10X,'X',11X,'Y',11X,'Z') 110 format (a,'(',i3,')',6f12.5) ishift_pdb=ishift return end c--------------------------------------------------------------------------- subroutine int_from_cart(lside,lprn) implicit none include 'DIMENSIONS' include 'DIMENSIONS.ZSCOPT' include 'COMMON.LOCAL' include 'COMMON.VAR' include 'COMMON.CHAIN' include 'COMMON.INTERACT' include 'COMMON.IOUNITS' include 'COMMON.GEO' include 'COMMON.NAMES' character*3 seq,atom,res character*80 card double precision sccor(3,50) integer rescode double precision dist,alpha,beta,di integer i,j,iti logical lside,lprn if (lprn) then write (iout,'(/a)') & 'Internal coordinates calculated from crystal structure.' if (lside) then write (iout,'(8a)') ' Res ',' dvb',' Theta', & ' Phi',' Dsc_id',' Dsc',' Alpha', & ' Omega' else write (iout,'(4a)') ' Res ',' dvb',' Theta', & ' Phi' endif endif do i=2,nres iti=itype(i) 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 stop endif 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 if (itype(1).eq.ntyp1) then do j=1,3 c(j,1)=c(j,2)+(c(j,3)-c(j,4)) enddo endif if (itype(nres).eq.ntyp1) then do j=1,3 c(j,nres)=c(j,nres-1)+(c(j,nres-2)-c(j,nres-3)) enddo endif if (lside) then do i=2,nres-1 do j=1,3 c(j,maxres2)=0.5D0*(c(j,i-1)+c(j,i+1)) enddo iti=itype(i) di=dist(i,nres+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) enddo endif return end 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