Adam's corrections
[unres.git] / source / wham / src-HCD-5D / readpdb.F
index b8ce4f4..6f4ba5f 100644 (file)
@@ -13,78 +13,155 @@ C geometry.
       include 'COMMON.GEO'
       include 'COMMON.NAMES'
       include 'COMMON.SBRIDGE'
+      include 'COMMON.FRAG'
       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
+      logical lsecondary,sccalc
+      integer iterter(maxres)
+      double precision efree_temp
+      iii=0
       ibeg=1
       ishift1=0
+      sccalc=.false.
       do
         read (ipdbin,'(a80)',end=10) card
+!       write (iout,'(a)') card
+        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)
+        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)
+!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
-c          ires_old=ires+1 
+! 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
+          ishift1=ishift1+1
           ibeg=2
-c          write (iout,*) "Chain ended",ires,ishift,ires_old
-          call sccenter(ires,iii,sccor)
+!          write (iout,*) "Chain ended",ires,ishift,ires_old
+          if (unres_pdb) then
+            do j=1,3
+              dc(j,ires)=sccor(j,iii)
+            enddo
+          else
+            call sccenter(ires,iii,sccor)
+          endif
+          iii=0
+          sccalc=.true.
         endif
-C Fish out the ATOM cards.
+! Read free energy
+        if (index(card,"FREE ENERGY").gt.0) read(card(35:),*) efree_temp
+! 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.
+          sccalc=.false.
+          read (card(12:16),*) atom
+c          write (2,'(a)') card
+!          write (iout,*) "! ",atom," !",ires
+!          if (atom.eq.'CA' .or. atom.eq.'CH3') then
+          read (card(23:26),*) ires
+          read (card(18:20),'(a3)') res
+!          write (iout,*) "ires",ires,ires-ishift+ishift1,
+!     &      " ires_old",ires_old
+!          write (iout,*) "ishift",ishift," ishift1",ishift1
+!          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
-              call sccenter(ires,iii,sccor)
+!              write (iout,*) "Calculating sidechain center iii",iii
+              if (unres_pdb) then
+                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
-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
+! 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
               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          
+              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
-c Start a new chain
-              ishift=-ires_old+ires-1
-c              write (iout,*) "New chain started",ires,ishift
+! Start a new chain
+              ishift=-ires_old+ires-1 !!!!!
+              ishift1=ishift1-1    !!!!!
+!              write (iout,*) "New chain started",ires,ishift,ishift1,"!"
+              ires=ires-ishift+ishift1
+              ires_old=ires
               ibeg=0
+            else
+              ishift=ishift-(ires-ishift+ishift1-ires_old-1)
+              ires=ires-ishift+ishift1
+              ires_old=ires
             endif
-            ires=ires-ishift
-c            write (2,*) "ires",ires," ishift",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
+!          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
+!          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,'(2i3,2x,a,3f8.3,5x,f8.3)') 
-c     &       ires,itype(ires),res,(c(j,ires),j=1,3),bfac(ires)
-            iii=1
+!            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(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   ' .and.
-     &             atom.ne.'OXT' ) then
+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
-c            write (iout,*) res,ires,iii,atom
             read(card(31:54),'(3f8.3)') (sccor(j,iii),j=1,3)
-c            write (iout,'(3f8.3)') (sccor(j,iii),j=1,3)
+c            write (2,*) "iii",iii
           endif
         endif
       enddo
@@ -141,7 +218,7 @@ C          endif !unres_pdb
         endif  !itype.eq.ntyp1
       enddo
 C Calculate the CM of the last side chain.
-      call sccenter(ires,iii,sccor)
+      if (.not. sccalc) call sccenter(ires,iii,sccor)
       nsup=nres
       nstart_sup=1
       if (itype(nres).ne.10) then
@@ -248,7 +325,7 @@ 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
+c          stop
         endif
         vbld(i)=dist(i-1,i)
         vbld_inv(i)=1.0d0/vbld(i)
@@ -410,20 +487,33 @@ c
       end
 c---------------------------------------------------------------------------
       subroutine bond_regular
-      implicit real*8 (a-h,o-z)
-      include 'DIMENSIONS'   
+      implicit none
+      include 'DIMENSIONS'
       include 'COMMON.VAR'
-      include 'COMMON.LOCAL'      
-      include 'COMMON.CALC'
+      include 'COMMON.LOCAL'
       include 'COMMON.INTERACT'
       include 'COMMON.CHAIN'
+      integer i,i1,i2
       do i=1,nres-1
        vbld(i+1)=vbl
-       vbld_inv(i+1)=1.0d0/vbld(i+1)
+       vbld_inv(i+1)=vblinv
        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
+c Adam 2/26/20 Alter virtual bonds for non-blocking end groups of each chain
+      do i=1,nchain
+        i1=chain_border(1,i)
+        i2=chain_border(2,i)
+        if (i1.gt.1) then
+          vbld(i1)=vbld(i1)/2
+          vbld_inv(i1)=vbld_inv(i1)*2
+        endif
+        if (i2.lt.nres) then
+          vbld(i2+1)=vbld(i2+1)/2
+          vbld_inv(i2+1)=vbld_inv(i2+1)*2
+        endif
+      enddo
       return
       end
 c---------------------------------------------------------------------------
@@ -714,8 +804,8 @@ C Calculate internal coordinates.
       endif
 C Calculate internal coordinates.
 c      call int_from_cart1(.false.)
-      call int_from_cart(.true.,.true.)
-      call sc_loc_geom(.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)