X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2Fgeometry.f90;h=9737d1a727db257fea34884d107acac091810641;hb=4fa6ed0fa1ee37552df6064fe60a73f218c101ca;hp=7a91cc7ef39b8f81143eee3b414b4a5d5f54fc9a;hpb=095c479c65c6ef7f85194cae2b096c4082b118ab;p=unres4.git diff --git a/source/unres/geometry.f90 b/source/unres/geometry.f90 index 7a91cc7..9737d1a 100644 --- a/source/unres/geometry.f90 +++ b/source/unres/geometry.f90 @@ -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). @@ -539,7 +540,7 @@ #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 !----------------------------------------------------------------------------- @@ -770,7 +771,7 @@ 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) ! @@ -1827,7 +1828,7 @@ 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 !----------------------------------------------------------------------------- @@ -2852,7 +2853,8 @@ 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 @@ -3046,7 +3048,7 @@ 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 @@ -3417,7 +3419,7 @@ ! 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 !----------------------------------------------------------------------------- @@ -3524,31 +3526,19 @@ ! 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/ @@ -3597,13 +3587,9 @@ #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