Zmiana 21 na ntyp1 w unres SRC_MD oraz SRC_MD-M
[unres.git] / source / cluster / wham / src-M / energy_p_new.F
index 030de74..44bdc8d 100644 (file)
@@ -364,7 +364,7 @@ cd    print *,'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
       evdw_t=0.0d0
       do i=iatsc_s,iatsc_e
         itypi=iabs(itype(i))
-        if (itypi.eq.21) cycle
+        if (itypi.eq.ntyp1) cycle
         itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
@@ -379,7 +379,7 @@ cd        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 cd   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
             itypj=iabs(itype(j))
-            if (itypj.eq.21) cycle
+            if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             zj=c(3,nres+j)-zi
@@ -529,7 +529,7 @@ c     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw_t=0.0d0
       do i=iatsc_s,iatsc_e
         itypi=iabs(itype(i))
-        if (itypi.eq.21) cycle
+        if (itypi.eq.ntyp1) cycle
         itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
@@ -540,7 +540,7 @@ C
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
             itypj=iabs(itype(j))
-            if (itypj.eq.21) cycle
+            if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             zj=c(3,nres+j)-zi
@@ -633,7 +633,7 @@ c     endif
       ind=0
       do i=iatsc_s,iatsc_e
         itypi=iabs(itype(i))
-        if (itypi.eq.21) cycle
+        if (itypi.eq.ntyp1) cycle
         itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
@@ -649,7 +649,7 @@ C
           do j=istart(i,iint),iend(i,iint)
             ind=ind+1
             itypj=iabs(itype(j))
-            if (itypj.eq.21) cycle
+            if (itypj.eq.ntyp1) cycle
             dscj_inv=vbld_inv(j+nres)
             chi1=chi(itypi,itypj)
             chi2=chi(itypj,itypi)
@@ -762,7 +762,7 @@ c      if (icall.gt.0) lprn=.true.
       ind=0
       do i=iatsc_s,iatsc_e
         itypi=iabs(itype(i))
-        if (itypi.eq.21) cycle
+        if (itypi.eq.ntyp1) cycle
         itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
@@ -778,7 +778,7 @@ C
           do j=istart(i,iint),iend(i,iint)
             ind=ind+1
             itypj=iabs(itype(j))
-            if (itypj.eq.21) cycle
+            if (itypj.eq.ntyp1) cycle
             dscj_inv=vbld_inv(j+nres)
             sig0ij=sigma(itypi,itypj)
             chi1=chi(itypi,itypj)
@@ -901,7 +901,7 @@ c      if (icall.gt.0) lprn=.true.
       ind=0
       do i=iatsc_s,iatsc_e
         itypi=iabs(itype(i))
-        if (itypi.eq.21) cycle
+        if (itypi.eq.ntyp1) cycle
         itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
@@ -917,7 +917,7 @@ C
           do j=istart(i,iint),iend(i,iint)
             ind=ind+1
             itypj=iabs(itype(j))
-            if (itypj.eq.21) cycle
+            if (itypj.eq.ntyp1) cycle
             dscj_inv=vbld_inv(j+nres)
             sig0ij=sigma(itypi,itypj)
             r0ij=r0(itypi,itypj)
@@ -1806,7 +1806,7 @@ cd      write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
         gcorr_loc(i)=0.0d0
       enddo
       do i=iatel_s,iatel_e
-        if (itype(i).eq.21 .or. itype(i+1).eq.21) cycle
+        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
         if (itel(i).eq.0) goto 1215
         dxi=dc(1,i)
         dyi=dc(2,i)
@@ -1820,7 +1820,7 @@ cd      write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
         num_conti=0
 c        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         do j=ielstart(i),ielend(i)
-          if (itype(j).eq.21 .or. itype(j+1).eq.21) cycle
+          if (itype(j).eq.ntyp1 .or. itype(j+1).eq.ntyp1) cycle
           if (itel(j).eq.0) goto 1216
           ind=ind+1
           iteli=itel(i)
