X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2Fminim.f90;h=a096a62872cccd1987d3ee9ab7199a2365bb555e;hb=fe0a8e52832b7703fb74f8b6909871fc17047a02;hp=d556363979d673f33374dc8437fd2d4447dcfd13;hpb=c43a5a1d5cc1d3f94c53de28dd1fd93bea770790;p=unres4.git diff --git a/source/unres/minim.f90 b/source/unres/minim.f90 index d556363..a096a62 100644 --- a/source/unres/minim.f90 +++ b/source/unres/minim.f90 @@ -3305,7 +3305,7 @@ ! "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)" ! do i=1,nres ! write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)') & -! restyp(itype(i)),i,(c(j,i),j=1,3),& +! restyp(itype(i,1)),i,(c(j,i),j=1,3),& ! (c(j,i+nres),j=1,3) ! enddo !el---------------------------- @@ -3413,7 +3413,7 @@ enddo do i=2,nres-1 - if (itype(i).ne.10) then + if (itype(i,1).ne.10) then IF (mask_side(i).eq.1) THEN ig=ig+1 galphai=0.0D0 @@ -3427,7 +3427,7 @@ do i=2,nres-1 - if (itype(i).ne.10) then + if (itype(i,1).ne.10) then IF (mask_side(i).eq.1) THEN ig=ig+1 gomegai=0.0D0 @@ -3463,7 +3463,7 @@ do ij=1,2 do i=2,nres-1 - if (itype(i).ne.10) then + if (itype(i,1).ne.10) then igall=igall+1 if (mask_side(i).eq.1) then ig=ig+1 @@ -3556,7 +3556,7 @@ do ij=1,2 do i=2,nres-1 - if (itype(i).ne.10) then + if (itype(i,1).ne.10) then igall=igall+1 if (mask_side(i).eq.1) then ig=ig+1 @@ -3664,9 +3664,9 @@ enddo endif enddo - call check_ecartint +! call check_ecartint call sumsl(k,d,x,func_dc,grad_dc,iv,liv,lv,v,idum,rdum,fdum) - call check_ecartint +! call check_ecartint k=0 do i=1,nres-1 do j=1,3 @@ -3702,7 +3702,7 @@ ! "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)" ! do i=1,nres ! write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)') & -! restyp(itype(i)),i,(c(j,i),j=1,3),& +! restyp(itype(i,1)),i,(c(j,i),j=1,3),& ! (c(j,i+nres),j=1,3) ! enddo !el---------------------------- @@ -4365,7 +4365,7 @@ sc_dist_cutoff=5.0D0 ! Don't do glycine or ends - i=itype(res_pick) + i=itype(res_pick,1) if (i.eq.10 .or. i.eq.ntyp1) return ! Freeze everything (later will relax only selected side-chains) @@ -4382,8 +4382,8 @@ !rc cur_e=orig_e nres_moved=0 do i=2,nres-1 -! Don't do glycine (itype(j)==10) - if (itype(i).ne.10) then +! Don't do glycine (itype(j,1)==10) + if (itype(i,1).ne.10) then sc_dist=dist(nres+i,nres+res_pick) else sc_dist=sc_dist_cutoff @@ -4411,7 +4411,7 @@ n_try=0 do while (n_try.lt.n_maxtry .and. orig_e-cur_e.lt.e_drop) ! Move the selected residue (don't worry if it fails) - call gen_side(iabs(itype(res_pick)),theta(res_pick+1),& + call gen_side(iabs(itype(res_pick,1)),theta(res_pick+1),& alph(res_pick),omeg(res_pick),fail) ! Minimize the side-chains starting from the new arrangement @@ -4672,7 +4672,7 @@ ! "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)" ! do i=1,nres ! write (iout,'(a3,1x,i3,3f8.3,5x,3f8.3)') & -! restyp(itype(i)),i,(c(j,i),j=1,3),& +! restyp(itype(i,1)),i,(c(j,i),j=1,3),& ! (c(j,i+nres),j=1,3) ! enddo ! call etotal(energia) @@ -4821,7 +4821,7 @@ enddo do i=2,nres-1 - if (itype(i).ne.10) then + if (itype(i,1).ne.10) then IF (mask_side(i).eq.1) THEN ig=ig+1 galphai=0.0D0 @@ -4835,7 +4835,7 @@ do i=2,nres-1 - if (itype(i).ne.10) then + if (itype(i,1).ne.10) then IF (mask_side(i).eq.1) THEN ig=ig+1 gomegai=0.0D0 @@ -4871,7 +4871,7 @@ do ij=1,2 do i=2,nres-1 - if (itype(i).ne.10) then + if (itype(i,1).ne.10) then igall=igall+1 if (mask_side(i).eq.1) then ig=ig+1 @@ -4921,8 +4921,8 @@ ind=0 do i=iatsc_s,iatsc_e - itypi=iabs(itype(i)) - itypi1=iabs(itype(i+1)) + itypi=iabs(itype(i,1)) + itypi1=iabs(itype(i+1,1)) xi=c(1,nres+i) yi=c(2,nres+i) zi=c(3,nres+i) @@ -4938,7 +4938,7 @@ do j=istart(i,iint),iend(i,iint) IF (mask_side(j).eq.1.or.mask_side(i).eq.1) THEN ind=ind+1 - itypj=iabs(itype(j)) + itypj=iabs(itype(j,1)) dscj_inv=dsc_inv(itypj) sig0ij=sigma(itypi,itypj) chi1=chi(itypi,itypj) @@ -4986,16 +4986,17 @@ !--------------------------------------------------------------- rij_shift=1.0D0/rij_shift fac=rij_shift**expon - e1=fac*fac*aa(itypi,itypj) - e2=fac*bb(itypi,itypj) + e1=fac*fac*aa_aq(itypi,itypj) + e2=fac*bb_aq(itypi,itypj) evdwij=eps1*eps2rt*eps3rt*(e1+e2) eps2der=evdwij*eps3rt eps3der=evdwij*eps2rt evdwij=evdwij*eps2rt*eps3rt evdw=evdw+evdwij +! if (wliptran.gt.0.0) print *,"WARNING eps_aq used!" if (lprn) then - sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0) - epsi=bb(itypi,itypj)**2/aa(itypi,itypj) + sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0) + epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj) !d write (iout,'(2(a3,i3,2x),17(0pf7.3))') & !d restyp(itypi),i,restyp(itypj),j, & !d epsi,sigm,chi1,chi2,chip1,chip2, &