unres
[unres.git] / source / unres / src-HCD-5D / readpdb-mult.F
index 8fd1da8..e603267 100644 (file)
@@ -19,120 +19,184 @@ C geometry.
       double precision sccor(3,50)
       double precision e1(3),e2(3),e3(3)
       integer rescode,iterter(maxres),cou
-      logical fail
-      integer i,j,iii,ires,ires_old,ishift,ishift1,ibeg
-      double precision dcj
+      logical fail,sccalc
+      integer i,j,iii,ires,ires_old,ishift,ishift1,ibeg,ifree
+      double precision dcj!,efree_temp
+      logical zero
       bfac=0.0d0
       do i=1,maxres
          iterter(i)=0
       enddo
       ibeg=1
+      ishift=0
       ishift1=0
       lsecondary=.false.
       nhfrag=0
       nbfrag=0
+      iii=0
+      sccalc=.false.
       do
         read (ipdbin,'(a80)',end=10) card
+c        write (iout,'(a)') card
+c        call flush(iout)
         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
+c          ishift1=ishift1+1
           ibeg=2
-          write (iout,*) "Chain ended",ires,ishift,ires_old
+          write (iout,*) "Chain ended",ires,ishift,ires_old,ibeg
           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
+          sccalc=.true.
         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
+c        if (index(card,"FREE ENERGY").gt.0) then
+c          ifree=index(card,"FREE ENERGY")+12
+c          read(card(ifree:),*,err=1115,end=1115) efree_temp
+c 1115     continue
+c        endif
+! Fish out the ATOM cards.
+        if (index(card(1:4),'ATOM').gt.0) then  
+          sccalc=.false.
+          read (card(12:16),*) atom
+c          write (2,'(a)') card
+c          write (iout,*) "ibeg",ibeg
+c          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
+          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
+c              write (iout,*) "Calculating sidechain center iii",iii
+c              write (iout,*) "ires",ires
+              if (unres_pdb) then
+c                write (iout,'(i5,3f10.5)') ires,(sccor(j,iii),j=1,3)
+                do j=1,3
+                  dc(j,ires_old)=sccor(j,iii)
+                enddo
+              else
+                call sccenter(ires_old,iii,sccor)
+              endif
+              iii=0
+              sccalc=.true.
+            endif
+! Start new residue.
+c            write (iout,*) "ibeg",ibeg
+            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 !!!!!
+c              ishift1=ishift1-1    !!!!!
+c              write (iout,*) "New chain started",ires,ires_old,ishift,
+c     &           ishift1
+              ires=ires-ishift+ishift1
+              write (iout,*) "New chain started ires",ires
+              ires_old=ires
+c              ires=ires_old+1
+              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
+c          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
+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)
+            read(card(61:66),*) bfac(ires)
+c            write (iout,*) "backbone ",atom
+c            write (iout,*) ires,res,(c(j,ires),j=1,3)
+#ifdef DEBUG
+            write (iout,'(i6,i3,2x,a,3f8.3)') 
+     &      ires,itype(ires),res,(c(j,ires),j=1,3)
+#endif
+            iii=iii+1
+            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)
+            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
+     & write (iout,'(a,i7)') ' Nres: ',ires
+c      write (iout,*) "iii",iii
 C Calculate dummy residue coordinates inside the "chain" of a multichain
 C system
       nres=ires
+c      write (iout,*) "dc"
+c      do i=1,nres
+c        write (iout,'(i5,3f10.5)') i,(dc(j,i),j=1,3)
+c      enddo
       do i=2,nres-1
 c        write (iout,*) i,itype(i),itype(i+1),ntyp1,iterter(i)
         if (itype(i).eq.ntyp1.and.iterter(i).eq.1) then
@@ -142,14 +206,14 @@ 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'
+c            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?'
+c            print *,i,'a tu?'
             do j=1,3
              c(j,i)=c(j,i-1)+1.9d0*(-e1(j)+e2(j))/sqrt(2.0d0)
             enddo
@@ -159,6 +223,7 @@ C 2/15/2013 by Adam: corrected insertion of the last dummy residue
             if (dcj.eq.0) dcj=1.23591524223
              c(j,i)=c(j,i-1)+dcj
              c(j,nres+i)=c(j,i)
+             dC(j,i)=c(j,i)
            enddo     
           endif   !unres_pdb
          else     !itype(i+1).eq.ntyp1
@@ -171,7 +236,7 @@ C 2/15/2013 by Adam: corrected insertion of the first dummy residue
               e2(3)=0.0d0
             endif
             do j=1,3
-              c(j,i)=c(j,i+1)-1.9d0*e2(j)
+              c(j,i)=c(j,i+1)+1.9d0*(-e1(j)+e2(j))/sqrt(2.0d0)
             enddo
           else !unres_pdb
            do j=1,3
@@ -179,6 +244,7 @@ C 2/15/2013 by Adam: corrected insertion of the first dummy residue
             if (dcj.eq.0) dcj=1.23591524223
             c(j,i)=c(j,i+1)-dcj
             c(j,nres+i)=c(j,i)
+            dC(j,i)=c(j,i)
            enddo
           endif !unres_pdb
          endif !itype(i+1).eq.ntyp1
@@ -186,13 +252,16 @@ C 2/15/2013 by Adam: corrected insertion of the first dummy residue
       enddo
       write (iout,*) "After loop in readpbd"
 C Calculate the CM of the last side chain.
