added nanostructures energy to wham, no differs
[unres.git] / source / wham / src-M / energy_p_new.F
index b266ab4..81df835 100644 (file)
@@ -22,6 +22,8 @@ cMS$ATTRIBUTES C ::  proc_proc
       include 'COMMON.INTERACT'
       include 'COMMON.SBRIDGE'
       include 'COMMON.CHAIN'
+      include 'COMMON.SHIELD'
+      include 'COMMON.CONTROL'
       double precision fact(6)
 cd      write(iout, '(a,i2)')'Calling etotal ipot=',ipot
 cd    print *,'nnt=',nnt,' nct=',nct
@@ -44,11 +46,19 @@ C Gay-Berne potential (shifted LJ, angular dependence).
       goto 106
 C Gay-Berne-Vorobjev potential (shifted LJ, angular dependence).
   105 call egbv(evdw,evdw_t)
+C      write(iout,*) 'po elektostatyce'
 C
 C Calculate electrostatic (H-bonding) energy of the main chain.
 C
-  106 call eelec(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
-C
+  106 continue
+      if (shield_mode.eq.1) then
+       call set_shield_fac
+      else if  (shield_mode.eq.2) then
+       call set_shield_fac2
+      endif
+      call eelec(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
+C            write(iout,*) 'po eelec'
+
 C Calculate excluded-volume interaction energy between peptide groups
 C and side chains.
 C
@@ -56,8 +66,9 @@ C
 c
 c Calculate the bond-stretching energy
 c
+
       call ebond(estr)
-c      write (iout,*) "estr",estr
+C       write (iout,*) "estr",estr
 C 
 C Calculate the disulfide-bridge and other energy and the contributions
 C from other distance constraints.
@@ -67,13 +78,14 @@ cd    print *,'EHPB exitted succesfully.'
 C
 C Calculate the virtual-bond-angle energy.
 C
-      call ebend(ebe)
+C      print *,'Bend energy finished.'
+      call ebend(ebe,ethetacnstr)
 cd    print *,'Bend energy finished.'
 C
 C Calculate the SC local energy.
 C
       call esc(escloc)
-cd    print *,'SCLOC energy finished.'
+C       print *,'SCLOC energy finished.'
 C
 C Calculate the virtual-bond torsional energy.
 C
@@ -87,6 +99,23 @@ C
 C 21/5/07 Calculate local sicdechain correlation energy
 C
       call eback_sc_corr(esccor)
+
+      if (wliptran.gt.0) then
+        call Eliptransfer(eliptran)
+      endif
+
+      if (TUBElog.eq.1) then
+      print *,"just before call"
+        call calctube(Etube)
+       print *,"just after call",etube
+       elseif (TUBElog.eq.2) then
+        call calctube2(Etube)
+       elseif (TUBElog.eq.3) then
+        call calcnano(Etube)
+       else
+       Etube=0.0d0
+       endif
+
 C 
 C 12/1/95 Multi-body terms
 C
@@ -98,29 +127,61 @@ c         print *,"calling multibody_eello"
          call multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,n_corr1)
 c         write (*,*) 'n_corr=',n_corr,' n_corr1=',n_corr1
 c         print *,ecorr,ecorr5,ecorr6,eturn6
+      else
+         ecorr=0.0d0
+         ecorr5=0.0d0
+         ecorr6=0.0d0
+         eturn6=0.0d0
       endif
       if (wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) then
          call multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
       endif
 c      write (iout,*) "ft(6)",fact(6)," evdw",evdw," evdw_t",evdw_t
 #ifdef SPLITELE
+      if (shield_mode.gt.0) then
+      etot=fact(1)*wsc*(evdw+fact(6)*evdw_t)+fact(1)*wscp*evdw2
+     & +welec*fact(1)*ees
+     & +fact(1)*wvdwpp*evdw1
+     & +wang*ebe+wtor*fact(1)*etors+wscloc*escloc
+     & +wstrain*ehpb+wcorr*fact(3)*ecorr+wcorr5*fact(4)*ecorr5
+     & +wcorr6*fact(5)*ecorr6+wturn4*fact(3)*eello_turn4
+     & +wturn3*fact(2)*eello_turn3+wturn6*fact(5)*eturn6
+     & +wel_loc*fact(2)*eel_loc+edihcnstr+wtor_d*fact(2)*etors_d
+     & +wbond*estr+wsccor*fact(1)*esccor+ethetacnstr
+     & +wliptran*eliptran+wtube*Etube
+      else
       etot=wsc*(evdw+fact(6)*evdw_t)+wscp*evdw2+welec*fact(1)*ees
      & +wvdwpp*evdw1
      & +wang*ebe+wtor*fact(1)*etors+wscloc*escloc
-     & +wstrain*ehpb+nss*ebr+wcorr*fact(3)*ecorr+wcorr5*fact(4)*ecorr5
+     & +wstrain*ehpb+wcorr*fact(3)*ecorr+wcorr5*fact(4)*ecorr5
      & +wcorr6*fact(5)*ecorr6+wturn4*fact(3)*eello_turn4
      & +wturn3*fact(2)*eello_turn3+wturn6*fact(5)*eturn6
      & +wel_loc*fact(2)*eel_loc+edihcnstr+wtor_d*fact(2)*etors_d
-     & +wbond*estr+wsccor*fact(1)*esccor
+     & +wbond*estr+wsccor*fact(1)*esccor+ethetacnstr
+     & +wliptran*eliptran+wtube*Etube
+      endif
 #else
+      if (shield_mode.gt.0) then
+      etot=fact(1)wsc*(evdw+fact(6)*evdw_t)+fact(1)*wscp*evdw2
+     & +welec*fact(1)*(ees+evdw1)
+     & +wang*ebe+wtor*fact(1)*etors+wscloc*escloc
+     & +wstrain*ehpb+wcorr*fact(3)*ecorr+wcorr5*fact(4)*ecorr5
+     & +wcorr6*fact(5)*ecorr6+wturn4*fact(3)*eello_turn4
+     & +wturn3*fact(2)*eello_turn3+wturn6*fact(5)*eturn6
+     & +wel_loc*fact(2)*eel_loc+edihcnstr+wtor_d*fact(2)*etors_d
+     & +wbond*estr+wsccor*fact(1)*esccor+ethetacnstr
+     & +wliptran*eliptran+wtube*Etube
+      else
       etot=wsc*(evdw+fact(6)*evdw_t)+wscp*evdw2
      & +welec*fact(1)*(ees+evdw1)
      & +wang*ebe+wtor*fact(1)*etors+wscloc*escloc
-     & +wstrain*ehpb+nss*ebr+wcorr*fact(3)*ecorr+wcorr5*fact(4)*ecorr5
+     & +wstrain*ehpb+wcorr*fact(3)*ecorr+wcorr5*fact(4)*ecorr5
      & +wcorr6*fact(5)*ecorr6+wturn4*fact(3)*eello_turn4
      & +wturn3*fact(2)*eello_turn3+wturn6*fact(5)*eturn6
      & +wel_loc*fact(2)*eel_loc+edihcnstr+wtor_d*fact(2)*etors_d
-     & +wbond*estr+wsccor*fact(1)*esccor
+     & +wbond*estr+wsccor*fact(1)*esccor+ethetacnstr
+     & +wliptran*eliptran+wtube*Etube
+      endif
 #endif
       energia(0)=etot
       energia(1)=evdw
@@ -154,6 +215,9 @@ c      write (iout,*) "ft(6)",fact(6)," evdw",evdw," evdw_t",evdw_t
       energia(19)=esccor
       energia(20)=edihcnstr
       energia(21)=evdw_t
+      energia(24)=ethetacnstr
+      energia(22)=eliptran
+      energia(25)=Etube
 c detecting NaNQ
 #ifdef ISNAN
 #ifdef AIX
@@ -173,6 +237,11 @@ c detecting NaNQ
 #ifdef MPL
 c     endif
 #endif
+#define DEBUG
+#ifdef DEBUG
+      call enerprint(energia,fact)
+#endif
+#undef DEBUG
       if (calc_grad) then
 C
 C Sum up the components of the Cartesian gradient.
@@ -180,6 +249,7 @@ C
 #ifdef SPLITELE
       do i=1,nct
         do j=1,3
+      if (shield_mode.eq.0) then
           gradc(j,i,icg)=wsc*gvdwc(j,i)+wscp*gvdwc_scp(j,i)+
      &                welec*fact(1)*gelc(j,i)+wvdwpp*gvdwpp(j,i)+
      &                wbond*gradb(j,i)+
@@ -192,14 +262,78 @@ C
      &                wcorr6*fact(5)*gradcorr6(j,i)+
      &                wturn6*fact(5)*gcorr6_turn(j,i)+
      &                wsccor*fact(2)*gsccorc(j,i)
+     &               +wliptran*gliptranc(j,i)
+     &                 +welec*gshieldc(j,i)
+     &                 +welec*gshieldc_loc(j,i)
+     &                 +wcorr*gshieldc_ec(j,i)
+     &                 +wcorr*gshieldc_loc_ec(j,i)
+     &                 +wturn3*gshieldc_t3(j,i)
+     &                 +wturn3*gshieldc_loc_t3(j,i)
+     &                 +wturn4*gshieldc_t4(j,i)
+     &                 +wturn4*gshieldc_loc_t4(j,i)
+     &                 +wel_loc*gshieldc_ll(j,i)
+     &                 +wel_loc*gshieldc_loc_ll(j,i)
+     &                +wtube*gg_tube(j,i)
+
+
           gradx(j,i,icg)=wsc*gvdwx(j,i)+wscp*gradx_scp(j,i)+
      &                  wbond*gradbx(j,i)+
      &                  wstrain*ghpbx(j,i)+wcorr*gradxorr(j,i)+
      &                  wsccor*fact(2)*gsccorx(j,i)
+     &                 +wliptran*gliptranx(j,i)
+     &                 +welec*gshieldx(j,i)
+     &                 +wcorr*gshieldx_ec(j,i)
+     &                 +wturn3*gshieldx_t3(j,i)
+     &                 +wturn4*gshieldx_t4(j,i)
+     &                 +wel_loc*gshieldx_ll(j,i)
+
+        else
+          gradc(j,i,icg)=fact(1)*wsc*gvdwc(j,i)
+     &                +fact(1)*wscp*gvdwc_scp(j,i)+
+     &               welec*fact(1)*gelc(j,i)+fact(1)*wvdwpp*gvdwpp(j,i)+
+     &                wbond*gradb(j,i)+
+     &                wstrain*ghpbc(j,i)+
+     &                wcorr*fact(3)*gradcorr(j,i)+
+     &                wel_loc*fact(2)*gel_loc(j,i)+
+     &                wturn3*fact(2)*gcorr3_turn(j,i)+
+     &                wturn4*fact(3)*gcorr4_turn(j,i)+
+     &                wcorr5*fact(4)*gradcorr5(j,i)+
+     &                wcorr6*fact(5)*gradcorr6(j,i)+
+     &                wturn6*fact(5)*gcorr6_turn(j,i)+
+     &                wsccor*fact(2)*gsccorc(j,i)
+     &               +wliptran*gliptranc(j,i)
+     &                 +welec*gshieldc(j,i)
+     &                 +welec*gshieldc_loc(j,i)
+     &                 +wcorr*gshieldc_ec(j,i)
+     &                 +wcorr*gshieldc_loc_ec(j,i)
+     &                 +wturn3*gshieldc_t3(j,i)
+     &                 +wturn3*gshieldc_loc_t3(j,i)
+     &                 +wturn4*gshieldc_t4(j,i)
+     &                 +wturn4*gshieldc_loc_t4(j,i)
+     &                 +wel_loc*gshieldc_ll(j,i)
+     &                 +wel_loc*gshieldc_loc_ll(j,i)
+     &                +wtube*gg_tube(j,i)
+
+
+          gradx(j,i,icg)=fact(1)*wsc*gvdwx(j,i)
+     &                 +fact(1)*wscp*gradx_scp(j,i)+
+     &                  wbond*gradbx(j,i)+
+     &                  wstrain*ghpbx(j,i)+wcorr*gradxorr(j,i)+
+     &                  wsccor*fact(2)*gsccorx(j,i)
+     &                 +wliptran*gliptranx(j,i)
+     &                 +welec*gshieldx(j,i)
+     &                 +wcorr*gshieldx_ec(j,i)
+     &                 +wturn3*gshieldx_t3(j,i)
+     &                 +wturn4*gshieldx_t4(j,i)
+     &                 +wel_loc*gshieldx_ll(j,i)
+
+
+        endif
         enddo
 #else
       do i=1,nct
         do j=1,3
+                if (shield_mode.eq.0) then
           gradc(j,i,icg)=wsc*gvdwc(j,i)+wscp*gvdwc_scp(j,i)+
      &                welec*fact(1)*gelc(j,i)+wstrain*ghpbc(j,i)+
      &                wbond*gradb(j,i)+
@@ -211,10 +345,71 @@ C
      &                wcorr6*fact(5)*gradcorr6(j,i)+
      &                wturn6*fact(5)*gcorr6_turn(j,i)+
      &                wsccor*fact(2)*gsccorc(j,i)
+     &               +wliptran*gliptranc(j,i)
+     &                 +welec*gshieldc(j,i)
+     &                 +welec*gshieldc_loc(j,i)
+     &                 +wcorr*gshieldc_ec(j,i)
+     &                 +wcorr*gshieldc_loc_ec(j,i)
+     &                 +wturn3*gshieldc_t3(j,i)
+     &                 +wturn3*gshieldc_loc_t3(j,i)
+     &                 +wturn4*gshieldc_t4(j,i)
+     &                 +wturn4*gshieldc_loc_t4(j,i)
+     &                 +wel_loc*gshieldc_ll(j,i)
+     &                 +wel_loc*gshieldc_loc_ll(j,i)
+
           gradx(j,i,icg)=wsc*gvdwx(j,i)+wscp*gradx_scp(j,i)+
      &                  wbond*gradbx(j,i)+
      &                  wstrain*ghpbx(j,i)+wcorr*gradxorr(j,i)+
      &                  wsccor*fact(1)*gsccorx(j,i)
+     &                 +wliptran*gliptranx(j,i)
+     &                 +welec*gshieldx(j,i)
+     &                 +wcorr*gshieldx_ec(j,i)
+     &                 +wturn3*gshieldx_t3(j,i)
+     &                 +wturn4*gshieldx_t4(j,i)
+     &                 +wel_loc*gshieldx_ll(j,i)
+     &                 +wtube*gg_tube_sc(j,i)
+
+
+              else
+          gradc(j,i,icg)=fact(1)*wsc*gvdwc(j,i)+
+     &                   fact(1)*wscp*gvdwc_scp(j,i)+
+     &                welec*fact(1)*gelc(j,i)+wstrain*ghpbc(j,i)+
+     &                wbond*gradb(j,i)+
+     &                wcorr*fact(3)*gradcorr(j,i)+
+     &                wel_loc*fact(2)*gel_loc(j,i)+
+     &                wturn3*fact(2)*gcorr3_turn(j,i)+
+     &                wturn4*fact(3)*gcorr4_turn(j,i)+
+     &                wcorr5*fact(4)*gradcorr5(j,i)+
+     &                wcorr6*fact(5)*gradcorr6(j,i)+
+     &                wturn6*fact(5)*gcorr6_turn(j,i)+
+     &                wsccor*fact(2)*gsccorc(j,i)
+     &               +wliptran*gliptranc(j,i)
+     &                 +welec*gshieldc(j,i)
+     &                 +welec*gshieldc_loc(j,i)
+     &                 +wcorr*gshieldc_ec(j,i)
+     &                 +wcorr*gshieldc_loc_ec(j,i)
+     &                 +wturn3*gshieldc_t3(j,i)
+     &                 +wturn3*gshieldc_loc_t3(j,i)
+     &                 +wturn4*gshieldc_t4(j,i)
+     &                 +wturn4*gshieldc_loc_t4(j,i)
+     &                 +wel_loc*gshieldc_ll(j,i)
+     &                 +wel_loc*gshieldc_loc_ll(j,i)
+
+          gradx(j,i,icg)=fact(1)*wsc*gvdwx(j,i)+
+     &                  fact(1)*wscp*gradx_scp(j,i)+
+     &                  wbond*gradbx(j,i)+
+     &                  wstrain*ghpbx(j,i)+wcorr*gradxorr(j,i)+
+     &                  wsccor*fact(1)*gsccorx(j,i)
+     &                 +wliptran*gliptranx(j,i)
+     &                 +welec*gshieldx(j,i)
+     &                 +wcorr*gshieldx_ec(j,i)
+     &                 +wturn3*gshieldx_t3(j,i)
+     &                 +wturn4*gshieldx_t4(j,i)
+     &                 +wel_loc*gshieldx_ll(j,i)
+     &                 +wtube*gg_tube_sc(j,i)
+
+
+         endif
         enddo
 #endif
       enddo
@@ -228,8 +423,11 @@ C
      &   +wturn3*fact(2)*gel_loc_turn3(i)
      &   +wturn6*fact(5)*gel_loc_turn6(i)
      &   +wel_loc*fact(2)*gel_loc_loc(i)
+c     &   +wsccor*fact(1)*gsccor_loc(i)
+c BYLA ROZNICA Z CLUSTER< OSTATNIA LINIA DODANA
       enddo
       endif
+      if (dyn_ss) call dyn_set_nss
       return
       end
 C------------------------------------------------------------------------
@@ -267,6 +465,9 @@ C------------------------------------------------------------------------
       esccor=energia(19)
       edihcnstr=energia(20)
       estr=energia(18)
+      ethetacnstr=energia(24)
+      eliptran=energia(22)
+      Etube=energia(25)
 #ifdef SPLITELE
       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec*fact(1),evdw1,
      &  wvdwpp,
@@ -275,7 +476,8 @@ C------------------------------------------------------------------------
      &  ecorr,wcorr*fact(3),ecorr5,wcorr5*fact(4),ecorr6,wcorr6*fact(5),
      &  eel_loc,wel_loc*fact(2),eello_turn3,wturn3*fact(2),
      &  eello_turn4,wturn4*fact(3),eello_turn6,wturn6*fact(5),
-     &  esccor,wsccor*fact(1),edihcnstr,ebr*nss,etot
+     &  esccor,wsccor*fact(1),edihcnstr,ethetacnstr,ebr*nss,
+     & eliptran,wliptran,etube,wtube ,etot
    10 format (/'Virtual-chain energies:'//
      & 'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/
      & 'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/
@@ -297,7 +499,10 @@ C------------------------------------------------------------------------
      & 'ETURN6=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 6th order)'/
      & 'ESCCOR=',1pE16.6,' WEIGHT=',1pD16.6,' (backbone-rotamer corr)'/
      & 'EDIHC= ',1pE16.6,' (dihedral angle constraints)'/
+     & 'ETHETC= ',1pE16.6,' (valence angle constraints)'/
      & 'ESS=   ',1pE16.6,' (disulfide-bridge intrinsic energy)'/ 
+     & 'ELT=',1pE16.6, ' WEIGHT=',1pD16.6,' (Lipid transfer energy)'/
+     & 'ETUBE=',1pE16.6, ' WEIGHT=',1pD16.6,' (Lipid transfer energy)'/
      & 'ETOT=  ',1pE16.6,' (total)')
 #else
       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec*fact(1),estr,wbond,
@@ -306,7 +511,7 @@ C------------------------------------------------------------------------
      &  ecorr6,wcorr6*fact(5),eel_loc,wel_loc*fact(2),
      &  eello_turn3,wturn3*fact(2),eello_turn4,wturn4*fact(3),
      &  eello_turn6,wturn6*fact(5),esccor*fact(1),wsccor,
-     &  edihcnstr,ebr*nss,etot
+     &  edihcnstr,ethetacnstr,ebr*nss,eliptran,wliptran,etube,wtube,etot
    10 format (/'Virtual-chain energies:'//
      & 'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/
      & 'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/
@@ -327,7 +532,9 @@ C------------------------------------------------------------------------
      & 'ETURN6=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 6th order)'/
      & 'ESCCOR=',1pE16.6,' WEIGHT=',1pD16.6,' (backbone-rotamer corr)'/
      & 'EDIHC= ',1pE16.6,' (dihedral angle constraints)'/
+     & 'ETHETC= ',1pE16.6,' (valence angle constraints)'/
      & 'ESS=   ',1pE16.6,' (disulfide-bridge intrinsic energy)'/ 
+     & 'ELT=',1pE16.6, ' WEIGHT=',1pD16.6,' (Lipid transfer energy)'/
      & 'ETOT=  ',1pE16.6,' (total)')
 #endif
       return
@@ -359,11 +566,14 @@ C
       integer icant
       external icant
 cd    print *,'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
+c ROZNICA z cluster
       do i=1,210
         do j=1,2
           eneps_temp(j,i)=0.0d0
         enddo
       enddo
+cROZNICA
+
       evdw=0.0D0
       evdw_t=0.0d0
       do i=iatsc_s,iatsc_e
@@ -393,19 +603,22 @@ C Change 12/1/95 to calculate four-body interactions
 c           write (iout,*)'i=',i,' j=',j,' itypi=',itypi,' itypj=',itypj
             eps0ij=eps(itypi,itypj)
             fac=rrij**expon2
-            e1=fac*fac*aa(itypi,itypj)
-            e2=fac*bb(itypi,itypj)
+            e1=fac*fac*aa
+            e2=fac*bb
             evdwij=e1+e2
             ij=icant(itypi,itypj)
+c ROZNICA z cluster
             eneps_temp(1,ij)=eneps_temp(1,ij)+e1/dabs(eps0ij)
             eneps_temp(2,ij)=eneps_temp(2,ij)+e2/eps0ij
+c
+
 cd          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 cd          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 cd          write (iout,'(2(a3,i3,2x),6(1pd12.4)/2(3(1pd12.4),5x)/)')
 cd   &        restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
 cd   &        bb(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,epsi,sigm,
 cd   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
-            if (bb(itypi,itypj).gt.0.0d0) then
+            if (bb.gt.0.0d0) then
               evdw=evdw+evdwij
             else
               evdw_t=evdw_t+evdwij
@@ -563,8 +776,8 @@ C
             rij=1.0D0/r_inv_ij 
             r_shift_inv=1.0D0/(rij+r0(itypi,itypj)-sigma(itypi,itypj))
             fac=r_shift_inv**expon
-            e1=fac*fac*aa(itypi,itypj)
-            e2=fac*bb(itypi,itypj)
+            e1=fac*fac*aa
+            e2=fac*bb
             evdwij=e_augm+e1+e2
             ij=icant(itypi,itypj)
             eneps_temp(1,ij)=eneps_temp(1,ij)+(e1+a_augm)
@@ -577,7 +790,7 @@ cd   &        restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
 cd   &        bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
 cd   &        sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
 cd   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
-            if (bb(itypi,itypj).gt.0.0d0) then
+            if (bb.gt.0.0d0) then
               evdw=evdw+evdwij
             else 
               evdw_t=evdw_t+evdwij
@@ -709,8 +922,8 @@ C Calculate the angle-dependent terms of energy & contributions to derivatives.
 C Calculate whole angle-dependent part of epsilon and contributions
 C to its derivatives
             fac=(rrij*sigsq)**expon2
-            e1=fac*fac*aa(itypi,itypj)
-            e2=fac*bb(itypi,itypj)
+            e1=fac*fac*aa
+            e2=fac*bb
             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
             eps2der=evdwij*eps3rt
             eps3der=evdwij*eps2rt
@@ -720,15 +933,15 @@ C to its derivatives
             eneps_temp(1,ij)=eneps_temp(1,ij)+e1*aux
      &        /dabs(eps(itypi,itypj))
             eneps_temp(2,ij)=eneps_temp(2,ij)+e2*aux/eps(itypi,itypj)
-            if (bb(itypi,itypj).gt.0.0d0) then
+            if (bb.gt.0.0d0) then
               evdw=evdw+evdwij
             else
               evdw_t=evdw_t+evdwij
             endif
             if (calc_grad) then
             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/bb)**(1.0D0/6.0D0)
+            epsi=bb**2/aa
             write (iout,'(2(a3,i3,2x),15(0pf7.3))')
      &        restyp(itypi),i,restyp(itypj),j,
      &        epsi,sigm,chi1,chi2,chip1,chip2,
@@ -775,9 +988,10 @@ C
       include 'COMMON.ENEPS'
       include 'COMMON.IOUNITS'
       include 'COMMON.CALC'
+      include 'COMMON.SBRIDGE'
       logical lprn
       common /srutu/icall
-      integer icant
+      integer icant,xshift,yshift,zshift
       external icant
       do i=1,210
         do j=1,2
@@ -797,6 +1011,36 @@ c      if (icall.gt.0) lprn=.true.
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
+C returning the ith atom to box
+          xi=mod(xi,boxxsize)
+          if (xi.lt.0) xi=xi+boxxsize
+          yi=mod(yi,boxysize)
+          if (yi.lt.0) yi=yi+boxysize
+          zi=mod(zi,boxzsize)
+          if (zi.lt.0) zi=zi+boxzsize
+       if ((zi.gt.bordlipbot)
+     &.and.(zi.lt.bordliptop)) then
+C the energy transfer exist
+        if (zi.lt.buflipbot) then
+C what fraction I am in
+         fracinbuf=1.0d0-
+     &        ((zi-bordlipbot)/lipbufthick)
+C lipbufthick is thickenes of lipid buffore
+         sslipi=sscalelip(fracinbuf)
+         ssgradlipi=-sscagradlip(fracinbuf)/lipbufthick
+        elseif (zi.gt.bufliptop) then
+         fracinbuf=1.0d0-((bordliptop-zi)/lipbufthick)
+         sslipi=sscalelip(fracinbuf)
+         ssgradlipi=sscagradlip(fracinbuf)/lipbufthick
+        else
+         sslipi=1.0d0
+         ssgradlipi=0.0
+        endif
+       else
+         sslipi=0.0d0
+         ssgradlipi=0.0
+       endif
+
         dxi=dc_norm(1,nres+i)
         dyi=dc_norm(2,nres+i)
         dzi=dc_norm(3,nres+i)
@@ -806,6 +1050,26 @@ C Calculate SC interaction energy.
 C
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
+            IF (dyn_ss_mask(i).and.dyn_ss_mask(j)) THEN
+              call dyn_ssbond_ene(i,j,evdwij)
+              evdw=evdw+evdwij
+C            write (iout,'(a6,2i5,0pf7.3,a3,2f10.3)')
+C     &                        'evdw',i,j,evdwij,' ss',evdw,evdw_t
+C triple bond artifac removal
+             do k=j+1,iend(i,iint)
+C search over all next residues
+              if (dyn_ss_mask(k)) then
+C check if they are cysteins
+C              write(iout,*) 'k=',k
+              call triple_ssbond_ene(i,j,k,evdwij)
+C call the energy function that removes the artifical triple disulfide
+C bond the soubroutine is located in ssMD.F
+              evdw=evdw+evdwij
+C             write (iout,'(a6,2i5,0pf7.3,a3,2f10.3)')
+C     &                        'evdw',i,j,evdwij,'tss',evdw,evdw_t
+              endif!dyn_ss_mask(k)
+             enddo! k
+            ELSE
             ind=ind+1
             itypj=iabs(itype(j))
             if (itypj.eq.ntyp1) cycle
@@ -830,17 +1094,96 @@ c           chip12=0.0D0
 c           alf1=0.0D0
 c           alf2=0.0D0
 c           alf12=0.0D0
-            xj=c(1,nres+j)-xi
-            yj=c(2,nres+j)-yi
-            zj=c(3,nres+j)-zi
+            xj=c(1,nres+j)
+            yj=c(2,nres+j)
+            zj=c(3,nres+j)
+C returning jth atom to box
+          xj=mod(xj,boxxsize)
+          if (xj.lt.0) xj=xj+boxxsize
+          yj=mod(yj,boxysize)
+          if (yj.lt.0) yj=yj+boxysize
+          zj=mod(zj,boxzsize)
+          if (zj.lt.0) zj=zj+boxzsize
+       if ((zj.gt.bordlipbot)
+     &.and.(zj.lt.bordliptop)) then
+C the energy transfer exist
+        if (zj.lt.buflipbot) then
+C what fraction I am in
+         fracinbuf=1.0d0-
+     &        ((zj-bordlipbot)/lipbufthick)
+C lipbufthick is thickenes of lipid buffore
+         sslipj=sscalelip(fracinbuf)
+         ssgradlipj=-sscagradlip(fracinbuf)/lipbufthick
+        elseif (zj.gt.bufliptop) then
+         fracinbuf=1.0d0-((bordliptop-zj)/lipbufthick)
+         sslipj=sscalelip(fracinbuf)
+         ssgradlipj=sscagradlip(fracinbuf)/lipbufthick
+        else
+         sslipj=1.0d0
+         ssgradlipj=0.0
+        endif
+       else
+         sslipj=0.0d0
+         ssgradlipj=0.0
+       endif
+      aa=aa_lip(itypi,itypj)*(sslipi+sslipj)/2.0d0
+     &  +aa_aq(itypi,itypj)*(2.0d0-sslipi-sslipj)/2.0d0
+      bb=bb_lip(itypi,itypj)*(sslipi+sslipj)/2.0d0
+     &  +bb_aq(itypi,itypj)*(2.0d0-sslipi-sslipj)/2.0d0
+C       if (aa.ne.aa_aq(itypi,itypj)) then
+       
+C      write(iout,*) "tu,", i,j,aa_aq(itypi,itypj)-aa,
+C     & bb_aq(itypi,itypj)-bb,
+C     & sslipi,sslipj
+C         endif
+
+C        write(iout,*),aa,aa_lip(itypi,itypj),aa_aq(itypi,itypj)
+C checking the distance
+      dist_init=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
+      xj_safe=xj
+      yj_safe=yj
+      zj_safe=zj
+      subchap=0
+C finding the closest
+      do xshift=-1,1
+      do yshift=-1,1
+      do zshift=-1,1
+          xj=xj_safe+xshift*boxxsize
+          yj=yj_safe+yshift*boxysize
+          zj=zj_safe+zshift*boxzsize
+          dist_temp=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
+          if(dist_temp.lt.dist_init) then
+            dist_init=dist_temp
+            xj_temp=xj
+            yj_temp=yj
+            zj_temp=zj
+            subchap=1
+          endif
+       enddo
+       enddo
+       enddo
+       if (subchap.eq.1) then
+          xj=xj_temp-xi
+          yj=yj_temp-yi
+          zj=zj_temp-zi
+       else
+          xj=xj_safe-xi
+          yj=yj_safe-yi
+          zj=zj_safe-zi
+       endif
+
             dxj=dc_norm(1,nres+j)
             dyj=dc_norm(2,nres+j)
             dzj=dc_norm(3,nres+j)
 c            write (iout,*) i,j,xj,yj,zj
             rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
             rij=dsqrt(rrij)
+            sss=sscale((1.0d0/rij)/sigma(itypi,itypj))
+            sssgrad=sscagrad((1.0d0/rij)/sigma(itypi,itypj))
+            if (sss.le.0.0) cycle
 C Calculate angle-dependent terms of energy and contributions to their
 C derivatives.
+
             call sc_angular
             sigsq=1.0D0/sigsq
             sig=sig0ij*dsqrt(sigsq)
@@ -854,16 +1197,16 @@ C I hate to put IF's in the loops, but here don't have another choice!!!!
 c---------------------------------------------------------------
             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
+            e2=fac*bb
             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
             eps2der=evdwij*eps3rt
             eps3der=evdwij*eps2rt
             evdwij=evdwij*eps2rt*eps3rt
-            if (bb(itypi,itypj).gt.0) then
-              evdw=evdw+evdwij
+            if (bb.gt.0) then
+              evdw=evdw+evdwij*sss
             else
-              evdw_t=evdw_t+evdwij
+              evdw_t=evdw_t+evdwij*sss
             endif
             ij=icant(itypi,itypj)
             aux=eps1*eps2rt**2*eps3rt**2
@@ -874,8 +1217,9 @@ c            write (iout,*) "i",i," j",j," itypi",itypi," itypj",itypj,
 c     &         " ij",ij," eneps",aux*e1/dabs(eps(itypi,itypj)),
 c     &         aux*e2/eps(itypi,itypj)
 c            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/bb)**(1.0D0/6.0D0)
