Zmiana 21 na ntyp1 w unres SRC_MD oraz SRC_MD-M
[unres.git] / source / unres / src_MD-M / energy_p_new_barrier.F
index f2f6372..0ce1a7b 100644 (file)
@@ -1026,7 +1026,7 @@ c      write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=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)
@@ -1041,7 +1041,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
@@ -1179,7 +1179,7 @@ c     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=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)
@@ -1190,7 +1190,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
@@ -1272,7 +1272,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)
@@ -1289,7 +1289,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
 c            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             chi1=chi(itypi,itypj)
@@ -1392,7 +1392,7 @@ c     if (icall.eq.0) lprn=.false.
       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)
@@ -1411,7 +1411,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
 c            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
 c            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
@@ -1537,7 +1537,7 @@ c     if (icall.eq.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)
@@ -1554,7 +1554,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
 c            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             sig0ij=sigma(itypi,itypj)
@@ -1785,7 +1785,7 @@ cd    print *,'Entering Esoft_sphere nnt=',nnt,' nct=',nct
       evdw=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)
@@ -1798,7 +1798,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
@@ -1866,7 +1866,7 @@ cd      write(iout,*) 'In EELEC_soft_sphere'
       eello_turn4=0.0d0
       ind=0
       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
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
@@ -1876,7 +1876,7 @@ cd      write(iout,*) 'In EELEC_soft_sphere'
         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
           ind=ind+1
           iteli=itel(i)
           itelj=itel(j)
@@ -2755,8 +2755,8 @@ C
 C Loop over i,i+2 and i,i+3 pairs of the peptide groups
 C
       do i=iturn3_start,iturn3_end
-        if (itype(i).eq.21 .or. itype(i+1).eq.21 
-     &  .or. itype(i+2).eq.21 .or. itype(i+3).eq.21) cycle
+        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
+     &  .or. itype(i+2).eq.ntyp1 .or. itype(i+3).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
@@ -2772,9 +2772,9 @@ C
         num_cont_hb(i)=num_conti
       enddo
       do i=iturn4_start,iturn4_end
-        if (itype(i).eq.21 .or. itype(i+1).eq.21
-     &    .or. itype(i+3).eq.21
-     &    .or. itype(i+4).eq.21) cycle
+        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
+     &    .or. itype(i+3).eq.ntyp1
+     &    .or. itype(i+4).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
@@ -2786,7 +2786,7 @@ C
         zmedi=c(3,i)+0.5d0*dzi
         num_conti=num_cont_hb(i)
         call eelecij(i,i+3,ees,evdw1,eel_loc)
-        if (wturn4.gt.0.0d0 .and. itype(i+2).ne.21) 
+        if (wturn4.gt.0.0d0 .and. itype(i+2).ne.ntyp1) 
      &   call eturn4(i,eello_turn4)
         num_cont_hb(i)=num_conti
       enddo   ! i
@@ -2794,7 +2794,7 @@ c
 c Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
 c
       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
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
@@ -2808,7 +2808,7 @@ c        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         num_conti=num_cont_hb(i)
         do j=ielstart(i),ielend(i)
 c          write (iout,*) i,j,itype(i),itype(j)
-          if (itype(j).eq.21 .or. itype(j+1).eq.21) cycle
+          if (itype(j).eq.ntyp1.or. itype(j+1).eq.ntyp1) cycle
           call eelecij(i,j,ees,evdw1,eel_loc)
         enddo ! j
         num_cont_hb(i)=num_conti
@@ -3802,7 +3802,7 @@ C
 cd    print '(a)','Enter ESCP'
 cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       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)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
@@ -3811,7 +3811,7 @@ cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
-          if (itype(j).eq.21) cycle
+          if (itype(j).eq.ntyp1) cycle
           itypj=iabs(itype(j))
 C Uncomment following three lines for SC-p interactions
 c         xj=c(1,nres+j)-xi
@@ -3898,7 +3898,7 @@ C
 cd    print '(a)','Enter ESCP'
 cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       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)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
@@ -3908,7 +3908,7 @@ cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
 
         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
@@ -4180,7 +4180,7 @@ c
       estr=0.0d0
       estr1=0.0d0
       do i=ibondp_start,ibondp_end
-        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)
@@ -4205,7 +4205,7 @@ c 09/18/07 AL: multimodal bond potential based on AM1 CA-SC PMF's included
 c
       do i=ibond_start,ibond_end
         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)
@@ -4278,7 +4278,7 @@ c      time12=1.0d0
       etheta=0.0D0
 c     write (*,'(a,i2)') 'EBEND ICG=',icg
       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)
@@ -4295,7 +4295,7 @@ C Zero the energy function and its derivative at 0 or pi.
           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)
           if (phii.ne.phii) phii=150.0
@@ -4308,7 +4308,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)
           if (phii1.ne.phii1) phii1=150.0
@@ -4516,7 +4516,7 @@ C
       logical lprn /.false./, lprn1 /.false./
       etheta=0.0D0
       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
@@ -4526,7 +4526,7 @@ C
           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
@@ -4546,7 +4546,7 @@ C
             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
@@ -4704,7 +4704,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
@@ -5003,7 +5003,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)))
@@ -5431,8 +5431,8 @@ c      lprn=.true.
       etors=0.0D0
       do i=iphi_start,iphi_end
       etors_ii=0.0D0
-        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)
@@ -5528,8 +5528,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
         etors_ii=0.0D0
          if (iabs(itype(i)).eq.20) then
          iblock=2
@@ -5629,8 +5629,8 @@ C Set lprn=.true. for debugging
 c     lprn=.true.
       etors_d=0.0D0
       do i=iphid_start,iphid_end
-        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
         itori=itortyp(itype(i-2))
         itori1=itortyp(itype(i-1))
         itori2=itortyp(itype(i))
@@ -5709,7 +5709,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=iabs(itype(i-2))
         itori1=iabs(itype(i-1))