+      if (.not. sccalc) then
       if (unres_pdb) then
         do j=1,3
           dc(j,ires)=sccor(j,iii)
         enddo
       else 
+c        write (iout,*) "Calling sccenter iii",iii
         call sccenter(ires,iii,sccor)
       endif
+      endif
       nsup=nres
       nstart_sup=1
       if (itype(nres).ne.10) then
@@ -251,19 +320,36 @@ C 2/15/2013 by Adam: corrected insertion of the first dummy residue
       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
-      endif
+      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,i6,3f8.3,5x,3f8.3)')
+     &    restyp(itype(ires)),ires,(c(j,ires),j=1,3),
+     &    (c(j,ires+nres),j=1,3)
+      enddo
       call flush(iout)
+      endif
+      zero=.false.
+      do ires=1,nres
+        zero=zero.or.itype(ires).eq.0
+      enddo
+      if (zero) then
+        write (iout,'(2a)') "Gaps in PDB coordinates detected;",
+     &    " look for ZERO in the control output above."
+        write (iout,'(2a)') "Repair the PDB file using MODELLER",
+     &    " or other softwared and resubmit."
+        call flush(iout)
+        stop
+      endif
 c      write(iout,*)"before int_from_cart nres",nres
       call int_from_cart(.true.,.false.)
       do i=1,nres
         thetaref(i)=theta(i)
         phiref(i)=phi(i)
       enddo
+      dc(:,0)=c(:,1)
       do i=1,nres-1
         do j=1,3
           dc(j,i)=c(j,i+1)-c(j,i)
@@ -292,9 +378,9 @@ C Copy the coordinates to reference coordinates
       enddo
   100 format (//'              alpha-carbon coordinates       ',
      &          '     centroid coordinates'/
-     1          '       ', 6X,'X',11X,'Y',11X,'Z',
+     1          '       ', 7X,'X',11X,'Y',11X,'Z',
      &                          10X,'X',11X,'Y',11X,'Z')
-  110 format (a,'(',i3,')',6f12.5)
+  110 format (a,'(',i4,')',6f12.5)
 cc enddiag
       do j=1,nbfrag     
         do i=1,4                                                       
@@ -333,8 +419,9 @@ C and convert the peptide geometry into virtual-chain geometry.
       character*3 seq,res
       character*5 atom
       character*80 card
-      double precision sccor(3,20)
+      double precision sccor(3,50)
       integer rescode,iterter(maxres)
+      logical zero
       do i=1,maxres
          iterter(i)=0
       enddo
@@ -385,7 +472,7 @@ C Calculate the CM of the preceding residue.
             if (ibeg.eq.0) then
               if (unres_pdb) then
                 do j=1,3
-                  dc(j,ires)=sccor(j,iii)
+                  dc(j,ires_old)=sccor(j,iii)
                 enddo
               else
                 call sccenter(ires_old,iii,sccor)
@@ -462,7 +549,7 @@ c            write (iout,*) "sidechain ",atom
         endif
       enddo
    10 if(me.eq.king.or..not.out1file) 
-     & write (iout,'(a,i5)') ' Nres: ',ires
+     & write (iout,'(a,i7)') ' Nres: ',ires
 C Calculate dummy residue coordinates inside the "chain" of a multichain
 C system
       nres=ires
@@ -502,7 +589,7 @@ C 2/15/2013 by Adam: corrected insertion of the first dummy residue
               e2(3)=0.0d0
             endif
             do j=1,3
-              c(j,i)=c(j,i+1)-1.9d0*e2(j)
+              c(j,i)=c(j,i+1)+1.9d0*(-e1(j)+e2(j))/sqrt(2.0d0)
             enddo
           else !unres_pdb
            do j=1,3
@@ -537,7 +624,7 @@ 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)-1.9d0*e2(j)
+            c(j,nres)=c(j,nres-1)+1.9d0*(-e1(j)+e2(j))/sqrt(2.0d0)
           enddo
         else
         do j=1,3
@@ -569,7 +656,7 @@ 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)-1.9d0*e2(j)
+            c(j,1)=c(j,2)+1.9d0*(e1(j)-e2(j))/dsqrt(2.0d0)
           enddo
         else
         do j=1,3
@@ -590,20 +677,33 @@ C Calculate internal coordinates.
       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)"
+     & "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)') 
+        write (iout,'(a3,1x,i4,3f8.3,5x,3f8.3)') 
      &    restyp(itype(ires)),ires,(c(j,ires),j=1,3),
      &    (c(j,ires+nres),j=1,3)
       enddo
       endif
+      zero=.false.
+      do ires=1,nres
+        zero=zero.or.itype(ires).eq.0
+      enddo
+      if (zero) then
+        write (iout,'(2a)') "Gaps in PDB coordinates detected;",
+     &    " look for ZERO in the control output above."
+        write (iout,'(2a)') "Repair the PDB file using MODELLER",
+     &    " or other softwared and resubmit."
+        call flush(iout)
+        stop
+      endif
 C Calculate internal coordinates.
-      call int_from_cart(.true.,.true.)
+      call int_from_cart(.true.,out_template_coord)
       call sc_loc_geom(.false.)
       do i=1,nres
         thetaref(i)=theta(i)
         phiref(i)=phi(i)
       enddo
+      dc(:,0)=c(:,1)
       do i=1,nres-1
         do j=1,3
           dc(j,i)=c(j,i+1)-c(j,i)