ifdef poporawa
[unres4.git] / source / unres / geometry.f90
index 8b30374..9737d1a 100644 (file)
@@ -83,6 +83,7 @@
       nres2=2*nres
 ! Set lprn=.true. for debugging
       lprn = .false.
+      print *,"I ENTER CHAINBUILD"
 !
 ! Define the origin and orientation of the coordinate system and locate the
 ! first three CA's and SC(2).
       write (iout,'(/a)') 'Recalculated internal coordinates'
       do i=2,nres-1
        do j=1,3
-         c(j,nres2)=0.5D0*(c(j,i-1)+c(j,i+1))  !maxres2=2*maxres
+         c(j,nres2+2)=0.5D0*(c(j,i-1)+c(j,i+1))        !maxres2=2*maxres
         enddo
         be=0.0D0
         if (i.gt.3) be=rad2deg*beta(i-3,i-2,i-1,i)
-        be1=rad2deg*beta(nres+i,i,nres2,i+1)
+        be1=rad2deg*beta(nres+i,i,nres2+2,i+1)
         alfai=0.0D0
         if (i.gt.2) alfai=rad2deg*alpha(i-2,i-1,i)
         write (iout,1212) restyp(itype(i)),i,dist(i-1,i),&
-        alfai,be,dist(nres+i,i),rad2deg*alpha(nres+i,i,nres2),be1
+        alfai,be,dist(nres+i,i),rad2deg*alpha(nres+i,i,nres2+2),be1
       enddo   
  1212 format (a3,'(',i3,')',2(f10.5,2f10.2))
 
         dnorm1=dist(i-1,i)
         dnorm2=dist(i,i+1) 
        do j=1,3
