bug fix in respa and readpdb
[unres.git] / source / unres / src_MD-M / readpdb.F
index edd478e..48bb75a 100644 (file)
@@ -16,7 +16,12 @@ C geometry.
       character*3 seq,atom,res
       character*80 card
       dimension sccor(3,20)
-      integer rescode
+      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
       lsecondary=.false.
       nhfrag=0
@@ -44,10 +49,13 @@ crc----------------------------------------
           goto 10
         else if (card(:3).eq.'TER') then
 C End current chain
-          ires_old=ires+1 
-          itype(ires_old)=21
+          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)
@@ -72,13 +80,13 @@ C Calculate the CM of the preceding residue.
             endif
 C Start new residue.
 c            write (iout,'(a80)') card
-            read (card(24:26),*) ires
+            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)=21
+                itype(1)=ntyp1
               endif
 c              write (iout,*) "ires",ires," ibeg",ibeg," ishift",ishift
               ibeg=0          
@@ -91,7 +99,7 @@ c              write (iout,*) "New chain started",ires,ishift
             ires=ires-ishift
 c            write (2,*) "ires",ires," ishift",ishift
             if (res.eq.'ACE') then
-              ity=10
+              itype(ires)=10
             else
               itype(ires)=rescode(ires,res,0)
             endif
@@ -116,15 +124,55 @@ 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.21) 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 (unres_pdb) then
@@ -138,14 +186,22 @@ C Calculate the CM of the last side chain.
       nstart_sup=1
       if (itype(nres).ne.10) then
         nres=nres+1
-        itype(nres)=21
+        itype(nres)=ntyp1
         if (unres_pdb) then
-          c(1,nres)=c(1,nres-1)+3.8d0
-          c(2,nres)=c(2,nres-1)
-          c(3,nres)=c(3,nres-1)
+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)-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
@@ -160,16 +216,23 @@ C Calculate the CM of the last side chain.
         c(j,nres+1)=c(j,1)
         c(j,2*nres)=c(j,nres)
       enddo
-      if (itype(1).eq.21) then
+      if (itype(1).eq.ntyp1) then
         nsup=nsup-1
         nstart_sup=2
         if (unres_pdb) then
-          c(1,1)=c(1,2)-3.8d0
-          c(2,1)=c(2,2)
-          c(3,1)=c(3,2)
+C 2/15/2013 by Adam: corrected insertion of the first dummy residue
+          call refsys(2,3,4,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,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
@@ -183,6 +246,7 @@ C Calculate internal coordinates.
      &    (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.)
       do i=1,nres
@@ -213,7 +277,7 @@ C Splits to single chain if occurs
       lll=lll+1
 cc      write (iout,*) "spraw lancuchy",(c(j,i),j=1,3)
       if (i.gt.1) then
-      if ((itype(i-1).eq.21)) then
+      if ((itype(i-1).eq.ntyp1).and.(i.gt.2)) then
       chain_length=lll-1
       kkk=kkk+1
 c       write (iout,*) "spraw lancuchy",(c(j,i),j=1,3)
@@ -229,6 +293,8 @@ c       write (iout,*) "spraw lancuchy",(c(j,i),j=1,3)
           endif
          enddo
       enddo
+      write (iout,*) chain_length
+      if (chain_length.eq.0) chain_length=nres
       do j=1,3
       chain_rep(j,chain_length,symetr)=chain_rep(j,chain_length,1)
       chain_rep(j,chain_length+nres,symetr)
@@ -244,7 +310,9 @@ c        enddo
 c enddiagnostic       
 C makes copy of chains
         write (iout,*) "symetr", symetr
-       
+      do j=1,3
+      dc(j,0)=c(j,1)
+      enddo 
       if (symetr.gt.1) then
        call permut(symetr)
        nperm=1
@@ -304,7 +372,6 @@ cc enddiag
          hfrag(i,j)=hfrag(i,j)-ishift
         enddo
       enddo
-
       return
       end
 c---------------------------------------------------------------------------
@@ -348,7 +415,7 @@ c---------------------------------------------------------------------------
 #endif
       do i=1,nres-1
         iti=itype(i)
-        if (iti.ne.21 .and. itype(i+1).ne.21 .and. 
+        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
@@ -372,6 +439,7 @@ c          vbld(nres)=3.8d0
 c          vbld_inv(nres)=1.0d0/vbld(2)
 c        endif
 c      endif
+      print *,"A TU2"
       if (lside) then
         do i=2,nres-1
           do j=1,3
@@ -431,7 +499,7 @@ c-------------------------------------------------------------------------------
         enddo
       enddo
       do i=2,nres-1
-        if (itype(i).ne.10 .and. itype(i).ne.21) 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
@@ -451,7 +519,7 @@ c-------------------------------------------------------------------------------
         sinfac2=0.5d0/(1.0d0-costtab(i+1))
         sinfac=dsqrt(sinfac2)
         it=itype(i)
-        if (it.ne.10 .and. itype(i).ne.21) 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 
@@ -530,8 +598,8 @@ 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