+            epsi=bb**2/aa
+C#define DEBUG
 #ifdef DEBUG
             write (iout,'(2(a3,i3,2x),17(0pf7.3))')
      &        restyp(itypi),i,restyp(itypj),j,
@@ -885,6 +1229,7 @@ c            if (lprn) then
      &        evdwij
              write (iout,*) "partial sum", evdw, evdw_t
 #endif
+C#undef DEBUG
 c            endif
             if (calc_grad) then
 C Calculate gradient components.
@@ -892,6 +1237,7 @@ C Calculate gradient components.
             fac=-expon*(e1+evdwij)*rij_shift
             sigder=fac*sigder
             fac=rij*fac
+            fac=fac+evdwij/sss*sssgrad/sigma(itypi,itypj)*rij
 C Calculate the radial part of the gradient
             gg(1)=xj*fac
             gg(2)=yj*fac
@@ -899,6 +1245,8 @@ C Calculate the radial part of the gradient
 C Calculate angular part of the gradient.
             call sc_grad
             endif
+C            write(iout,*)  "partial sum", evdw, evdw_t
+            ENDIF    ! dyn_ss            
           enddo      ! j
         enddo        ! iint
       enddo          ! i
@@ -1004,15 +1352,15 @@ C I hate to put IF's in the loops, but here don't have another choice!!!!
 c---------------------------------------------------------------
             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
+            e2=fac*bb
             evdwij=eps1*eps2rt*eps3rt*(e1+e2)
             eps2der=evdwij*eps3rt
             eps3der=evdwij*eps2rt
             fac_augm=rrij**expon
             e_augm=augm(itypi,itypj)*fac_augm
             evdwij=evdwij*eps2rt*eps3rt
-            if (bb(itypi,itypj).gt.0.0d0) then
+            if (bb.gt.0.0d0) then
               evdw=evdw+evdwij+e_augm
             else
               evdw_t=evdw_t+evdwij+e_augm
@@ -1723,6 +2071,8 @@ c        print *,"itilde3 i iti iti1",i,iti,iti1
         do k=1,2
           mu(k,i-2)=Ub2(k,i-2)+b1(k,iti1)
         enddo
+C        write (iout,*) 'mumu',i,b1(1,iti),Ub2(1,i-2)
+
 C Vectors and matrices dependent on a single virtual-bond dihedral.
         call matvec2(DD(1,1,iti),b1tilde(1,iti1),auxvec(1))
         call matvec2(Ug2(1,1,i-2),auxvec(1),Ug2Db1t(1,i-2)) 
@@ -1782,6 +2132,7 @@ C
       include 'COMMON.TORSION'
       include 'COMMON.VECTORS'
       include 'COMMON.FFIELD'
+      include 'COMMON.SHIELD'
       dimension ggg(3),gggp(3),gggm(3),erij(3),dcosb(3),dcosg(3),
      &          erder(3,3),uryg(3,3),urzg(3,3),vryg(3,3),vrzg(3,3)
       double precision acipa(2,2),agg(3,4),aggi(3,4),aggi1(3,4),
@@ -1845,14 +2196,22 @@ cd      enddo
       do i=1,nres
         num_cont_hb(i)=0
       enddo
-cd      print '(a)','Enter EELEC'
-cd      write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
+C      print '(a)','Enter EELEC'
+C      write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
       do i=1,nres
         gel_loc_loc(i)=0.0d0
         gcorr_loc(i)=0.0d0
       enddo
       do i=iatel_s,iatel_e
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+C          if (i.eq.1) then 
+           if (itype(i).eq.ntyp1.or. itype(i+1).eq.ntyp1
+C     &  .or. itype(i+2).eq.ntyp1) cycle
+C          else
+C        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
+C     &  .or. itype(i+2).eq.ntyp1
+C     &  .or. itype(i-1).eq.ntyp1
+     &) cycle
+C         endif
         if (itel(i).eq.0) goto 1215
         dxi=dc(1,i)
         dyi=dc(2,i)
@@ -1863,10 +2222,52 @@ cd      write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
         xmedi=c(1,i)+0.5d0*dxi
         ymedi=c(2,i)+0.5d0*dyi
         zmedi=c(3,i)+0.5d0*dzi
+          xmedi=mod(xmedi,boxxsize)
+          if (xmedi.lt.0) xmedi=xmedi+boxxsize
+          ymedi=mod(ymedi,boxysize)
+          if (ymedi.lt.0) ymedi=ymedi+boxysize
+          zmedi=mod(zmedi,boxzsize)
+          if (zmedi.lt.0) zmedi=zmedi+boxzsize
+          zmedi2=mod(zmedi,boxzsize)
+          if (zmedi2.lt.0) zmedi2=zmedi2+boxzsize
+       if ((zmedi2.gt.bordlipbot)
+     &.and.(zmedi2.lt.bordliptop)) then
+C the energy transfer exist
+        if (zmedi2.lt.buflipbot) then
+C what fraction I am in
+         fracinbuf=1.0d0-
+     &        ((zmedi2-bordlipbot)/lipbufthick)
+C lipbufthick is thickenes of lipid buffore
+         sslipi=sscalelip(fracinbuf)
+         ssgradlipi=-sscagradlip(fracinbuf)/lipbufthick
+        elseif (zmedi2.gt.bufliptop) then
+         fracinbuf=1.0d0-((bordliptop-zmedi2)/lipbufthick)
+         sslipi=sscalelip(fracinbuf)
+         ssgradlipi=sscagradlip(fracinbuf)/lipbufthick
+        else
+         sslipi=1.0d0
+         ssgradlipi=0.0d0
+        endif
+       else
+         sslipi=0.0d0
+         ssgradlipi=0.0d0
+       endif
+
         num_conti=0
-c        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
+C        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         do j=ielstart(i),ielend(i)
-          if (itype(j).eq.ntyp1 .or. itype(j+1).eq.ntyp1) cycle
+          if (j.lt.1) cycle
+C           if (itype(j).eq.ntyp1 .or. itype(j+1).eq.ntyp1
+C     & .or.itype(j+2).eq.ntyp1
+C     &) cycle  
+C          else     
+          if (itype(j).eq.ntyp1 .or. itype(j+1).eq.ntyp1
+C     & .or.itype(j+2).eq.ntyp1
+C     & .or.itype(j-1).eq.ntyp1
+     &) cycle
+C         endif
+C
+C) cycle
           if (itel(j).eq.0) goto 1216
           ind=ind+1
           iteli=itel(i)
@@ -1888,10 +2289,71 @@ C End diagnostics
           dx_normj=dc_norm(1,j)
           dy_normj=dc_norm(2,j)
           dz_normj=dc_norm(3,j)
-          xj=c(1,j)+0.5D0*dxj-xmedi
-          yj=c(2,j)+0.5D0*dyj-ymedi
-          zj=c(3,j)+0.5D0*dzj-zmedi
+          xj=c(1,j)+0.5D0*dxj
+          yj=c(2,j)+0.5D0*dyj
+          zj=c(3,j)+0.5D0*dzj
+         xj=mod(xj,boxxsize)
+          if (xj.lt.0) xj=xj+boxxsize
+          yj=mod(yj,boxysize)
+          if (yj.lt.0) yj=yj+boxysize
+          zj=mod(zj,boxzsize)
+          if (zj.lt.0) zj=zj+boxzsize
+       if ((zj.gt.bordlipbot)
+     &.and.(zj.lt.bordliptop)) then
+C the energy transfer exist
+        if (zj.lt.buflipbot) then
+C what fraction I am in
+         fracinbuf=1.0d0-
+     &        ((zj-bordlipbot)/lipbufthick)
+C lipbufthick is thickenes of lipid buffore
+         sslipj=sscalelip(fracinbuf)
+         ssgradlipj=-sscagradlip(fracinbuf)/lipbufthick
+        elseif (zj.gt.bufliptop) then
+         fracinbuf=1.0d0-((bordliptop-zj)/lipbufthick)
+         sslipj=sscalelip(fracinbuf)
+         ssgradlipj=sscagradlip(fracinbuf)/lipbufthick
+        else
+         sslipj=1.0d0
+         ssgradlipj=0.0
+        endif
+       else
+         sslipj=0.0d0
+         ssgradlipj=0.0
+       endif
+      dist_init=(xj-xmedi)**2+(yj-ymedi)**2+(zj-zmedi)**2
+      xj_safe=xj
+      yj_safe=yj
+      zj_safe=zj
+      isubchap=0
+      do xshift=-1,1
+      do yshift=-1,1
+      do zshift=-1,1
+          xj=xj_safe+xshift*boxxsize
+          yj=yj_safe+yshift*boxysize
+          zj=zj_safe+zshift*boxzsize
+          dist_temp=(xj-xmedi)**2+(yj-ymedi)**2+(zj-zmedi)**2
+          if(dist_temp.lt.dist_init) then
+            dist_init=dist_temp
+            xj_temp=xj
+            yj_temp=yj
+            zj_temp=zj
+            isubchap=1
+          endif
+       enddo
+       enddo
+       enddo
+       if (isubchap.eq.1) then
+          xj=xj_temp-xmedi
+          yj=yj_temp-ymedi
+          zj=zj_temp-zmedi
+       else
+          xj=xj_safe-xmedi
+          yj=yj_safe-ymedi
+          zj=zj_safe-zmedi
+       endif
           rij=xj*xj+yj*yj+zj*zj
+            sss=sscale(sqrt(rij))
+            sssgrad=sscagrad(sqrt(rij))
           rrmij=1.0D0/rij
           rij=dsqrt(rij)
           rmij=1.0D0/rij
@@ -1914,17 +2376,40 @@ c 4/26/02 - AL scaling down 1,4 repulsive VDW interactions
 c          write (iout,*) "i",i,iteli," j",j,itelj," eesij",eesij
 C 12/26/95 - for the evaluation of multi-body H-bonding interactions
           ees0ij=4.0D0+fac*fac-3.0D0*(cosb*cosb+cosg*cosg)