-         c(j,nres2)=0.5D0*(2*c(j,i)+(c(j,i-1)-c(j,i))/dnorm1 &
+         c(j,nres2+2)=0.5D0*(2*c(j,i)+(c(j,i-1)-c(j,i))/dnorm1 &
            +(c(j,i+1)-c(j,i))/dnorm2)
         enddo
         be=0.0D0
          tauangle(2,i+1)=beta(i-2,i-1,i,i+nres)
         endif
         endif
-        omeg(i)=beta(nres+i,i,nres2,i+1)
-        alph(i)=alpha(nres+i,i,nres2)
+        omeg(i)=beta(nres+i,i,nres2+2,i+1)
+        alph(i)=alpha(nres+i,i,nres2+2)
         theta(i+1)=alpha(i-1,i,i+1)
         vbld(i)=dist(i-1,i)
         vbld_inv(i)=1.0d0/vbld(i)
 #endif
       return
       end subroutine int_from_cart1
-#if .not. defined(WHAM_RUN) && .not. defined(CLUSTER)
+#if !defined(WHAM_RUN) && !defined(CLUSTER)
 !-----------------------------------------------------------------------------
 ! check_sc_distr.f
 !-----------------------------------------------------------------------------
       thetnorm=xx 
       return
       end function thetnorm
-#if .not. defined(WHAM_RUN) && .not. defined(CLUSTER)
+#if !defined(WHAM_RUN) && !defined(CLUSTER)
 !-----------------------------------------------------------------------------
       subroutine var_to_geom_restr(n,xx)
 !
 ! SCs.
       iteli=itel(i)
       do j=1,3
-       c(j,nres2+1)=0.5D0*(c(j,i)+c(j,i+1))
+!      c(j,nres2+1)=0.5D0*(c(j,i)+c(j,i+1))
+       c(j,nres2+3)=0.5D0*(c(j,i)+c(j,i+1))
       enddo
       do j=nnt,i-2
        itj=iabs(itype(j))
 !d      print *,'overlap, p-Sc: i=',i,' j=',j,
 !d   &         ' dist=',dist(nres+j,maxres2+1)
-       if (dist(nres+j,nres2+1).lt.4.0D0*redfac) then
+       if (dist(nres+j,nres2+3).lt.4.0D0*redfac) then
          overlap=.true.
          return
         endif
 ! groups.
       do j=1,nnt-2
        do k=1,3
-         c(k,nres2+1)=0.5D0*(c(k,j)+c(k,j+1))
+         c(k,nres2+3)=0.5D0*(c(k,j)+c(k,j+1))
         enddo
 !d      print *,'overlap, SC-p: i=',i,' j=',j,
 !d   &         ' dist=',dist(nres+i,maxres2+1)
-       if (dist(nres+i,nres2+1).lt.4.0D0*redfac) then
+       if (dist(nres+i,nres2+3).lt.4.0D0*redfac) then
           overlap=.true.
          return
         endif
       enddo
 ! Check for p-p overlaps
       do j=1,3
-       c(j,nres2+2)=0.5D0*(c(j,i)+c(j,i+1))
+       c(j,nres2+4)=0.5D0*(c(j,i)+c(j,i+1))
       enddo
       do j=nnt,i-2
         itelj=itel(j)
        do k=1,3
-         c(k,nres2+2)=0.5D0*(c(k,j)+c(k,j+1))
+         c(k,nres2+4)=0.5D0*(c(k,j)+c(k,j+1))
         enddo
 !d      print *,'overlap, p-p: i=',i,' j=',j,
 !d   &         ' dist=',dist(maxres2+1,maxres2+2)
         if(iteli.ne.0.and.itelj.ne.0)then
-        if (dist(nres2+1,nres2+2).lt.rpp(iteli,itelj)*redfac) then
+        if (dist(nres2+3,nres2+4).lt.rpp(iteli,itelj)*redfac) then
           overlap=.true.
           return
         endif
       dist=dsqrt(x12*x12+y12*y12+z12*z12)
       return
       end function dist
-#if .not. defined(WHAM_RUN) && .not. defined(CLUSTER)
+#if !defined(WHAM_RUN) && !defined(CLUSTER)
 !-----------------------------------------------------------------------------
 ! local_move.f
 !-----------------------------------------------------------------------------
       do i=1,nres-1
 !in wham      do i=1,nres
         iti=itype(i)
-        if (dist(i,i+1).lt.2.0D0 .or. dist(i,i+1).gt.5.0D0) then
+        if ((dist(i,i+1).lt.2.0D0 .or. dist(i,i+1).gt.5.0D0).and.&
+       (iti.ne.ntyp1  .and. itype(i+1).ne.ntyp1)) then
           write (iout,'(a,i4)') 'Bad Cartesians for residue',i
 !test          stop
         endif
       if (lside) then
         do i=2,nres-1
           do j=1,3
-            c(j,nres2)=0.5D0*(2*c(j,i)+(c(j,i-1)-c(j,i))*vbld_inv(i) &
+            c(j,nres2+2)=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))
 ! in wham            c(j,maxres2)=0.5D0*(c(j,i-1)+c(j,i+1)
           enddo
           endif
 !#endif
           if (iti.ne.10) then
-            alph(i)=alpha(nres+i,i,nres2)
-            omeg(i)=beta(nres+i,i,nres2,i+1)
+            alph(i)=alpha(nres+i,i,nres2+2)
+            omeg(i)=beta(nres+i,i,nres2+2,i+1)
           endif
           if(me.eq.king.or..not.out1file)then
            if (lprn) &
       enddo
       return
       end subroutine sccenter
-#if .not. defined(WHAM_RUN) && .not. defined(CLUSTER)
+#if !defined(WHAM_RUN) && !defined(CLUSTER)
 !-----------------------------------------------------------------------------
       subroutine bond_regular
       use calc_data
 !   The side-chain vector derivatives
       return
       end subroutine int_to_cart
-#if .not. defined(WHAM_RUN) && .not. defined(CLUSTER)
+#if !defined(WHAM_RUN) && !defined(CLUSTER)
 !-----------------------------------------------------------------------------
 ! readrtns_CSA.F
 !-----------------------------------------------------------------------------
 !      if(.not.allocated(dc_norm2)) allocate(dc_norm2(3,0:nres2+2)) !(3,0:maxres2)      
       if(.not.allocated(dc_norm2)) then
         allocate(dc_norm2(3,0:nres2+2)) !(3,0:maxres2)
-        do i=0,nres2+2
-          dc_norm2(1,i)=0.d0
-          dc_norm2(2,i)=0.d0
-          dc_norm2(3,i)=0.d0
-        enddo
+        dc_norm2(:,:)=0.d0
       endif
 !
 !el      if(.not.allocated(dc_norm)) 
 !elwrite(iout,*) "jestem w alloc geo 1"
       if(.not.allocated(dc_norm)) then
         allocate(dc_norm(3,0:nres2+2)) !(3,0:maxres2)
-        do i=0,nres2+2
-          dc_norm(1,i)=0.d0
-          dc_norm(2,i)=0.d0
-          dc_norm(3,i)=0.d0
-        enddo
+        dc_norm(:,:)=0.d0
       endif
 !elwrite(iout,*) "jestem w alloc geo 1"
       allocate(xloc(3,nres),xrot(3,nres))
 !elwrite(iout,*) "jestem w alloc geo 1"
-      do i=1,nres
-       do j=1,3
-         xloc(j,i)=0.0D0
-        enddo
-      enddo
+      xloc(:,:)=0.0D0
 !elwrite(iout,*) "jestem w alloc geo 1"
       allocate(dc_work(6*nres)) !(MAXRES6) maxres6=6*maxres
 !      common /rotmat/
 
 #if defined(WHAM_RUN) || defined(CLUSTER)
       allocate(vbld(2*nres))
-      do i=1,2*nres
-        vbld(i)=0.d0
-      enddo
+      vbld(:)=0.d0
       allocate(vbld_inv(2*nres))
-      do i=1,2*nres
-        vbld_inv(i)=0.d0
-      enddo
+      vbld_inv(:)=0.d0
 #endif
 
       return