X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2Fsrc_MD-M%2Freadpdb.F;h=778df3c93a9e19b5f1bddae0c66e5a1d9beb0cf3;hb=34d3ad3987785642be58fb2f26557d3314215577;hp=ef48c2a2bb9cc74fcd3faa5bd804b46e6d831f6f;hpb=f690e8b70bab14132839afebf080d4a28363b226;p=unres.git diff --git a/source/unres/src_MD-M/readpdb.F b/source/unres/src_MD-M/readpdb.F index ef48c2a..778df3c 100644 --- a/source/unres/src_MD-M/readpdb.F +++ b/source/unres/src_MD-M/readpdb.F @@ -13,31 +13,21 @@ C geometry. include 'COMMON.CONTROL' include 'COMMON.DISTFIT' include 'COMMON.SETUP' - integer i,j,ibeg,ishift1,ires,iii,ires_old,ishift,ity, - & ishift_pdb - logical lprn /.true./,fail - double precision e1(3),e2(3),e3(3) - double precision dcj,efree_temp - character*3 seq,res - character*5 atom + character*3 seq,atom,res character*80 card - double precision sccor(3,20) - integer rescode - efree_temp=0.0d0 + dimension sccor(3,20) + double precision e1(3),e2(3),e3(3) + integer rescode,iterter(maxres),cou + logical fail + do i=1,maxres + iterter(i)=0 + enddo ibeg=1 - ishift1=0 - ishift=0 -c write (2,*) "UNRES_PDB",unres_pdb - ires=0 - ires_old=0 - nres=0 - iii=0 lsecondary=.false. nhfrag=0 nbfrag=0 - do i=1,100000 + do read (ipdbin,'(a80)',end=10) card -c write (iout,'(a)') card if (card(:5).eq.'HELIX') then nhfrag=nhfrag+1 lsecondary=.true. @@ -59,139 +49,139 @@ crc---------------------------------------- goto 10 else if (card(:3).eq.'TER') then C End current chain - ires_old=ires+1 - ishift1=ishift1+1 + 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 + 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 - iii=0 endif -c Read free energy - if (index(card,"FREE ENERGY").gt.0) read(card(35:),*) efree_temp C 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 - 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 - if (ires-ishift+ishift1.ne.ires_old) then + read (card(14:16),'(a3)') atom + if (atom.eq.'CA' .or. atom.eq.'CH3') 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+nres)=sccor(j,iii) enddo else - call sccenter(ires_old,iii,sccor) + call sccenter(ires,iii,sccor) endif - iii=0 endif C 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 +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 - ires=ires-ishift+ishift1 - ires_old=ires -c write (iout,*) "ishift",ishift," ires",ires, -c & " ires_old",ires_old - ibeg=0 +c write (iout,*) "ires",ires," ibeg",ibeg," ishift",ishift + ibeg=0 else if (ibeg.eq.2) then c Start a new chain -c ishift=-ires_old+ires-1 -c ishift1=ishift1+1 -c write (iout,*) "New chain started",ires,ishift,ishift1,"!" - ires=ires-ishift+ishift1 - ires_old=ires + ishift=-ires_old+ires-1 +c write (iout,*) "New chain started",ires,ishift ibeg=0 - else - ishift=ishift-(ires-ishift+ishift1-ires_old-1) - ires=ires-ishift+ishift1 - ires_old=ires endif - if (res.eq.'ACE' .or. res.eq.'NHE') then + ires=ires-ishift +c write (2,*) "ires",ires," ishift",ishift + if (res.eq.'ACE') then itype(ires)=10 else itype(ires)=rescode(ires,res,0) endif - else - 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 ishift1=ishift1+1 - 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 -#ifdef DEBUG - write (iout,'(2i3,2x,a,3f8.3)') - & ires,itype(ires),res,(c(j,ires),j=1,3) -#endif - iii=iii+1 + if(me.eq.king.or..not.out1file) + & write (iout,'(2i3,2x,a,3f8.3)') + & ires,itype(ires),res,(c(j,ires),j=1,3) + iii=1 do j=1,3 sccor(j,iii)=c(j,ires) enddo -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. - & atom.ne.'OXT' .and. atom(:2).ne.'3H') then -c write (iout,*) "sidechain ",atom + else if (atom.ne.'O '.and.atom(1:1).ne.'H' .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)') ' Number of residues found: ',ires - if (ires.eq.0) return + 10 if(me.eq.king.or..not.out1file) + & 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 -c write (iout,*) "dummy",i,itype(i) - do j=1,3 - c(j,i)=((c(j,i-1)+c(j,i+1))/2+2*c(j,i-1)-c(j,i-2))/2 -c c(j,i)=(c(j,i-1)+c(j,i+1))/2 - dc(j,i)=c(j,i) - enddo - endif + 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 + print *,i,'tu dochodze' + 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 + print *,i,'a tu?' + 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) enddo - else + else call sccenter(ires,iii,sccor) endif - endif -c nres=ires nsup=nres nstart_sup=1 if (itype(nres).ne.10) then @@ -206,11 +196,12 @@ C 2/15/2013 by Adam: corrected insertion of the last dummy residue e2(3)=0.0d0 endif do j=1,3 - c(j,nres)=c(j,nres-1)-3.8d0*e2(j) + 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 @@ -237,47 +228,27 @@ C 2/15/2013 by Adam: corrected insertion of the first dummy residue 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 - 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 C Calculate internal coordinates. if(me.eq.king.or..not.out1file)then - 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 endif +C print *,"before int_from_cart" call int_from_cart(.true.,.false.) call sc_loc_geom(.true.) -c wczesbiej bylo false do i=1,nres thetaref(i)=theta(i) phiref(i)=phi(i) @@ -299,13 +270,6 @@ c & vbld_inv(i+nres) c call chainbuild C Copy the coordinates to reference coordinates C Splits to single chain if occurs - -c do i=1,2*nres -c do j=1,3 -c cref(j,i,cou)=c(j,i) -c enddo -c enddo -c kkk=1 lll=0 cou=1 @@ -343,10 +307,11 @@ c do kkk=1,chain_length c write (iout,*) itype(kkk),(chain_rep(j,kkk,i), j=1,3) c enddo c enddo -c enddiagnostic +c enddiagnostic C makes copy of chains - write (iout,*) "symetr", symetr - + nperm=1 + write (iout,*) "symetr", symetr + if (symetr.gt.1) then call permut(symetr) nperm=1 @@ -392,7 +357,7 @@ c diag 1 ' ', 6X,'X',11X,'Y',11X,'Z', & 10X,'X',11X,'Y',11X,'Z') 110 format (a,'(',i3,')',6f12.5) - + enddo cc enddiag do j=1,nbfrag @@ -406,7 +371,6 @@ cc enddiag hfrag(i,j)=hfrag(i,j)-ishift enddo enddo - ishift_pdb=ishift return end c--------------------------------------------------------------------------- @@ -415,7 +379,7 @@ c--------------------------------------------------------------------------- include 'DIMENSIONS' #ifdef MPI include "mpif.h" -#endif +#endif include 'COMMON.LOCAL' include 'COMMON.VAR' include 'COMMON.CHAIN' @@ -425,29 +389,33 @@ c--------------------------------------------------------------------------- include 'COMMON.NAMES' include 'COMMON.CONTROL' include 'COMMON.SETUP' - character*3 seq,res -c character*5 atom + character*3 seq,atom,res character*80 card dimension sccor(3,20) integer rescode logical lside,lprn +#ifdef MPI if(me.eq.king.or..not.out1file)then +#endif 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 +#ifdef MPI endif +#endif do i=1,nres-1 iti=itype(i) - if (dist(i,i+1).lt.2.0D0 .or. dist(i,i+1).gt.5.0D0) then + if (iti.ne.ntyp1 .and. itype(i+1).ne.ntyp1 .and. + & (dist(i,i+1).lt.2.0D0 .or. dist(i,i+1).gt.5.0D0)) then write (iout,'(a,i4)') 'Bad Cartesians for residue',i ctest stop endif @@ -470,6 +438,7 @@ c vbld(nres)=3.8d0 c vbld_inv(nres)=1.0d0/vbld(2) c endif c endif +c print *,"A TU2" if (lside) then do i=2,nres-1 do j=1,3 @@ -478,9 +447,6 @@ c endif 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 if (itype(i).ne.10) then vbld_inv(i+nres)=1.0d0/di @@ -514,7 +480,7 @@ c------------------------------------------------------------------------------- include 'DIMENSIONS' #ifdef MPI include "mpif.h" -#endif +#endif include 'COMMON.LOCAL' include 'COMMON.VAR' include 'COMMON.CHAIN' @@ -532,7 +498,7 @@ c------------------------------------------------------------------------------- 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 @@ -552,7 +518,7 @@ c------------------------------------------------------------------------------- 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 @@ -592,9 +558,14 @@ c if (lprn) then do i=2,nres iti=itype(i) +#ifdef MPI if(me.eq.king.or..not.out1file) & write (iout,'(a3,i4,3f10.5)') restyp(iti),i,xxref(i), & yyref(i),zzref(i) +#else + write (iout,'(a3,i4,3f10.5)') restyp(iti),i,xxref(i),yyref(i), + & zzref(i) +#endif enddo endif return @@ -626,9 +597,10 @@ c--------------------------------------------------------------------------- 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(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 return end +