+          if (shield_mode.gt.0) then
+C#define DEBUG
+#ifdef DEBUG
+          write(iout,*) "ees_compon",i,j,el1,el2,
+     &    fac_shield(i),fac_shield(j)
+#endif
+C#undef DEBUG
+C          fac_shield(i)=0.4
+C          fac_shield(j)=0.6
+          el1=el1*fac_shield(i)**2*fac_shield(j)**2
+          el2=el2*fac_shield(i)**2*fac_shield(j)**2
+          eesij=(el1+el2)
+          ees=ees+eesij
+          else
+          fac_shield(i)=1.0
+          fac_shield(j)=1.0
+          eesij=(el1+el2)
           ees=ees+eesij
-          evdw1=evdw1+evdwij
-cd          write(iout,'(2(2i3,2x),7(1pd12.4)/2(3(1pd12.4),5x)/)')
-cd     &      iteli,i,itelj,j,aaa,bbb,ael6i,ael3i,
-cd     &      1.0D0/dsqrt(rrmij),evdwij,eesij,
-cd     &      xmedi,ymedi,zmedi,xj,yj,zj
+          endif
+          evdw1=evdw1+evdwij*sss
+c             write (iout,'(a6,2i5,0pf7.3,2i5,2e11.3)') 
+c     &'evdw1',i,j,evdwij
+c     &,iteli,itelj,aaa,evdw1
+
+C              write (iout,'(a6,2i5,0pf7.3)') 'ees',i,j,eesij
+c          write(iout,'(2(2i3,2x),7(1pd12.4)/2(3(1pd12.4),5x)/)')
+c     &      iteli,i,itelj,j,aaa,bbb,ael6i,ael3i,
+c     &      1.0D0/dsqrt(rrmij),evdwij,eesij,
+c     &      xmedi,ymedi,zmedi,xj,yj,zj
 C
 C Calculate contributions to the Cartesian gradient.
 C
 #ifdef SPLITELE
-          facvdw=-6*rrmij*(ev1+evdwij) 
+          facvdw=-6*rrmij*(ev1+evdwij)*sss
           facel=-3*rrmij*(el1+eesij)
           fac1=fac
           erij(1)=xj*rmij
@@ -1937,6 +2422,60 @@ C
           ggg(1)=facel*xj
           ggg(2)=facel*yj
           ggg(3)=facel*zj
