pdbread-mult
[unres.git] / source / unres / src-HCD-5D / readpdb-mult.F
index 40bf9ac..76cb6b6 100644 (file)
@@ -20,8 +20,9 @@ C geometry.
       double precision e1(3),e2(3),e3(3)
       integer rescode,iterter(maxres),cou
       logical fail,sccalc
-      integer i,j,iii,ires,ires_old,ishift,ishift1,ibeg
-      double precision dcj,efree_temp
+      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
@@ -36,6 +37,7 @@ C geometry.
       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.
@@ -62,9 +64,9 @@ c        write (iout,'(a)') card
           iterter(ires_old-1)=1
           itype(ires_old)=ntyp1
           iterter(ires_old)=1
-          ishift1=ishift1+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)
@@ -76,7 +78,11 @@ c        write (iout,'(a)') card
           sccalc=.true.
         endif
 ! Read free energy
-        if (index(card,"FREE ENERGY").gt.0) read(card(35:),*) efree_temp
+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.
@@ -89,16 +95,18 @@ c          write (iout,*) "! ",atom," !",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
+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+nres)=sccor(j,iii)
+                  dc(j,ires_old)=sccor(j,iii)
                 enddo
               else
                 call sccenter(ires_old,iii,sccor)
@@ -107,6 +115,7 @@ c              write (iout,*) "Calculating sidechain center iii",iii
               sccalc=.true.
             endif
 ! Start new residue.
+c            write (iout,*) "ibeg",ibeg
             if (res.eq.'Cl-' .or. res.eq.'Na+') then
               ires=ires_old
               cycle
@@ -125,10 +134,13 @@ c              write (iout,*) "BEG ires",ires
             else if (ibeg.eq.2) then
 ! Start a new chain
               ishift=-ires_old+ires-1 !!!!!
-              ishift1=ishift1-1    !!!!!
-c              write (iout,*) "New chain started",ires,ishift,ishift1,"!"
+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
               ishift=ishift-(ires-ishift+ishift1-ires_old-1)
@@ -151,9 +163,10 @@ 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)
-!            write (iout,*) "backbone ",atom
+c            write (iout,*) "backbone ",atom
+c            write (iout,*) ires,res,(c(j,ires),j=1,3)
 #ifdef DEBUG
-            write (iout,'(2i3,2x,a,3f8.3)') 
+            write (iout,'(i6,i3,2x,a,3f8.3)') 
      &      ires,itype(ires),res,(c(j,ires),j=1,3)
 #endif
             iii=iii+1
@@ -178,6 +191,10 @@ 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
@@ -187,14 +204,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
@@ -217,7 +234,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
@@ -312,12 +329,25 @@ C Calculate internal coordinates.
       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)
@@ -387,8 +417,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
@@ -439,7 +470,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)
@@ -556,7 +587,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
@@ -591,7 +622,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
@@ -623,7 +654,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
@@ -651,13 +682,26 @@ C Calculate internal coordinates.
      &    (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)