Merge branch 'bartek2' into bartek
[unres.git] / source / unres / src_CSA_DiL / energy_p_new_barrier.F
index 8f1e838..b4e0b64 100644 (file)
@@ -1089,8 +1089,8 @@ C
 c      write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
-        itypi1=itype(i+1)
+        itypi=iabs(itype(i))
+        itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -1103,7 +1103,7 @@ C
 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=itype(j)
+            itypj=iabs(itype(j))
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             zj=c(3,nres+j)-zi
@@ -1266,8 +1266,8 @@ C
 c     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
-        itypi1=itype(i+1)
+        itypi=iabs(itype(i))
+        itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -1276,7 +1276,7 @@ C Calculate SC interaction energy.
 C
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
-            itypj=itype(j)
+            itypj=iabs(itype(j))
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             zj=c(3,nres+j)-zi
@@ -1383,8 +1383,8 @@ c     else
 c     endif
       ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
-        itypi1=itype(i+1)
+        itypi=iabs(itype(i))
+        itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -1519,8 +1519,8 @@ c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
 c     if (icall.eq.0) lprn=.false.
       ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
-        itypi1=itype(i+1)
+        itypi=iabs(itype(i))
+        itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -1537,7 +1537,7 @@ C
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
             ind=ind+1
-            itypj=itype(j)
+            itypj=iabs(itype(j))
 c            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
 c            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
@@ -1678,8 +1678,8 @@ c     print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
 c     if (icall.eq.0) lprn=.true.
       ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
-        itypi1=itype(i+1)
+        itypi=iabs(itype(i))
+        itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -1694,7 +1694,7 @@ C
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
             ind=ind+1
-            itypj=itype(j)
+            itypj=iabs(itype(j))
 c            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             sig0ij=sigma(itypi,itypj)
@@ -2001,8 +2001,8 @@ C
 cd    print *,'Entering Esoft_sphere nnt=',nnt,' nct=',nct
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
-        itypi1=itype(i+1)
+        itypi=iabs(itype(i))
+        itypi1=iabs(itype(i+1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -2013,7 +2013,7 @@ C
 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=itype(j)
+            itypj=iabs(itype(j))
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             zj=c(3,nres+j)-zi
@@ -4032,7 +4032,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)
-          itypj=itype(j)
+          itypj=iabs(itype(j))
 C Uncomment following three lines for SC-p interactions
 c         xj=c(1,nres+j)-xi
 c         yj=c(2,nres+j)-yi
@@ -4126,7 +4126,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)
-          itypj=itype(j)
+          itypj=iabs(itype(j))
 C Uncomment following three lines for SC-p interactions
 c         xj=c(1,nres+j)-xi
 c         yj=c(2,nres+j)-yi
@@ -4242,7 +4242,8 @@ C iii and jjj point to the residues for which the distance is assigned.
 cd        write (iout,*) "i",i," ii",ii," iii",iii," jj",jj," jjj",jjj
 C 24/11/03 AL: SS bridges handled separately because of introducing a specific
 C    distance and angle dependent SS bond potential.
-        if (ii.gt.nres .and. itype(iii).eq.1 .and. itype(jjj).eq.1) then
+        if (ii.gt.nres .and. iabs(itype(iii)).eq.1 .and. iabs(itype(jjj
+     &)).eq.1) then
           call ssbond_ene(iii,jjj,eij)
           ehpb=ehpb+2*eij
 cd          write (iout,*) "eij",eij
@@ -4306,7 +4307,7 @@ C
       include 'COMMON.VAR'
       include 'COMMON.IOUNITS'
       double precision erij(3),dcosom1(3),dcosom2(3),gg(3)
-      itypi=itype(i)
+      itypi=iabs(itype(i))
       xi=c(1,nres+i)
       yi=c(2,nres+i)
       zi=c(3,nres+i)
@@ -4315,7 +4316,7 @@ C
       dzi=dc_norm(3,nres+i)
 c      dsci_inv=dsc_inv(itypi)
       dsci_inv=vbld_inv(nres+i)
-      itypj=itype(j)
+      itypj=iabs(itype(j))
 c      dscj_inv=dsc_inv(itypj)
       dscj_inv=vbld_inv(nres+j)
       xj=c(1,nres+j)-xi
@@ -4409,7 +4410,7 @@ c
 c 09/18/07 AL: multimodal bond potential based on AM1 CA-SC PMF's included
 c
       do i=ibond_start,ibond_end
-        iti=itype(i)
+        iti=iabs(itype(i))
         if (iti.ne.10) then
           nbi=nbondterm(iti)
           if (nbi.eq.1) then
@@ -4484,6 +4485,9 @@ c     write (*,'(a,i2)') 'EBEND ICG=',icg
       do i=ithet_start,ithet_end
 C Zero the energy function and its derivative at 0 or pi.
         call splinthet(theta(i),0.5d0*delta,ss,ssd)
+<<<<<<< HEAD
+        it=iabs(itype(i-1))
+=======
         it=itype(i-1)
         ichir1=isign(1,itype(i-2))
         ichir2=isign(1,itype(i))
@@ -4497,6 +4501,7 @@ C Zero the energy function and its derivative at 0 or pi.
          ichir21=isign(1,itype(i))
          ichir22=isign(1,itype(i))
         endif
