Commit new changes 10/26/14
[unres.git] / source / unres / src_Eshel / readpdb.F
index 5d6acc0..3ce8334 100644 (file)
@@ -13,25 +13,30 @@ C geometry.
       include 'COMMON.CONTROL'
       include 'COMMON.DISTFIT'
       include 'COMMON.SETUP'
-      character*3 seq,atom,res
-      character*80 card
-      dimension sccor(3,20)
+      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)
-      logical fail
+      double precision dcj,efree_temp
+      character*3 seq,res
+      character*5 atom
+      character*80 card
+      double precision sccor(3,20)
       integer rescode
+      efree_temp=0.0d0
       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 i=1,maxres
-        itype(i)=21
-        do j=1,3
-          c(j,i)=0.0d0
-          c(j,i+nres)=0.0d0
-        enddo
-      enddo
       do i=1,10000
         read (ipdbin,'(a80)',end=10) card
+c        write (iout,'(a)') card
         if (card(:5).eq.'HELIX') then
          nhfrag=nhfrag+1
          lsecondary=.true.
@@ -50,86 +55,118 @@ crc  to be corrected !!!
 crc----------------------------------------
         endif
         if (card(:3).eq.'END' .or. card(:3).eq.'TER') goto 10
+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(14:16),'(a3)') atom
-          if (atom.eq.'CA' .or. atom.eq.'CH3') 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
 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)
+                  dc(j,ires)=sccor(j,iii)
                 enddo
               else
-                call sccenter(ires,iii,sccor)
+                call sccenter(ires_old,iii,sccor)
               endif
+              iii=0
             endif
 C Start new residue.
-            read (card(24:26),*) ires
-            read (card(18:20),'(a3)') res
-            if (ibeg.eq.1) then
+            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)=21
               endif
+              ires=ires-ishift+ishift1
+              ires_old=ires
+c              write (iout,*) "ishift",ishift," ires",ires,
+c     &         " ires_old",ires_old
               ibeg=0          
+            else
+              ishift=ishift-(ires-ishift+ishift1-ires_old-1)
+              ires=ires-ishift+ishift1
+              ires_old=ires
             endif
-            ires=ires-ishift
-            if (res.eq.'ACE') then
-              ity=10
+            if (res.eq.'ACE' .or. res.eq.'NHE') 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            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
+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
             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
+            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.
+     &             atom.ne.'OXT' .and. atom(:2).ne.'3H') then
+c            write (iout,*) "sidechain ",atom
             iii=iii+1
             read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
           endif
         endif
       enddo
-   10 if(me.eq.king.or..not.out1file) 
-     & write (iout,'(a,i5)') ' Nres: ',ires
+   10 write (iout,'(a,i5)') ' Number of residues found: ',ires
+      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+nres)=sccor(j,iii)
+          dc(j,ires)=sccor(j,iii)
         enddo
-      else if (.not.catrace) then
+      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)=21
-        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 if (.not.catrace) then
         do j=1,3
           dcj=c(j,nres-2)-c(j,nres-3)
           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
@@ -154,7 +191,7 @@ C 2/15/2013 by Adam: corrected insertion of the first dummy residue
           do j=1,3
             c(j,1)=c(j,2)-3.8d0*e2(j)
           enddo
-        else if (.not.catrace) then
+        else
         do j=1,3
           dcj=c(j,4)-c(j,3)
           c(j,1)=c(j,2)-dcj
@@ -162,6 +199,24 @@ C 2/15/2013 by Adam: corrected insertion of the first dummy residue
         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)') 
@@ -172,8 +227,8 @@ C Calculate internal coordinates.
      &    (c(j,nres+ires),j=1,3)
        enddo
       endif
-      call int_from_cart(.not.catrace,.false.)
-      if (.not.catrace) call sc_loc_geom(.false.)
+      call int_from_cart(.true.,.false.)
+      call sc_loc_geom(.false.)
       do i=1,nres
         thetaref(i)=theta(i)
         phiref(i)=phi(i)
@@ -212,7 +267,7 @@ C Copy the coordinates to reference coordinates
          hfrag(i,j)=hfrag(i,j)-ishift
         enddo
       enddo
-
+      ishift_pdb=ishift
       return
       end
 c---------------------------------------------------------------------------
@@ -231,7 +286,8 @@ c---------------------------------------------------------------------------
       include 'COMMON.NAMES'
       include 'COMMON.CONTROL'
       include 'COMMON.SETUP'
-      character*3 seq,atom,res
+      character*3 seq,res
+c      character*5 atom
       character*80 card
       dimension sccor(3,20)
       integer rescode
@@ -251,7 +307,6 @@ c---------------------------------------------------------------------------
        endif
       endif
       do i=1,nres-1
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
         iti=itype(i)
         if (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
@@ -278,7 +333,6 @@ c        endif
 c      endif
       if (lside) then
         do i=2,nres-1
-          if (itype(i).eq.ntyp1) cycle
           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))
@@ -286,7 +340,7 @@ c      endif
           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)
+          if (itype(i).ne.10 .and. itype(i).ne.21. and. di.eq.0.0d0)
      &     di=dsc(itype(i))
           vbld(i+nres)=di
           if (itype(i).ne.10) then