correction for gfortran
[unres4.git] / source / unres / minim.f90
index d556363..a096a62 100644 (file)
 !       "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----------------------------
       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
 
       
       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
      
       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
 
       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                                                             
         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
 !       "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----------------------------
       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)
 !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
       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
 !       "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)
       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
 
       
       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
      
       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
       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)
           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)
 !---------------------------------------------------------------
             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, &