+          if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
+     &  (shield_mode.gt.0)) then
+C          print *,i,j     
+          do ilist=1,ishield_list(i)
+           iresshield=shield_list(ilist,i)
+           do k=1,3
+           rlocshield=grad_shield_side(k,ilist,i)*eesij/fac_shield(i)
+     &      *2.0
+           gshieldx(k,iresshield)=gshieldx(k,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(k,ilist,i)*eesij/fac_shield(i)*2.0
+            gshieldc(k,iresshield-1)=gshieldc(k,iresshield-1)+rlocshield
+C           gshieldc_loc(k,iresshield)=gshieldc_loc(k,iresshield)
+C     & +grad_shield_loc(k,ilist,i)*eesij/fac_shield(i)
+C             if (iresshield.gt.i) then
+C               do ishi=i+1,iresshield-1
+C                gshieldc(k,ishi)=gshieldc(k,ishi)+rlocshield
+C     & +grad_shield_loc(k,ilist,i)*eesij/fac_shield(i)
+C
+C              enddo
+C             else
+C               do ishi=iresshield,i
+C                gshieldc(k,ishi)=gshieldc(k,ishi)-rlocshield
+C     & -grad_shield_loc(k,ilist,i)*eesij/fac_shield(i)
+C
+C               enddo
+C              endif
+           enddo
+          enddo
+          do ilist=1,ishield_list(j)
+           iresshield=shield_list(ilist,j)
+           do k=1,3
+           rlocshield=grad_shield_side(k,ilist,j)*eesij/fac_shield(j)
+     &     *2.0
+           gshieldx(k,iresshield)=gshieldx(k,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(k,ilist,j)*eesij/fac_shield(j)*2.0
+           gshieldc(k,iresshield-1)=gshieldc(k,iresshield-1)+rlocshield
+           enddo
+          enddo
+
+          do k=1,3
+            gshieldc(k,i)=gshieldc(k,i)+
+     &              grad_shield(k,i)*eesij/fac_shield(i)*2.0
+            gshieldc(k,j)=gshieldc(k,j)+
+     &              grad_shield(k,j)*eesij/fac_shield(j)*2.0
+            gshieldc(k,i-1)=gshieldc(k,i-1)+
+     &              grad_shield(k,i)*eesij/fac_shield(i)*2.0
+            gshieldc(k,j-1)=gshieldc(k,j-1)+
+     &              grad_shield(k,j)*eesij/fac_shield(j)*2.0
+
+           enddo
+           endif
+
           do k=1,3
             ghalf=0.5D0*ggg(k)
             gelc(k,i)=gelc(k,i)+ghalf
@@ -1950,9 +2489,18 @@ C
               gelc(l,k)=gelc(l,k)+ggg(l)
             enddo
           enddo
-          ggg(1)=facvdw*xj
-          ggg(2)=facvdw*yj
-          ggg(3)=facvdw*zj
+C          ggg(1)=facvdw*xj
+C          ggg(2)=facvdw*yj
+C          ggg(3)=facvdw*zj
+          if (sss.gt.0.0) then
+          ggg(1)=facvdw*xj+sssgrad*rmij*evdwij*xj
+          ggg(2)=facvdw*yj+sssgrad*rmij*evdwij*yj
+          ggg(3)=facvdw*zj+sssgrad*rmij*evdwij*zj
+          else
+          ggg(1)=0.0
+          ggg(2)=0.0
+          ggg(3)=0.0
+          endif
           do k=1,3
             ghalf=0.5D0*ggg(k)
             gvdwpp(k,i)=gvdwpp(k,i)+ghalf
@@ -1967,7 +2515,7 @@ C
             enddo
           enddo
 #else
-          facvdw=ev1+evdwij 
+          facvdw=(ev1+evdwij)*sss
           facel=el1+eesij  
           fac1=fac
           fac=-3*rrmij*(facvdw+facvdw+facel)
@@ -2011,15 +2559,19 @@ cd        print '(2i3,2(3(1pd14.5),3x))',i,j,(dcosb(k),k=1,3),
 cd   &          (dcosg(k),k=1,3)
           do k=1,3
             ggg(k)=ecosb*dcosb(k)+ecosg*dcosg(k) 
+     &      *fac_shield(i)**2*fac_shield(j)**2
           enddo
           do k=1,3
             ghalf=0.5D0*ggg(k)
             gelc(k,i)=gelc(k,i)+ghalf
      &               +(ecosa*(dc_norm(k,j)-cosa*dc_norm(k,i))
      &               + ecosb*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
+     &           *fac_shield(i)**2*fac_shield(j)**2
+
             gelc(k,j)=gelc(k,j)+ghalf
      &               +(ecosa*(dc_norm(k,i)-cosa*dc_norm(k,j))
      &               + ecosg*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
+     &           *fac_shield(i)**2*fac_shield(j)**2
           enddo
           do k=i+1,j-1
             do l=1,3
@@ -2265,18 +2817,81 @@ C Check the loc-el terms by numerical integration
 C Contribution to the local-electrostatic energy coming from the i-j pair
           eel_loc_ij=a22*muij(1)+a23*muij(2)+a32*muij(3)
      &     +a33*muij(4)
-cd          write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
-cd          write (iout,*) a22,muij(1),a23,muij(2),a32,muij(3)
+          if (shield_mode.eq.0) then
+           fac_shield(i)=1.0
+           fac_shield(j)=1.0
+C          else
+C           fac_shield(i)=0.4
+C           fac_shield(j)=0.6
+          endif
+          eel_loc_ij=eel_loc_ij
+     &    *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+c          write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
+C          write (iout,'(a6,2i5,0pf7.3)')
+C     &            'eelloc',i,j,eel_loc_ij
+C          write(iout,*) 'muije=',i,j,muij(1),muij(2),muij(3),muij(4)
+c          write (iout,*) a22,muij(1),a23,muij(2),a32,muij(3)
+C          eel_loc=eel_loc+eel_loc_ij
+          if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
+     &  (shield_mode.gt.0)) then
+C          print *,i,j     
+
+          do ilist=1,ishield_list(i)
+           iresshield=shield_list(ilist,i)
+           do k=1,3
+           rlocshield=grad_shield_side(k,ilist,i)*eel_loc_ij
+     &                                          /fac_shield(i)
+C     &      *2.0
+           gshieldx_ll(k,iresshield)=gshieldx_ll(k,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(k,ilist,i)*eel_loc_ij/fac_shield(i)
+            gshieldc_ll(k,iresshield-1)=gshieldc_ll(k,iresshield-1)
+     &      +rlocshield
+           enddo
+          enddo
+          do ilist=1,ishield_list(j)
+           iresshield=shield_list(ilist,j)
+           do k=1,3
+           rlocshield=grad_shield_side(k,ilist,j)*eel_loc_ij
+     &                                       /fac_shield(j)
+C     &     *2.0
+           gshieldx_ll(k,iresshield)=gshieldx_ll(k,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(k,ilist,j)*eel_loc_ij/fac_shield(j)
+           gshieldc_ll(k,iresshield-1)=gshieldc_ll(k,iresshield-1)
+     &             +rlocshield
+
+           enddo
+          enddo
+          do k=1,3
+            gshieldc_ll(k,i)=gshieldc_ll(k,i)+
+     &              grad_shield(k,i)*eel_loc_ij/fac_shield(i)
+            gshieldc_ll(k,j)=gshieldc_ll(k,j)+
+     &              grad_shield(k,j)*eel_loc_ij/fac_shield(j)
+            gshieldc_ll(k,i-1)=gshieldc_ll(k,i-1)+
+     &              grad_shield(k,i)*eel_loc_ij/fac_shield(i)
+            gshieldc_ll(k,j-1)=gshieldc_ll(k,j-1)+
+     &              grad_shield(k,j)*eel_loc_ij/fac_shield(j)
+           enddo
+           endif
           eel_loc=eel_loc+eel_loc_ij
+
 C Partial derivatives in virtual-bond dihedral angles gamma
           if (calc_grad) then
           if (i.gt.1)
      &    gel_loc_loc(i-1)=gel_loc_loc(i-1)+ 
-     &            a22*muder(1,i)*mu(1,j)+a23*muder(1,i)*mu(2,j)
-     &           +a32*muder(2,i)*mu(1,j)+a33*muder(2,i)*mu(2,j)
+     &            (a22*muder(1,i)*mu(1,j)+a23*muder(1,i)*mu(2,j)
+     &           +a32*muder(2,i)*mu(1,j)+a33*muder(2,i)*mu(2,j))
+     &    *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           gel_loc_loc(j-1)=gel_loc_loc(j-1)+ 
-     &            a22*mu(1,i)*muder(1,j)+a23*mu(1,i)*muder(2,j)
-     &           +a32*mu(2,i)*muder(1,j)+a33*mu(2,i)*muder(2,j)
+     &            (a22*mu(1,i)*muder(1,j)+a23*mu(1,i)*muder(2,j)
+     &           +a32*mu(2,i)*muder(1,j)+a33*mu(2,i)*muder(2,j))
+     &    *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 cd          call checkint3(i,j,mu1,mu2,a22,a23,a32,a33,acipa,eel_loc_ij)
 cd          write(iout,*) 'agg  ',agg
 cd          write(iout,*) 'aggi ',aggi
@@ -2286,8 +2901,11 @@ cd          write(iout,*) 'aggj1',aggj1
 
 C Derivatives of eello in DC(i+1) thru DC(j-1) or DC(nres-2)
           do l=1,3
-            ggg(l)=agg(l,1)*muij(1)+
-     &          agg(l,2)*muij(2)+agg(l,3)*muij(3)+agg(l,4)*muij(4)
+            ggg(l)=(agg(l,1)*muij(1)+
+     &          agg(l,2)*muij(2)+agg(l,3)*muij(3)+agg(l,4)*muij(4))
+     &    *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           enddo
           do k=i+2,j2
             do l=1,3
@@ -2296,14 +2914,26 @@ C Derivatives of eello in DC(i+1) thru DC(j-1) or DC(nres-2)
           enddo
 C Remaining derivatives of eello
           do l=1,3
-            gel_loc(l,i)=gel_loc(l,i)+aggi(l,1)*muij(1)+
-     &          aggi(l,2)*muij(2)+aggi(l,3)*muij(3)+aggi(l,4)*muij(4)
-            gel_loc(l,i+1)=gel_loc(l,i+1)+aggi1(l,1)*muij(1)+
-     &          aggi1(l,2)*muij(2)+aggi1(l,3)*muij(3)+aggi1(l,4)*muij(4)
-            gel_loc(l,j)=gel_loc(l,j)+aggj(l,1)*muij(1)+
-     &          aggj(l,2)*muij(2)+aggj(l,3)*muij(3)+aggj(l,4)*muij(4)
-            gel_loc(l,j1)=gel_loc(l,j1)+aggj1(l,1)*muij(1)+
-     &          aggj1(l,2)*muij(2)+aggj1(l,3)*muij(3)+aggj1(l,4)*muij(4)
+            gel_loc(l,i)=gel_loc(l,i)+(aggi(l,1)*muij(1)+
+     &          aggi(l,2)*muij(2)+aggi(l,3)*muij(3)+aggi(l,4)*muij(4))
+     &    *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
+            gel_loc(l,i+1)=gel_loc(l,i+1)+(aggi1(l,1)*muij(1)+
+     &         aggi1(l,2)*muij(2)+aggi1(l,3)*muij(3)+aggi1(l,4)*muij(4))
+     &    *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
+            gel_loc(l,j)=gel_loc(l,j)+(aggj(l,1)*muij(1)+
+     &          aggj(l,2)*muij(2)+aggj(l,3)*muij(3)+aggj(l,4)*muij(4))
+     &    *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
+            gel_loc(l,j1)=gel_loc(l,j1)+(aggj1(l,1)*muij(1)+
+     &         aggj1(l,2)*muij(2)+aggj1(l,3)*muij(3)+aggj1(l,4)*muij(4))
+     &    *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           enddo
           endif
           ENDIF
@@ -2410,8 +3040,20 @@ c               fac3=dsqrt(-ael6i)/r0ij**3
                 ees0pij=dsqrt(4.0D0+cosa4+wij*wij-3.0D0*cosbg1*cosbg1)
                 ees0mij=dsqrt(4.0D0-cosa4+wij*wij-3.0D0*cosbg2*cosbg2)
 c               ees0mij=0.0D0
+                if (shield_mode.eq.0) then
+                fac_shield(i)=1.0d0
+                fac_shield(j)=1.0d0
+                else
+                ees0plist(num_conti,i)=j
+C                fac_shield(i)=0.4d0
+C                fac_shield(j)=0.6d0
+                endif
                 ees0p(num_conti,i)=0.5D0*fac3*(ees0pij+ees0mij)
+     &          *fac_shield(i)*fac_shield(j)
+
                 ees0m(num_conti,i)=0.5D0*fac3*(ees0pij-ees0mij)
+     &          *fac_shield(i)*fac_shield(j)
+
 C Diagnostics. Comment out or remove after debugging!
 c               ees0p(num_conti,i)=0.5D0*fac3*ees0pij
 c               ees0m(num_conti,i)=0.5D0*fac3*ees0mij
@@ -2476,17 +3118,29 @@ C Derivatives due to the contact function
                   gacontp_hb1(k,num_conti,i)=ghalfp
      &              +(ecosap*(dc_norm(k,j)-cosa*dc_norm(k,i))
      &              + ecosbp*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
+     &          *fac_shield(i)*fac_shield(j)
+
                   gacontp_hb2(k,num_conti,i)=ghalfp
      &              +(ecosap*(dc_norm(k,i)-cosa*dc_norm(k,j))
      &              + ecosgp*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
+     &          *fac_shield(i)*fac_shield(j)
+
                   gacontp_hb3(k,num_conti,i)=gggp(k)
+     &          *fac_shield(i)*fac_shield(j)
+
                   gacontm_hb1(k,num_conti,i)=ghalfm
      &              +(ecosam*(dc_norm(k,j)-cosa*dc_norm(k,i))
      &              + ecosbm*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
+     &          *fac_shield(i)*fac_shield(j)
+
                   gacontm_hb2(k,num_conti,i)=ghalfm
      &              +(ecosam*(dc_norm(k,i)-cosa*dc_norm(k,j))
      &              + ecosgm*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
+     &          *fac_shield(i)*fac_shield(j)
+
                   gacontm_hb3(k,num_conti,i)=gggm(k)
+     &          *fac_shield(i)*fac_shield(j)
+
                 enddo
                 endif
 C Diagnostics. Comment out or remove after debugging!
@@ -2532,6 +3186,8 @@ C Third- and fourth-order contributions from turns
       include 'COMMON.TORSION'
       include 'COMMON.VECTORS'
       include 'COMMON.FFIELD'
+      include 'COMMON.SHIELD'
+      include 'COMMON.CONTROL'
       dimension ggg(3)
       double precision auxmat(2,2),auxmat1(2,2),auxmat2(2,2),pizda(2,2),
      &  e1t(2,2),e2t(2,2),e3t(2,2),e1tder(2,2),e2tder(2,2),e3tder(2,2),
@@ -2539,7 +3195,50 @@ C Third- and fourth-order contributions from turns
       double precision agg(3,4),aggi(3,4),aggi1(3,4),
      &    aggj(3,4),aggj1(3,4),a_temp(2,2)
       common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,j1,j2
+          zj=(c(3,j)+c(3,j+1))/2.0d0
+C          xj=mod(xj,boxxsize)
+C          if (xj.lt.0) xj=xj+boxxsize
+C          yj=mod(yj,boxysize)
+C          if (yj.lt.0) yj=yj+boxysize
+          zj=mod(zj,boxzsize)
+          if (zj.lt.0) zj=zj+boxzsize
+C          if ((zj.lt.0).or.(xj.lt.0).or.(yj.lt.0)) write (*,*) "CHUJ"
+       if ((zj.gt.bordlipbot)
+     &.and.(zj.lt.bordliptop)) then
+C the energy transfer exist
+        if (zj.lt.buflipbot) then
+C what fraction I am in
+         fracinbuf=1.0d0-
+     &        ((zj-bordlipbot)/lipbufthick)
+C lipbufthick is thickenes of lipid buffore
+         sslipj=sscalelip(fracinbuf)
+         ssgradlipj=-sscagradlip(fracinbuf)/lipbufthick
+        elseif (zj.gt.bufliptop) then
+         fracinbuf=1.0d0-((bordliptop-zj)/lipbufthick)
+         sslipj=sscalelip(fracinbuf)
+         ssgradlipj=sscagradlip(fracinbuf)/lipbufthick
+        else
+         sslipj=1.0d0
+         ssgradlipj=0.0
+        endif
+       else
+         sslipj=0.0d0
+         ssgradlipj=0.0
+       endif
+
       if (j.eq.i+2) then
+      if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
+C changes suggested by Ana to avoid out of bounds
+C     & .or.((i+5).gt.nres)
+C     & .or.((i-1).le.0)
+C end of changes suggested by Ana
+     &    .or. itype(i+2).eq.ntyp1
+     &    .or. itype(i+3).eq.ntyp1
+C     &    .or. itype(i+5).eq.ntyp1
+C     &    .or. itype(i).eq.ntyp1
+C     &    .or. itype(i-1).eq.ntyp1
+     &    ) goto 179
+
 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
 C
 C               Third-order contributions
@@ -2554,22 +3253,86 @@ cd        call checkint_turn3(i,a_temp,eello_turn3_num)
         call matmat2(EUg(1,1,i+1),EUg(1,1,i+2),auxmat(1,1))
         call transpose2(auxmat(1,1),auxmat1(1,1))
         call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
+        if (shield_mode.eq.0) then
+        fac_shield(i)=1.0
+        fac_shield(j)=1.0
+C        else
+C        fac_shield(i)=0.4
+C        fac_shield(j)=0.6
+        endif
+
         eello_turn3=eello_turn3+0.5d0*(pizda(1,1)+pizda(2,2))
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
+        eello_t3=0.5d0*(pizda(1,1)+pizda(2,2))
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 cd        write (2,*) 'i,',i,' j',j,'eello_turn3',
 cd     &    0.5d0*(pizda(1,1)+pizda(2,2)),
 cd     &    ' eello_turn3_num',4*eello_turn3_num
         if (calc_grad) then
+C Derivatives in shield mode
+          if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
+     &  (shield_mode.gt.0)) then
+C          print *,i,j     
+
+          do ilist=1,ishield_list(i)
+           iresshield=shield_list(ilist,i)
+           do k=1,3
+           rlocshield=grad_shield_side(k,ilist,i)*eello_t3/fac_shield(i)
+C     &      *2.0
+           gshieldx_t3(k,iresshield)=gshieldx_t3(k,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(k,ilist,i)*eello_t3/fac_shield(i)
+            gshieldc_t3(k,iresshield-1)=gshieldc_t3(k,iresshield-1)
+     &      +rlocshield
+           enddo
+          enddo
+          do ilist=1,ishield_list(j)
+           iresshield=shield_list(ilist,j)
+           do k=1,3
+           rlocshield=grad_shield_side(k,ilist,j)*eello_t3/fac_shield(j)
+C     &     *2.0
+           gshieldx_t3(k,iresshield)=gshieldx_t3(k,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(k,ilist,j)*eello_t3/fac_shield(j)
+           gshieldc_t3(k,iresshield-1)=gshieldc_t3(k,iresshield-1)
+     &             +rlocshield
+
+           enddo
+          enddo
+
+          do k=1,3
+            gshieldc_t3(k,i)=gshieldc_t3(k,i)+
+     &              grad_shield(k,i)*eello_t3/fac_shield(i)
+            gshieldc_t3(k,j)=gshieldc_t3(k,j)+
+     &              grad_shield(k,j)*eello_t3/fac_shield(j)
+            gshieldc_t3(k,i-1)=gshieldc_t3(k,i-1)+
+     &              grad_shield(k,i)*eello_t3/fac_shield(i)
+            gshieldc_t3(k,j-1)=gshieldc_t3(k,j-1)+
+     &              grad_shield(k,j)*eello_t3/fac_shield(j)
+           enddo
+           endif
+
 C Derivatives in gamma(i)
         call matmat2(EUgder(1,1,i+1),EUg(1,1,i+2),auxmat2(1,1))
         call transpose2(auxmat2(1,1),pizda(1,1))
         call matmat2(a_temp(1,1),pizda(1,1),pizda(1,1))
         gel_loc_turn3(i)=gel_loc_turn3(i)+0.5d0*(pizda(1,1)+pizda(2,2))
+     &   *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 C Derivatives in gamma(i+1)
         call matmat2(EUg(1,1,i+1),EUgder(1,1,i+2),auxmat2(1,1))
         call transpose2(auxmat2(1,1),pizda(1,1))
         call matmat2(a_temp(1,1),pizda(1,1),pizda(1,1))
         gel_loc_turn3(i+1)=gel_loc_turn3(i+1)
      &    +0.5d0*(pizda(1,1)+pizda(2,2))
+     &   *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 C Cartesian derivatives
         do l=1,3
           a_temp(1,1)=aggi(l,1)
@@ -2579,6 +3342,9 @@ C Cartesian derivatives
           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
           gcorr3_turn(l,i)=gcorr3_turn(l,i)
      &      +0.5d0*(pizda(1,1)+pizda(2,2))
+     &   *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           a_temp(1,1)=aggi1(l,1)
           a_temp(1,2)=aggi1(l,2)
           a_temp(2,1)=aggi1(l,3)
@@ -2586,6 +3352,9 @@ C Cartesian derivatives
           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
           gcorr3_turn(l,i+1)=gcorr3_turn(l,i+1)
      &      +0.5d0*(pizda(1,1)+pizda(2,2))
+     &   *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           a_temp(1,1)=aggj(l,1)
           a_temp(1,2)=aggj(l,2)
           a_temp(2,1)=aggj(l,3)
@@ -2593,6 +3362,9 @@ C Cartesian derivatives
           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
           gcorr3_turn(l,j)=gcorr3_turn(l,j)
      &      +0.5d0*(pizda(1,1)+pizda(2,2))
+     &   *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           a_temp(1,1)=aggj1(l,1)
           a_temp(1,2)=aggj1(l,2)
           a_temp(2,1)=aggj1(l,3)
@@ -2600,9 +3372,24 @@ C Cartesian derivatives
           call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
           gcorr3_turn(l,j1)=gcorr3_turn(l,j1)
      &      +0.5d0*(pizda(1,1)+pizda(2,2))
+     &   *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
         enddo
         endif
+  179 continue
       else if (j.eq.i+3 .and. itype(i+2).ne.ntyp1) then
+      if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
+C changes suggested by Ana to avoid out of bounds
+C     & .or.((i+5).gt.nres)
+C     & .or.((i-1).le.0)
+C end of changes suggested by Ana
+     &    .or. itype(i+3).eq.ntyp1
+     &    .or. itype(i+4).eq.ntyp1
+C     &    .or. itype(i+5).eq.ntyp1
+     &    .or. itype(i).eq.ntyp1
+C     &    .or. itype(i-1).eq.ntyp1
+     &    ) goto 178
 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
 C
 C               Fourth-order contributions
@@ -2630,11 +3417,64 @@ cd        call checkint_turn4(i,a_temp,eello_turn4_num)
         call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
         call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
         s3=0.5d0*(pizda(1,1)+pizda(2,2))
+        if (shield_mode.eq.0) then
+        fac_shield(i)=1.0
+        fac_shield(j)=1.0
+C        else
+C        fac_shield(i)=0.4
+C        fac_shield(j)=0.6
+        endif
+
         eello_turn4=eello_turn4-(s1+s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+        eello_t4=-(s1+s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+
 cd        write (2,*) 'i,',i,' j',j,'eello_turn4',-(s1+s2+s3),
 cd     &    ' eello_turn4_num',8*eello_turn4_num
 C Derivatives in gamma(i)
         if (calc_grad) then
+          if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
+     &  (shield_mode.gt.0)) then
+C          print *,i,j     
+
+          do ilist=1,ishield_list(i)
+           iresshield=shield_list(ilist,i)
+           do k=1,3
+           rlocshield=grad_shield_side(k,ilist,i)*eello_t4/fac_shield(i)
+C     &      *2.0
+           gshieldx_t4(k,iresshield)=gshieldx_t4(k,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(k,ilist,i)*eello_t4/fac_shield(i)
+            gshieldc_t4(k,iresshield-1)=gshieldc_t4(k,iresshield-1)
+     &      +rlocshield
+           enddo
+          enddo
+          do ilist=1,ishield_list(j)
+           iresshield=shield_list(ilist,j)
+           do k=1,3
+           rlocshield=grad_shield_side(k,ilist,j)*eello_t4/fac_shield(j)
+C     &     *2.0
+           gshieldx_t4(k,iresshield)=gshieldx_t4(k,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(k,ilist,j)*eello_t4/fac_shield(j)
+           gshieldc_t4(k,iresshield-1)=gshieldc_t4(k,iresshield-1)
+     &             +rlocshield
+
+           enddo
+          enddo
+
+          do k=1,3
+            gshieldc_t4(k,i)=gshieldc_t4(k,i)+
+     &              grad_shield(k,i)*eello_t4/fac_shield(i)
+            gshieldc_t4(k,j)=gshieldc_t4(k,j)+
+     &              grad_shield(k,j)*eello_t4/fac_shield(j)
+            gshieldc_t4(k,i-1)=gshieldc_t4(k,i-1)+
+     &              grad_shield(k,i)*eello_t4/fac_shield(i)
+            gshieldc_t4(k,j-1)=gshieldc_t4(k,j-1)+
+     &              grad_shield(k,j)*eello_t4/fac_shield(j)
+           enddo
+           endif
         call transpose2(EUgder(1,1,i+1),e1tder(1,1))
         call matmat2(e1tder(1,1),a_temp(1,1),auxmat(1,1))
         call matvec2(auxmat(1,1),Ub2(1,i+3),auxvec(1))
@@ -2642,6 +3482,9 @@ C Derivatives in gamma(i)
         call matmat2(ae3e2(1,1),e1tder(1,1),pizda(1,1))
         s3=0.5d0*(pizda(1,1)+pizda(2,2))
         gel_loc_turn4(i)=gel_loc_turn4(i)-(s1+s3)
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 C Derivatives in gamma(i+1)
         call transpose2(EUgder(1,1,i+2),e2tder(1,1))
         call matvec2(ae3(1,1),Ub2der(1,i+2),auxvec(1)) 
@@ -2650,6 +3493,9 @@ C Derivatives in gamma(i+1)
         call matmat2(auxmat(1,1),e1t(1,1),pizda(1,1))
         s3=0.5d0*(pizda(1,1)+pizda(2,2))
         gel_loc_turn4(i+1)=gel_loc_turn4(i+1)-(s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 C Derivatives in gamma(i+2)
         call transpose2(EUgder(1,1,i+3),e3tder(1,1))
         call matvec2(e1a(1,1),Ub2der(1,i+3),auxvec(1))
@@ -2661,7 +3507,11 @@ C Derivatives in gamma(i+2)
         call matmat2(auxmat(1,1),e1t(1,1),pizda(1,1))
         s3=0.5d0*(pizda(1,1)+pizda(2,2))
         gel_loc_turn4(i+2)=gel_loc_turn4(i+2)-(s1+s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 C Cartesian derivatives
+
 C Derivatives of this turn contributions in DC(i+2)
         if (j.lt.nres-1) then
           do l=1,3
@@ -2680,6 +3530,9 @@ C Derivatives of this turn contributions in DC(i+2)
             s3=0.5d0*(pizda(1,1)+pizda(2,2))
             ggg(l)=-(s1+s2+s3)
             gcorr4_turn(l,i+2)=gcorr4_turn(l,i+2)-(s1+s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           enddo
         endif
 C Remaining derivatives of this turn contribution
@@ -2698,6 +3551,9 @@ C Remaining derivatives of this turn contribution
           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
           s3=0.5d0*(pizda(1,1)+pizda(2,2))
           gcorr4_turn(l,i)=gcorr4_turn(l,i)-(s1+s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           a_temp(1,1)=aggi1(l,1)
           a_temp(1,2)=aggi1(l,2)
           a_temp(2,1)=aggi1(l,3)
@@ -2712,6 +3568,9 @@ C Remaining derivatives of this turn contribution
           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
           s3=0.5d0*(pizda(1,1)+pizda(2,2))
           gcorr4_turn(l,i+1)=gcorr4_turn(l,i+1)-(s1+s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           a_temp(1,1)=aggj(l,1)
           a_temp(1,2)=aggj(l,2)
           a_temp(2,1)=aggj(l,3)
@@ -2726,6 +3585,9 @@ C Remaining derivatives of this turn contribution
           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
           s3=0.5d0*(pizda(1,1)+pizda(2,2))
           gcorr4_turn(l,j)=gcorr4_turn(l,j)-(s1+s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
           a_temp(1,1)=aggj1(l,1)
           a_temp(1,2)=aggj1(l,2)
           a_temp(2,1)=aggj1(l,3)
@@ -2740,8 +3602,20 @@ C Remaining derivatives of this turn contribution
           call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
           s3=0.5d0*(pizda(1,1)+pizda(2,2))
           gcorr4_turn(l,j1)=gcorr4_turn(l,j1)-(s1+s2+s3)
+     &  *fac_shield(i)*fac_shield(j)
+     &*((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
         enddo
+         gshieldc_t4(3,i)=gshieldc_t4(3,i)+
+     &     ssgradlipi*eello_t4/4.0d0*lipscale
+         gshieldc_t4(3,j)=gshieldc_t4(3,j)+
+     &     ssgradlipj*eello_t4/4.0d0*lipscale
+         gshieldc_t4(3,i-1)=gshieldc_t4(3,i-1)+
+     &     ssgradlipi*eello_t4/4.0d0*lipscale
+         gshieldc_t4(3,j-1)=gshieldc_t4(3,j-1)+
+     &     ssgradlipj*eello_t4/4.0d0*lipscale
         endif
+ 178  continue
       endif          
       return
       end
@@ -2811,7 +3685,13 @@ c     &   " iscp",(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         zi=0.5D0*(c(3,i)+c(3,i+1))
-
+C Returning the ith atom to box
+          xi=mod(xi,boxxsize)
+          if (xi.lt.0) xi=xi+boxxsize
+          yi=mod(yi,boxysize)
+          if (yi.lt.0) yi=yi+boxysize
+          zi=mod(zi,boxzsize)
+          if (zi.lt.0) zi=zi+boxzsize
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
@@ -2822,28 +3702,73 @@ c         xj=c(1,nres+j)-xi
 c         yj=c(2,nres+j)-yi
 c         zj=c(3,nres+j)-zi
 C Uncomment following three lines for Ca-p interactions
-          xj=c(1,j)-xi
-          yj=c(2,j)-yi
-          zj=c(3,j)-zi
+          xj=c(1,j)
+          yj=c(2,j)
+          zj=c(3,j)
+C returning the jth atom to box
+          xj=mod(xj,boxxsize)
+          if (xj.lt.0) xj=xj+boxxsize
+          yj=mod(yj,boxysize)
+          if (yj.lt.0) yj=yj+boxysize
+          zj=mod(zj,boxzsize)
+          if (zj.lt.0) zj=zj+boxzsize
+      dist_init=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
+      xj_safe=xj
+      yj_safe=yj
+      zj_safe=zj
+      subchap=0
+C Finding the closest jth atom
+      do xshift=-1,1
+      do yshift=-1,1
+      do zshift=-1,1
+          xj=xj_safe+xshift*boxxsize
+          yj=yj_safe+yshift*boxysize
+          zj=zj_safe+zshift*boxzsize
+          dist_temp=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
+          if(dist_temp.lt.dist_init) then
+            dist_init=dist_temp
+            xj_temp=xj
+            yj_temp=yj
+            zj_temp=zj
+            subchap=1
+          endif
+       enddo
+       enddo
+       enddo
+       if (subchap.eq.1) then
+          xj=xj_temp-xi
+          yj=yj_temp-yi
+          zj=zj_temp-zi
+       else
+          xj=xj_safe-xi
+          yj=yj_safe-yi
+          zj=zj_safe-zi
+       endif
           rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
+C sss is scaling function for smoothing the cutoff gradient otherwise
+C the gradient would not be continuouse
+          sss=sscale(1.0d0/(dsqrt(rrij)))
+          if (sss.le.0.0d0) cycle
+          sssgrad=sscagrad(1.0d0/(dsqrt(rrij)))
           fac=rrij**expon2
           e1=fac*fac*aad(itypj,iteli)
           e2=fac*bad(itypj,iteli)
           if (iabs(j-i) .le. 2) then
             e1=scal14*e1
             e2=scal14*e2
-            evdw2_14=evdw2_14+e1+e2
+            evdw2_14=evdw2_14+(e1+e2)*sss
           endif
           evdwij=e1+e2
-          write (iout,'(a6,2i5,0pf7.3,2i3,3e11.3)')
-     &        'evdw2',i,j,evdwij,iteli,itypj,fac,aad(itypj,iteli),
-     &       bad(itypj,iteli)
-          evdw2=evdw2+evdwij
+c          write (iout,'(a6,2i5,0pf7.3,2i3,3e11.3)')
+c     &        'evdw2',i,j,evdwij,iteli,itypj,fac,aad(itypj,iteli),
+c     &       bad(itypj,iteli)
+          evdw2=evdw2+evdwij*sss
           if (calc_grad) then
 C
 C Calculate contributions to the gradient in the virtual-bond and SC vectors.
 C
-          fac=-(evdwij+e1)*rrij
+          fac=-(evdwij+e1)*rrij*sss
+          fac=fac+(evdwij)*sssgrad*dsqrt(rrij)/expon
           ggg(1)=xj*fac
           ggg(2)=yj*fac
           ggg(3)=zj*fac
       include 'COMMON.DERIV'
       include 'COMMON.VAR'
       include 'COMMON.INTERACT'
+      include 'COMMON.CONTROL'
+      include 'COMMON.IOUNITS'
       dimension ggg(3)
       ehpb=0.0D0
 cd    print *,'edis: nhpb=',nhpb,' fbr=',fbr
 cd    print *,'link_start=',link_start,' link_end=',link_end
+C      write(iout,*) link_end, "link_end"
       if (link_end.eq.0) return
       do i=link_start,link_end
 C If ihpb(i) and jhpb(i) > NRES, this is a SC-SC distance, otherwise a
@@ -2928,25 +3856,98 @@ C iii and jjj point to the residues for which the distance is assigned.
         endif
 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. iabs(itype(iii)).eq.1 .and. 
+C        if (ii.gt.nres .and. iabs(itype(iii)).eq.1 .and. 
+C     & iabs(itype(jjj)).eq.1) then
+C       write(iout,*) constr_dist,"const"
+       if (.not.dyn_ss .and. i.le.nss) 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
-        else
-C Calculate the distance between the two points and its difference from the
-C target distance.
-        dd=dist(ii,jj)
-        rdis=dd-dhpb(i)
+           endif !ii.gt.neres
+        else if (ii.gt.nres .and. jj.gt.nres) then
+c Restraints from contact prediction
+          dd=dist(ii,jj)
+          if (constr_dist.eq.11) then
+C            ehpb=ehpb+fordepth(i)**4.0d0
+C     &          *rlornmr1(dd,dhpb(i),dhpb1(i),forcon(i))
+            ehpb=ehpb+fordepth(i)**4.0d0
+     &          *rlornmr1(dd,dhpb(i),dhpb1(i),forcon(i))
+            fac=fordepth(i)**4.0d0
+     &          *rlornmr1prim(dd,dhpb(i),dhpb1(i),forcon(i))/dd
+C          write (iout,'(a6,2i5,3f8.3)') "edisl",ii,jj,
+C     &    ehpb,fordepth(i),dd
+C            write(iout,*) ehpb,"atu?"
+C            ehpb,"tu?"
+C            fac=fordepth(i)**4.0d0
+C     &          *rlornmr1prim(dd,dhpb(i),dhpb1(i),forcon(i))/dd
+           else
+          if (dhpb1(i).gt.0.0d0) then
+            ehpb=ehpb+2*forcon(i)*gnmr1(dd,dhpb(i),dhpb1(i))
+            fac=forcon(i)*gnmr1prim(dd,dhpb(i),dhpb1(i))/dd
+c            write (iout,*) "beta nmr",
+c     &        dd,2*forcon(i)*gnmr1(dd,dhpb(i),dhpb1(i))
+          else
+            dd=dist(ii,jj)
+            rdis=dd-dhpb(i)
+C Get the force constant corresponding to this distance.
+            waga=forcon(i)
+C Calculate the contribution to energy.
+            ehpb=ehpb+waga*rdis*rdis
+c            write (iout,*) "beta reg",dd,waga*rdis*rdis
+C
+C Evaluate gradient.
+C
+            fac=waga*rdis/dd
+          endif !end dhpb1(i).gt.0
+          endif !end const_dist=11
+          do j=1,3
+            ggg(j)=fac*(c(j,jj)-c(j,ii))
+          enddo
+          do j=1,3
+            ghpbx(j,iii)=ghpbx(j,iii)-ggg(j)
+            ghpbx(j,jjj)=ghpbx(j,jjj)+ggg(j)
+          enddo
+          do k=1,3
+            ghpbc(k,jjj)=ghpbc(k,jjj)+ggg(k)
+            ghpbc(k,iii)=ghpbc(k,iii)-ggg(k)
+          enddo
+        else !ii.gt.nres
+C          write(iout,*) "before"
+          dd=dist(ii,jj)
+C          write(iout,*) "after",dd
+          if (constr_dist.eq.11) then
+            ehpb=ehpb+fordepth(i)**4.0d0
+     &          *rlornmr1(dd,dhpb(i),dhpb1(i),forcon(i))
+            fac=fordepth(i)**4.0d0
+     &          *rlornmr1prim(dd,dhpb(i),dhpb1(i),forcon(i))/dd
+C            ehpb=ehpb+fordepth(i)**4*rlornmr1(dd,dhpb(i),dhpb1(i))
+C            fac=fordepth(i)**4*rlornmr1prim(dd,dhpb(i),dhpb1(i))/dd
+C            print *,ehpb,"tu?"
+C            write(iout,*) ehpb,"btu?",
+C     & dd,dhpb(i),dhpb1(i),fordepth(i),forcon(i)
+C          write (iout,'(a6,2i5,3f8.3)') "edisl",ii,jj,
+C     &    ehpb,fordepth(i),dd
+           else   
+          if (dhpb1(i).gt.0.0d0) then
+            ehpb=ehpb+2*forcon(i)*gnmr1(dd,dhpb(i),dhpb1(i))
+            fac=forcon(i)*gnmr1prim(dd,dhpb(i),dhpb1(i))/dd
+c            write (iout,*) "alph nmr",
+c     &        dd,2*forcon(i)*gnmr1(dd,dhpb(i),dhpb1(i))
+          else
+            rdis=dd-dhpb(i)
 C Get the force constant corresponding to this distance.
-        waga=forcon(i)
+            waga=forcon(i)
 C Calculate the contribution to energy.
-        ehpb=ehpb+waga*rdis*rdis
+            ehpb=ehpb+waga*rdis*rdis
+c            write (iout,*) "alpha reg",dd,waga*rdis*rdis
 C
 C Evaluate gradient.
 C
-        fac=waga*rdis/dd
-cd      print *,'i=',i,' ii=',ii,' jj=',jj,' dhpb=',dhpb(i),' dd=',dd,
-cd   &   ' waga=',waga,' fac=',fac
+            fac=waga*rdis/dd
+          endif
+          endif
+
         do j=1,3
           ggg(j)=fac*(c(j,jj)-c(j,ii))
         enddo
@@ -2966,7 +3967,7 @@ C Cartesian gradient in the SC vectors (ghpbx).
         enddo
         endif
       enddo
-      ehpb=0.5D0*ehpb
+      if (constr_dist.ne.11) ehpb=0.5D0*ehpb
       return
       end
 C--------------------------------------------------------------------------
       estr1=0.0d0
 c      write (iout,*) "distchainmax",distchainmax
       do i=nnt+1,nct
-        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)
-     &      *dc(j,i-1)/vbld(i)
-          enddo
-          if (energy_dec) write(iout,*)
-     &       "estr1",i,vbld(i),distchainmax,
-     &       gnmr1(vbld(i),-1.0d0,distchainmax)
-        else
+        if (itype(i-1).eq.ntyp1 .and. itype(i).eq.ntyp1) cycle
+C          estr1=estr1+gnmr1(vbld(i),-1.0d0,distchainmax)
+C          do j=1,3
+C          gradb(j,i-1)=gnmr1prim(vbld(i),-1.0d0,distchainmax)
+C     &      *dc(j,i-1)/vbld(i)
+C          enddo
+C          if (energy_dec) write(iout,*)
+C     &       "estr1",i,vbld(i),distchainmax,
+C     &       gnmr1(vbld(i),-1.0d0,distchainmax)
+C        else
+         if (itype(i-1).eq.ntyp1 .or. itype(i).eq.ntyp1) then
+        diff = vbld(i)-vbldpDUM
+C         write(iout,*) i,diff
+         else
           diff = vbld(i)-vbldp0
 c          write (iout,*) i,vbld(i),vbldp0,diff,AKP*diff*diff
+         endif
           estr=estr+diff*diff
           do j=1,3
             gradb(j,i-1)=AKP*diff*dc(j,i-1)/vbld(i)
           enddo
-        endif
-
+C        endif
+C        write (iout,'(a7,i5,4f7.3)')
+C     &     "estr bb",i,vbld(i),vbldp0,diff,AKP*diff*diff
       enddo
       estr=0.5d0*AKP*estr+estr1
 c
@@ -3107,8 +4114,8 @@ c
           nbi=nbondterm(iti)
           if (nbi.eq.1) then
             diff=vbld(i+nres)-vbldsc0(1,iti)
-c            write (iout,*) i,iti,vbld(i+nres),vbldsc0(1,iti),diff,
-c     &      AKSC(1,iti),AKSC(1,iti)*diff*diff
+C            write (iout,*) i,iti,vbld(i+nres),vbldsc0(1,iti),diff,
+C     &      AKSC(1,iti),AKSC(1,iti)*diff*diff
             estr=estr+0.5d0*AKSC(1,iti)*diff*diff
             do j=1,3
               gradbx(j,i)=AKSC(1,iti)*diff*dc(j,i+nres)/vbld(i+nres)
@@ -3150,7 +4157,7 @@ c     &      AKSC(j,iti),abond0(j,iti),u(j),j=1,nbi)
       end
 #ifdef CRYST_THETA
 C--------------------------------------------------------------------------
-      subroutine ebend(etheta)
+      subroutine ebend(etheta,ethetacnstr)
 C
 C Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
 C angles gamma and its derivatives in consecutive thetas and gammas.
       include 'COMMON.IOUNITS'
       include 'COMMON.NAMES'
       include 'COMMON.FFIELD'
+      include 'COMMON.TORCNSTR'
       common /calcthet/ term1,term2,termm,diffak,ratak,
      & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
      & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
       double precision y(2),z(2)
       delta=0.02d0*pi
-      time11=dexp(-2*time)
-      time12=1.0d0
+c      time11=dexp(-2*time)
+c      time12=1.0d0
       etheta=0.0D0
 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.ntyp1) cycle
+C        if (itype(i-1).eq.ntyp1) cycle
+        if (i.le.2) cycle
+        if ((itype(i-1).eq.ntyp1).or.itype(i-2).eq.ntyp1
+     &  .or.itype(i).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)
@@ -3195,12 +4206,16 @@ 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.eq.3) then
+          y(1)=0.0D0
+          y(2)=0.0D0
+          else
 
-        if (i.gt.3 .and. itype(i-2).ne.ntyp1) then
+        if (i.gt.3 .and. itype(i-3).ne.ntyp1) then
 #ifdef OSF
           phii=phi(i)
-          icrc=0
-          call proc_proc(phii,icrc)
+c          icrc=0
+c          call proc_proc(phii,icrc)
           if (icrc.eq.1) phii=150.0
 #else
           phii=phi(i)
@@ -3211,11 +4226,12 @@ 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.ntyp1) then
+        endif
+        if (i.lt.nres .and. itype(i+1).ne.ntyp1) then
 #ifdef OSF
           phii1=phi(i+1)
-          icrc=0
-          call proc_proc(phii1,icrc)
+c          icrc=0
+c          call proc_proc(phii1,icrc)
           if (icrc.eq.1) phii1=150.0
           phii1=pinorm(phii1)
           z(1)=cos(phii1)
@@ -3278,12 +4294,41 @@ C Derivatives of the "mean" values in gamma1 and gamma2.
      &        E_theta,E_tc)
         endif
         etheta=etheta+ethetai
+c         write (iout,'(a6,i5,0pf7.3,f7.3,i5)')
+c     &      'ebend',i,ethetai,theta(i),itype(i)
 c        write (iout,'(2i3,3f8.3,f10.5)') i,it,rad2deg*theta(i),
 c     &    rad2deg*phii,rad2deg*phii1,ethetai
         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*E_tc*dthetg1
         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*E_tc*dthetg2
         gloc(nphi+i-2,icg)=wang*(E_theta+E_tc*dthett)
- 1215   continue
+c 1215   continue
+      enddo
+      ethetacnstr=0.0d0
+C      print *,ithetaconstr_start,ithetaconstr_end,"TU"
+      do i=1,ntheta_constr
+        itheta=itheta_constr(i)
+        thetiii=theta(itheta)
+        difi=pinorm(thetiii-theta_constr0(i))
+        if (difi.gt.theta_drange(i)) then
+          difi=difi-theta_drange(i)
+          ethetacnstr=ethetacnstr+0.25d0*for_thet_constr(i)*difi**4
+          gloc(itheta+nphi-2,icg)=gloc(itheta+nphi-2,icg)
+     &    +for_thet_constr(i)*difi**3
+        else if (difi.lt.-drange(i)) then
+          difi=difi+drange(i)
+          ethetacnstr=ethetacnstr+0.25d0*for_thet_constr(i)*difi**4
+          gloc(itheta+nphi-2,icg)=gloc(itheta+nphi-2,icg)
+     &    +for_thet_constr(i)*difi**3
+        else
+          difi=0.0
+        endif
+C       if (energy_dec) then
+C        write (iout,'(a6,2i5,4f8.3,2e14.5)') "ethetc",
+C     &    i,itheta,rad2deg*thetiii,
+C     &    rad2deg*theta_constr0(i),  rad2deg*theta_drange(i),
+C     &    rad2deg*difi,0.25d0*for_thet_constr(i)*difi**4,
+C     &    gloc(itheta+nphi-2,icg)
+C        endif
       enddo
 C Ufff.... We've done all this!!! 
       return
@@ -3398,7 +4443,7 @@ C "Thank you" to MAPLE (probably spared one day of hand-differentiation).
       end
 #else
 C--------------------------------------------------------------------------
-      subroutine ebend(etheta)
+      subroutine ebend(etheta,ethetacnstr)
 C
 C Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
 C angles gamma and its derivatives in consecutive thetas and gammas.
@@ -3418,6 +4463,7 @@ C
       include 'COMMON.NAMES'
       include 'COMMON.FFIELD'
       include 'COMMON.CONTROL'
+      include 'COMMON.TORCNSTR'
       double precision coskt(mmaxtheterm),sinkt(mmaxtheterm),
      & cosph1(maxsingle),sinph1(maxsingle),cosph2(maxsingle),
      & sinph2(maxsingle),cosph1ph2(maxdouble,maxdouble),
@@ -3426,7 +4472,11 @@ C
       etheta=0.0D0
 c      write (iout,*) "ithetyp",(ithetyp(i),i=1,ntyp1)
       do i=ithet_start,ithet_end
-        if (itype(i-1).eq.ntyp1) cycle
+C         if (i.eq.2) cycle
+C        if (itype(i-1).eq.ntyp1) cycle
+        if (i.le.2) cycle
+        if ((itype(i-1).eq.ntyp1).or.itype(i-2).eq.ntyp1
+     &  .or.itype(i).eq.ntyp1) cycle
         if (iabs(itype(i+1)).eq.20) iblock=2
         if (iabs(itype(i+1)).ne.20) iblock=1
         dethetai=0.0d0
@@ -3438,7 +4488,15 @@ c      write (iout,*) "ithetyp",(ithetyp(i),i=1,ntyp1)
           coskt(k)=dcos(k*theti2)
           sinkt(k)=dsin(k*theti2)
         enddo
-        if (i.gt.3 .and. itype(i-2).ne.ntyp1) then
+        if (i.eq.3) then 
+          phii=0.0d0
+          ityp1=nthetyp+1
+          do k=1,nsingle
+            cosph1(k)=0.0d0
+            sinph1(k)=0.0d0
+          enddo
+        else
+        if (i.gt.3 .and. itype(i-3).ne.ntyp1) then
 #ifdef OSF
           phii=phi(i)
           if (phii.ne.phii) phii=150.0
@@ -3452,13 +4510,15 @@ c      write (iout,*) "ithetyp",(ithetyp(i),i=1,ntyp1)
           enddo
         else
           phii=0.0d0
-          ityp1=nthetyp+1
+c          ityp1=nthetyp+1
           do k=1,nsingle
+            ityp1=ithetyp((itype(i-2)))
             cosph1(k)=0.0d0
             sinph1(k)=0.0d0
           enddo 
         endif
-        if (i.lt.nres .and. itype(i).ne.ntyp1) then
+        endif
+        if (i.lt.nres .and. itype(i+1).ne.ntyp1) then
 #ifdef OSF
           phii1=phi(i+1)
           if (phii1.ne.phii1) phii1=150.0
@@ -3473,7 +4533,8 @@ c      write (iout,*) "ithetyp",(ithetyp(i),i=1,ntyp1)
           enddo
         else
           phii1=0.0d0
-          ityp3=nthetyp+1
+c          ityp3=nthetyp+1
+          ityp3=ithetyp((itype(i)))
           do k=1,nsingle
             cosph2(k)=0.0d0
             sinph2(k)=0.0d0
@@ -3590,7 +4651,36 @@ c        call flush(iout)
         etheta=etheta+ethetai
         if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*dephii
         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*dephii1
-        gloc(nphi+i-2,icg)=wang*dethetai
+c        gloc(nphi+i-2,icg)=wang*dethetai
+        gloc(nphi+i-2,icg)=gloc(nphi+i-2,icg)+wang*dethetai
+      enddo
+C now constrains
+      ethetacnstr=0.0d0
+C      print *,ithetaconstr_start,ithetaconstr_end,"TU"
+      do i=1,ntheta_constr
+        itheta=itheta_constr(i)
+        thetiii=theta(itheta)
+        difi=pinorm(thetiii-theta_constr0(i))
+        if (difi.gt.theta_drange(i)) then
+          difi=difi-theta_drange(i)
+          ethetacnstr=ethetacnstr+0.25d0*for_thet_constr(i)*difi**4
+          gloc(itheta+nphi-2,icg)=gloc(itheta+nphi-2,icg)
+     &    +for_thet_constr(i)*difi**3
+        else if (difi.lt.-drange(i)) then
+          difi=difi+drange(i)
+          ethetacnstr=ethetacnstr+0.25d0*for_thet_constr(i)*difi**4
+          gloc(itheta+nphi-2,icg)=gloc(itheta+nphi-2,icg)
+     &    +for_thet_constr(i)*difi**3
+        else
+          difi=0.0
+        endif
+C       if (energy_dec) then
+C        write (iout,'(a6,2i5,4f8.3,2e14.5)') "ethetc",
+C     &    i,itheta,rad2deg*thetiii,
+C     &    rad2deg*theta_constr0(i),  rad2deg*theta_drange(i),
+C     &    rad2deg*difi,0.25d0*for_thet_constr(i)*difi**4,
+C     &    gloc(itheta+nphi-2,icg)
+C        endif
       enddo
       return
       end
@@ -3618,14 +4708,14 @@ C ALPHA and OMEGA.
       common /sccalc/ time11,time12,time112,theti,it,nlobit
       delta=0.02d0*pi
       escloc=0.0D0
-c     write (iout,'(a)') 'ESC'
+C      write (iout,*) 'ESC'
       do i=loc_start,loc_end
         it=itype(i)
         if (it.eq.ntyp1) cycle
         if (it.eq.10) goto 1
         nlobit=nlob(iabs(it))
 c       print *,'i=',i,' it=',it,' nlobit=',nlobit
-c       write (iout,*) 'i=',i,' ssa=',ssa,' ssad=',ssad
+C        write (iout,*) 'i=',i,' ssa=',ssa,' ssad=',ssad
         theti=theta(i+1)-pipol
         x(1)=dtan(theti)
         x(2)=alph(i)
@@ -3661,8 +4751,8 @@ c        write (iout,*) "i",i," x",x(1),x(2),x(3)
             dersc(k)=ss*dersc(k)+(1.0d0-ss)*dersc0(k)
           enddo
           dersc(2)=dersc(2)+ssd*(escloci-esclocbi)
-c         write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
-c    &             esclocbi,ss,ssd
+          write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
+     &             esclocbi,ss,ssd
           escloci=ss*escloci+(1.0d0-ss)*esclocbi
 c         escloci=esclocbi
 c         write (iout,*) escloci
@@ -3696,15 +4786,17 @@ c         write (iout,*) escloci
           enddo
           dersc(2)=dersc(2)+ssd*(escloci-esclocbi)
 c         write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
-c    &             esclocbi,ss,ssd
+c     &             esclocbi,ss,ssd
           escloci=ss*escloci+(1.0d0-ss)*esclocbi
-c         write (iout,*) escloci
+C         write (iout,*) 'i=',i, escloci
         else
           call enesc(x,escloci,dersc,ddummy,.false.)
         endif
 
         escloc=escloc+escloci
-c        write (iout,*) 'i=',i,' escloci=',escloci,' dersc=',dersc
+C        write (iout,*) 'i=',i,' escloci=',escloci,' dersc=',dersc
+            write (iout,'(a6,i5,0pf7.3)')
+     &     'escloc',i,escloci
 
         gloc(nphi+i-1,icg)=gloc(nphi+i-1,icg)+
      &   wscloc*dersc(1)
@@ -3941,7 +5033,7 @@ C     &   dc_norm(3,i+nres)
           y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
         enddo
         do j = 1,3
-          z_prime(j) = -uz(j,i-1)*dsign(1.0,dfloat(itype(i)))
+          z_prime(j) = -uz(j,i-1)*dsign(1.0d0,dfloat(itype(i)))
         enddo     
 c       write (2,*) "i",i
 c       write (2,*) "x_prime",(x_prime(j),j=1,3)
@@ -3981,7 +5073,7 @@ c        write (2,*) "xx",xx," yy",yy," zz",zz
 Cc diagnostics - remove later
         xx1 = dcos(alph(2))
         yy1 = dsin(alph(2))*dcos(omeg(2))
-        zz1 = -dsign(1.0,itype(i))*dsin(alph(2))*dsin(omeg(2))
+        zz1 = -dsign(1.0d0,itype(i))*dsin(alph(2))*dsin(omeg(2))
         write(2,'(3f8.1,3f9.3,1x,3f9.3)') 
      &    alph(2)*rad2deg,omeg(2)*rad2deg,theta(3)*rad2deg,xx,yy,zz,
      &    xx1,yy1,zz1
@@ -4024,6 +5116,8 @@ c     &   dscp1,dscp2,sumene
 c        sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
         escloc = escloc + sumene
 c        write (2,*) "escloc",escloc
+c        write (2,*) "i",i," escloc",sumene,escloc,it,itype(i),
+c     &  zz,xx,yy
         if (.not. calc_grad) goto 1
 #ifdef DEBUG
 C
@@ -4153,9 +5247,9 @@ c     &   (dC_norm(j,i-1),j=1,3)," vbld_inv",vbld_inv(i+1),vbld_inv(i)
          dZZ_Ci(k)=0.0d0
          do j=1,3
            dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1)
-     & *dsign(1.0,dfloat(itype(i)))*dC_norm(j,i+nres)
+     & *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
            dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1)
-     &  *dsign(1.0,dfloat(itype(i)))*dC_norm(j,i+nres)
+     &  *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
          enddo
           
          dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
@@ -4356,15 +5450,16 @@ c       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
         difi=phii-phi0(i)
         if (difi.gt.drange(i)) then
           difi=difi-drange(i)
-          edihcnstr=edihcnstr+0.25d0*ftors*difi**4
-          gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
+          edihcnstr=edihcnstr+0.25d0*ftors(i)*difi**4
+          gloc(itori-3,icg)=gloc(itori-3,icg)+ftors(i)*difi**3
         else if (difi.lt.-drange(i)) then
           difi=difi+drange(i)
-          edihcnstr=edihcnstr+0.25d0*ftors*difi**4
-          gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
+          edihcnstr=edihcnstr+0.25d0*ftors(i)*difi**4
+          gloc(itori-3,icg)=gloc(itori-3,icg)+ftors(i)*difi**3
         endif
-!        write (iout,'(2i5,2f8.3,2e14.5)') i,itori,rad2deg*phii,
-!     &    rad2deg*difi,0.25d0*ftors*difi**4,gloc(itori-3,icg)
+C        write (iout,'(a6,2i5,2f8.3,2e14.5)') "edih",
+C     &    i,itori,rad2deg*phii,
+C     &    rad2deg*difi,0.25d0*ftors(i)*difi**4,gloc(itori-3,icg)
       enddo
 !      write (iout,*) 'edihcnstr',edihcnstr
       return
@@ -4392,8 +5487,11 @@ C Set lprn=.true. for debugging
 c      lprn=.true.
       etors=0.0D0
       do i=iphi_start,iphi_end
-        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1
-     &       .or. itype(i).eq.ntyp1) cycle
+        if (i.le.2) cycle
+        if (itype(i-2).eq.ntyp1.or. itype(i-1).eq.ntyp1
+     &      .or. itype(i).eq.ntyp1 .or. itype(i-3).eq.ntyp1) cycle
+C        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1
+C     &       .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
@@ -4451,21 +5549,24 @@ c       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
         edihi=0.0d0
         if (difi.gt.drange(i)) then
           difi=difi-drange(i)
-          edihcnstr=edihcnstr+0.25d0*ftors*difi**4
-          gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
-          edihi=0.25d0*ftors*difi**4
+          edihcnstr=edihcnstr+0.25d0*ftors(i)*difi**4
+          gloc(itori-3,icg)=gloc(itori-3,icg)+ftors(i)*difi**3
+          edihi=0.25d0*ftors(i)*difi**4
         else if (difi.lt.-drange(i)) then
           difi=difi+drange(i)
-          edihcnstr=edihcnstr+0.25d0*ftors*difi**4
-          gloc(itori-3,icg)=gloc(itori-3,icg)+ftors*difi**3
-          edihi=0.25d0*ftors*difi**4
+          edihcnstr=edihcnstr+0.25d0*ftors(i)*difi**4
+          gloc(itori-3,icg)=gloc(itori-3,icg)+ftors(i)*difi**3
+          edihi=0.25d0*ftors(i)*difi**4
         else
           difi=0.0d0
         endif
+        write (iout,'(a6,2i5,2f8.3,2e14.5)') "edih",
+     &    i,itori,rad2deg*phii,
+     &    rad2deg*difi,0.25d0*ftors(i)*difi**4
 c        write (iout,'(2i5,4f10.5,e15.5)') i,itori,phii,phi0(i),difi,
 c     &    drange(i),edihi
 !        write (iout,'(2i5,2f8.3,2e14.5)') i,itori,rad2deg*phii,
-!     &    rad2deg*difi,0.25d0*ftors*difi**4,gloc(itori-3,icg)
+!     &    rad2deg*difi,0.25d0*ftors(i)*difi**4,gloc(itori-3,icg)
       enddo
 !      write (iout,*) 'edihcnstr',edihcnstr
       return
@@ -4493,8 +5594,12 @@ 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.ntyp1.or. itype(i-1).eq.ntyp1
-     &      .or. itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+        if (i.le.3) cycle
+C        if (itype(i-2).eq.ntyp1.or. itype(i-1).eq.ntyp1
+C     &      .or. itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+         if ((itype(i-2).eq.ntyp1).or.itype(i-3).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))
@@ -4608,6 +5713,7 @@ c   3 = SC...Ca...Ca...SCi
            esccor=esccor+v1ij*cosphi+v2ij*sinphi
            gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
          enddo
+C      write (iout,*)"EBACK_SC_COR",esccor,i
 c      write (iout,*) "EBACK_SC_COR",i,v1ij*cosphi+v2ij*sinphi,intertyp,
 c     & nterm_sccor(isccori,isccori1),isccori,isccori1
 c        gloc_sc(intertyp,i-3,icg)=gloc_sc(intertyp,i-3,icg)+wsccor*gloci
@@ -4726,9 +5832,9 @@ c------------------------------------------------------------------------------
       integer dimen1,dimen2,atom,indx
       double precision buffer(dimen1,dimen2)
       double precision zapas 
-      common /contacts_hb/ zapas(3,20,maxres,7),
-     &   facont_hb(20,maxres),ees0p(20,maxres),ees0m(20,maxres),
-     &         num_cont_hb(maxres),jcont_hb(20,maxres)
+      common /contacts_hb/ zapas(3,ntyp,maxres,7),
+     &   facont_hb(ntyp,maxres),ees0p(ntyp,maxres),ees0m(ntyp,maxres),
+     &         num_cont_hb(maxres),jcont_hb(ntyp,maxres)
       num_kont=num_cont_hb(atom)
       do i=1,num_kont
         do k=1,7
@@ -4751,9 +5857,10 @@ c------------------------------------------------------------------------------
       integer dimen1,dimen2,atom,indx
       double precision buffer(dimen1,dimen2)
       double precision zapas 
-      common /contacts_hb/ zapas(3,20,maxres,7),
-     &         facont_hb(20,maxres),ees0p(20,maxres),ees0m(20,maxres),
-     &         num_cont_hb(maxres),jcont_hb(20,maxres)
+      common /contacts_hb/ zapas(3,ntyp,maxres,7),
+     &         facont_hb(ntyp,maxres),ees0p(ntyp,maxres),
+     &         ees0m(ntyp,maxres),
+     &         num_cont_hb(maxres),jcont_hb(ntyp,maxres)
       num_kont=buffer(1,indx+26)
       num_kont_old=num_cont_hb(atom)
       num_cont_hb(atom)=num_kont+num_kont_old
@@ -4986,6 +6093,7 @@ C This subroutine calculates multi-body contributions to hydrogen-bonding
 C Set lprn=.true. for debugging
       lprn=.false.
       eturn6=0.0d0
+      ecorr6=0.0d0
 #ifdef MPL
       n_corr=0
       n_corr1=0
@@ -5175,7 +6283,11 @@ cd     &          dabs(eello6(i,j,i+1,j1,jj,kk))
 cd                  write (iout,*) '******eturn6: i,j,i+1,j1',i,j,i+1,j1
                   eturn6=eturn6+eello_turn6(i,jj,kk)
 cd                  write (2,*) 'multibody_eello:eturn6',eturn6
+                 else if ((wturn6.eq.0.0d0).and.(wcorr6.eq.0.0d0)) then
+                   eturn6=0.0d0
+                   ecorr6=0.0d0
                 endif
+              
               ENDIF
 1111          continue
             else if (j1.eq.j) then
@@ -5196,6 +6308,7 @@ c             ecorr=ecorr+ehbcorr(i,j,i,j+1,jj,kk,0.60D0,-0.40D0)
           enddo ! kk
         enddo ! jj
       enddo ! i
+      write (iout,*) "eturn6",eturn6,ecorr6
       return
       end
 c------------------------------------------------------------------------------
@@ -5206,6 +6319,8 @@ c------------------------------------------------------------------------------
       include 'COMMON.DERIV'
       include 'COMMON.INTERACT'
       include 'COMMON.CONTACTS'
+      include 'COMMON.CONTROL'
+      include 'COMMON.SHIELD'
       double precision gx(3),gx1(3)
       logical lprn
       lprn=.false.
@@ -5229,7 +6344,7 @@ c     write (iout,*)'Contacts have occurred for peptide groups',
 c    &  i,j,' fcont:',eij,' eij',' eesij',ees0pij,ees0mij,' and ',k,l
 c    & ,' fcont ',ekl,' eeskl',ees0pkl,ees0mkl,' ees=',ees
 C Calculate the multi-body contribution to energy.
-      ecorr=ecorr+ekont*ees
+C      ecorr=ecorr+ekont*ees
       if (calc_grad) then
 C Calculate multi-body contributions to the gradient.
       do ll=1,3
@@ -5263,7 +6378,85 @@ C Calculate multi-body contributions to the gradient.
      &     ekont*(coeffp*ees0pij*gacontp_hb3(ll,kk,k)+
      &     coeffm*ees0mij*gacontm_hb3(ll,kk,k))
         enddo
-      enddo 
+      enddo
+      if (shield_mode.gt.0) then
+       j=ees0plist(jj,i)
+       l=ees0plist(kk,k)
+C        print *,i,j,fac_shield(i),fac_shield(j),
+C     &fac_shield(k),fac_shield(l)
+        if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
+     &      (fac_shield(k).gt.0).and.(fac_shield(l).gt.0)) then
+          do ilist=1,ishield_list(i)
+           iresshield=shield_list(ilist,i)
+           do m=1,3
+           rlocshield=grad_shield_side(m,ilist,i)*ehbcorr/fac_shield(i)
+C     &      *2.0
+           gshieldx_ec(m,iresshield)=gshieldx_ec(m,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(m,ilist,i)*ehbcorr/fac_shield(i)
+            gshieldc_ec(m,iresshield-1)=gshieldc_ec(m,iresshield-1)
+     &+rlocshield
+           enddo
+          enddo
+          do ilist=1,ishield_list(j)
+           iresshield=shield_list(ilist,j)
+           do m=1,3
+           rlocshield=grad_shield_side(m,ilist,j)*ehbcorr/fac_shield(j)
+C     &     *2.0
+           gshieldx_ec(m,iresshield)=gshieldx_ec(m,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(m,ilist,j)*ehbcorr/fac_shield(j)
+           gshieldc_ec(m,iresshield-1)=gshieldc_ec(m,iresshield-1)
+     &     +rlocshield
+           enddo
+          enddo
+          do ilist=1,ishield_list(k)
+           iresshield=shield_list(ilist,k)
+           do m=1,3
+           rlocshield=grad_shield_side(m,ilist,k)*ehbcorr/fac_shield(k)
+C     &     *2.0
+           gshieldx_ec(m,iresshield)=gshieldx_ec(m,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(m,ilist,k)*ehbcorr/fac_shield(k)
+           gshieldc_ec(m,iresshield-1)=gshieldc_ec(m,iresshield-1)
+     &     +rlocshield
+           enddo
+          enddo
+          do ilist=1,ishield_list(l)
+           iresshield=shield_list(ilist,l)
+           do m=1,3
+           rlocshield=grad_shield_side(m,ilist,l)*ehbcorr/fac_shield(l)
+C     &     *2.0
+           gshieldx_ec(m,iresshield)=gshieldx_ec(m,iresshield)+
+     &              rlocshield
+     & +grad_shield_loc(m,ilist,l)*ehbcorr/fac_shield(l)
+           gshieldc_ec(m,iresshield-1)=gshieldc_ec(m,iresshield-1)
+     &     +rlocshield
+           enddo
+          enddo
+C          print *,gshieldx(m,iresshield)
+          do m=1,3
+            gshieldc_ec(m,i)=gshieldc_ec(m,i)+
+     &              grad_shield(m,i)*ehbcorr/fac_shield(i)
+            gshieldc_ec(m,j)=gshieldc_ec(m,j)+
+     &              grad_shield(m,j)*ehbcorr/fac_shield(j)
+            gshieldc_ec(m,i-1)=gshieldc_ec(m,i-1)+
+     &              grad_shield(m,i)*ehbcorr/fac_shield(i)
+            gshieldc_ec(m,j-1)=gshieldc_ec(m,j-1)+
+     &              grad_shield(m,j)*ehbcorr/fac_shield(j)
+
+            gshieldc_ec(m,k)=gshieldc_ec(m,k)+
+     &              grad_shield(m,k)*ehbcorr/fac_shield(k)
+            gshieldc_ec(m,l)=gshieldc_ec(m,l)+
+     &              grad_shield(m,l)*ehbcorr/fac_shield(l)
+            gshieldc_ec(m,k-1)=gshieldc_ec(m,k-1)+
+     &              grad_shield(m,k)*ehbcorr/fac_shield(k)
+            gshieldc_ec(m,l-1)=gshieldc_ec(m,l-1)+
+     &              grad_shield(m,l)*ehbcorr/fac_shield(l)
+
+           enddo
+      endif 
+      endif
       endif
       ehbcorr=ekont*ees
       return
@@ -6492,7 +7685,7 @@ c----------------------------------------------------------------------------
       include 'COMMON.GEO'
       logical swap
       double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2),
-     & auxvec1(2),auxvec2(1),auxmat1(2,2)
+     & auxvec1(2),auxvec2(2),auxmat1(2,2)
       logical lprn
       common /kutas/ lprn
 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
@@ -7369,6 +8562,125 @@ cd      write (2,*) 'eel_turn6',ekont*eel_turn6
       return
       end
 crc-------------------------------------------------
+CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
+      subroutine Eliptransfer(eliptran)
+      implicit real*8 (a-h,o-z)
+      include 'DIMENSIONS'
+      include 'COMMON.GEO'
+      include 'COMMON.VAR'
+      include 'COMMON.LOCAL'
+      include 'COMMON.CHAIN'
+      include 'COMMON.DERIV'
+      include 'COMMON.INTERACT'
+      include 'COMMON.IOUNITS'
+      include 'COMMON.CALC'
+      include 'COMMON.CONTROL'
+      include 'COMMON.SPLITELE'
+      include 'COMMON.SBRIDGE'
+C this is done by Adasko
+C      print *,"wchodze"
+C structure of box:
+C      water
+C--bordliptop-- buffore starts
+C--bufliptop--- here true lipid starts
+C      lipid
+C--buflipbot--- lipid ends buffore starts
+C--bordlipbot--buffore ends
+      eliptran=0.0
+      do i=1,nres
+C       do i=1,1
+        if (itype(i).eq.ntyp1) cycle
+
+        positi=(mod(((c(3,i)+c(3,i+1))/2.0d0),boxzsize))
+        if (positi.le.0) positi=positi+boxzsize
+C        print *,i
+C first for peptide groups
+c for each residue check if it is in lipid or lipid water border area
+       if ((positi.gt.bordlipbot)
+     &.and.(positi.lt.bordliptop)) then
+C the energy transfer exist
+        if (positi.lt.buflipbot) then
+C what fraction I am in
+         fracinbuf=1.0d0-
+     &        ((positi-bordlipbot)/lipbufthick)
+C lipbufthick is thickenes of lipid buffore
+         sslip=sscalelip(fracinbuf)
+         ssgradlip=-sscagradlip(fracinbuf)/lipbufthick
+         eliptran=eliptran+sslip*pepliptran
+         gliptranc(3,i)=gliptranc(3,i)+ssgradlip*pepliptran/2.0d0
+         gliptranc(3,i-1)=gliptranc(3,i-1)+ssgradlip*pepliptran/2.0d0
+C         gliptranc(3,i-2)=gliptranc(3,i)+ssgradlip*pepliptran
+        elseif (positi.gt.bufliptop) then
+         fracinbuf=1.0d0-((bordliptop-positi)/lipbufthick)
+         sslip=sscalelip(fracinbuf)
+         ssgradlip=sscagradlip(fracinbuf)/lipbufthick
+         eliptran=eliptran+sslip*pepliptran
+         gliptranc(3,i)=gliptranc(3,i)+ssgradlip*pepliptran/2.0d0
+         gliptranc(3,i-1)=gliptranc(3,i-1)+ssgradlip*pepliptran/2.0d0
+C         gliptranc(3,i-2)=gliptranc(3,i)+ssgradlip*pepliptran
+C          print *, "doing sscalefor top part"
+C         print *,i,sslip,fracinbuf,ssgradlip
+        else
+         eliptran=eliptran+pepliptran
+C         print *,"I am in true lipid"
+        endif
+C       else
+C       eliptran=elpitran+0.0 ! I am in water
+       endif
+       enddo
+C       print *, "nic nie bylo w lipidzie?"
+C now multiply all by the peptide group transfer factor
+C       eliptran=eliptran*pepliptran
+C now the same for side chains
+CV       do i=1,1
+       do i=1,nres
+        if (itype(i).eq.ntyp1) cycle
+        positi=(mod(c(3,i+nres),boxzsize))
+        if (positi.le.0) positi=positi+boxzsize
+C       print *,mod(c(3,i+nres),boxzsize),bordlipbot,bordliptop
+c for each residue check if it is in lipid or lipid water border area
+C       respos=mod(c(3,i+nres),boxzsize)
+C       print *,positi,bordlipbot,buflipbot
+       if ((positi.gt.bordlipbot)
+     & .and.(positi.lt.bordliptop)) then
+C the energy transfer exist
+        if (positi.lt.buflipbot) then
+         fracinbuf=1.0d0-
+     &     ((positi-bordlipbot)/lipbufthick)
+C lipbufthick is thickenes of lipid buffore
+         sslip=sscalelip(fracinbuf)
+         ssgradlip=-sscagradlip(fracinbuf)/lipbufthick
+         eliptran=eliptran+sslip*liptranene(itype(i))
+         gliptranx(3,i)=gliptranx(3,i)
+     &+ssgradlip*liptranene(itype(i))
+         gliptranc(3,i-1)= gliptranc(3,i-1)
+     &+ssgradlip*liptranene(itype(i))
+C         print *,"doing sccale for lower part"
+        elseif (positi.gt.bufliptop) then
+         fracinbuf=1.0d0-
+     &((bordliptop-positi)/lipbufthick)
+         sslip=sscalelip(fracinbuf)
+         ssgradlip=sscagradlip(fracinbuf)/lipbufthick
+         eliptran=eliptran+sslip*liptranene(itype(i))
+         gliptranx(3,i)=gliptranx(3,i)
+     &+ssgradlip*liptranene(itype(i))
+         gliptranc(3,i-1)= gliptranc(3,i-1)
+     &+ssgradlip*liptranene(itype(i))
+C          print *, "doing sscalefor top part",sslip,fracinbuf
+        else
+         eliptran=eliptran+liptranene(itype(i))
+C         print *,"I am in true lipid"
+        endif
+        endif ! if in lipid or buffor
+C       else
+C       eliptran=elpitran+0.0 ! I am in water
+       enddo
+       return
+       end
+
+
+CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
+
       SUBROUTINE MATVEC2(A1,V1,V2)
       implicit real*8 (a-h,o-z)
       include 'DIMENSIONS'
@@ -7502,4 +8814,1086 @@ C-----------------------------------------------------------------------------
       scalar=sc
       return
       end
+C-----------------------------------------------------------------------
+      double precision function sscale(r)
+      double precision r,gamm
+      include "COMMON.SPLITELE"
+      if(r.lt.r_cut-rlamb) then
+        sscale=1.0d0
+      else if(r.le.r_cut.and.r.ge.r_cut-rlamb) then
+        gamm=(r-(r_cut-rlamb))/rlamb
+        sscale=1.0d0+gamm*gamm*(2*gamm-3.0d0)
+      else
+        sscale=0d0
+      endif
+      return
+      end
+C-----------------------------------------------------------------------
+C-----------------------------------------------------------------------
+      double precision function sscagrad(r)
+      double precision r,gamm
+      include "COMMON.SPLITELE"
+      if(r.lt.r_cut-rlamb) then
+        sscagrad=0.0d0
+      else if(r.le.r_cut.and.r.ge.r_cut-rlamb) then
+        gamm=(r-(r_cut-rlamb))/rlamb
+        sscagrad=gamm*(6*gamm-6.0d0)/rlamb
+      else
+        sscagrad=0.0d0
+      endif
+      return
+      end
+C-----------------------------------------------------------------------
+C-----------------------------------------------------------------------
+      double precision function sscalelip(r)
+      double precision r,gamm
+      include "COMMON.SPLITELE"
+C      if(r.lt.r_cut-rlamb) then
+C        sscale=1.0d0
+C      else if(r.le.r_cut.and.r.ge.r_cut-rlamb) then
+C        gamm=(r-(r_cut-rlamb))/rlamb
+        sscalelip=1.0d0+r*r*(2*r-3.0d0)
+C      else
+C        sscale=0d0
+C      endif
+      return
+      end
+C-----------------------------------------------------------------------
+      double precision function sscagradlip(r)
+      double precision r,gamm
+      include "COMMON.SPLITELE"
+C     if(r.lt.r_cut-rlamb) then
+C        sscagrad=0.0d0
+C      else if(r.le.r_cut.and.r.ge.r_cut-rlamb) then
+C        gamm=(r-(r_cut-rlamb))/rlamb
+        sscagradlip=r*(6*r-6.0d0)
+C      else
+C        sscagrad=0.0d0
+C      endif
+      return
+      end
+
+C-----------------------------------------------------------------------
+       subroutine set_shield_fac
+      implicit real*8 (a-h,o-z)
+      include 'DIMENSIONS'
+      include 'COMMON.CHAIN'
+      include 'COMMON.DERIV'
+      include 'COMMON.IOUNITS'
+      include 'COMMON.SHIELD'
+      include 'COMMON.INTERACT'
+C this is the squar root 77 devided by 81 the epislion in lipid (in protein)
+      double precision div77_81/0.974996043d0/,
+     &div4_81/0.2222222222d0/,sh_frac_dist_grad(3)
+
+C the vector between center of side_chain and peptide group
+       double precision pep_side(3),long,side_calf(3),
+     &pept_group(3),costhet_grad(3),cosphi_grad_long(3),
+     &cosphi_grad_loc(3),pep_side_norm(3),side_calf_norm(3)
+C the line belowe needs to be changed for FGPROC>1
+      do i=1,nres-1
+      if ((itype(i).eq.ntyp1).and.itype(i+1).eq.ntyp1) cycle
+      ishield_list(i)=0
+Cif there two consequtive dummy atoms there is no peptide group between them
+C the line below has to be changed for FGPROC>1
+      VolumeTotal=0.0
+      do k=1,nres
+       if ((itype(k).eq.ntyp1).or.(itype(k).eq.10)) cycle
+       dist_pep_side=0.0
+       dist_side_calf=0.0
+       do j=1,3
+C first lets set vector conecting the ithe side-chain with kth side-chain
+      pep_side(j)=c(j,k+nres)-(c(j,i)+c(j,i+1))/2.0d0
+C      pep_side(j)=2.0d0
+C and vector conecting the side-chain with its proper calfa
+      side_calf(j)=c(j,k+nres)-c(j,k)
+C      side_calf(j)=2.0d0
+      pept_group(j)=c(j,i)-c(j,i+1)
+C lets have their lenght
+      dist_pep_side=pep_side(j)**2+dist_pep_side
+      dist_side_calf=dist_side_calf+side_calf(j)**2
+      dist_pept_group=dist_pept_group+pept_group(j)**2
+      enddo
+       dist_pep_side=dsqrt(dist_pep_side)
+       dist_pept_group=dsqrt(dist_pept_group)
+       dist_side_calf=dsqrt(dist_side_calf)
+      do j=1,3
+        pep_side_norm(j)=pep_side(j)/dist_pep_side
+        side_calf_norm(j)=dist_side_calf
+      enddo
+C now sscale fraction
+       sh_frac_dist=-(dist_pep_side-rpp(1,1)-buff_shield)/buff_shield
+C       print *,buff_shield,"buff"
+C now sscale
+        if (sh_frac_dist.le.0.0) cycle
+C If we reach here it means that this side chain reaches the shielding sphere
+C Lets add him to the list for gradient       
+        ishield_list(i)=ishield_list(i)+1
+C ishield_list is a list of non 0 side-chain that contribute to factor gradient
+C this list is essential otherwise problem would be O3
+        shield_list(ishield_list(i),i)=k
+C Lets have the sscale value
+        if (sh_frac_dist.gt.1.0) then
+         scale_fac_dist=1.0d0
+         do j=1,3
+         sh_frac_dist_grad(j)=0.0d0
+         enddo
+        else
+         scale_fac_dist=-sh_frac_dist*sh_frac_dist
+     &                   *(2.0*sh_frac_dist-3.0d0)
+         fac_help_scale=6.0*(sh_frac_dist-sh_frac_dist**2)
+     &                  /dist_pep_side/buff_shield*0.5
+C remember for the final gradient multiply sh_frac_dist_grad(j) 
+C for side_chain by factor -2 ! 
+         do j=1,3
+         sh_frac_dist_grad(j)=fac_help_scale*pep_side(j)
+C         print *,"jestem",scale_fac_dist,fac_help_scale,
+C     &                    sh_frac_dist_grad(j)
+         enddo
+        endif
+C        if ((i.eq.3).and.(k.eq.2)) then
+C        print *,i,sh_frac_dist,dist_pep,fac_help_scale,scale_fac_dist
+C     & ,"TU"
+C        endif
+
+C this is what is now we have the distance scaling now volume...
+      short=short_r_sidechain(itype(k))
+      long=long_r_sidechain(itype(k))
+      costhet=1.0d0/dsqrt(1.0+short**2/dist_pep_side**2)
+C now costhet_grad
+C       costhet=0.0d0
+       costhet_fac=costhet**3*short**2*(-0.5)/dist_pep_side**4
+C       costhet_fac=0.0d0
+       do j=1,3
+         costhet_grad(j)=costhet_fac*pep_side(j)
+       enddo
+C remember for the final gradient multiply costhet_grad(j) 
+C for side_chain by factor -2 !
+C fac alfa is angle between CB_k,CA_k, CA_i,CA_i+1
+C pep_side0pept_group is vector multiplication  
+      pep_side0pept_group=0.0
+      do j=1,3
+      pep_side0pept_group=pep_side0pept_group+pep_side(j)*side_calf(j)
+      enddo
+      cosalfa=(pep_side0pept_group/
+     & (dist_pep_side*dist_side_calf))
+      fac_alfa_sin=1.0-cosalfa**2
+      fac_alfa_sin=dsqrt(fac_alfa_sin)
+      rkprim=fac_alfa_sin*(long-short)+short
+C now costhet_grad
+       cosphi=1.0d0/dsqrt(1.0+rkprim**2/dist_pep_side**2)
+       cosphi_fac=cosphi**3*rkprim**2*(-0.5)/dist_pep_side**4
+
+       do j=1,3
+         cosphi_grad_long(j)=cosphi_fac*pep_side(j)
+     &+cosphi**3*0.5/dist_pep_side**2*(-rkprim)
+     &*(long-short)/fac_alfa_sin*cosalfa/
+     &((dist_pep_side*dist_side_calf))*
+     &((side_calf(j))-cosalfa*
+     &((pep_side(j)/dist_pep_side)*dist_side_calf))
+
+        cosphi_grad_loc(j)=cosphi**3*0.5/dist_pep_side**2*(-rkprim)
+     &*(long-short)/fac_alfa_sin*cosalfa
+     &/((dist_pep_side*dist_side_calf))*
+     &(pep_side(j)-
+     &cosalfa*side_calf(j)/dist_side_calf*dist_pep_side)
+       enddo
+
+      VofOverlap=VSolvSphere/2.0d0*(1.0-costhet)*(1.0-cosphi)
+     &                    /VSolvSphere_div
+     &                    *wshield
+C now the gradient...
+C grad_shield is gradient of Calfa for peptide groups
+C      write(iout,*) "shield_compon",i,k,VSolvSphere,scale_fac_dist,
+C     &               costhet,cosphi
+C       write(iout,*) "cosphi_compon",i,k,pep_side0pept_group,
+C     & dist_pep_side,dist_side_calf,c(1,k+nres),c(1,k),itype(k)
+      do j=1,3
+      grad_shield(j,i)=grad_shield(j,i)
+C gradient po skalowaniu
+     &                +(sh_frac_dist_grad(j)
+C  gradient po costhet
+     &-scale_fac_dist*costhet_grad(j)/(1.0-costhet)
+     &-scale_fac_dist*(cosphi_grad_long(j))
+     &/(1.0-cosphi) )*div77_81
+     &*VofOverlap
+C grad_shield_side is Cbeta sidechain gradient
+      grad_shield_side(j,ishield_list(i),i)=
+     &        (sh_frac_dist_grad(j)*-2.0d0
+     &       +scale_fac_dist*costhet_grad(j)*2.0d0/(1.0-costhet)
+     &       +scale_fac_dist*(cosphi_grad_long(j))
+     &        *2.0d0/(1.0-cosphi))
+     &        *div77_81*VofOverlap
+
+       grad_shield_loc(j,ishield_list(i),i)=
+     &   scale_fac_dist*cosphi_grad_loc(j)
+     &        *2.0d0/(1.0-cosphi)
+     &        *div77_81*VofOverlap
+      enddo
+      VolumeTotal=VolumeTotal+VofOverlap*scale_fac_dist
+      enddo
+      fac_shield(i)=VolumeTotal*div77_81+div4_81
+C      write(2,*) "TOTAL VOLUME",i,VolumeTotal,fac_shield(i)
+      enddo
+      return
+      end
+C--------------------------------------------------------------------------
+C first for shielding is setting of function of side-chains
+       subroutine set_shield_fac2
+      implicit real*8 (a-h,o-z)
+      include 'DIMENSIONS'
+      include 'COMMON.CHAIN'
+      include 'COMMON.DERIV'
+      include 'COMMON.IOUNITS'
+      include 'COMMON.SHIELD'
+      include 'COMMON.INTERACT'
+C this is the squar root 77 devided by 81 the epislion in lipid (in protein)
+      double precision div77_81/0.974996043d0/,
+     &div4_81/0.2222222222d0/,sh_frac_dist_grad(3)
+
+C the vector between center of side_chain and peptide group
+       double precision pep_side(3),long,side_calf(3),
+     &pept_group(3),costhet_grad(3),cosphi_grad_long(3),
+     &cosphi_grad_loc(3),pep_side_norm(3),side_calf_norm(3)
+C the line belowe needs to be changed for FGPROC>1
+      do i=1,nres-1
+      if ((itype(i).eq.ntyp1).and.itype(i+1).eq.ntyp1) cycle
+      ishield_list(i)=0
+Cif there two consequtive dummy atoms there is no peptide group between them
+C the line below has to be changed for FGPROC>1
+      VolumeTotal=0.0
+      do k=1,nres
+       if ((itype(k).eq.ntyp1).or.(itype(k).eq.10)) cycle
+       dist_pep_side=0.0
+       dist_side_calf=0.0
+       do j=1,3
+C first lets set vector conecting the ithe side-chain with kth side-chain
+      pep_side(j)=c(j,k+nres)-(c(j,i)+c(j,i+1))/2.0d0
+C      pep_side(j)=2.0d0
+C and vector conecting the side-chain with its proper calfa
+      side_calf(j)=c(j,k+nres)-c(j,k)
+C      side_calf(j)=2.0d0
+      pept_group(j)=c(j,i)-c(j,i+1)
+C lets have their lenght
+      dist_pep_side=pep_side(j)**2+dist_pep_side
+      dist_side_calf=dist_side_calf+side_calf(j)**2
+      dist_pept_group=dist_pept_group+pept_group(j)**2
+      enddo
+       dist_pep_side=dsqrt(dist_pep_side)
+       dist_pept_group=dsqrt(dist_pept_group)
+       dist_side_calf=dsqrt(dist_side_calf)
+      do j=1,3
+        pep_side_norm(j)=pep_side(j)/dist_pep_side
+        side_calf_norm(j)=dist_side_calf
+      enddo
+C now sscale fraction
+       sh_frac_dist=-(dist_pep_side-rpp(1,1)-buff_shield)/buff_shield
+C       print *,buff_shield,"buff"
+C now sscale
+        if (sh_frac_dist.le.0.0) cycle
+C If we reach here it means that this side chain reaches the shielding sphere
+C Lets add him to the list for gradient       
+        ishield_list(i)=ishield_list(i)+1
+C ishield_list is a list of non 0 side-chain that contribute to factor gradient
+C this list is essential otherwise problem would be O3
+        shield_list(ishield_list(i),i)=k
+C Lets have the sscale value
+        if (sh_frac_dist.gt.1.0) then
+         scale_fac_dist=1.0d0
+         do j=1,3
+         sh_frac_dist_grad(j)=0.0d0
+         enddo
+        else
+         scale_fac_dist=-sh_frac_dist*sh_frac_dist
+     &                   *(2.0d0*sh_frac_dist-3.0d0)
+         fac_help_scale=6.0d0*(sh_frac_dist-sh_frac_dist**2)
+     &                  /dist_pep_side/buff_shield*0.5d0
+C remember for the final gradient multiply sh_frac_dist_grad(j) 
+C for side_chain by factor -2 ! 
+         do j=1,3
+         sh_frac_dist_grad(j)=fac_help_scale*pep_side(j)
+C         sh_frac_dist_grad(j)=0.0d0
+C         scale_fac_dist=1.0d0
+C         print *,"jestem",scale_fac_dist,fac_help_scale,
+C     &                    sh_frac_dist_grad(j)
+         enddo
+        endif
+C this is what is now we have the distance scaling now volume...
+      short=short_r_sidechain(itype(k))
+      long=long_r_sidechain(itype(k))
+      costhet=1.0d0/dsqrt(1.0d0+short**2/dist_pep_side**2)
+      sinthet=short/dist_pep_side*costhet
+C now costhet_grad
+C       costhet=0.6d0
+C       sinthet=0.8
+       costhet_fac=costhet**3*short**2*(-0.5d0)/dist_pep_side**4
+C       sinthet_fac=costhet**2*0.5d0*(short**3/dist_pep_side**4*costhet
+C     &             -short/dist_pep_side**2/costhet)
+C       costhet_fac=0.0d0
+       do j=1,3
+         costhet_grad(j)=costhet_fac*pep_side(j)
+       enddo
+C remember for the final gradient multiply costhet_grad(j) 
+C for side_chain by factor -2 !
+C fac alfa is angle between CB_k,CA_k, CA_i,CA_i+1
+C pep_side0pept_group is vector multiplication  
+      pep_side0pept_group=0.0d0
+      do j=1,3
+      pep_side0pept_group=pep_side0pept_group+pep_side(j)*side_calf(j)
+      enddo
+      cosalfa=(pep_side0pept_group/
+     & (dist_pep_side*dist_side_calf))
+      fac_alfa_sin=1.0d0-cosalfa**2
+      fac_alfa_sin=dsqrt(fac_alfa_sin)
+      rkprim=fac_alfa_sin*(long-short)+short
+C      rkprim=short
+
+C now costhet_grad
+       cosphi=1.0d0/dsqrt(1.0d0+rkprim**2/dist_pep_side**2)
+C       cosphi=0.6
+       cosphi_fac=cosphi**3*rkprim**2*(-0.5d0)/dist_pep_side**4
+       sinphi=rkprim/dist_pep_side/dsqrt(1.0d0+rkprim**2/
+     &      dist_pep_side**2)
+C       sinphi=0.8
+       do j=1,3
+         cosphi_grad_long(j)=cosphi_fac*pep_side(j)
+     &+cosphi**3*0.5d0/dist_pep_side**2*(-rkprim)
+     &*(long-short)/fac_alfa_sin*cosalfa/
+     &((dist_pep_side*dist_side_calf))*
+     &((side_calf(j))-cosalfa*
+     &((pep_side(j)/dist_pep_side)*dist_side_calf))
+C       cosphi_grad_long(j)=0.0d0
+        cosphi_grad_loc(j)=cosphi**3*0.5d0/dist_pep_side**2*(-rkprim)
+     &*(long-short)/fac_alfa_sin*cosalfa
+     &/((dist_pep_side*dist_side_calf))*
+     &(pep_side(j)-
+     &cosalfa*side_calf(j)/dist_side_calf*dist_pep_side)
+C       cosphi_grad_loc(j)=0.0d0
+       enddo
+C      print *,sinphi,sinthet
+      VofOverlap=VSolvSphere/2.0d0*(1.0d0-dsqrt(1.0d0-sinphi*sinthet))
+     &                    /VSolvSphere_div
+C     &                    *wshield
+C now the gradient...
+      do j=1,3
+      grad_shield(j,i)=grad_shield(j,i)
+C gradient po skalowaniu
+     &                +(sh_frac_dist_grad(j)*VofOverlap
+C  gradient po costhet
+     &       +scale_fac_dist*VSolvSphere/VSolvSphere_div/4.0d0*
+     &(1.0d0/(-dsqrt(1.0d0-sinphi*sinthet))*(
+     &       sinphi/sinthet*costhet*costhet_grad(j)
+     &      +sinthet/sinphi*cosphi*cosphi_grad_long(j)))
+     & )*wshield
+C grad_shield_side is Cbeta sidechain gradient
+      grad_shield_side(j,ishield_list(i),i)=
+     &        (sh_frac_dist_grad(j)*-2.0d0
+     &        *VofOverlap
+     &       -scale_fac_dist*VSolvSphere/VSolvSphere_div/2.0d0*
+     &(1.0d0/(-dsqrt(1.0d0-sinphi*sinthet))*(
+     &       sinphi/sinthet*costhet*costhet_grad(j)
+     &      +sinthet/sinphi*cosphi*cosphi_grad_long(j)))
+     &       )*wshield
+
+       grad_shield_loc(j,ishield_list(i),i)=
+     &       scale_fac_dist*VSolvSphere/VSolvSphere_div/2.0d0*
+     &(1.0d0/(dsqrt(1.0d0-sinphi*sinthet))*(
+     &       sinthet/sinphi*cosphi*cosphi_grad_loc(j)
+     &        ))
+     &        *wshield
+      enddo
+      VolumeTotal=VolumeTotal+VofOverlap*scale_fac_dist
+      enddo
+      fac_shield(i)=VolumeTotal*wshield+(1.0d0-wshield)
+C      write(2,*) "TOTAL VOLUME",i,VolumeTotal,fac_shield(i)
+C      write(2,*) "TU",rpp(1,1),short,long,buff_shield
+      enddo
+      return
+      end
+
+C-----------------------------------------------------------------------
+C-----------------------------------------------------------
+C This subroutine is to mimic the histone like structure but as well can be
+C utilizet to nanostructures (infinit) small modification has to be used to 
+C make it finite (z gradient at the ends has to be changes as well as the x,y
+C gradient has to be modified at the ends 
+C The energy function is Kihara potential 
+C E=4esp*((sigma/(r-r0))^12 - (sigma/(r-r0))^6)
+C 4eps is depth of well sigma is r_minimum r is distance from center of tube 
+C and r0 is the excluded size of nanotube (can be set to 0 if we want just a 
+C simple Kihara potential
+      subroutine calctube(Etube)
+       implicit real*8 (a-h,o-z)
+      include 'DIMENSIONS'
+      include 'COMMON.GEO'
+      include 'COMMON.VAR'
+      include 'COMMON.LOCAL'
+      include 'COMMON.CHAIN'
+      include 'COMMON.DERIV'
+      include 'COMMON.INTERACT'
+      include 'COMMON.IOUNITS'
+      include 'COMMON.CALC'
+      include 'COMMON.CONTROL'
+      include 'COMMON.SPLITELE'
+      include 'COMMON.SBRIDGE'
+      double precision tub_r,vectube(3),enetube(maxres*2)
+      Etube=0.0d0
+      do i=itube_start,itube_end
+        enetube(i)=0.0d0
+        enetube(i+nres)=0.0d0
+      enddo
+C first we calculate the distance from tube center
+C first sugare-phosphate group for NARES this would be peptide group 
+C for UNRES
+       do i=itube_start,itube_end
+C lets ommit dummy atoms for now
+       if ((itype(i).eq.ntyp1).or.(itype(i+1).eq.ntyp1)) cycle
+C now calculate distance from center of tube and direction vectors
+      xmin=boxxsize
+      ymin=boxysize
+        do j=-1,1
+         vectube(1)=mod((c(1,i)+c(1,i+1))/2.0d0,boxxsize)
+         vectube(1)=vectube(1)+boxxsize*j
+         vectube(2)=mod((c(2,i)+c(2,i+1))/2.0d0,boxysize)
+         vectube(2)=vectube(2)+boxysize*j
+       
+         xminact=abs(vectube(1)-tubecenter(1))
+         yminact=abs(vectube(2)-tubecenter(2))
+           if (xmin.gt.xminact) then
+            xmin=xminact
+            xtemp=vectube(1)
+           endif
+           if (ymin.gt.yminact) then
+             ymin=yminact
+             ytemp=vectube(2)
+            endif
+         enddo
+      vectube(1)=xtemp
+      vectube(2)=ytemp
+      vectube(1)=vectube(1)-tubecenter(1)
+      vectube(2)=vectube(2)-tubecenter(2)
+
+C      print *,"x",(c(1,i)+c(1,i+1))/2.0d0,tubecenter(1)
+C      print *,"y",(c(2,i)+c(2,i+1))/2.0d0,tubecenter(2)
+
+C as the tube is infinity we do not calculate the Z-vector use of Z
+C as chosen axis
+      vectube(3)=0.0d0
+C now calculte the distance
+       tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
+C now normalize vector
+      vectube(1)=vectube(1)/tub_r
+      vectube(2)=vectube(2)/tub_r
+C calculte rdiffrence between r and r0
+      rdiff=tub_r-tubeR0
+C and its 6 power
+      rdiff6=rdiff**6.0d0
+C for vectorization reasons we will sumup at the end to avoid depenence of previous
+       enetube(i)=pep_aa_tube/rdiff6**2.0d0+pep_bb_tube/rdiff6
+C       write(iout,*) "TU13",i,rdiff6,enetube(i)
+C       print *,rdiff,rdiff6,pep_aa_tube
+C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
+C now we calculate gradient
+       fac=(-12.0d0*pep_aa_tube/rdiff6-
+     &       6.0d0*pep_bb_tube)/rdiff6/rdiff
+C       write(iout,'(a5,i4,f12.1,3f12.5)') "TU13",i,rdiff6,enetube(i),
+C     &rdiff,fac
+
+C now direction of gg_tube vector
+        do j=1,3
+        gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac/2.0d0
+        gg_tube(j,i)=gg_tube(j,i)+vectube(j)*fac/2.0d0
+        enddo
+        enddo
+C basically thats all code now we split for side-chains (REMEMBER to sum up at the END)
+C        print *,gg_tube(1,0),"TU"
+
+
+       do i=itube_start,itube_end
+C Lets not jump over memory as we use many times iti
+         iti=itype(i)
+C lets ommit dummy atoms for now
+         if ((iti.eq.ntyp1)
+C in UNRES uncomment the line below as GLY has no side-chain...
+C      .or.(iti.eq.10)
+     &   ) cycle
+      xmin=boxxsize
+      ymin=boxysize
+        do j=-1,1
+         vectube(1)=mod((c(1,i+nres)),boxxsize)
+         vectube(1)=vectube(1)+boxxsize*j
+         vectube(2)=mod((c(2,i+nres)),boxysize)
+         vectube(2)=vectube(2)+boxysize*j
+
+         xminact=abs(vectube(1)-tubecenter(1))
+         yminact=abs(vectube(2)-tubecenter(2))
+           if (xmin.gt.xminact) then
+            xmin=xminact
+            xtemp=vectube(1)
+           endif
+           if (ymin.gt.yminact) then
+             ymin=yminact
+             ytemp=vectube(2)
+            endif
+         enddo
+      vectube(1)=xtemp
+      vectube(2)=ytemp
+C          write(iout,*), "tututu", vectube(1),tubecenter(1),vectube(2),
+C     &     tubecenter(2)
+      vectube(1)=vectube(1)-tubecenter(1)
+      vectube(2)=vectube(2)-tubecenter(2)
+
+C as the tube is infinity we do not calculate the Z-vector use of Z
+C as chosen axis
+      vectube(3)=0.0d0
+C now calculte the distance
+       tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
+C now normalize vector
+      vectube(1)=vectube(1)/tub_r
+      vectube(2)=vectube(2)/tub_r
+
+C calculte rdiffrence between r and r0
+      rdiff=tub_r-tubeR0
+C and its 6 power
+      rdiff6=rdiff**6.0d0
+C for vectorization reasons we will sumup at the end to avoid depenence of previous
+       sc_aa_tube=sc_aa_tube_par(iti)
+       sc_bb_tube=sc_bb_tube_par(iti)
+       enetube(i+nres)=sc_aa_tube/rdiff6**2.0d0+sc_bb_tube/rdiff6
+C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
+C now we calculate gradient
+       fac=-12.0d0*sc_aa_tube/rdiff6**2.0d0/rdiff-
+     &       6.0d0*sc_bb_tube/rdiff6/rdiff
+C now direction of gg_tube vector
+         do j=1,3
+          gg_tube_SC(j,i)=gg_tube_SC(j,i)+vectube(j)*fac
+          gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac
+         enddo
+        enddo
+        do i=itube_start,itube_end
+          Etube=Etube+enetube(i)+enetube(i+nres)
+        enddo
+C        print *,"ETUBE", etube
+        return
+        end
+C TO DO 1) add to total energy
+C       2) add to gradient summation
+C       3) add reading parameters (AND of course oppening of PARAM file)
+C       4) add reading the center of tube
+C       5) add COMMONs
+C       6) add to zerograd
+
+C-----------------------------------------------------------------------
+C-----------------------------------------------------------
+C This subroutine is to mimic the histone like structure but as well can be
+C utilizet to nanostructures (infinit) small modification has to be used to 
+C make it finite (z gradient at the ends has to be changes as well as the x,y
+C gradient has to be modified at the ends 
+C The energy function is Kihara potential 
+C E=4esp*((sigma/(r-r0))^12 - (sigma/(r-r0))^6)
+C 4eps is depth of well sigma is r_minimum r is distance from center of tube 
+C and r0 is the excluded size of nanotube (can be set to 0 if we want just a 
+C simple Kihara potential
+      subroutine calctube2(Etube)
+       implicit real*8 (a-h,o-z)
+      include 'DIMENSIONS'
+      include 'COMMON.GEO'
+      include 'COMMON.VAR'
+      include 'COMMON.LOCAL'
+      include 'COMMON.CHAIN'
+      include 'COMMON.DERIV'
+      include 'COMMON.INTERACT'
+      include 'COMMON.IOUNITS'
+      include 'COMMON.CALC'
+      include 'COMMON.CONTROL'
+      include 'COMMON.SPLITELE'
+      include 'COMMON.SBRIDGE'
+      double precision tub_r,vectube(3),enetube(maxres*2)
+      Etube=0.0d0
+      do i=itube_start,itube_end
+        enetube(i)=0.0d0
+        enetube(i+nres)=0.0d0
+      enddo
+C first we calculate the distance from tube center
+C first sugare-phosphate group for NARES this would be peptide group 
+C for UNRES
+       do i=itube_start,itube_end
+C lets ommit dummy atoms for now
+       
+       if ((itype(i).eq.ntyp1).or.(itype(i+1).eq.ntyp1)) cycle
+C now calculate distance from center of tube and direction vectors
+C      vectube(1)=mod((c(1,i)+c(1,i+1))/2.0d0,boxxsize)
+C          if (vectube(1).lt.0) vectube(1)=vectube(1)+boxxsize
+C      vectube(2)=mod((c(2,i)+c(2,i+1))/2.0d0,boxysize)
+C          if (vectube(2).lt.0) vectube(2)=vectube(2)+boxysize
+      xmin=boxxsize
+      ymin=boxysize
+        do j=-1,1
+         vectube(1)=mod((c(1,i)+c(1,i+1))/2.0d0,boxxsize)
+         vectube(1)=vectube(1)+boxxsize*j
+         vectube(2)=mod((c(2,i)+c(2,i+1))/2.0d0,boxysize)
+         vectube(2)=vectube(2)+boxysize*j
+
+         xminact=abs(vectube(1)-tubecenter(1))
+         yminact=abs(vectube(2)-tubecenter(2))
+           if (xmin.gt.xminact) then
+            xmin=xminact
+            xtemp=vectube(1)
+           endif
+           if (ymin.gt.yminact) then
+             ymin=yminact
+             ytemp=vectube(2)
+            endif
+         enddo
+      vectube(1)=xtemp
+      vectube(2)=ytemp
+      vectube(1)=vectube(1)-tubecenter(1)
+      vectube(2)=vectube(2)-tubecenter(2)
+
+C      print *,"x",(c(1,i)+c(1,i+1))/2.0d0,tubecenter(1)
+C      print *,"y",(c(2,i)+c(2,i+1))/2.0d0,tubecenter(2)
+
+C as the tube is infinity we do not calculate the Z-vector use of Z
+C as chosen axis
+      vectube(3)=0.0d0
+C now calculte the distance
+       tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
+C now normalize vector
+      vectube(1)=vectube(1)/tub_r
+      vectube(2)=vectube(2)/tub_r
+C calculte rdiffrence between r and r0
+      rdiff=tub_r-tubeR0
+C and its 6 power
+      rdiff6=rdiff**6.0d0
+C THIS FRAGMENT MAKES TUBE FINITE
+        positi=mod((c(3,i)+c(3,i+1))/2.0d0,boxzsize)
+        if (positi.le.0) positi=positi+boxzsize
+C       print *,mod(c(3,i+nres),boxzsize),bordlipbot,bordliptop
+c for each residue check if it is in lipid or lipid water border area
+C       respos=mod(c(3,i+nres),boxzsize)
+       print *,positi,bordtubebot,buftubebot,bordtubetop
+       if ((positi.gt.bordtubebot)
+     & .and.(positi.lt.bordtubetop)) then
+C the energy transfer exist
+        if (positi.lt.buftubebot) then
+         fracinbuf=1.0d0-
+     &     ((positi-bordtubebot)/tubebufthick)
+C lipbufthick is thickenes of lipid buffore
+         sstube=sscalelip(fracinbuf)
+         ssgradtube=-sscagradlip(fracinbuf)/tubebufthick
+         print *,ssgradtube, sstube,tubetranene(itype(i))
+         enetube(i)=enetube(i)+sstube*tubetranenepep
+C         gg_tube_SC(3,i)=gg_tube_SC(3,i)
+C     &+ssgradtube*tubetranene(itype(i))
+C         gg_tube(3,i-1)= gg_tube(3,i-1)
+C     &+ssgradtube*tubetranene(itype(i))
+C         print *,"doing sccale for lower part"
+        elseif (positi.gt.buftubetop) then
+         fracinbuf=1.0d0-
+     &((bordtubetop-positi)/tubebufthick)
+         sstube=sscalelip(fracinbuf)
+         ssgradtube=sscagradlip(fracinbuf)/tubebufthick
+         enetube(i)=enetube(i)+sstube*tubetranenepep
+C         gg_tube_SC(3,i)=gg_tube_SC(3,i)
+C     &+ssgradtube*tubetranene(itype(i))
+C         gg_tube(3,i-1)= gg_tube(3,i-1)
+C     &+ssgradtube*tubetranene(itype(i))
+C          print *, "doing sscalefor top part",sslip,fracinbuf
+        else
+         sstube=1.0d0
+         ssgradtube=0.0d0
+         enetube(i)=enetube(i)+sstube*tubetranenepep
+C         print *,"I am in true lipid"
+        endif
+        else
+C          sstube=0.0d0
+C          ssgradtube=0.0d0
+        cycle
+        endif ! if in lipid or buffor
+
+C for vectorization reasons we will sumup at the end to avoid depenence of previous
+       enetube(i)=enetube(i)+sstube*
+     &(pep_aa_tube/rdiff6**2.0d0+pep_bb_tube/rdiff6)
+C       write(iout,*) "TU13",i,rdiff6,enetube(i)
+C       print *,rdiff,rdiff6,pep_aa_tube
+C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
+C now we calculate gradient
+       fac=(-12.0d0*pep_aa_tube/rdiff6-
+     &       6.0d0*pep_bb_tube)/rdiff6/rdiff*sstube
+C       write(iout,'(a5,i4,f12.1,3f12.5)') "TU13",i,rdiff6,enetube(i),
+C     &rdiff,fac
+
+C now direction of gg_tube vector
+        do j=1,3
+        gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac/2.0d0
+        gg_tube(j,i)=gg_tube(j,i)+vectube(j)*fac/2.0d0
+        enddo
+         gg_tube(3,i)=gg_tube(3,i)
+     &+ssgradtube*enetube(i)/sstube/2.0d0
+         gg_tube(3,i-1)= gg_tube(3,i-1)
+     &+ssgradtube*enetube(i)/sstube/2.0d0
+
+        enddo
+C basically thats all code now we split for side-chains (REMEMBER to sum up at the END)
+C        print *,gg_tube(1,0),"TU"
+        do i=itube_start,itube_end
+C Lets not jump over memory as we use many times iti
+         iti=itype(i)
+C lets ommit dummy atoms for now
+         if ((iti.eq.ntyp1)
+C in UNRES uncomment the line below as GLY has no side-chain...
+     &      .or.(iti.eq.10)
+     &   ) cycle
+          vectube(1)=c(1,i+nres)
+          vectube(1)=mod(vectube(1),boxxsize)
+          if (vectube(1).lt.0) vectube(1)=vectube(1)+boxxsize
+          vectube(2)=c(2,i+nres)
+          vectube(2)=mod(vectube(2),boxysize)
+          if (vectube(2).lt.0) vectube(2)=vectube(2)+boxysize
+
+      vectube(1)=vectube(1)-tubecenter(1)
+      vectube(2)=vectube(2)-tubecenter(2)
+C THIS FRAGMENT MAKES TUBE FINITE
+        positi=(mod(c(3,i+nres),boxzsize))
+        if (positi.le.0) positi=positi+boxzsize
+C       print *,mod(c(3,i+nres),boxzsize),bordlipbot,bordliptop
+c for each residue check if it is in lipid or lipid water border area
+C       respos=mod(c(3,i+nres),boxzsize)
+       print *,positi,bordtubebot,buftubebot,bordtubetop
+       if ((positi.gt.bordtubebot)
+     & .and.(positi.lt.bordtubetop)) then
+C the energy transfer exist
+        if (positi.lt.buftubebot) then
+         fracinbuf=1.0d0-
+     &     ((positi-bordtubebot)/tubebufthick)
+C lipbufthick is thickenes of lipid buffore
+         sstube=sscalelip(fracinbuf)
+         ssgradtube=-sscagradlip(fracinbuf)/tubebufthick
+         print *,ssgradtube, sstube,tubetranene(itype(i))
+         enetube(i+nres)=enetube(i+nres)+sstube*tubetranene(itype(i))
+C         gg_tube_SC(3,i)=gg_tube_SC(3,i)
+C     &+ssgradtube*tubetranene(itype(i))
+C         gg_tube(3,i-1)= gg_tube(3,i-1)
+C     &+ssgradtube*tubetranene(itype(i))
+C         print *,"doing sccale for lower part"
+        elseif (positi.gt.buftubetop) then
+         fracinbuf=1.0d0-
+     &((bordtubetop-positi)/tubebufthick)
+         sstube=sscalelip(fracinbuf)
+         ssgradtube=sscagradlip(fracinbuf)/tubebufthick
+         enetube(i+nres)=enetube(i+nres)+sstube*tubetranene(itype(i))
+C         gg_tube_SC(3,i)=gg_tube_SC(3,i)
+C     &+ssgradtube*tubetranene(itype(i))
+C         gg_tube(3,i-1)= gg_tube(3,i-1)
+C     &+ssgradtube*tubetranene(itype(i))
+C          print *, "doing sscalefor top part",sslip,fracinbuf
+        else
+         sstube=1.0d0
+         ssgradtube=0.0d0
+         enetube(i+nres)=enetube(i+nres)+sstube*tubetranene(itype(i))
+C         print *,"I am in true lipid"
+        endif
+        else
+C          sstube=0.0d0
+C          ssgradtube=0.0d0
+        cycle
+        endif ! if in lipid or buffor
+CEND OF FINITE FRAGMENT
+C as the tube is infinity we do not calculate the Z-vector use of Z
+C as chosen axis
+      vectube(3)=0.0d0
+C now calculte the distance
+       tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
+C now normalize vector
+      vectube(1)=vectube(1)/tub_r
+      vectube(2)=vectube(2)/tub_r
+C calculte rdiffrence between r and r0
+      rdiff=tub_r-tubeR0
+C and its 6 power
+      rdiff6=rdiff**6.0d0
+C for vectorization reasons we will sumup at the end to avoid depenence of previous
+       sc_aa_tube=sc_aa_tube_par(iti)
+       sc_bb_tube=sc_bb_tube_par(iti)
+       enetube(i+nres)=(sc_aa_tube/rdiff6**2.0d0+sc_bb_tube/rdiff6)
+     &                 *sstube+enetube(i+nres)
+C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
+C now we calculate gradient
+       fac=(-12.0d0*sc_aa_tube/rdiff6**2.0d0/rdiff-
+     &       6.0d0*sc_bb_tube/rdiff6/rdiff)*sstube
+C now direction of gg_tube vector
+         do j=1,3
+          gg_tube_SC(j,i)=gg_tube_SC(j,i)+vectube(j)*fac
+          gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac
+         enddo
+         gg_tube_SC(3,i)=gg_tube_SC(3,i)
+     &+ssgradtube*enetube(i+nres)/sstube
+         gg_tube(3,i-1)= gg_tube(3,i-1)
+     &+ssgradtube*enetube(i+nres)/sstube
+
+        enddo
+        do i=itube_start,itube_end
+          Etube=Etube+enetube(i)+enetube(i+nres)
+        enddo
+C        print *,"ETUBE", etube
+        return
+        end
+C TO DO 1) add to total energy
+C       2) add to gradient summation
+C       3) add reading parameters (AND of course oppening of PARAM file)
+C       4) add reading the center of tube
+C       5) add COMMONs
+C       6) add to zerograd
+
+
+C#-------------------------------------------------------------------------------
+C This subroutine is to mimic the histone like structure but as well can be
+C utilizet to nanostructures (infinit) small modification has to be used to 
+C make it finite (z gradient at the ends has to be changes as well as the x,y
+C gradient has to be modified at the ends 
+C The energy function is Kihara potential 
+C E=4esp*((sigma/(r-r0))^12 - (sigma/(r-r0))^6)
+C 4eps is depth of well sigma is r_minimum r is distance from center of tube 
+C and r0 is the excluded size of nanotube (can be set to 0 if we want just a 
+C simple Kihara potential
+      subroutine calcnano(Etube)
+       implicit real*8 (a-h,o-z)
+      include 'DIMENSIONS'
+      include 'COMMON.GEO'
+      include 'COMMON.VAR'
+      include 'COMMON.LOCAL'
+      include 'COMMON.CHAIN'
+      include 'COMMON.DERIV'
+      include 'COMMON.INTERACT'
+      include 'COMMON.IOUNITS'
+      include 'COMMON.CALC'
+      include 'COMMON.CONTROL'
+      include 'COMMON.SPLITELE'
+      include 'COMMON.SBRIDGE'
+      double precision tub_r,vectube(3),enetube(maxres*2),
+     & enecavtube(maxres*2)
+      Etube=0.0d0
+      do i=itube_start,itube_end
+        enetube(i)=0.0d0
+        enetube(i+nres)=0.0d0
+      enddo
+C first we calculate the distance from tube center
+C first sugare-phosphate group for NARES this would be peptide group 
+C for UNRES
+       do i=itube_start,itube_end
+C lets ommit dummy atoms for now
+       if ((itype(i).eq.ntyp1).or.(itype(i+1).eq.ntyp1)) cycle
+C now calculate distance from center of tube and direction vectors
+      xmin=boxxsize
+      ymin=boxysize
+      zmin=boxzsize
+
+        do j=-1,1
+         vectube(1)=mod((c(1,i)+c(1,i+1))/2.0d0,boxxsize)
+         vectube(1)=vectube(1)+boxxsize*j
+         vectube(2)=mod((c(2,i)+c(2,i+1))/2.0d0,boxysize)
+         vectube(2)=vectube(2)+boxysize*j
+         vectube(3)=mod((c(3,i)+c(3,i+1))/2.0d0,boxzsize)
+         vectube(3)=vectube(3)+boxzsize*j
+
+
+         xminact=abs(vectube(1)-tubecenter(1))
+         yminact=abs(vectube(2)-tubecenter(2))
+         zminact=abs(vectube(3)-tubecenter(3))
+
+           if (xmin.gt.xminact) then
+            xmin=xminact
+            xtemp=vectube(1)
+           endif
+           if (ymin.gt.yminact) then
+             ymin=yminact
+             ytemp=vectube(2)
+            endif
+           if (zmin.gt.zminact) then
+             zmin=zminact
+             ztemp=vectube(3)
+            endif
+         enddo
+      vectube(1)=xtemp
+      vectube(2)=ytemp
+      vectube(3)=ztemp
+
+      vectube(1)=vectube(1)-tubecenter(1)
+      vectube(2)=vectube(2)-tubecenter(2)
+      vectube(3)=vectube(3)-tubecenter(3)
+
+C      print *,"x",(c(1,i)+c(1,i+1))/2.0d0,tubecenter(1)
+C      print *,"y",(c(2,i)+c(2,i+1))/2.0d0,tubecenter(2)
+C as the tube is infinity we do not calculate the Z-vector use of Z
+C as chosen axis
+C      vectube(3)=0.0d0
+C now calculte the distance
+       tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
+C now normalize vector
+      vectube(1)=vectube(1)/tub_r
+      vectube(2)=vectube(2)/tub_r
+      vectube(3)=vectube(3)/tub_r
+C calculte rdiffrence between r and r0
+      rdiff=tub_r-tubeR0
+C and its 6 power
+      rdiff6=rdiff**6.0d0
+C for vectorization reasons we will sumup at the end to avoid depenence of previous
+       enetube(i)=pep_aa_tube/rdiff6**2.0d0+pep_bb_tube/rdiff6
+C       write(iout,*) "TU13",i,rdiff6,enetube(i)
+C       print *,rdiff,rdiff6,pep_aa_tube
+C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
+C now we calculate gradient
+       fac=(-12.0d0*pep_aa_tube/rdiff6-
+     &       6.0d0*pep_bb_tube)/rdiff6/rdiff
+C       write(iout,'(a5,i4,f12.1,3f12.5)') "TU13",i,rdiff6,enetube(i),
+C     &rdiff,fac
+         if (acavtubpep.eq.0.0d0) then
+C go to 667
+         enecavtube(i)=0.0
+         faccav=0.0
+         else
+         denominator=(1.0+dcavtubpep*rdiff6*rdiff6)
+         enecavtube(i)=
+     &   (bcavtubpep*rdiff+acavtubpep*sqrt(rdiff)+ccavtubpep)
+     &   /denominator
+         enecavtube(i)=0.0
+         faccav=((bcavtubpep*1.0d0+acavtubpep/2.0d0/sqrt(rdiff))
+     &   *denominator-(bcavtubpep*rdiff+acavtubpep*sqrt(rdiff)
+     &   +ccavtubpep)*rdiff6**2.0d0/rdiff*dcavtubpep*12.0d0)
+     &   /denominator**2.0d0
+C         faccav=0.0
+C         fac=fac+faccav
+C 667     continue
+         endif
+C         print *,"TUT",i,iti,rdiff,rdiff6,acavtubpep,denominator,
+C     &   enecavtube(i),faccav
+C         print *,"licz=",
+C     & (bcavtub(iti)*rdiff+acavtub(iti)*sqrt(rdiff)+ccavtub(iti))
+CX         print *,"finene=",enetube(i+nres)+enecavtube(i)
+         
+C now direction of gg_tube vector
+        do j=1,3
+        gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac/2.0d0
+        gg_tube(j,i)=gg_tube(j,i)+vectube(j)*fac/2.0d0
+        enddo
+        enddo
+
+       do i=itube_start,itube_end
+        enecavtube(i)=0.0 
+C Lets not jump over memory as we use many times iti
+         iti=itype(i)
+C lets ommit dummy atoms for now
+         if ((iti.eq.ntyp1)
+C in UNRES uncomment the line below as GLY has no side-chain...
+C      .or.(iti.eq.10)
+     &   ) cycle
+      xmin=boxxsize
+      ymin=boxysize
+      zmin=boxzsize
+        do j=-1,1
+         vectube(1)=mod((c(1,i+nres)),boxxsize)
+         vectube(1)=vectube(1)+boxxsize*j
+         vectube(2)=mod((c(2,i+nres)),boxysize)
+         vectube(2)=vectube(2)+boxysize*j
+         vectube(3)=mod((c(3,i+nres)),boxzsize)
+         vectube(3)=vectube(3)+boxzsize*j
+
+
+         xminact=abs(vectube(1)-tubecenter(1))
+         yminact=abs(vectube(2)-tubecenter(2))
+         zminact=abs(vectube(3)-tubecenter(3))
+
+           if (xmin.gt.xminact) then
+            xmin=xminact
+            xtemp=vectube(1)
+           endif
+           if (ymin.gt.yminact) then
+             ymin=yminact
+             ytemp=vectube(2)
+            endif
+           if (zmin.gt.zminact) then
+             zmin=zminact
+             ztemp=vectube(3)
+            endif
+         enddo
+      vectube(1)=xtemp
+      vectube(2)=ytemp
+      vectube(3)=ztemp
+
+C          write(iout,*), "tututu", vectube(1),tubecenter(1),vectube(2),
+C     &     tubecenter(2)
+      vectube(1)=vectube(1)-tubecenter(1)
+      vectube(2)=vectube(2)-tubecenter(2)
+      vectube(3)=vectube(3)-tubecenter(3)
+C now calculte the distance
+       tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
+C now normalize vector
+      vectube(1)=vectube(1)/tub_r
+      vectube(2)=vectube(2)/tub_r
+      vectube(3)=vectube(3)/tub_r
+
+C calculte rdiffrence between r and r0
+      rdiff=tub_r-tubeR0
+C and its 6 power
+      rdiff6=rdiff**6.0d0
+C for vectorization reasons we will sumup at the end to avoid depenence of previous
+       sc_aa_tube=sc_aa_tube_par(iti)
+       sc_bb_tube=sc_bb_tube_par(iti)
+       enetube(i+nres)=sc_aa_tube/rdiff6**2.0d0+sc_bb_tube/rdiff6
+C       enetube(i+nres)=0.0d0
+C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
+C now we calculate gradient
+       fac=-12.0d0*sc_aa_tube/rdiff6**2.0d0/rdiff-
+     &       6.0d0*sc_bb_tube/rdiff6/rdiff
+C       fac=0.0
+C now direction of gg_tube vector
+C Now cavity term E=a(x+bsqrt(x)+c)/(1+dx^12)
+         if (acavtub(iti).eq.0.0d0) then
+C go to 667
+         enecavtube(i+nres)=0.0
+         faccav=0.0
+         else
+         denominator=(1.0+dcavtub(iti)*rdiff6*rdiff6)
+         enecavtube(i+nres)=
+     &   (bcavtub(iti)*rdiff+acavtub(iti)*sqrt(rdiff)+ccavtub(iti))
+     &   /denominator
+C         enecavtube(i)=0.0
+         faccav=((bcavtub(iti)*1.0d0+acavtub(iti)/2.0d0/sqrt(rdiff))
+     &   *denominator-(bcavtub(iti)*rdiff+acavtub(iti)*sqrt(rdiff)
+     &   +ccavtub(iti))*rdiff6**2.0d0/rdiff*dcavtub(iti)*12.0d0)
+     &   /denominator**2.0d0
+C         faccav=0.0
+         fac=fac+faccav
+C 667     continue
+         endif
+C         print *,"TUT",i,iti,rdiff,rdiff6,acavtub(iti),denominator,
+C     &   enecavtube(i),faccav
+C         print *,"licz=",
+C     & (bcavtub(iti)*rdiff+acavtub(iti)*sqrt(rdiff)+ccavtub(iti))
+C         print *,"finene=",enetube(i+nres)+enecavtube(i)
+         do j=1,3
+          gg_tube_SC(j,i)=gg_tube_SC(j,i)+vectube(j)*fac
+          gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac
+         enddo
+        enddo
+C Now cavity term E=a(x+bsqrt(x)+c)/(1+dx^12)
+C        do i=itube_start,itube_end
+C        enecav(i)=0.0        
+C        iti=itype(i)
+C        if (acavtub(iti).eq.0.0) cycle
+        
+
+
+        do i=itube_start,itube_end
+          Etube=Etube+enetube(i)+enetube(i+nres)+enecavtube(i)
+     & +enecavtube(i+nres)
+        enddo
+C        print *,"ETUBE", etube
+        return
+        end
+C TO DO 1) add to total energy
+C       2) add to gradient summation
+C       3) add reading parameters (AND of course oppening of PARAM file)
+C       4) add reading the center of tube
+C       5) add COMMONs
+C       6) add to zerograd