+>>>>>>> bartek2
         if (i.gt.3) then
 #ifdef OSF
          phii=phi(i)
@@ -4722,7 +4727,7 @@ C
         dephii=0.0d0
         dephii1=0.0d0
         theti2=0.5d0*theta(i)
-        ityp2=ithetyp(itype(i-1))
+        ityp2=ithetyp(iabs(itype(i-1)))
         do k=1,nntheterm
           coskt(k)=dcos(k*theti2)
           sinkt(k)=dsin(k*theti2)
@@ -4734,7 +4739,7 @@ C
 #else
           phii=phi(i)
 #endif
-          ityp1=ithetyp(itype(i-2))
+          ityp1=ithetyp(iabs(itype(i-2)))
           do k=1,nsingle
             cosph1(k)=dcos(k*phii)
             sinph1(k)=dsin(k*phii)
@@ -4755,7 +4760,7 @@ C
 #else
           phii1=phi(i+1)
 #endif
-          ityp3=ithetyp(itype(i))
+          ityp3=ithetyp(iabs(itype(i)))
           do k=1,nsingle
             cosph2(k)=dcos(k*phii1)
             sinph2(k)=dsin(k*phii1)
@@ -4906,7 +4911,7 @@ c     write (iout,'(a)') 'ESC'
       do i=loc_start,loc_end
         it=itype(i)
         if (it.eq.10) goto 1
-        nlobit=nlob(it)
+        nlobit=nlob(iabs(it))
 c       print *,'i=',i,' it=',it,' nlobit=',nlobit
 c       write (iout,*) 'i=',i,' ssa=',ssa,' ssad=',ssad
         theti=theta(i+1)-pipol
@@ -5063,11 +5068,11 @@ C Compute the contribution to SC energy and derivatives
 
           do j=1,nlobit
 #ifdef OSF
-            adexp=bsc(j,it)-0.5D0*contr(j,iii)+emin
+            adexp=bsc(j,iabs(it))-0.5D0*contr(j,iii)+emin
             if(adexp.ne.adexp) adexp=1.0
             expfac=dexp(adexp)
 #else
-            expfac=dexp(bsc(j,it)-0.5D0*contr(j,iii)+emin)
+            expfac=dexp(bsc(j,iabs(it))-0.5D0*contr(j,iii)+emin)
 #endif
 cd          print *,'j=',j,' expfac=',expfac
             escloc_i=escloc_i+expfac
@@ -5149,7 +5154,7 @@ C Compute the contribution to SC energy and derivatives
 
       dersc12=0.0d0
       do j=1,nlobit
-        expfac=dexp(bsc(j,it)-0.5D0*contr(j)+emin)
+        expfac=dexp(bsc(j,iabs(it))-0.5D0*contr(j)+emin)
         escloc_i=escloc_i+expfac
         do k=1,2
           dersc(k)=dersc(k)+Ax(k,j)*expfac
@@ -5632,6 +5637,11 @@ c      lprn=.true.
       etors_ii=0.0D0
        itori=itortyp(itype(i-2))
        itori1=itortyp(itype(i-1))
+        if (iabs(itype(i)).eq.20) then
+        iblock=2
+        else
+        iblock=1
+        endif
         phii=phi(i)
         gloci=0.0D0
 C Proline-Proline pair is a special case...
@@ -5731,9 +5741,9 @@ c     lprn=.true.
         phii=phi(i)
         gloci=0.0D0
 C Regular cosine and sine terms
-        do j=1,nterm(itori,itori1)
-          v1ij=v1(j,itori,itori1)
-          v2ij=v2(j,itori,itori1)
+        do j=1,nterm(itori,itori1,iblock)
+          v1ij=v1(j,itori,itori1,iblock)
+          v2ij=v2(j,itori,itori1,iblock)
           cosphi=dcos(j*phii)
           sinphi=dsin(j*phii)
           etors=etors+v1ij*cosphi+v2ij*sinphi
@@ -5748,7 +5758,7 @@ C          [v2 cos(phi/2)+v3 sin(phi/2)]^2 + 1
 C
         cosphi=dcos(0.5d0*phii)
         sinphi=dsin(0.5d0*phii)
-        do j=1,nlor(itori,itori1)
+        do j=1,nlor(itori,itori1,iblock)
           vl1ij=vlor1(j,itori,itori1)
           vl2ij=vlor2(j,itori,itori1)
           vl3ij=vlor3(j,itori,itori1)
           gloci=gloci+vl1ij*(vl3ij*cosphi-vl2ij*sinphi)*pom
         enddo
 C Subtract the constant term
-        etors=etors-v0(itori,itori1)
+        etors=etors-v0(itori,itori1,iblock)
           if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
-     &         'etor',i,etors_ii-v0(itori,itori1)
+     &         'etor',i,etors_ii-v0(itori,itori1,iblock)
         if (lprn)
      &  write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
      &  restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,
-     &  (v1(j,itori,itori1),j=1,6),(v2(j,itori,itori1),j=1,6)
+     &  (v1(j,itori,itori1,iblock),j=1,6),
+     &  (v2(j,itori,itori1,iblock),j=1,6)
         gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
 c       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
       enddo