@@ -2556,7 +2556,7 @@ C Cartesian derivatives
      &      +0.5d0*(pizda(1,1)+pizda(2,2))
         enddo
         endif
-      else if (j.eq.i+3 .and. itype(i+2).ne.21) then
+      else if (j.eq.i+3 .and. itype(i+2).ne.ntyp1) then
 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
 C
 C               Fourth-order contributions
@@ -2757,7 +2757,7 @@ cd    print '(a)','Enter ESCP'
 c      write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e,
 c     &  ' scal14',scal14
       do i=iatscp_s,iatscp_e
-        if (itype(i).eq.21 .or. itype(i+1).eq.21) cycle
+        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
         iteli=itel(i)
 c        write (iout,*) "i",i," iteli",iteli," nscp_gr",nscp_gr(i),
 c     &   " iscp",(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
@@ -2770,7 +2770,7 @@ c     &   " iscp",(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
 
         do j=iscpstart(i,iint),iscpend(i,iint)
           itypj=iabs(itype(j))
-          if (itypj.eq.21) cycle
+          if (itypj.eq.ntyp1) cycle
 C Uncomment following three lines for SC-p interactions
 c         xj=c(1,nres+j)-xi
 c         yj=c(2,nres+j)-yi
@@ -3029,7 +3029,7 @@ c
       estr=0.0d0
       estr1=0.0d0
       do i=nnt+1,nct
-        if (itype(i-1).eq.21 .or. itype(i).eq.21) then
+        if (itype(i-1).eq.ntyp1 .or. itype(i).eq.ntyp1) then
           estr1=estr1+gnmr1(vbld(i),-1.0d0,distchainmax)
           do j=1,3
           gradb(j,i-1)=gnmr1prim(vbld(i),-1.0d0,distchainmax)
@@ -3053,7 +3053,7 @@ c 09/18/07 AL: multimodal bond potential based on AM1 CA-SC PMF's included
 c
       do i=nnt,nct
         iti=iabs(itype(i))
-        if (iti.ne.10 .and. iti.ne.21) then
+        if (iti.ne.10 .and. iti.ne.ntyp1) then
           nbi=nbondterm(iti)
           if (nbi.eq.1) then
             diff=vbld(i+nres)-vbldsc0(1,iti)
@@ -3129,7 +3129,7 @@ c      write (iout,*) "nres",nres
 c     write (*,'(a,i2)') 'EBEND ICG=',icg
 c      write (iout,*) ithet_start,ithet_end
       do i=ithet_start,ithet_end
-        if (itype(i-1).eq.21) cycle
+        if (itype(i-1).eq.ntyp1) cycle
 C Zero the energy function and its derivative at 0 or pi.
         call splinthet(theta(i),0.5d0*delta,ss,ssd)
         it=itype(i-1)
@@ -3145,7 +3145,7 @@ C Zero the energy function and its derivative at 0 or pi.
           ichir21=isign(1,itype(i))
           ichir22=isign(1,itype(i))
          endif
-        if (i.gt.3 .and. itype(i-2).ne.21) then
+        if (i.gt.3 .and. itype(i-2).ne.ntyp1) then
 #ifdef OSF
           phii=phi(i)
           icrc=0
@@ -3160,7 +3160,7 @@ C Zero the energy function and its derivative at 0 or pi.
           y(1)=0.0D0
           y(2)=0.0D0
         endif
-        if (i.lt.nres .and. itype(i).ne.21) then
+        if (i.lt.nres .and. itype(i).ne.ntyp1) then
 #ifdef OSF
           phii1=phi(i+1)
           icrc=0
@@ -3375,7 +3375,7 @@ C
       etheta=0.0D0
 c      write (iout,*) "ithetyp",(ithetyp(i),i=1,ntyp1)
       do i=ithet_start,ithet_end
-        if (itype(i-1).eq.21) cycle
+        if (itype(i-1).eq.ntyp1) cycle
         dethetai=0.0d0
         dephii=0.0d0
         dephii1=0.0d0
@@ -3386,7 +3386,7 @@ CC Ta zmina jest niewlasciwa
           coskt(k)=dcos(k*theti2)
           sinkt(k)=dsin(k*theti2)
         enddo
-        if (i.gt.3 .and. itype(i-2).ne.21) then
+        if (i.gt.3 .and. itype(i-2).ne.ntyp1) then
 #ifdef OSF
           phii=phi(i)
           if (phii.ne.phii) phii=150.0
@@ -3406,7 +3406,7 @@ CC Ta zmina jest niewlasciwa
             sinph1(k)=0.0d0
           enddo 
         endif
-        if (i.lt.nres .and. itype(i).ne.21) then
+        if (i.lt.nres .and. itype(i).ne.ntyp1) then
 #ifdef OSF
           phii1=phi(i+1)
           if (phii1.ne.phii1) phii1=150.0
@@ -3567,7 +3567,7 @@ C ALPHA and OMEGA.
 c     write (iout,'(a)') 'ESC'
       do i=loc_start,loc_end
         it=itype(i)
-        if (it.eq.21) cycle
+        if (it.eq.ntyp1) cycle
         if (it.eq.10) goto 1
         nlobit=nlob(iabs(it))
 c       print *,'i=',i,' it=',it,' nlobit=',nlobit
@@ -3860,7 +3860,7 @@ C
       delta=0.02d0*pi
       escloc=0.0D0
       do i=loc_start,loc_end
-        if (itype(i).eq.21) cycle
+        if (itype(i).eq.ntyp1) cycle
         costtab(i+1) =dcos(theta(i+1))
         sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
         cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
@@ -4251,8 +4251,8 @@ C Set lprn=.true. for debugging
 c      lprn=.true.
       etors=0.0D0
       do i=iphi_start,iphi_end
-        if (itype(i-2).eq.21 .or. itype(i-1).eq.21
-     &      .or. itype(i).eq.21) cycle
+        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1
+     &      .or. itype(i).eq.ntyp1) cycle
        itori=itortyp(itype(i-2))
        itori1=itortyp(itype(i-1))
         phii=phi(i)
@@ -4336,8 +4336,8 @@ C Set lprn=.true. for debugging
 c      lprn=.true.
       etors=0.0D0
       do i=iphi_start,iphi_end
-        if (itype(i-2).eq.21 .or. itype(i-1).eq.21
-     &       .or. itype(i).eq.21) cycle
+        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1
+     &       .or. itype(i).eq.ntyp1) cycle
         if (itel(i-2).eq.0 .or. itel(i-1).eq.0) goto 1215
          if (iabs(itype(i)).eq.20) then
          iblock=2
@@ -4435,8 +4435,8 @@ C Set lprn=.true. for debugging
 c     lprn=.true.
       etors_d=0.0D0
       do i=iphi_start,iphi_end-1
-        if (itype(i-2).eq.21 .or. itype(i-1).eq.21
-     &      .or. itype(i).eq.21 .or. itype(i+1).eq.21) cycle
+        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1
+     &      .or. itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
         if (itel(i-2).eq.0 .or. itel(i-1).eq.0 .or. itel(i).eq.0) 
      &     goto 1215
         itori=itortyp(itype(i-2))
@@ -4518,7 +4518,7 @@ c      lprn=.true.
 c      write (iout,*) "EBACK_SC_COR",iphi_start,iphi_end,nterm_sccor
       esccor=0.0D0
       do i=iphi_start,iphi_end
-        if (itype(i-2).eq.21 .or. itype(i-1).eq.21) cycle
+        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1) cycle
         esccor_ii=0.0D0
         itori=itype(i-2)
         itori1=itype(i-1)