newest dihed constr added
[unres4.git] / source / unres / energy.f90
index 014ce41..d770307 100644 (file)
 ! Change 12/1/95 - common block CONTACTS1 included.
 !      common /contacts1/
       
 ! Change 12/1/95 - common block CONTACTS1 included.
 !      common /contacts1/
       
-      integer,dimension(:),allocatable :: num_cont     !(maxres)
-      integer,dimension(:,:),allocatable :: jcont      !(maxconts,maxres)
-      real(kind=8),dimension(:,:),allocatable :: facont,ees0plist      !(maxconts,maxres)
-      real(kind=8),dimension(:,:,:),allocatable :: gacont      !(3,maxconts,maxres)
+      integer,dimension(:),allocatable :: num_cont      !(maxres)
+      integer,dimension(:,:),allocatable :: jcont      !(maxconts,maxres)
+      real(kind=8),dimension(:,:),allocatable :: facont,ees0plist      !(maxconts,maxres)
+      real(kind=8),dimension(:,:,:),allocatable :: gacont      !(3,maxconts,maxres)
       integer,dimension(:),allocatable :: ishield_list
       integer,dimension(:,:),allocatable ::  shield_list
       integer,dimension(:),allocatable :: ishield_list
       integer,dimension(:,:),allocatable ::  shield_list
+      real(kind=8),dimension(:),allocatable :: enetube,enecavtube
 !                
 ! 12/26/95 - H-bonding contacts
 !      common /contacts_hb/ 
       real(kind=8),dimension(:,:,:),allocatable :: gacontp_hb1,gacontp_hb2,&
 !                
 ! 12/26/95 - H-bonding contacts
 !      common /contacts_hb/ 
       real(kind=8),dimension(:,:,:),allocatable :: gacontp_hb1,gacontp_hb2,&
-       gacontp_hb3,gacontm_hb1,gacontm_hb2,gacontm_hb3,gacont_hbr,grij_hb_cont !(3,maxconts,maxres)
+       gacontp_hb3,gacontm_hb1,gacontm_hb2,gacontm_hb3,gacont_hbr,grij_hb_cont      !(3,maxconts,maxres)
       real(kind=8),dimension(:,:),allocatable :: facont_hb,ees0p,&
       real(kind=8),dimension(:,:),allocatable :: facont_hb,ees0p,&
-        ees0m,d_cont   !(maxconts,maxres)
-      integer,dimension(:),allocatable :: num_cont_hb  !(maxres)
-      integer,dimension(:,:),allocatable :: jcont_hb   !(maxconts,maxres)
+        ees0m,d_cont      !(maxconts,maxres)
+      integer,dimension(:),allocatable :: num_cont_hb      !(maxres)
+      integer,dimension(:,:),allocatable :: jcont_hb      !(maxconts,maxres)
 ! 9/23/99 Added improper rotation matrices and matrices of dipole-dipole 
 !         interactions     
 ! 7/25/08 commented out; not needed when cumulants used
 ! Interactions of pseudo-dipoles generated by loc-el interactions.
 !  common /dipint/
       real(kind=8),dimension(:,:,:),allocatable :: dip,&
 ! 9/23/99 Added improper rotation matrices and matrices of dipole-dipole 
 !         interactions     
 ! 7/25/08 commented out; not needed when cumulants used
 ! Interactions of pseudo-dipoles generated by loc-el interactions.
 !  common /dipint/
       real(kind=8),dimension(:,:,:),allocatable :: dip,&
-         dipderg       !(4,maxconts,maxres)
+         dipderg      !(4,maxconts,maxres)
       real(kind=8),dimension(:,:,:,:,:),allocatable :: dipderx !(3,5,4,maxconts,maxres)
 ! 10/30/99 Added other pre-computed vectors and matrices needed 
 !          to calculate three - six-order el-loc correlation terms
 ! common /rotat/
       real(kind=8),dimension(:,:,:,:,:),allocatable :: dipderx !(3,5,4,maxconts,maxres)
 ! 10/30/99 Added other pre-computed vectors and matrices needed 
 !          to calculate three - six-order el-loc correlation terms
 ! common /rotat/
-      real(kind=8),dimension(:,:,:),allocatable :: Ug,Ugder,Ug2,Ug2der !(2,2,maxres)
+      real(kind=8),dimension(:,:,:),allocatable :: Ug,Ugder,Ug2,Ug2der      !(2,2,maxres)
       real(kind=8),dimension(:,:),allocatable :: obrot,obrot2,obrot_der,&
       real(kind=8),dimension(:,:),allocatable :: obrot,obrot2,obrot_der,&
-       obrot2_der      !(2,maxres)
+       obrot2_der      !(2,maxres)
 !
 ! This common block contains vectors and matrices dependent on a single
 ! amino-acid residue.
 !      common /precomp1/
       real(kind=8),dimension(:,:),allocatable :: mu,muder,Ub2,Ub2der,&
 !
 ! This common block contains vectors and matrices dependent on a single
 ! amino-acid residue.
 !      common /precomp1/
       real(kind=8),dimension(:,:),allocatable :: mu,muder,Ub2,Ub2der,&
-       Ctobr,Ctobrder,Dtobr2,Dtobr2der !(2,maxres)
+       Ctobr,Ctobrder,Dtobr2,Dtobr2der      !(2,maxres)
       real(kind=8),dimension(:,:,:),allocatable :: EUg,EUgder,CUg,&
       real(kind=8),dimension(:,:,:),allocatable :: EUg,EUgder,CUg,&
-       CUgder,DUg,Dugder,DtUg2,DtUg2der        !(2,2,maxres)
+       CUgder,DUg,Dugder,DtUg2,DtUg2der      !(2,2,maxres)
 ! This common block contains vectors and matrices dependent on two
 ! consecutive amino-acid residues.
 !      common /precomp2/
       real(kind=8),dimension(:,:),allocatable :: Ug2Db1t,Ug2Db1tder,&
 ! This common block contains vectors and matrices dependent on two
 ! consecutive amino-acid residues.
 !      common /precomp2/
       real(kind=8),dimension(:,:),allocatable :: Ug2Db1t,Ug2Db1tder,&
-       CUgb2,CUgb2der  !(2,maxres)
+       CUgb2,CUgb2der      !(2,maxres)
       real(kind=8),dimension(:,:,:),allocatable :: EUgC,EUgCder,&
       real(kind=8),dimension(:,:,:),allocatable :: EUgC,EUgCder,&
-       EUgD,EUgDder,DtUg2EUg,Ug2DtEUg  !(2,2,maxres)
+       EUgD,EUgDder,DtUg2EUg,Ug2DtEUg      !(2,2,maxres)
       real(kind=8),dimension(:,:,:,:),allocatable :: Ug2DtEUgder,&
       real(kind=8),dimension(:,:,:,:),allocatable :: Ug2DtEUgder,&
-       DtUg2EUgder     !(2,2,2,maxres)
+       DtUg2EUgder      !(2,2,2,maxres)
 !      common /rotat_old/
       real(kind=8),dimension(:),allocatable :: costab,sintab,&
 !      common /rotat_old/
       real(kind=8),dimension(:),allocatable :: costab,sintab,&
-       costab2,sintab2 !(maxres)
+       costab2,sintab2      !(maxres)
 ! This common block contains dipole-interaction matrices and their 
 ! Cartesian derivatives.
 !      common /dipmat/ 
 ! This common block contains dipole-interaction matrices and their 
 ! Cartesian derivatives.
 !      common /dipmat/ 
-      real(kind=8),dimension(:,:,:,:),allocatable :: a_chuj    !(2,2,maxconts,maxres)
-      real(kind=8),dimension(:,:,:,:,:,:),allocatable :: a_chuj_der    !(2,2,3,5,maxconts,maxres)
+      real(kind=8),dimension(:,:,:,:),allocatable :: a_chuj      !(2,2,maxconts,maxres)
+      real(kind=8),dimension(:,:,:,:,:,:),allocatable :: a_chuj_der      !(2,2,3,5,maxconts,maxres)
 !      common /diploc/
       real(kind=8),dimension(2,2,2) :: AEA,AEAderg,EAEA,AECA,&
        AECAderg,ADtEA,ADtEA1,AEAb1,AEAb1derg,AEAb2
 !      common /diploc/
       real(kind=8),dimension(2,2,2) :: AEA,AEAderg,EAEA,AECA,&
        AECAderg,ADtEA,ADtEA1,AEAb1,AEAb1derg,AEAb2
         gshieldc_ec,gshieldc_loc_ec,gshieldx_t3, &
         gshieldc_t3,gshieldc_loc_t3,gshieldx_t4,gshieldc_t4, &
         gshieldc_loc_t4,gshieldx_ll,gshieldc_ll,gshieldc_loc_ll,&
         gshieldc_ec,gshieldc_loc_ec,gshieldx_t3, &
         gshieldc_t3,gshieldc_loc_t3,gshieldx_t4,gshieldc_t4, &
         gshieldc_loc_t4,gshieldx_ll,gshieldc_ll,gshieldc_loc_ll,&
-        grad_shield !(3,maxres)
+        grad_shield,gg_tube,gg_tube_sc,gradafm !(3,maxres)
+!-----------------------------NUCLEIC GRADIENT
+      real(kind=8),dimension(:,:),allocatable  ::gradb_nucl,gradbx_nucl, &
+        gvdwpsb1,gelpp,gvdwpsb,gelsbc,gelsbx,gvdwsbx,gvdwsbc,gsbloc,&
+        gsblocx,gradcorr_nucl,gradxorr_nucl,gradcorr3_nucl,gradxorr3_nucl,&
+        gvdwpp_nucl
+!-----------------------------NUCLEIC-PROTEIN GRADIENT
+      real(kind=8),dimension(:,:),allocatable  :: gvdwx_scbase,gvdwc_scbase,&
+         gvdwx_pepbase,gvdwc_pepbase,gvdwx_scpho,gvdwc_scpho,&
+         gvdwc_peppho
+!------------------------------IONS GRADIENT
+        real(kind=8),dimension(:,:),allocatable  ::  gradcatcat, &
+          gradpepcat,gradpepcatx
 !      real(kind=8),dimension(:,:),allocatable :: gloc,gloc_x !(maxvar,2)
 !      real(kind=8),dimension(:,:),allocatable :: gloc,gloc_x !(maxvar,2)
+
+
       real(kind=8),dimension(:,:),allocatable :: gel_loc,gel_loc_long,&
         gcorr3_turn,gcorr4_turn,gcorr6_turn,gradb,gradbx !(3,maxres)
       real(kind=8),dimension(:),allocatable :: gel_loc_loc,&
         gel_loc_turn3,gel_loc_turn4,gel_loc_turn6,gcorr_loc,g_corr5_loc,&
       real(kind=8),dimension(:,:),allocatable :: gel_loc,gel_loc_long,&
         gcorr3_turn,gcorr4_turn,gcorr6_turn,gradb,gradbx !(3,maxres)
       real(kind=8),dimension(:),allocatable :: gel_loc_loc,&
         gel_loc_turn3,gel_loc_turn4,gel_loc_turn6,gcorr_loc,g_corr5_loc,&
-        g_corr6_loc    !(maxvar)
+        g_corr6_loc      !(maxvar)
       real(kind=8),dimension(:,:),allocatable :: gsccorc,gsccorx !(3,maxres)
       real(kind=8),dimension(:,:),allocatable :: gsccorc,gsccorx !(3,maxres)
-      real(kind=8),dimension(:),allocatable :: gsccor_loc      !(maxres)
-!      real(kind=8),dimension(:,:,:),allocatable :: dtheta     !(3,2,maxres)
+      real(kind=8),dimension(:),allocatable :: gsccor_loc      !(maxres)
+!      real(kind=8),dimension(:,:,:),allocatable :: dtheta      !(3,2,maxres)
       real(kind=8),dimension(:,:),allocatable :: gscloc,gsclocx !(3,maxres)
 !      real(kind=8),dimension(:,:,:),allocatable :: dphi,dalpha,domega !(3,3,maxres)
       real(kind=8),dimension(:,:,:),allocatable :: grad_shield_side, &
       real(kind=8),dimension(:,:),allocatable :: gscloc,gsclocx !(3,maxres)
 !      real(kind=8),dimension(:,:,:),allocatable :: dphi,dalpha,domega !(3,3,maxres)
       real(kind=8),dimension(:,:,:),allocatable :: grad_shield_side, &
 !      common /deriv_scloc/
       real(kind=8),dimension(:,:),allocatable :: dXX_C1tab,dYY_C1tab,&
        dZZ_C1tab,dXX_Ctab,dYY_Ctab,dZZ_Ctab,dXX_XYZtab,dYY_XYZtab,&
 !      common /deriv_scloc/
       real(kind=8),dimension(:,:),allocatable :: dXX_C1tab,dYY_C1tab,&
        dZZ_C1tab,dXX_Ctab,dYY_Ctab,dZZ_Ctab,dXX_XYZtab,dYY_XYZtab,&
-       dZZ_XYZtab      !(3,maxres)
+       dZZ_XYZtab      !(3,maxres)
 !-----------------------------------------------------------------------------
 ! common.maxgrad
 !      common /maxgrad/
 !-----------------------------------------------------------------------------
 ! common.maxgrad
 !      common /maxgrad/
 !      common /qmeas/
       real(kind=8) :: Ucdfrag,Ucdpair
       real(kind=8),dimension(:,:),allocatable :: dUdconst,dUdxconst,&
 !      common /qmeas/
       real(kind=8) :: Ucdfrag,Ucdpair
       real(kind=8),dimension(:,:),allocatable :: dUdconst,dUdxconst,&
-       dqwol,dxqwol    !(3,0:MAXRES)
+       dqwol,dxqwol      !(3,0:MAXRES)
 !-----------------------------------------------------------------------------
 ! common.sbridge
 !      common /dyn_ssbond/
 !-----------------------------------------------------------------------------
 ! common.sbridge
 !      common /dyn_ssbond/
 ! Parameters of the SCCOR term
 !      common/sccor/
       real(kind=8),dimension(:,:,:,:),allocatable :: dcostau,dsintau,&
 ! Parameters of the SCCOR term
 !      common/sccor/
       real(kind=8),dimension(:,:,:,:),allocatable :: dcostau,dsintau,&
-       dcosomicron,domicron    !(3,3,3,maxres2)
+       dcosomicron,domicron      !(3,3,3,maxres2)
 !-----------------------------------------------------------------------------
 ! common.vectors
 !      common /vectors/
 !-----------------------------------------------------------------------------
 ! common.vectors
 !      common /vectors/
       real(kind=8),dimension(:,:,:,:),allocatable :: uygrad,uzgrad !(3,3,2,maxres)
 !-----------------------------------------------------------------------------
 ! common /przechowalnia/
       real(kind=8),dimension(:,:,:,:),allocatable :: uygrad,uzgrad !(3,3,2,maxres)
 !-----------------------------------------------------------------------------
 ! common /przechowalnia/
-      real(kind=8),dimension(:,:,:),allocatable :: zapas !(max_dim,maxconts,max_fg_procs)
+      real(kind=8),dimension(:,:,:),allocatable :: zapas 
+      real(kind=8),dimension(:,:,:,:),allocatable ::zapas2 !(max_dim,maxconts,max_fg_procs)
       real(kind=8),dimension(:,:,:),allocatable :: fromto !(3,3,maxdim)(maxdim=(maxres-1)*(maxres-2)/2)
 !-----------------------------------------------------------------------------
 !-----------------------------------------------------------------------------
       real(kind=8),dimension(:,:,:),allocatable :: fromto !(3,3,maxdim)(maxdim=(maxres-1)*(maxres-2)/2)
 !-----------------------------------------------------------------------------
 !-----------------------------------------------------------------------------
       integer :: n_corr,n_corr1,ierror
       real(kind=8) :: etors,edihcnstr,etors_d,esccor,ehpb
       real(kind=8) :: evdw,evdw1,evdw2,evdw2_14,escloc,ees,eel_loc
       integer :: n_corr,n_corr1,ierror
       real(kind=8) :: etors,edihcnstr,etors_d,esccor,ehpb
       real(kind=8) :: evdw,evdw1,evdw2,evdw2_14,escloc,ees,eel_loc
-      real(kind=8) :: eello_turn3,eello_turn4,estr,ebe,eliptran
+      real(kind=8) :: eello_turn3,eello_turn4,estr,ebe,eliptran,etube, &
+                      Eafmforce,ethetacnstr
       real(kind=8) :: ecorr,ecorr5,ecorr6,eturn6
       real(kind=8) :: ecorr,ecorr5,ecorr6,eturn6
+! now energies for nulceic alone parameters
+      real(kind=8) :: evdwpp,eespp,evdwpsb,eelpsb,evdwsb,eelsb,estr_nucl,&
+                      ebe_nucl,esbloc,etors_nucl,etors_d_nucl,ecorr_nucl,&
+                      ecorr3_nucl
+! energies for ions 
+      real(kind=8) :: ecation_prot,ecationcation
+! energies for protein nucleic acid interaction
+      real(kind=8) :: escbase,epepbase,escpho,epeppho
 
 #ifdef MPI      
       real(kind=8) :: weights_(n_ene) !,time_Bcast,time_Bcastw
 
 #ifdef MPI      
       real(kind=8) :: weights_(n_ene) !,time_Bcast,time_Bcastw
           weights_(17)=wbond
           weights_(18)=scal14
           weights_(21)=wsccor
           weights_(17)=wbond
           weights_(18)=scal14
           weights_(21)=wsccor
+          weights_(26)=wvdwpp_nucl
+          weights_(27)=welpp
+          weights_(28)=wvdwpsb
+          weights_(29)=welpsb
+          weights_(30)=wvdwsb
+          weights_(31)=welsb
+          weights_(32)=wbond_nucl
+          weights_(33)=wang_nucl
+          weights_(34)=wsbloc
+          weights_(35)=wtor_nucl
+          weights_(36)=wtor_d_nucl
+          weights_(37)=wcorr_nucl
+          weights_(38)=wcorr3_nucl
+          weights_(41)=wcatcat
+          weights_(42)=wcatprot
+          weights_(46)=wscbase
+          weights_(47)=wscpho
+          weights_(48)=wpeppho
+!          wcatcat= weights(41)
+!          wcatprot=weights(42)
+
 ! FG Master broadcasts the WEIGHTS_ array
           call MPI_Bcast(weights_(1),n_ene,&
              MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
 ! FG Master broadcasts the WEIGHTS_ array
           call MPI_Bcast(weights_(1),n_ene,&
              MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
           wbond=weights(17)
           scal14=weights(18)
           wsccor=weights(21)
           wbond=weights(17)
           scal14=weights(18)
           wsccor=weights(21)
+          wvdwpp_nucl =weights(26)
+          welpp  =weights(27)
+          wvdwpsb=weights(28)
+          welpsb =weights(29)
+          wvdwsb =weights(30)
+          welsb  =weights(31)
+          wbond_nucl  =weights(32)
+          wang_nucl   =weights(33)
+          wsbloc =weights(34)
+          wtor_nucl   =weights(35)
+          wtor_d_nucl =weights(36)
+          wcorr_nucl  =weights(37)
+          wcorr3_nucl =weights(38)
+          wcatcat= weights(41)
+          wcatprot=weights(42)
+          wscbase=weights(46)
+          wscpho=weights(47)
+          wpeppho=weights(48)
         endif
         time_Bcast=time_Bcast+MPI_Wtime()-time00
         time_Bcastw=time_Bcastw+MPI_Wtime()-time00
         endif
         time_Bcast=time_Bcast+MPI_Wtime()-time00
         time_Bcastw=time_Bcastw+MPI_Wtime()-time00
 #endif
 ! 
 ! Compute the side-chain and electrostatic interaction energy
 #endif
 ! 
 ! Compute the side-chain and electrostatic interaction energy
-        print *, "Before EVDW"
+!        print *, "Before EVDW"
 !      goto (101,102,103,104,105,106) ipot
       select case(ipot)
 ! Lennard-Jones potential.
 !      goto (101,102,103,104,105,106) ipot
       select case(ipot)
 ! Lennard-Jones potential.
        if (shield_mode.eq.2) then
                  call set_shield_fac2
        endif
        if (shield_mode.eq.2) then
                  call set_shield_fac2
        endif
+!       print *,"AFTER EGB",ipot,evdw
 !mc
 !mc Sep-06: egb takes care of dynamic ss bonds too
 !mc
 !mc
 !mc Sep-06: egb takes care of dynamic ss bonds too
 !mc
 !        print *,"Processor",myrank," left VEC_AND_DERIV"
       if (ipot.lt.6) then
 #ifdef SPLITELE
 !        print *,"Processor",myrank," left VEC_AND_DERIV"
       if (ipot.lt.6) then
 #ifdef SPLITELE
-         print *,"after ipot if", ipot
+!         print *,"after ipot if", ipot
          if (welec.gt.0d0.or.wvdwpp.gt.0d0.or.wel_loc.gt.0d0.or. &
              wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0 &
              .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0 &
          if (welec.gt.0d0.or.wvdwpp.gt.0d0.or.wel_loc.gt.0d0.or. &
              wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0 &
              .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0 &
 ! Calculate the bond-stretching energy
 !
       call ebond(estr)
 ! Calculate the bond-stretching energy
 !
       call ebond(estr)
+!       print *,"EBOND",estr
 !       write(iout,*) "in etotal afer ebond",ipot
 
 ! 
 !       write(iout,*) "in etotal afer ebond",ipot
 
 ! 
 ! Calculate the virtual-bond-angle energy.
 !
       if (wang.gt.0d0) then
 ! Calculate the virtual-bond-angle energy.
 !
       if (wang.gt.0d0) then
-        call ebend(ebe)
+        call ebend(ebe,ethetacnstr)
       else
         ebe=0
       else
         ebe=0
+        ethetacnstr=0
       endif
 !      print *,"Processor",myrank," computed UB"
 !
       endif
 !      print *,"Processor",myrank," computed UB"
 !
       else
        eliptran=0.0d0
       endif
       else
        eliptran=0.0d0
       endif
-
+      if (fg_rank.eq.0) then
+      if (AFMlog.gt.0) then
+        call AFMforce(Eafmforce)
+      else if (selfguide.gt.0) then
+        call AFMvel(Eafmforce)
+      endif
+      endif
+      if (tubemode.eq.1) then
+       call calctube(etube)
+      else if (tubemode.eq.2) then
+       call calctube2(etube)
+      elseif (tubemode.eq.3) then
+       call calcnano(etube)
+      else
+       etube=0.0d0
+      endif
+!--------------------------------------------------------
+!      write (iout,*) "NRES_MOLEC(2),",nres_molec(2)
+!      print *,"before",ees,evdw1,ecorr
+      if (nres_molec(2).gt.0) then
+      call ebond_nucl(estr_nucl)
+      call ebend_nucl(ebe_nucl)
+      call etor_nucl(etors_nucl)
+      call esb_gb(evdwsb,eelsb)
+      call epp_nucl_sub(evdwpp,eespp)
+      call epsb(evdwpsb,eelpsb)
+      call esb(esbloc)
+      call multibody_hb_nucl(ecorr_nucl,ecorr3_nucl,n_corr,n_corr1)
+      else
+       etors_nucl=0.0d0
+       estr_nucl=0.0d0
+       ebe_nucl=0.0d0
+       evdwsb=0.0d0
+       eelsb=0.0d0
+       esbloc=0.0d0
+      endif
+      if (nfgtasks.gt.1) then
+      if (fg_rank.eq.0) then
+      call ecatcat(ecationcation)
+      endif
+      else
+      call ecatcat(ecationcation)
+      endif
+      call ecat_prot(ecation_prot)
+      if (nres_molec(2).gt.0) then
+      call eprot_sc_base(escbase)
+      call epep_sc_base(epepbase)
+      call eprot_sc_phosphate(escpho)
+      call eprot_pep_phosphate(epeppho)
+      endif
+!      call ecatcat(ecationcation)
+!      print *,"after ebend", ebe_nucl
 #ifdef TIMING
       time_enecalc=time_enecalc+MPI_Wtime()-time00
 #endif
 #ifdef TIMING
       time_enecalc=time_enecalc+MPI_Wtime()-time00
 #endif
       energia(20)=Uconst+Uconst_back
       energia(21)=esccor
       energia(22)=eliptran
       energia(20)=Uconst+Uconst_back
       energia(21)=esccor
       energia(22)=eliptran
+      energia(23)=Eafmforce
+      energia(24)=ethetacnstr
+      energia(25)=etube
+!---------------------------------------------------------------
+      energia(26)=evdwpp
+      energia(27)=eespp
+      energia(28)=evdwpsb
+      energia(29)=eelpsb
+      energia(30)=evdwsb
+      energia(31)=eelsb
+      energia(32)=estr_nucl
+      energia(33)=ebe_nucl
+      energia(34)=esbloc
+      energia(35)=etors_nucl
+      energia(36)=etors_d_nucl
+      energia(37)=ecorr_nucl
+      energia(38)=ecorr3_nucl
+!----------------------------------------------------------------------
 !    Here are the energies showed per procesor if the are more processors 
 !    per molecule then we sum it up in sum_energy subroutine 
 !      print *," Processor",myrank," calls SUM_ENERGY"
 !    Here are the energies showed per procesor if the are more processors 
 !    per molecule then we sum it up in sum_energy subroutine 
 !      print *," Processor",myrank," calls SUM_ENERGY"
+      energia(41)=ecation_prot
+      energia(42)=ecationcation
+      energia(46)=escbase
+      energia(47)=epepbase
+      energia(48)=escpho
+      energia(49)=epeppho
       call sum_energy(energia,.true.)
       if (dyn_ss) call dyn_set_nss
 !      print *," Processor",myrank," left SUM_ENERGY"
       call sum_energy(energia,.true.)
       if (dyn_ss) call dyn_set_nss
 !      print *," Processor",myrank," left SUM_ENERGY"
       real(kind=8) :: evdw,evdw2,evdw2_14,ees,evdw1,ecorr,ecorr5,ecorr6
       real(kind=8) :: eel_loc,eello_turn3,eello_turn4,eturn6,ebe,escloc
       real(kind=8) :: etors,etors_d,ehpb,edihcnstr,estr,esccor,etot,   &
       real(kind=8) :: evdw,evdw2,evdw2_14,ees,evdw1,ecorr,ecorr5,ecorr6
       real(kind=8) :: eel_loc,eello_turn3,eello_turn4,eturn6,ebe,escloc
       real(kind=8) :: etors,etors_d,ehpb,edihcnstr,estr,esccor,etot,   &
-        eliptran
+        eliptran,etube, Eafmforce,ethetacnstr
+      real(kind=8) :: evdwpp,eespp,evdwpsb,eelpsb,evdwsb,eelsb,estr_nucl,&
+                      ebe_nucl,esbloc,etors_nucl,etors_d_nucl,ecorr_nucl,&
+                      ecorr3_nucl
+      real(kind=8) :: ecation_prot,ecationcation
+      real(kind=8) :: escbase,epepbase,escpho,epeppho
       integer :: i
 #ifdef MPI
       integer :: ierr
       integer :: i
 #ifdef MPI
       integer :: ierr
       Uconst=energia(20)
       esccor=energia(21)
       eliptran=energia(22)
       Uconst=energia(20)
       esccor=energia(21)
       eliptran=energia(22)
+      Eafmforce=energia(23)
+      ethetacnstr=energia(24)
+      etube=energia(25)
+      evdwpp=energia(26)
+      eespp=energia(27)
+      evdwpsb=energia(28)
+      eelpsb=energia(29)
+      evdwsb=energia(30)
+      eelsb=energia(31)
+      estr_nucl=energia(32)
+      ebe_nucl=energia(33)
+      esbloc=energia(34)
+      etors_nucl=energia(35)
+      etors_d_nucl=energia(36)
+      ecorr_nucl=energia(37)
+      ecorr3_nucl=energia(38)
+      ecation_prot=energia(41)
+      ecationcation=energia(42)
+      escbase=energia(46)
+      epepbase=energia(47)
+      escpho=energia(48)
+      epeppho=energia(49)
+!      energia(41)=ecation_prot
+!      energia(42)=ecationcation
+
+
 #ifdef SPLITELE
       etot=wsc*evdw+wscp*evdw2+welec*ees+wvdwpp*evdw1 &
        +wang*ebe+wtor*etors+wscloc*escloc &
        +wstrain*ehpb+wcorr*ecorr+wcorr5*ecorr5 &
        +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3 &
        +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d &
 #ifdef SPLITELE
       etot=wsc*evdw+wscp*evdw2+welec*ees+wvdwpp*evdw1 &
        +wang*ebe+wtor*etors+wscloc*escloc &
        +wstrain*ehpb+wcorr*ecorr+wcorr5*ecorr5 &
        +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3 &
        +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d &
-       +wbond*estr+Uconst+wsccor*esccor+wliptran*eliptran
+       +wbond*estr+Uconst+wsccor*esccor+wliptran*eliptran+wtube*etube&
+       +Eafmforce+ethetacnstr  &
+       +wbond_nucl*estr_nucl+wang_nucl*ebe_nucl&
+       +wvdwpp_nucl*evdwpp+welpp*eespp+wvdwpsb*evdwpsb+welpsb*eelpsb&
+       +wvdwsb*evdwsb+welsb*eelsb+wsbloc*esbloc+wtor_nucl*etors_nucl&
+       +wtor_d_nucl*etors_d_nucl+wcorr_nucl*ecorr_nucl+wcorr3_nucl*ecorr3_nucl&
+       +wcatprot*ecation_prot+wcatcat*ecationcation+wscbase*escbase&
+       +wpepbase*epepbase+wscpho*escpho+wpeppho*epeppho
 #else
       etot=wsc*evdw+wscp*evdw2+welec*(ees+evdw1) &
        +wang*ebe+wtor*etors+wscloc*escloc &
        +wstrain*ehpb+wcorr*ecorr+wcorr5*ecorr5 &
        +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3 &
        +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d &
 #else
       etot=wsc*evdw+wscp*evdw2+welec*(ees+evdw1) &
        +wang*ebe+wtor*etors+wscloc*escloc &
        +wstrain*ehpb+wcorr*ecorr+wcorr5*ecorr5 &
        +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3 &
        +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d &
-       +wbond*estr+Uconst+wsccor*esccor+wliptran*eliptran
+       +wbond*estr+Uconst+wsccor*esccor+wliptran*eliptran+wtube*etube&
+       +Eafmforce+ethetacnstr &
+       +wbond_nucl*estr_nucl+wang_nucl*ebe_nucl&
+       +wvdwpp_nucl*evdwpp+welpp*eespp+wvdwpsb*evdwpsb+welpsb*eelpsb&
+       +wvdwsb*evdwsb+welsb*eelsb+wsbloc*esbloc+wtor_nucl*etors_nucl&
+       +wtor_d_nucl*etors_d_nucl+wcorr_nucl*ecorr_nucl+wcorr3_nucl*ecorr3_nucl&
+       +wcatprot*ecation_prot+wcatcat*ecationcation+wscbase*escbase&
+       +wpepbase*epepbase+wscpho*escpho+wpeppho*epeppho
 #endif
       energia(0)=etot
 ! detecting NaNQ
 #endif
       energia(0)=etot
 ! detecting NaNQ
 !el local variables
       real(kind=8) :: etot,evdw,evdw2,ees,evdw1,ecorr,ecorr5,ecorr6,eel_loc
       real(kind=8) :: eello_turn6,eello_turn3,eello_turn4,ebe,escloc
 !el local variables
       real(kind=8) :: etot,evdw,evdw2,ees,evdw1,ecorr,ecorr5,ecorr6,eel_loc
       real(kind=8) :: eello_turn6,eello_turn3,eello_turn4,ebe,escloc
-      real(kind=8) :: etors,etors_d,ehpb,edihcnstr,estr,Uconst,esccor,eliptran
+      real(kind=8) :: etors,etors_d,ehpb,edihcnstr,estr,Uconst,esccor,eliptran,&
+       etube,ethetacnstr,Eafmforce
+      real(kind=8) :: evdwpp,eespp,evdwpsb,eelpsb,evdwsb,eelsb,estr_nucl,&
+                      ebe_nucl,esbloc,etors_nucl,etors_d_nucl,ecorr_nucl,&
+                      ecorr3_nucl
+      real(kind=8) :: ecation_prot,ecationcation
+      real(kind=8) :: escbase,epepbase,escpho,epeppho
 
       etot=energia(0)
       evdw=energia(1)
 
       etot=energia(0)
       evdw=energia(1)
       Uconst=energia(20)
       esccor=energia(21)
       eliptran=energia(22)
       Uconst=energia(20)
       esccor=energia(21)
       eliptran=energia(22)
-
+      Eafmforce=energia(23)
+      ethetacnstr=energia(24)
+      etube=energia(25)
+      evdwpp=energia(26)
+      eespp=energia(27)
+      evdwpsb=energia(28)
+      eelpsb=energia(29)
+      evdwsb=energia(30)
+      eelsb=energia(31)
+      estr_nucl=energia(32)
+      ebe_nucl=energia(33)
+      esbloc=energia(34)
+      etors_nucl=energia(35)
+      etors_d_nucl=energia(36)
+      ecorr_nucl=energia(37)
+      ecorr3_nucl=energia(38)
+      ecation_prot=energia(41)
+      ecationcation=energia(42)
+      escbase=energia(46)
+      epepbase=energia(47)
+      escpho=energia(48)
+      epeppho=energia(49)
 #ifdef SPLITELE
       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,evdw1,wvdwpp,&
         estr,wbond,ebe,wang,&
 #ifdef SPLITELE
       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,evdw1,wvdwpp,&
         estr,wbond,ebe,wang,&
         ecorr,wcorr,&
         ecorr5,wcorr5,ecorr6,wcorr6,eel_loc,wel_loc,eello_turn3,wturn3,&
         eello_turn4,wturn4,eello_turn6,wturn6,esccor,wsccor,&
         ecorr,wcorr,&
         ecorr5,wcorr5,ecorr6,wcorr6,eel_loc,wel_loc,eello_turn3,wturn3,&
         eello_turn4,wturn4,eello_turn6,wturn6,esccor,wsccor,&
-        edihcnstr,ebr*nss,&
-        Uconst,eliptran,wliptran,etot
+        edihcnstr,ethetacnstr,ebr*nss,&
+        Uconst,eliptran,wliptran,Eafmforce,etube,wtube, & ! till now protein
+        estr_nucl,wbond_nucl,ebe_nucl,wang_nucl, &
+        evdwpp,wvdwpp_nucl,eespp,welpp,evdwpsb,wvdwpsb,eelpsb,welpsb,&
+        evdwsb,wvdwsb,eelsb,welsb,esbloc,wsbloc,etors_nucl,wtor_nucl,&
+        etors_d_nucl,wtor_d_nucl,ecorr_nucl,wcorr_nucl,&
+        ecorr3_nucl,wcorr3_nucl,ecation_prot,wcatprot,ecationcation,wcatcat, &
+        escbase,wscbase,epepbase,wpepbase,escpho,wscpho,epeppho,wpeppho,&
+        etot
    10 format (/'Virtual-chain energies:'// &
        'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/ &
        'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/ &
    10 format (/'Virtual-chain energies:'// &
        'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/ &
        'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/ &
        'ETURN6=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 6th order)'/ &
        'ESCCOR=',1pE16.6,' WEIGHT=',1pD16.6,' (backbone-rotamer corr)'/ &
        'EDIHC= ',1pE16.6,' (dihedral angle constraints)'/ &
        '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)'/ &
        'UCONST= ',1pE16.6,' (Constraint energy)'/ &
        'ELT=',1pE16.6, ' WEIGHT=',1pD16.6,' (Lipid transfer energy)'/&
        'ESS=   ',1pE16.6,' (disulfide-bridge intrinsic energy)'/ &
        'UCONST= ',1pE16.6,' (Constraint energy)'/ &
        'ELT=',1pE16.6, ' WEIGHT=',1pD16.6,' (Lipid transfer energy)'/&
+       'EAFM=  ',1pE16.6,' (atomic-force microscopy)'/ &
+       'ETUBE=',1pE16.6, ' WEIGHT=',1pD16.6,' (cylindrical energy)'/ &
+       'ESTR_nucl=',1pE16.6,' WEIGHT=',1pD16.6,' (stretching for nucleic)'/ &
+       'EBE_nucl=',1pE16.6,' WEIGHT=',1pD16.6,' (bending for nucleic)'/ &
+       'EVDW_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(phosphate-phosphate VDW)'/ &
+       'EESPP_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(phosphate-phosphate elec)'/ &
+       'EVDWPSB_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(phosphate-sugarbase VDW)'/ &
+       'EESPSB_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(phosphate-sugarbase elec)'/ &
+       'EVDWSB_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(sugarbase-sugarbase VDW)'/ &
+       'EESSB_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(sugarbase-sugarbase elec)'/ &
+       'ESBLOC_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(sugarbase rotamer)'/ &
+       'ETORS_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(torsional)'/ &
+       'ETORSD_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(double torsional)'/ &
+       'ECORR_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(multibody 4th order)'/ &
+       'ECORR3_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(multibody 3th order)'/ &
+       'ECATPROT=',1pE16.6,' WEIGHT=',1pD16.6,'(cation prot)'/ &
+       'ECATCAT=',1pE16.6,' WEIGHT=',1pD16.6,'(cation cation)'/ &
+       'ESCBASE=',1pE16.6,' WEIGHT=',1pD16.6,'(sc-prot nucl-base)'/ &
+       'EPEPBASE=',1pE16.6,' WEIGHT=',1pD16.6,'(pep-prot nucl-base)'/ &
+       'ESCPHO=',1pE16.6,' WEIGHT=',1pD16.6,'(sc-prot nucl-phosphate)'/&
+       'EPEPPHO=',1pE16.6,' WEIGHT=',1pD16.6,'(pep-prot nucl-phosphate)'/&
        'ETOT=  ',1pE16.6,' (total)')
 #else
       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,&
        'ETOT=  ',1pE16.6,' (total)')
 #else
       write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,&
         ecorr,wcorr,&
         ecorr5,wcorr5,ecorr6,wcorr6,eel_loc,wel_loc,eello_turn3,wturn3,&
         eello_turn4,wturn4,eello_turn6,wturn6,esccor,wsccor,edihcnstr,&
         ecorr,wcorr,&
         ecorr5,wcorr5,ecorr6,wcorr6,eel_loc,wel_loc,eello_turn3,wturn3,&
         eello_turn4,wturn4,eello_turn6,wturn6,esccor,wsccor,edihcnstr,&
-        ebr*nss,Uconst,eliptran,wliptran,etot
+        ethetacnstr,ebr*nss,Uconst,eliptran,wliptran,Eafmforc,     &
+        etube,wtube, &
+        estr_nucl,wbond_nucl, ebe_nucl,wang_nucl,&
+        evdwpp,wvdwpp_nucl,eespp,welpp,evdwpsb,wvdwpsb,eelpsb,welpsb&
+        evdwsb,wvdwsb,eelsb,welsb,esbloc,wsbloc,etors_nucl,wtor_nucl&
+        etors_d_nucl,wtor_d_nucl,ecorr_nucl,wcorr_nucl,&
+        ecorr3_nucl,wcorr3_nucl,ecation_prot,wcatprot,ecationcation,wcatcat,  &
+        escbase,wscbase,epepbase,wpepbase,escpho,wscpho,epeppho,wpeppho,&
+        etot
    10 format (/'Virtual-chain energies:'// &
        'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/ &
        'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/ &
    10 format (/'Virtual-chain energies:'// &
        'EVDW=  ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-SC)'/ &
        'EVDW2= ',1pE16.6,' WEIGHT=',1pD16.6,' (SC-p)'/ &
        'ETURN6=',1pE16.6,' WEIGHT=',1pD16.6,' (turns, 6th order)'/ &
        'ESCCOR=',1pE16.6,' WEIGHT=',1pD16.6,' (backbone-rotamer corr)'/ &
        'EDIHC= ',1pE16.6,' (dihedral angle constraints)'/ &
        '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)'/ &
        'UCONST=',1pE16.6,' (Constraint energy)'/ &
        'ELT=',1pE16.6, ' WEIGHT=',1pD16.6,' (Lipid transfer energy)'/ &
        'ESS=   ',1pE16.6,' (disulfide-bridge intrinsic energy)'/ &
        'UCONST=',1pE16.6,' (Constraint energy)'/ &
        'ELT=',1pE16.6, ' WEIGHT=',1pD16.6,' (Lipid transfer energy)'/ &
+       'EAFM=  ',1pE16.6,' (atomic-force microscopy)'/ &
+       'ETUBE=',1pE16.6, ' WEIGHT=',1pD16.6,' (cylindrical energy)'/ &
+       'ESTR_nucl=  ',1pE16.6,' WEIGHT=',1pD16.6,' (stretching for nucleic)'/ &
+       'EBE_nucl=',1pE16.6,' WEIGHT=',1pD16.6,' (bending for nucleic)'/ &
+       'EVDW_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(phosphate-phosphate VDW)'/ &
+       'EESPP_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(phosphate-phosphate elec)'/ &
+       'EVDWPSB_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(phosphate-sugarbase VDW)'/ &
+       'EESPSB_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(phosphate-sugarbase elec)'/ &
+       'EVDWSB_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(sugarbase-sugarbase VDW)'/ &
+       'EESSB_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(sugarbase-sugarbase elec)'/ &
+       'ESBLOC_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(sugarbase rotamer)'/ &
+       'ETORS_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(torsional)'/ &
+       'ETORSD_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(double torsional)'/ &
+       'ECORR_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(multibody 4th order)'/ &
+       'ECORR3_nucl=',1pE16.6,' WEIGHT=',1pD16.6,'(multibody 3th order)'/ &
+       'ECATPROT=',1pE16.6,' WEIGHT=',1pD16.6,'(cation prot)'/ &
+       'ECATCAT=',1pE16.6,' WEIGHT=',1pD16.6,'(cation cation)'/ &
+       'ESCBASE=',1pE16.6,' WEIGHT=',1pD16.6,'(sc-prot nucl-base)'/ &
+       'EPEPBASE=',1pE16.6,' WEIGHT=',1pD16.6,'(pep-prot nucl-base)'/ &
+       'ESCPHO=',1pE16.6,' WEIGHT=',1pD16.6,'(sc-prot nucl-phosphate)'/&
+       'EPEPPHO=',1pE16.6,' WEIGHT=',1pD16.6,'(pep-prot nucl-phosphate)'/&
        'ETOT=  ',1pE16.6,' (total)')
 #endif
       return
        'ETOT=  ',1pE16.6,' (total)')
 #endif
       return
       evdw=0.0D0
 !      allocate(num_cont(iatsc_s:iatsc_e)) !(maxres) nnt,nct-2
 !      allocate(jcont(nres/4,iatsc_s:iatsc_e)) !(maxconts,maxres) (maxconts=maxres/4)
       evdw=0.0D0
 !      allocate(num_cont(iatsc_s:iatsc_e)) !(maxres) nnt,nct-2
 !      allocate(jcont(nres/4,iatsc_s:iatsc_e)) !(maxconts,maxres) (maxconts=maxres/4)
-!      allocate(facont(nres/4,iatsc_s:iatsc_e))        !(maxconts,maxres)
-!      allocate(gacont(3,nres/4,iatsc_s:iatsc_e))      !(3,maxconts,maxres)
+!      allocate(facont(nres/4,iatsc_s:iatsc_e))      !(maxconts,maxres)
+!      allocate(gacont(3,nres/4,iatsc_s:iatsc_e))      !(3,maxconts,maxres)
 
       do i=iatsc_s,iatsc_e
 
       do i=iatsc_s,iatsc_e
-        itypi=iabs(itype(i))
+        itypi=iabs(itype(i,1))
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=iabs(itype(i+1))
+        itypi1=iabs(itype(i+1,1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
 !d        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 !d   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
 !d        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 !d   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
-            itypj=iabs(itype(j)) 
+            itypj=iabs(itype(j,1)) 
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
 !d          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 !d          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 !d          write (iout,'(2(a3,i3,2x),6(1pd12.4)/2(3(1pd12.4),5x)/)')
 !d          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 !d          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 !d          write (iout,'(2(a3,i3,2x),6(1pd12.4)/2(3(1pd12.4),5x)/)')
-!d   &        restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
+!d   &        restyp(itypi,1),i,restyp(itypj,1),j,aa(itypi,itypj),
 !d   &        bb(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,epsi,sigm,
 !d   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
             evdw=evdw+evdwij
 !d   &        bb(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,epsi,sigm,
 !d   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
             evdw=evdw+evdwij
 !     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
 !     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=iabs(itype(i))
+        itypi=iabs(itype(i,1))
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=iabs(itype(i+1))
+        itypi1=iabs(itype(i+1,1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
 !
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
-            itypj=iabs(itype(j))
+            itypj=iabs(itype(j,1))
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
 !d          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 !d          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 !d          write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
 !d          sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 !d          epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 !d          write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
-!d   &        restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
+!d   &        restyp(itypi,1),i,restyp(itypj,1),j,aa(itypi,itypj),
 !d   &        bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
 !d   &        sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
 !d   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
 !d   &        bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
 !d   &        sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
 !d   &        (c(k,i),k=1,3),(c(k,j),k=1,3)
 !     endif
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     endif
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        itypi=iabs(itype(i))
+        itypi=iabs(itype(i,1))
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=iabs(itype(i+1))
+        itypi1=iabs(itype(i+1,1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
-            itypj=iabs(itype(j))
+            itypj=iabs(itype(j,1))
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
             epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
 !d            write (iout,'(2(a3,i3,2x),15(0pf7.3))')
             sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
             epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
 !d            write (iout,'(2(a3,i3,2x),15(0pf7.3))')
-!d     &        restyp(itypi),i,restyp(itypj),j,
+!d     &        restyp(itypi,1),i,restyp(itypj,1),j,
 !d     &        epsi,sigm,chi1,chi2,chip1,chip2,
 !d     &        eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
 !d     &        om1,om2,om12,1.0D0/dsqrt(rrij),
 !d     &        epsi,sigm,chi1,chi2,chip1,chip2,
 !d     &        eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
 !d     &        om1,om2,om12,1.0D0/dsqrt(rrij),
 !     if (icall.eq.0) lprn=.false.
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     if (icall.eq.0) lprn=.false.
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        print *,"I am in EVDW",i
-        itypi=iabs(itype(i))
+!C        print *,"I am in EVDW",i
+        itypi=iabs(itype(i,1))
+!        if (i.ne.47) cycle
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=iabs(itype(i+1))
+        itypi1=iabs(itype(i+1,1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
          sslipi=0.0d0
          ssgradlipi=0.0
        endif
          sslipi=0.0d0
          ssgradlipi=0.0
        endif
-       print *, sslipi,ssgradlipi
+!       print *, sslipi,ssgradlipi
         dxi=dc_norm(1,nres+i)
         dyi=dc_norm(2,nres+i)
         dzi=dc_norm(3,nres+i)
         dxi=dc_norm(1,nres+i)
         dyi=dc_norm(2,nres+i)
         dzi=dc_norm(3,nres+i)
                               'evdw',i,j,evdwij,' ss'
 !              if (energy_dec) write (iout,*) &
 !                              'evdw',i,j,evdwij,' ss'
                               'evdw',i,j,evdwij,' ss'
 !              if (energy_dec) write (iout,*) &
 !                              'evdw',i,j,evdwij,' ss'
+             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
+
+!c              write(iout,*) "PRZED TRI", evdwij
+!               evdwij_przed_tri=evdwij
+              call triple_ssbond_ene(i,j,k,evdwij)
+!c               if(evdwij_przed_tri.ne.evdwij) then
+!c                 write (iout,*) "TRI:", evdwij, evdwij_przed_tri
+!c               endif
+
+!c              write(iout,*) "PO TRI", evdwij
+!C call the energy function that removes the artifical triple disulfide
+!C bond the soubroutine is located in ssMD.F
+              evdw=evdw+evdwij
+              if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') &
+                            'evdw',i,j,evdwij,'tss'
+              endif!dyn_ss_mask(k)
+             enddo! k
             ELSE
 !el            ind=ind+1
             ELSE
 !el            ind=ind+1
-            itypj=iabs(itype(j))
+            itypj=iabs(itype(j,1))
             if (itypj.eq.ntyp1) cycle
             if (itypj.eq.ntyp1) cycle
+!             if (j.ne.78) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
 !            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,&
 !              1.0d0/vbld(j+nres) !d
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
 !            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,&
 !              1.0d0/vbld(j+nres) !d
-!            write (iout,*) "i",i," j", j," itype",itype(i),itype(j)
+!            write (iout,*) "i",i," j", j," itype",itype(i,1),itype(j,1)
             sig0ij=sigma(itypi,itypj)
             chi1=chi(itypi,itypj)
             chi2=chi(itypj,itypi)
             sig0ij=sigma(itypi,itypj)
             chi1=chi(itypi,itypj)
             chi2=chi(itypj,itypi)
             if (rij_shift.le.0.0D0) then
               evdw=1.0D20
 !d              write (iout,'(2(a3,i3,2x),17(0pf7.3))')
             if (rij_shift.le.0.0D0) then
               evdw=1.0D20
 !d              write (iout,'(2(a3,i3,2x),17(0pf7.3))')
-!d     &        restyp(itypi),i,restyp(itypj),j,
+!d     &        restyp(itypi,1),i,restyp(itypj,1),j,
 !d     &        rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq) 
               return
             endif
 !d     &        rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq) 
               return
             endif
             sigm=dabs(aa/bb)**(1.0D0/6.0D0)
             epsi=bb**2/aa!(itypi,itypj)
             write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
             sigm=dabs(aa/bb)**(1.0D0/6.0D0)
             epsi=bb**2/aa!(itypi,itypj)
             write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
-              restyp(itypi),i,restyp(itypj),j, &
+              restyp(itypi,1),i,restyp(itypj,1),j, &
               epsi,sigm,chi1,chi2,chip1,chip2, &
               eps1,eps2rt**2,eps3rt**2,sig,sig0ij, &
               om1,om2,om12,1.0D0/rij,1.0D0/rij_shift, &
               epsi,sigm,chi1,chi2,chip1,chip2, &
               eps1,eps2rt**2,eps3rt**2,sig,sig0ij, &
               om1,om2,om12,1.0D0/rij,1.0D0/rij_shift, &
 !C             print *,i,j,c(1,i),c(1,j),c(2,i),c(2,j),c(3,i),c(3,j)
 !            if (energy_dec) write (iout,*) &
 !                             'evdw',i,j,evdwij
 !C             print *,i,j,c(1,i),c(1,j),c(2,i),c(2,j),c(3,i),c(3,j)
 !            if (energy_dec) write (iout,*) &
 !                             'evdw',i,j,evdwij
+!                       print *,"ZALAMKA", evdw
 
 ! Calculate gradient components.
             e1=e1*eps1*eps2rt**2*eps3rt**2
 
 ! Calculate gradient components.
             e1=e1*eps1*eps2rt**2*eps3rt**2
           enddo      ! j
         enddo        ! iint
       enddo          ! i
           enddo      ! j
         enddo        ! iint
       enddo          ! i
+!       print *,"ZALAMKA", evdw
 !      write (iout,*) "Number of loop steps in EGB:",ind
 !ccc      energy_dec=.false.
       return
 !      write (iout,*) "Number of loop steps in EGB:",ind
 !ccc      energy_dec=.false.
       return
 !     if (icall.eq.0) lprn=.true.
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     if (icall.eq.0) lprn=.true.
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        itypi=iabs(itype(i))
+        itypi=iabs(itype(i,1))
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=iabs(itype(i+1))
+        itypi1=iabs(itype(i+1,1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
-            itypj=iabs(itype(j))
+            itypj=iabs(itype(j,1))
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             bb_aq(itypi,itypj))**(1.0D0/6.0D0)
             epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
             write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
             bb_aq(itypi,itypj))**(1.0D0/6.0D0)
             epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
             write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
-              restyp(itypi),i,restyp(itypj),j,&
+              restyp(itypi,1),i,restyp(itypj,1),j,&
               epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),&
               chi1,chi2,chip1,chip2,&
               eps1,eps2rt**2,eps3rt**2,&
               epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),&
               chi1,chi2,chip1,chip2,&
               eps1,eps2rt**2,eps3rt**2,&
 
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
 
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=iabs(itype(i))
+        itypi=iabs(itype(i,1))
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=iabs(itype(i+1))
+        itypi1=iabs(itype(i+1,1))
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
 !d        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 !d   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
 !d        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 !d   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
-            itypj=iabs(itype(j))
+            itypj=iabs(itype(j,1))
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
       eello_turn4=0.0d0
 !el      ind=0
       do i=iatel_s,iatel_e
       eello_turn4=0.0d0
 !el      ind=0
       do i=iatel_s,iatel_e
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         num_conti=0
 !        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         do j=ielstart(i),ielend(i)
         num_conti=0
 !        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 (itype(j,1).eq.ntyp1 .or. itype(j+1,1).eq.ntyp1) cycle
 !el          ind=ind+1
           iteli=itel(i)
           itelj=itel(j)
 !el          ind=ind+1
           iteli=itel(i)
           itelj=itel(j)
 !      include 'COMMON.LOCAL'
 !      include 'COMMON.CHAIN'
 !      include 'COMMON.VECTORS'
 !      include 'COMMON.LOCAL'
 !      include 'COMMON.CHAIN'
 !      include 'COMMON.VECTORS'
-      real(kind=8),dimension(3,3,2,nres) :: uygradt,uzgradt    !(3,3,2,maxres)
-      real(kind=8),dimension(3,nres) :: uyt,uzt        !(3,maxres)
+      real(kind=8),dimension(3,3,2,nres) :: uygradt,uzgradt      !(3,3,2,maxres)
+      real(kind=8),dimension(3,nres) :: uyt,uzt      !(3,maxres)
       real(kind=8),dimension(3,3,2) :: uygradn,uzgradn
       real(kind=8),dimension(3) :: erij
       real(kind=8) :: delta=1.0d-7
       real(kind=8),dimension(3,3,2) :: uygradn,uzgradn
       real(kind=8),dimension(3) :: erij
       real(kind=8) :: delta=1.0d-7
         endif
 !        if (i.gt. iatel_s+2 .and. i.lt.iatel_e+5) then
         if (i.gt. nnt+2 .and. i.lt.nct+2) then
         endif
 !        if (i.gt. iatel_s+2 .and. i.lt.iatel_e+5) then
         if (i.gt. nnt+2 .and. i.lt.nct+2) then
-          iti = itortyp(itype(i-2))
+           if (itype(i-2,1).eq.0) then
+          iti=ntortyp+1
+           else
+          iti = itortyp(itype(i-2,1))
+           endif
         else
           iti=ntortyp+1
         endif
 !        if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
         if (i.gt. nnt+1 .and. i.lt.nct+1) then
         else
           iti=ntortyp+1
         endif
 !        if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
         if (i.gt. nnt+1 .and. i.lt.nct+1) then
-          iti1 = itortyp(itype(i-1))
+           if (itype(i-1,1).eq.0) then
+          iti1=ntortyp+1
+           else
+          iti1 = itortyp(itype(i-1,1))
+           endif
         else
           iti1=ntortyp+1
         endif
         else
           iti1=ntortyp+1
         endif
-!          print *,iti,i,"iti",iti1,itype(i-1),itype(i-2)
+!          print *,iti,i,"iti",iti1,itype(i-1,1),itype(i-2,1)
 !d        write (iout,*) '*******i',i,' iti1',iti
 !d        write (iout,*) 'b1',b1(:,iti)
 !d        write (iout,*) 'b2',b2(:,iti)
 !d        write (iout,*) '*******i',i,' iti1',iti
 !d        write (iout,*) 'b1',b1(:,iti)
 !d        write (iout,*) 'b2',b2(:,iti)
         enddo
 !        if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
         if (i.gt. nnt+1 .and. i.lt.nct+1) then
         enddo
 !        if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
         if (i.gt. nnt+1 .and. i.lt.nct+1) then
-          if (itype(i-1).le.ntyp) then
-            iti1 = itortyp(itype(i-1))
+          if (itype(i-1,1).eq.0) then
+           iti1=ntortyp+1
+          elseif (itype(i-1,1).le.ntyp) then
+            iti1 = itortyp(itype(i-1,1))
           else
             iti1=ntortyp+1
           endif
           else
             iti1=ntortyp+1
           endif
 #endif
 #endif
 !d      do i=1,nres
 #endif
 #endif
 !d      do i=1,nres
-!d        iti = itortyp(itype(i))
+!d        iti = itortyp(itype(i,1))
 !d        write (iout,*) i
 !d        do j=1,2
 !d        write (iout,'(2f10.5,5x,2f10.5,5x,2f10.5)') 
 !d        write (iout,*) i
 !d        do j=1,2
 !d        write (iout,'(2f10.5,5x,2f10.5,5x,2f10.5)') 
     
 
 !d      write(iout,*) 'In EELEC'
     
 
 !d      write(iout,*) 'In EELEC'
-        print *,"IN EELEC"
+!        print *,"IN EELEC"
 !d      do i=1,nloctyp
 !d        write(iout,*) 'Type',i
 !d        write(iout,*) 'B1',B1(:,i)
 !d      do i=1,nloctyp
 !d        write(iout,*) 'Type',i
 !d        write(iout,*) 'B1',B1(:,i)
 !          write (iout,*) 'i',i,' fac',fac
         enddo
       endif
 !          write (iout,*) 'i',i,' fac',fac
         enddo
       endif
-      print *,wel_loc,"wel_loc",wcorr4,wcorr5,wcorr6,wturn3,wturn4,  &
-        wturn6
+!      print *,wel_loc,"wel_loc",wcorr4,wcorr5,wcorr6,wturn3,wturn4,  &
+!        wturn6
       if (wel_loc.gt.0.0d0 .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 &
           .or. wcorr6.gt.0.0d0 .or. wturn3.gt.0.0d0 .or. &
           wturn4.gt.0.0d0 .or. wturn6.gt.0.0d0) then
       if (wel_loc.gt.0.0d0 .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 &
           .or. wcorr6.gt.0.0d0 .or. wturn3.gt.0.0d0 .or. &
           wturn4.gt.0.0d0 .or. wturn6.gt.0.0d0) then
         time_mat=time_mat+MPI_Wtime()-time01
 #endif
       endif
         time_mat=time_mat+MPI_Wtime()-time01
 #endif
       endif
-       print *, "after set matrices"
+!       print *, "after set matrices"
 !d      do i=1,nres-1
 !d        write (iout,*) 'i=',i
 !d        do k=1,3
 !d      do i=1,nres-1
 !d        write (iout,*) 'i=',i
 !d        do k=1,3
 !
 
 
 !
 
 
-        print *,"before iturn3 loop"
+!        print *,"before iturn3 loop"
       do i=iturn3_start,iturn3_end
       do i=iturn3_start,iturn3_end
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1 &
-        .or. itype(i+2).eq.ntyp1 .or. itype(i+3).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1 &
+        .or. itype(i+2,1).eq.ntyp1 .or. itype(i+3,1).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
          sslipi=0.0d0
          ssgradlipi=0.0
        endif 
          sslipi=0.0d0
          ssgradlipi=0.0
        endif 
-       print *,i,sslipi,ssgradlipi
+!       print *,i,sslipi,ssgradlipi
        call eelecij(i,i+2,ees,evdw1,eel_loc)
         if (wturn3.gt.0.0d0) call eturn3(i,eello_turn3)
         num_cont_hb(i)=num_conti
       enddo
       do i=iturn4_start,iturn4_end
        call eelecij(i,i+2,ees,evdw1,eel_loc)
         if (wturn3.gt.0.0d0) call eturn3(i,eello_turn3)
         num_cont_hb(i)=num_conti
       enddo
       do i=iturn4_start,iturn4_end
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1 &
-          .or. itype(i+3).eq.ntyp1 &
-          .or. itype(i+4).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1 &
+          .or. itype(i+3,1).eq.ntyp1 &
+          .or. itype(i+4,1).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
 
         num_conti=num_cont_hb(i)
         call eelecij(i,i+3,ees,evdw1,eel_loc)
 
         num_conti=num_cont_hb(i)
         call eelecij(i,i+3,ees,evdw1,eel_loc)
-        if (wturn4.gt.0.0d0 .and. itype(i+2).ne.ntyp1) &
+        if (wturn4.gt.0.0d0 .and. itype(i+2,1).ne.ntyp1) &
          call eturn4(i,eello_turn4)
         num_cont_hb(i)=num_conti
       enddo   ! i
 !
 ! Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
 !
          call eturn4(i,eello_turn4)
         num_cont_hb(i)=num_conti
       enddo   ! i
 !
 ! Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
 !
+!      print *,"iatel_s,iatel_e,",iatel_s,iatel_e
       do i=iatel_s,iatel_e
       do i=iatel_s,iatel_e
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
 !        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         num_conti=num_cont_hb(i)
         do j=ielstart(i),ielend(i)
 !        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         num_conti=num_cont_hb(i)
         do j=ielstart(i),ielend(i)
-!          write (iout,*) i,j,itype(i),itype(j)
-          if (itype(j).eq.ntyp1.or. itype(j+1).eq.ntyp1) cycle
+!          write (iout,*) i,j,itype(i,1),itype(j,1)
+          if (itype(j,1).eq.ntyp1.or. itype(j+1,1).eq.ntyp1) cycle
           call eelecij(i,j,ees,evdw1,eel_loc)
         enddo ! j
         num_cont_hb(i)=num_conti
           call eelecij(i,j,ees,evdw1,eel_loc)
         enddo ! j
         num_cont_hb(i)=num_conti
                   ecosa1,ecosb1,ecosg1,ecosa2,ecosb2,ecosg2,ecosap,ecosbp,&
                   ecosgp,ecosam,ecosbm,ecosgm,ghalf
 !      maxconts=nres/4
                   ecosa1,ecosb1,ecosg1,ecosa2,ecosb2,ecosg2,ecosap,ecosbp,&
                   ecosgp,ecosam,ecosbm,ecosgm,ghalf
 !      maxconts=nres/4
-!      allocate(a_chuj(2,2,maxconts,nres))     !(2,2,maxconts,maxres)
-!      allocate(a_chuj_der(2,2,3,5,maxconts,nres))     !(2,2,3,5,maxconts,maxres)
+!      allocate(a_chuj(2,2,maxconts,nres))      !(2,2,maxconts,maxres)
+!      allocate(a_chuj_der(2,2,3,5,maxconts,nres))      !(2,2,3,5,maxconts,maxres)
 
 !          time00=MPI_Wtime()
 !d      write (iout,*) "eelecij",i,j
 
 !          time00=MPI_Wtime()
 !d      write (iout,*) "eelecij",i,j
 !
 ! Radial derivatives. First process both termini of the fragment (i,j)
 !
 !
 ! Radial derivatives. First process both termini of the fragment (i,j)
 !
-          ggg(1)=facel*xj+sss_ele_grad*rmij*eesij*xj
-          ggg(2)=facel*yj+sss_ele_grad*rmij*eesij*yj
-          ggg(3)=facel*zj+sss_ele_grad*rmij*eesij*zj
+          ggg(1)=facel*xj+sss_ele_grad*rmij*eesij*xj* &
+          ((sslipi+sslipj)/2.0d0*lipscale**2+1.0d0)
+          ggg(2)=facel*yj+sss_ele_grad*rmij*eesij*yj* & 
+           ((sslipi+sslipj)/2.0d0*lipscale**2+1.0d0)
+          ggg(3)=facel*zj+sss_ele_grad*rmij*eesij*zj* &
+            ((sslipi+sslipj)/2.0d0*lipscale**2+1.0d0)
 
           if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and. &
           (shield_mode.gt.0)) then
 
           if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and. &
           (shield_mode.gt.0)) then
           a32=a32*fac
           a33=a33*fac
 !d          write (iout,'(4i5,4f10.5)')
           a32=a32*fac
           a33=a33*fac
 !d          write (iout,'(4i5,4f10.5)')
-!d     &     i,itortyp(itype(i)),j,itortyp(itype(j)),a22,a23,a32,a33
+!d     &     i,itortyp(itype(i,1)),j,itortyp(itype(j,1)),a22,a23,a32,a33
 !d          write (iout,'(6f10.5)') (muij(k),k=1,4),fac,eel_loc_ij
 !d          write (iout,'(2(3f10.5,5x)/2(3f10.5,5x))') uy(:,i),uz(:,i),
 !d     &      uy(:,j),uz(:,j)
 !d          write (iout,'(6f10.5)') (muij(k),k=1,4),fac,eel_loc_ij
 !d          write (iout,'(2(3f10.5,5x)/2(3f10.5,5x))') uy(:,i),uz(:,i),
 !d     &      uy(:,j),uz(:,j)
             ggg(l)=(agg(l,1)*muij(1)+ &
                 agg(l,2)*muij(2)+agg(l,3)*muij(3)+agg(l,4)*muij(4))&
             *sss_ele_cut &
             ggg(l)=(agg(l,1)*muij(1)+ &
                 agg(l,2)*muij(2)+agg(l,3)*muij(3)+agg(l,4)*muij(4))&
             *sss_ele_cut &
-             +eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
+          *fac_shield(i)*fac_shield(j) &
+          *((sslipi+sslipj)/2.0d0*lipscale+1.0d0) &
+             +eel_loc_ij*sss_ele_grad*rmij*xtemp(l) 
+
 
             gel_loc_long(l,j)=gel_loc_long(l,j)+ggg(l)
             gel_loc_long(l,i)=gel_loc_long(l,i)-ggg(l)
 
             gel_loc_long(l,j)=gel_loc_long(l,j)+ggg(l)
             gel_loc_long(l,i)=gel_loc_long(l,i)-ggg(l)
           enddo
             gel_loc_long(3,j)=gel_loc_long(3,j)+ &
           ssgradlipj*eel_loc_ij/2.0d0*lipscale/  &
           enddo
             gel_loc_long(3,j)=gel_loc_long(3,j)+ &
           ssgradlipj*eel_loc_ij/2.0d0*lipscale/  &
-          ((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+          ((sslipi+sslipj)/2.0d0*lipscale+1.0d0)*sss_ele_cut
 
             gel_loc_long(3,i)=gel_loc_long(3,i)+ &
           ssgradlipi*eel_loc_ij/2.0d0*lipscale/  &
 
             gel_loc_long(3,i)=gel_loc_long(3,i)+ &
           ssgradlipi*eel_loc_ij/2.0d0*lipscale/  &
-          ((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+          ((sslipi+sslipj)/2.0d0*lipscale+1.0d0)*sss_ele_cut
 
 !grad          do k=i+1,j2
 !grad            do l=1,3
 
 !grad          do k=i+1,j2
 !grad            do l=1,3
           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))&
           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))&
-            *sss_ele_cut
+            *sss_ele_cut &
+          *fac_shield(i)*fac_shield(j) &
+          *((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 !+eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
             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))&
 !+eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
             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))&
-            *sss_ele_cut
+            *sss_ele_cut &
+          *fac_shield(i)*fac_shield(j) &
+          *((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 !+eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
             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))&
 !+eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
             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))&
-            *sss_ele_cut
+            *sss_ele_cut &
+          *fac_shield(i)*fac_shield(j) &
+          *((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 !+eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
             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))&
 !+eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
             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))&
-            *sss_ele_cut
+            *sss_ele_cut &
+          *fac_shield(i)*fac_shield(j) &
+          *((sslipi+sslipj)/2.0d0*lipscale+1.0d0)
+
 !+eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
           enddo
           ENDIF
 !+eel_loc_ij*sss_ele_grad*rmij*xtemp(l)
           enddo
           ENDIF
         call matmat2(EUgder(1,1,i+1),EUg(1,1,i+2),auxmat2(1,1))
         call transpose2(auxmat2(1,1),auxmat3(1,1))
         call matmat2(a_temp(1,1),auxmat3(1,1),pizda(1,1))
         call matmat2(EUgder(1,1,i+1),EUg(1,1,i+2),auxmat2(1,1))
         call transpose2(auxmat2(1,1),auxmat3(1,1))
         call matmat2(a_temp(1,1),auxmat3(1,1),pizda(1,1))
-        gel_loc_turn3(i)=gel_loc_turn3(i)+0.5d0*(pizda(1,1)+pizda(2,2))
+        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)
 ! 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),auxmat3(1,1))
 ! 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),auxmat3(1,1))
         a_temp(1,2)=a23
         a_temp(2,1)=a32
         a_temp(2,2)=a33
         a_temp(1,2)=a23
         a_temp(2,1)=a32
         a_temp(2,2)=a33
-        iti1=itortyp(itype(i+1))
-        iti2=itortyp(itype(i+2))
-        iti3=itortyp(itype(i+3))
+        iti1=itortyp(itype(i+1,1))
+        iti2=itortyp(itype(i+2,1))
+        iti3=itortyp(itype(i+3,1))
 !        write(iout,*) "iti1",iti1," iti2",iti2," iti3",iti3
         call transpose2(EUg(1,1,i+1),e1t(1,1))
         call transpose2(Eug(1,1,i+2),e2t(1,1))
 !        write(iout,*) "iti1",iti1," iti2",iti2," iti3",iti3
         call transpose2(EUg(1,1,i+1),e1t(1,1))
         call transpose2(Eug(1,1,i+2),e2t(1,1))
             call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
             s3=0.5d0*(pizda(1,1)+pizda(2,2))
             ggg(l)=-(s1+s2+s3)
             call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
             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)
+            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
 ! Remaining derivatives of this turn contribution
           enddo
         endif
 ! Remaining derivatives of this turn contribution
 !      implicit none
       real(kind=8),dimension(3) :: u,vec
       real(kind=8),dimension(3,3) ::ugrad,ungrad
 !      implicit none
       real(kind=8),dimension(3) :: u,vec
       real(kind=8),dimension(3,3) ::ugrad,ungrad
-      real(kind=8) :: unorm    !,scalar
+      real(kind=8) :: unorm      !,scalar
       integer :: i,j
 !      write (2,*) 'ugrad',ugrad
 !      write (2,*) 'u',u
       integer :: i,j
 !      write (2,*) 'ugrad',ugrad
 !      write (2,*) 'u',u
 !d    print '(a)','Enter ESCP'
 !d    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       do i=iatscp_s,iatscp_e
 !d    print '(a)','Enter ESCP'
 !d    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       do i=iatscp_s,iatscp_e
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) cycle
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
-          if (itype(j).eq.ntyp1) cycle
-          itypj=iabs(itype(j))
+          if (itype(j,1).eq.ntyp1) cycle
+          itypj=iabs(itype(j,1))
 ! Uncomment following three lines for SC-p interactions
 !         xj=c(1,nres+j)-xi
 !         yj=c(2,nres+j)-yi
 ! Uncomment following three lines for SC-p interactions
 !         xj=c(1,nres+j)-xi
 !         yj=c(2,nres+j)-yi
 !d    print '(a)','Enter ESCP'
 !d    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       do i=iatscp_s,iatscp_e
 !d    print '(a)','Enter ESCP'
 !d    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       do i=iatscp_s,iatscp_e
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) cycle
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
-          itypj=iabs(itype(j))
+          itypj=iabs(itype(j,1))
           if (itypj.eq.ntyp1) cycle
 ! Uncomment following three lines for SC-p interactions
 !         xj=c(1,nres+j)-xi
           if (itypj.eq.ntyp1) cycle
 ! Uncomment following three lines for SC-p interactions
 !         xj=c(1,nres+j)-xi
 ! 18/07/06 MC: Use the convention that the first nss pairs are SS bonds
         if (.not.dyn_ss .and. i.le.nss) then
 ! 15/02/13 CC dynamic SSbond - additional check
 ! 18/07/06 MC: Use the convention that the first nss pairs are SS bonds
         if (.not.dyn_ss .and. i.le.nss) then
 ! 15/02/13 CC dynamic SSbond - additional check
-         if (ii.gt.nres .and. iabs(itype(iii)).eq.1 .and. &
-        iabs(itype(jjj)).eq.1) then
+         if (ii.gt.nres .and. iabs(itype(iii,1)).eq.1 .and. &
+        iabs(itype(jjj,1)).eq.1) then
           call ssbond_ene(iii,jjj,eij)
           ehpb=ehpb+2*eij
 !d          write (iout,*) "eij",eij
          endif
           call ssbond_ene(iii,jjj,eij)
           ehpb=ehpb+2*eij
 !d          write (iout,*) "eij",eij
          endif
+        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
+            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
+          if (energy_dec) write (iout,'(a6,2i5,3f8.3)') "edisl",ii,jj, &
+            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,*) "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
+          endif
+          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
         else
-! Calculate the distance between the two points and its difference from the
-! target distance.
-        dd=dist(ii,jj)
-        rdis=dd-dhpb(i)
-! Get the force constant corresponding to this distance.
-        waga=forcon(i)
-! Calculate the contribution to energy.
-        ehpb=ehpb+waga*rdis*rdis
-!
-! Evaluate gradient.
-!
-        fac=waga*rdis/dd
-!d      print *,'i=',i,' ii=',ii,' jj=',jj,' dhpb=',dhpb(i),' dd=',dd,
-!d   &   ' waga=',waga,' fac=',fac
-        do j=1,3
-          ggg(j)=fac*(c(j,jj)-c(j,ii))
-        enddo
-!d      print '(i3,3(1pe14.5))',i,(ggg(j),j=1,3)
-! If this is a SC-SC distance, we need to calculate the contributions to the
-! Cartesian gradient in the SC vectors (ghpbx).
-        if (iii.lt.ii) then
+          dd=dist(ii,jj)
+          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
+          if (energy_dec) write (iout,'(a6,2i5,3f8.3)') "edisl",ii,jj, &
+         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)
+!C Calculate the contribution to energy.
+            ehpb=ehpb+waga*rdis*rdis
+!c            write (iout,*) "alpha reg",dd,waga*rdis*rdis
+!C
+!C Evaluate gradient.
+!C
+            fac=waga*rdis/dd
+          endif
+          endif
+
+            do j=1,3
+              ggg(j)=fac*(c(j,jj)-c(j,ii))
+            enddo
+!cd      print '(i3,3(1pe14.5))',i,(ggg(j),j=1,3)
+!C If this is a SC-SC distance, we need to calculate the contributions to the
+!C Cartesian gradient in the SC vectors (ghpbx).
+          if (iii.lt.ii) then
           do j=1,3
             ghpbx(j,iii)=ghpbx(j,iii)-ggg(j)
             ghpbx(j,jjj)=ghpbx(j,jjj)+ggg(j)
           enddo
           do j=1,3
             ghpbx(j,iii)=ghpbx(j,iii)-ggg(j)
             ghpbx(j,jjj)=ghpbx(j,jjj)+ggg(j)
           enddo
-        endif
-!grad        do j=iii,jjj-1
-!grad          do k=1,3
-!grad            ghpbc(k,j)=ghpbc(k,j)+ggg(k)
-!grad          enddo
-!grad        enddo
-        do k=1,3
-          ghpbc(k,jjj)=ghpbc(k,jjj)+ggg(k)
-          ghpbc(k,iii)=ghpbc(k,iii)-ggg(k)
-        enddo
+          endif
+!cgrad        do j=iii,jjj-1
+!cgrad          do k=1,3
+!cgrad            ghpbc(k,j)=ghpbc(k,j)+ggg(k)
+!cgrad          enddo
+!cgrad        enddo
+          do k=1,3
+            ghpbc(k,jjj)=ghpbc(k,jjj)+ggg(k)
+            ghpbc(k,iii)=ghpbc(k,iii)-ggg(k)
+          enddo
         endif
       enddo
         endif
       enddo
-      ehpb=0.5D0*ehpb
+      if (constr_dist.ne.11) ehpb=0.5D0*ehpb
+
       return
       end subroutine edis
 !-----------------------------------------------------------------------------
       return
       end subroutine edis
 !-----------------------------------------------------------------------------
                    deltat1,deltat2,deltat12,ed,pom1,pom2,eom1,eom2,eom12,&
                    cosphi,ggk
 
                    deltat1,deltat2,deltat12,ed,pom1,pom2,eom1,eom2,eom12,&
                    cosphi,ggk
 
-      itypi=iabs(itype(i))
+      itypi=iabs(itype(i,1))
       xi=c(1,nres+i)
       yi=c(2,nres+i)
       zi=c(3,nres+i)
       xi=c(1,nres+i)
       yi=c(2,nres+i)
       zi=c(3,nres+i)
       dzi=dc_norm(3,nres+i)
 !      dsci_inv=dsc_inv(itypi)
       dsci_inv=vbld_inv(nres+i)
       dzi=dc_norm(3,nres+i)
 !      dsci_inv=dsc_inv(itypi)
       dsci_inv=vbld_inv(nres+i)
-      itypj=iabs(itype(j))
+      itypj=iabs(itype(j,1))
 !      dscj_inv=dsc_inv(itypj)
       dscj_inv=vbld_inv(nres+j)
       xj=c(1,nres+j)-xi
 !      dscj_inv=dsc_inv(itypj)
       dscj_inv=vbld_inv(nres+j)
       xj=c(1,nres+j)-xi
 !      if (.not.allocated(gradbx)) allocate(gradbx(3,nres)) !(3,maxres)
 
       do i=ibondp_start,ibondp_end
 !      if (.not.allocated(gradbx)) allocate(gradbx(3,nres)) !(3,maxres)
 
       do i=ibondp_start,ibondp_end
-        if (itype(i-1).eq.ntyp1 .and. itype(i).eq.ntyp1) cycle
-        if (itype(i-1).eq.ntyp1 .or. itype(i).eq.ntyp1) then
+        if (itype(i-1,1).eq.ntyp1 .and. itype(i,1).eq.ntyp1) cycle
+        if (itype(i-1,1).eq.ntyp1 .or. itype(i,1).eq.ntyp1) then
 !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          estr1=estr1+gnmr1(vbld(i),-1.0d0,distchainmax)
 !C          do j=1,3
 !C          gradb(j,i-1)=gnmr1prim(vbld(i),-1.0d0,distchainmax) &
 !        endif
       enddo
       estr=0.5d0*AKP*estr+estr1
 !        endif
       enddo
       estr=0.5d0*AKP*estr+estr1
+!      print *,"estr_bb",estr,AKP
 !
 ! 09/18/07 AL: multimodal bond potential based on AM1 CA-SC PMF's included
 !
       do i=ibond_start,ibond_end
 !
 ! 09/18/07 AL: multimodal bond potential based on AM1 CA-SC PMF's included
 !
       do i=ibond_start,ibond_end
-        iti=iabs(itype(i))
+        iti=iabs(itype(i,1))
+        if (iti.eq.0) print *,"WARNING WRONG SETTTING",i
         if (iti.ne.10 .and. iti.ne.ntyp1) then
           nbi=nbondterm(iti)
           if (nbi.eq.1) then
         if (iti.ne.10 .and. iti.ne.ntyp1) then
           nbi=nbondterm(iti)
           if (nbi.eq.1) then
             "estr sc",i,iti,vbld(i+nres),vbldsc0(1,iti),diff,&
             AKSC(1,iti),AKSC(1,iti)*diff*diff
             estr=estr+0.5d0*AKSC(1,iti)*diff*diff
             "estr sc",i,iti,vbld(i+nres),vbldsc0(1,iti),diff,&
             AKSC(1,iti),AKSC(1,iti)*diff*diff
             estr=estr+0.5d0*AKSC(1,iti)*diff*diff
+!            print *,"estr_sc",estr
             do j=1,3
               gradbx(j,i)=AKSC(1,iti)*diff*dc(j,i+nres)/vbld(i+nres)
             enddo
             do j=1,3
               gradbx(j,i)=AKSC(1,iti)*diff*dc(j,i+nres)/vbld(i+nres)
             enddo
               usumsqder=usumsqder+ud(j)*uprod2   
             enddo
             estr=estr+uprod/usum
               usumsqder=usumsqder+ud(j)*uprod2   
             enddo
             estr=estr+uprod/usum
+!            print *,"estr_sc",estr,i
+
+             if (energy_dec) write (iout,*) &
+            "estr sc",i,iti,vbld(i+nres),vbldsc0(1,iti),diff,&
+            AKSC(1,iti),uprod/usum
             do j=1,3
              gradbx(j,i)=usumsqder/(usum*usum)*dc(j,i+nres)/vbld(i+nres)
             enddo
             do j=1,3
              gradbx(j,i)=usumsqder/(usum*usum)*dc(j,i+nres)/vbld(i+nres)
             enddo
       etheta=0.0D0
 !     write (*,'(a,i2)') 'EBEND ICG=',icg
       do i=ithet_start,ithet_end
       etheta=0.0D0
 !     write (*,'(a,i2)') 'EBEND ICG=',icg
       do i=ithet_start,ithet_end
-        if (itype(i-1).eq.ntyp1) cycle
+        if (itype(i-1,1).eq.ntyp1) cycle
 ! Zero the energy function and its derivative at 0 or pi.
         call splinthet(theta(i),0.5d0*delta,ss,ssd)
 ! Zero the energy function and its derivative at 0 or pi.
         call splinthet(theta(i),0.5d0*delta,ss,ssd)
-        it=itype(i-1)
-        ichir1=isign(1,itype(i-2))
-        ichir2=isign(1,itype(i))
-         if (itype(i-2).eq.10) ichir1=isign(1,itype(i-1))
-         if (itype(i).eq.10) ichir2=isign(1,itype(i-1))
-         if (itype(i-1).eq.10) then
-          itype1=isign(10,itype(i-2))
-          ichir11=isign(1,itype(i-2))
-          ichir12=isign(1,itype(i-2))
-          itype2=isign(10,itype(i))
-          ichir21=isign(1,itype(i))
-          ichir22=isign(1,itype(i))
+        it=itype(i-1,1)
+        ichir1=isign(1,itype(i-2,1))
+        ichir2=isign(1,itype(i,1))
+         if (itype(i-2,1).eq.10) ichir1=isign(1,itype(i-1,1))
+         if (itype(i,1).eq.10) ichir2=isign(1,itype(i-1,1))
+         if (itype(i-1,1).eq.10) then
+          itype1=isign(10,itype(i-2,1))
+          ichir11=isign(1,itype(i-2,1))
+          ichir12=isign(1,itype(i-2,1))
+          itype2=isign(10,itype(i,1))
+          ichir21=isign(1,itype(i,1))
+          ichir22=isign(1,itype(i,1))
          endif
 
          endif
 
-        if (i.gt.3 .and. itype(i-2).ne.ntyp1) then
+        if (i.gt.3 .and. itype(i-2,1).ne.ntyp1) then
 #ifdef OSF
           phii=phi(i)
           if (phii.ne.phii) phii=150.0
 #ifdef OSF
           phii=phi(i)
           if (phii.ne.phii) phii=150.0
           y(1)=0.0D0
           y(2)=0.0D0
         endif
           y(1)=0.0D0
           y(2)=0.0D0
         endif
-        if (i.lt.nres .and. itype(i).ne.ntyp1) then
+        if (i.lt.nres .and. itype(i,1).ne.ntyp1) then
 #ifdef OSF
           phii1=phi(i+1)
           if (phii1.ne.phii1) phii1=150.0
 #ifdef OSF
           phii1=phi(i+1)
           if (phii1.ne.phii1) phii1=150.0
         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)
       enddo
         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)
       enddo
+!      print *,ithetaconstr_start,ithetaconstr_end,"TU"
+
 ! Ufff.... We've done all this!!!
       return
       end subroutine ebend
 ! Ufff.... We've done all this!!!
       return
       end subroutine ebend
       end subroutine theteng
 #else
 !-----------------------------------------------------------------------------
       end subroutine theteng
 #else
 !-----------------------------------------------------------------------------
-      subroutine ebend(etheta)
+      subroutine ebend(etheta,ethetacnstr)
 !
 ! Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
 ! angles gamma and its derivatives in consecutive thetas and gammas.
 !
 ! Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
 ! angles gamma and its derivatives in consecutive thetas and gammas.
 !el local variables
       integer :: i,k,iblock,ityp1,ityp2,ityp3,l,m
       real(kind=8) :: dethetai,dephii,dephii1,theti2,phii,phii1,ethetai
 !el local variables
       integer :: i,k,iblock,ityp1,ityp2,ityp3,l,m
       real(kind=8) :: dethetai,dephii,dephii1,theti2,phii,phii1,ethetai
-      real(kind=8) :: aux,etheta,ccl,ssl,scl,csl
+      real(kind=8) :: aux,etheta,ccl,ssl,scl,csl,ethetacnstr
+! local variables for constrains
+      real(kind=8) :: difi,thetiii
+       integer itheta
 
       etheta=0.0D0
       do i=ithet_start,ithet_end
 
       etheta=0.0D0
       do i=ithet_start,ithet_end
-        if (itype(i-1).eq.ntyp1) cycle
-        if (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
+        if (itype(i-1,1).eq.ntyp1) cycle
+        if (itype(i-2,1).eq.ntyp1.or.itype(i,1).eq.ntyp1) cycle
+        if (iabs(itype(i+1,1)).eq.20) iblock=2
+        if (iabs(itype(i+1,1)).ne.20) iblock=1
         dethetai=0.0d0
         dephii=0.0d0
         dephii1=0.0d0
         theti2=0.5d0*theta(i)
         dethetai=0.0d0
         dephii=0.0d0
         dephii1=0.0d0
         theti2=0.5d0*theta(i)
-        ityp2=ithetyp((itype(i-1)))
+        ityp2=ithetyp((itype(i-1,1)))
         do k=1,nntheterm
           coskt(k)=dcos(k*theti2)
           sinkt(k)=dsin(k*theti2)
         enddo
         do k=1,nntheterm
           coskt(k)=dcos(k*theti2)
           sinkt(k)=dsin(k*theti2)
         enddo
-        if (i.gt.3 .and. itype(max0(i-3,1)).ne.ntyp1) then
+        if (i.gt.3 .and. itype(max0(i-3,1),1).ne.ntyp1) then
 #ifdef OSF
           phii=phi(i)
           if (phii.ne.phii) phii=150.0
 #else
           phii=phi(i)
 #endif
 #ifdef OSF
           phii=phi(i)
           if (phii.ne.phii) phii=150.0
 #else
           phii=phi(i)
 #endif
-          ityp1=ithetyp((itype(i-2)))
+          ityp1=ithetyp((itype(i-2,1)))
 ! propagation of chirality for glycine type
           do k=1,nsingle
             cosph1(k)=dcos(k*phii)
 ! propagation of chirality for glycine type
           do k=1,nsingle
             cosph1(k)=dcos(k*phii)
           enddo
         else
           phii=0.0d0
           enddo
         else
           phii=0.0d0
-          ityp1=ithetyp(itype(i-2))
+          ityp1=ithetyp(itype(i-2,1))
           do k=1,nsingle
             cosph1(k)=0.0d0
             sinph1(k)=0.0d0
           enddo 
         endif
           do k=1,nsingle
             cosph1(k)=0.0d0
             sinph1(k)=0.0d0
           enddo 
         endif
-        if (i.lt.nres .and. itype(i+1).ne.ntyp1) then
+        if (i.lt.nres .and. itype(i+1,1).ne.ntyp1) then
 #ifdef OSF
           phii1=phi(i+1)
           if (phii1.ne.phii1) phii1=150.0
 #ifdef OSF
           phii1=phi(i+1)
           if (phii1.ne.phii1) phii1=150.0
 #else
           phii1=phi(i+1)
 #endif
 #else
           phii1=phi(i+1)
 #endif
-          ityp3=ithetyp((itype(i)))
+          ityp3=ithetyp((itype(i,1)))
           do k=1,nsingle
             cosph2(k)=dcos(k*phii1)
             sinph2(k)=dsin(k*phii1)
           enddo
         else
           phii1=0.0d0
           do k=1,nsingle
             cosph2(k)=dcos(k*phii1)
             sinph2(k)=dsin(k*phii1)
           enddo
         else
           phii1=0.0d0
-          ityp3=ithetyp(itype(i))
+          ityp3=ithetyp(itype(i,1))
           do k=1,nsingle
             cosph2(k)=0.0d0
             sinph2(k)=0.0d0
           do k=1,nsingle
             cosph2(k)=0.0d0
             sinph2(k)=0.0d0
         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*dephii1
         gloc(nphi+i-2,icg)=wang*dethetai
       enddo
         if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*dephii1
         gloc(nphi+i-2,icg)=wang*dethetai
       enddo
+!-----------thete constrains
+!      if (tor_mode.ne.2) then
+      ethetacnstr=0.0d0
+!      print *,ithetaconstr_start,ithetaconstr_end,"TU"
+      do i=ithetaconstr_start,ithetaconstr_end
+        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
+       if (energy_dec) then
+        write (iout,'(a6,2i5,4f8.3,2e14.5)') "ethetc", &
+         i,itheta,rad2deg*thetiii, &
+         rad2deg*theta_constr0(i),  rad2deg*theta_drange(i), &
+         rad2deg*difi,0.25d0*for_thet_constr(i)*difi**4, &
+         gloc(itheta+nphi-2,icg)
+        endif
+      enddo
+!      endif
+
       return
       end subroutine ebend
 #endif
       return
       end subroutine ebend
 #endif
       escloc=0.0D0
 !     write (iout,'(a)') 'ESC'
       do i=loc_start,loc_end
       escloc=0.0D0
 !     write (iout,'(a)') 'ESC'
       do i=loc_start,loc_end
-        it=itype(i)
+        it=itype(i,1)
         if (it.eq.ntyp1) cycle
         if (it.eq.10) goto 1
         nlobit=nlob(iabs(it))
         if (it.eq.ntyp1) cycle
         if (it.eq.10) goto 1
         nlobit=nlob(iabs(it))
       delta=0.02d0*pi
       escloc=0.0D0
       do i=loc_start,loc_end
       delta=0.02d0*pi
       escloc=0.0D0
       do i=loc_start,loc_end
-        if (itype(i).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1) cycle
         costtab(i+1) =dcos(theta(i+1))
         sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
         cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
         costtab(i+1) =dcos(theta(i+1))
         sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
         cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
         cosfac=dsqrt(cosfac2)
         sinfac2=0.5d0/(1.0d0-costtab(i+1))
         sinfac=dsqrt(sinfac2)
         cosfac=dsqrt(cosfac2)
         sinfac2=0.5d0/(1.0d0-costtab(i+1))
         sinfac=dsqrt(sinfac2)
-        it=iabs(itype(i))
+        it=iabs(itype(i,1))
         if (it.eq.10) goto 1
 !
 !  Compute the axes of tghe local cartesian coordinates system; store in
         if (it.eq.10) goto 1
 !
 !  Compute the axes of tghe local cartesian coordinates system; store in
           y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
         enddo
         do j = 1,3
           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.0d0,dfloat(itype(i)))
+          z_prime(j) = -uz(j,i-1)*dsign(1.0d0,dfloat(itype(i,1)))
         enddo     
 !       write (2,*) "i",i
 !       write (2,*) "x_prime",(x_prime(j),j=1,3)
         enddo     
 !       write (2,*) "i",i
 !       write (2,*) "x_prime",(x_prime(j),j=1,3)
 ! Compute the energy of the ith side cbain
 !
 !        write (2,*) "xx",xx," yy",yy," zz",zz
 ! Compute the energy of the ith side cbain
 !
 !        write (2,*) "xx",xx," yy",yy," zz",zz
-        it=iabs(itype(i))
+        it=iabs(itype(i,1))
         do j = 1,65
           x(j) = sc_parmin(j,it) 
         enddo
         do j = 1,65
           x(j) = sc_parmin(j,it) 
         enddo
 !c diagnostics - remove later
         xx1 = dcos(alph(2))
         yy1 = dsin(alph(2))*dcos(omeg(2))
 !c diagnostics - remove later
         xx1 = dcos(alph(2))
         yy1 = dsin(alph(2))*dcos(omeg(2))
-        zz1 = -dsign(1.0,dfloat(itype(i)))*dsin(alph(2))*dsin(omeg(2))
+        zz1 = -dsign(1.0,dfloat(itype(i,1)))*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
         write(2,'(3f8.1,3f9.3,1x,3f9.3)') &
           alph(2)*rad2deg,omeg(2)*rad2deg,theta(3)*rad2deg,xx,yy,zz,&
           xx1,yy1,zz1
 !     &   dscp1,dscp2,sumene
 !        sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
         escloc = escloc + sumene
 !     &   dscp1,dscp2,sumene
 !        sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
         escloc = escloc + sumene
-!        write (2,*) "i",i," escloc",sumene,escloc,it,itype(i)
+!        write (2,*) "i",i," escloc",sumene,escloc,it,itype(i,1)
 !     & ,zz,xx,yy
 !#define DEBUG
 #ifdef DEBUG
 !     & ,zz,xx,yy
 !#define DEBUG
 #ifdef DEBUG
 !        
 ! Compute the gradient of esc
 !
 !        
 ! Compute the gradient of esc
 !
-!        zz=zz*dsign(1.0,dfloat(itype(i)))
+!        zz=zz*dsign(1.0,dfloat(itype(i,1)))
         pom_s1=(1.0d0+x(63))/(0.1d0 + dscp1)**2
         pom_s16=6*(1.0d0+x(64))/(0.1d0 + dscp1**6)**2
         pom_s2=(1.0d0+x(65))/(0.1d0 + dscp2)**2
         pom_s1=(1.0d0+x(63))/(0.1d0 + dscp1)**2
         pom_s16=6*(1.0d0+x(64))/(0.1d0 + dscp1**6)**2
         pom_s2=(1.0d0+x(65))/(0.1d0 + dscp2)**2
               +(sumene2x+sumene4x*cost2tab(i+1))*(s2+s2_6) &
               +(pom1+pom2)*pom_dx
 #ifdef DEBUG
               +(sumene2x+sumene4x*cost2tab(i+1))*(s2+s2_6) &
               +(pom1+pom2)*pom_dx
 #ifdef DEBUG
-        write(2,*), "de_dxx = ", de_dxx,de_dxx_num,itype(i)
+        write(2,*), "de_dxx = ", de_dxx,de_dxx_num,itype(i,1)
 #endif
 !
         sumene1y=x(3) + 2*x(6)*yy + x(9)*xx + x(10)*zz
 #endif
 !
         sumene1y=x(3) + 2*x(6)*yy + x(9)*xx + x(10)*zz
               +(sumene2y+sumene4y*cost2tab(i+1))*(s2+s2_6) &
               +(pom1-pom2)*pom_dy
 #ifdef DEBUG
               +(sumene2y+sumene4y*cost2tab(i+1))*(s2+s2_6) &
               +(pom1-pom2)*pom_dy
 #ifdef DEBUG
-        write(2,*), "de_dyy = ", de_dyy,de_dyy_num,itype(i)
+        write(2,*), "de_dyy = ", de_dyy,de_dyy_num,itype(i,1)
 #endif
 !
         de_dzz =(x(24) +2*x(27)*zz +x(28)*xx +x(30)*yy &
 #endif
 !
         de_dzz =(x(24) +2*x(27)*zz +x(28)*xx +x(30)*yy &
         +x(60)*xx*yy)*cost2tab(i+1)*(s2+s2_6) &
         + ( x(14) + 2*x(17)*zz+  x(18)*xx + x(20)*yy)*(s2+s2_6)
 #ifdef DEBUG
         +x(60)*xx*yy)*cost2tab(i+1)*(s2+s2_6) &
         + ( x(14) + 2*x(17)*zz+  x(18)*xx + x(20)*yy)*(s2+s2_6)
 #ifdef DEBUG
-        write(2,*), "de_dzz = ", de_dzz,de_dzz_num,itype(i)
+        write(2,*), "de_dzz = ", de_dzz,de_dzz_num,itype(i,1)
 #endif
 !
         de_dt =  0.5d0*sumene3*cost2tab(i+1)*(s1+s1_6) &
         -0.5d0*sumene4*sint2tab(i+1)*(s2+s2_6) &
         +pom1*pom_dt1+pom2*pom_dt2
 #ifdef DEBUG
 #endif
 !
         de_dt =  0.5d0*sumene3*cost2tab(i+1)*(s1+s1_6) &
         -0.5d0*sumene4*sint2tab(i+1)*(s2+s2_6) &
         +pom1*pom_dt1+pom2*pom_dt2
 #ifdef DEBUG
-        write(2,*), "de_dt = ", de_dt,de_dt_num,itype(i)
+        write(2,*), "de_dt = ", de_dt,de_dt_num,itype(i,1)
 #endif
 ! 
 !
 #endif
 ! 
 !
          dZZ_Ci(k)=0.0d0
          do j=1,3
            dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1) &
          dZZ_Ci(k)=0.0d0
          do j=1,3
            dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1) &
-           *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
+           *dsign(1.0d0,dfloat(itype(i,1)))*dC_norm(j,i+nres)
            dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1) &
            dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1) &
-           *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
+           *dsign(1.0d0,dfloat(itype(i,1)))*dC_norm(j,i+nres)
          enddo
           
          dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
          enddo
           
          dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
       etors=0.0D0
       do i=iphi_start,iphi_end
       etors_ii=0.0D0
       etors=0.0D0
       do i=iphi_start,iphi_end
       etors_ii=0.0D0
-        if (itype(i-2).eq.ntyp1.or. itype(i-1).eq.ntyp1 &
-            .or. itype(i).eq.ntyp1) cycle
-        itori=itortyp(itype(i-2))
-        itori1=itortyp(itype(i-1))
+        if (itype(i-2,1).eq.ntyp1.or. itype(i-1,1).eq.ntyp1 &
+            .or. itype(i,1).eq.ntyp1) cycle
+        itori=itortyp(itype(i-2,1))
+        itori1=itortyp(itype(i-1,1))
         phii=phi(i)
         gloci=0.0D0
 ! Proline-Proline pair is a special case...
         phii=phi(i)
         gloci=0.0D0
 ! Proline-Proline pair is a special case...
              'etor',i,etors_ii
         if (lprn) &
         write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)') &
              'etor',i,etors_ii
         if (lprn) &
         write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)') &
-        restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,&
+        restyp(itype(i-2,1),1),i-2,restyp(itype(i-1,1),1),i-1,itori,itori1,&
         (v1(j,itori,itori1),j=1,6),(v2(j,itori,itori1),j=1,6)
         gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
 !       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
         (v1(j,itori,itori1),j=1,6),(v2(j,itori,itori1),j=1,6)
         gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
 !       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
         difi=phii-phi0(i)
         if (difi.gt.drange(i)) then
           difi=difi-drange(i)
         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)
         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)
         endif
 !        write (iout,'(2i5,2f8.3,2e14.5)') i,itori,rad2deg*phii,
 !     &    rad2deg*difi,0.25d0*ftors*difi**4,gloc(itori-3,icg)
 !     lprn=.true.
       etors=0.0D0
       do i=iphi_start,iphi_end
 !     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-3).eq.ntyp1 &
-             .or. itype(i).eq.ntyp1) cycle
+        if (itype(i-2,1).eq.ntyp1 .or. itype(i-1,1).eq.ntyp1 &
+             .or. itype(i-3,1).eq.ntyp1 &
+             .or. itype(i,1).eq.ntyp1) cycle
         etors_ii=0.0D0
         etors_ii=0.0D0
-         if (iabs(itype(i)).eq.20) then
+         if (iabs(itype(i,1)).eq.20) then
          iblock=2
          else
          iblock=1
          endif
          iblock=2
          else
          iblock=1
          endif
-        itori=itortyp(itype(i-2))
-        itori1=itortyp(itype(i-1))
+        itori=itortyp(itype(i-2,1))
+        itori1=itortyp(itype(i-1,1))
         phii=phi(i)
         gloci=0.0D0
 ! Regular cosine and sine terms
         phii=phi(i)
         gloci=0.0D0
 ! Regular cosine and sine terms
                'etor',i,etors_ii-v0(itori,itori1,iblock)
         if (lprn) &
         write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)') &
                'etor',i,etors_ii-v0(itori,itori1,iblock)
         if (lprn) &
         write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)') &
-        restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,&
+        restyp(itype(i-2,1),1),i-2,restyp(itype(i-1,1),1),i-1,itori,itori1,&
         (v1(j,itori,itori1,iblock),j=1,6),&
         (v2(j,itori,itori1,iblock),j=1,6)
         gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
         (v1(j,itori,itori1,iblock),j=1,6),&
         (v2(j,itori,itori1,iblock),j=1,6)
         gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
         difi=pinorm(phii-phi0(i))
         if (difi.gt.drange(i)) then
           difi=difi-drange(i)
         difi=pinorm(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)
         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
         else
           difi=0.0
         endif
         else
           difi=0.0
         endif
 !      write(iout,*) "a tu??"
       do i=iphid_start,iphid_end
         etors_d_ii=0.0D0
 !      write(iout,*) "a tu??"
       do i=iphid_start,iphid_end
         etors_d_ii=0.0D0
-        if (itype(i-2).eq.ntyp1 .or. itype(i-1).eq.ntyp1 &
-            .or. itype(i-3).eq.ntyp1 &
-            .or. itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
-        itori=itortyp(itype(i-2))
-        itori1=itortyp(itype(i-1))
-        itori2=itortyp(itype(i))
+        if (itype(i-2,1).eq.ntyp1 .or. itype(i-1,1).eq.ntyp1 &
+            .or. itype(i-3,1).eq.ntyp1 &
+            .or. itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) cycle
+        itori=itortyp(itype(i-2,1))
+        itori1=itortyp(itype(i-1,1))
+        itori2=itortyp(itype(i,1))
         phii=phi(i)
         phii1=phi(i+1)
         gloci1=0.0D0
         gloci2=0.0D0
         iblock=1
         phii=phi(i)
         phii1=phi(i+1)
         gloci1=0.0D0
         gloci2=0.0D0
         iblock=1
-        if (iabs(itype(i+1)).eq.20) iblock=2
+        if (iabs(itype(i+1,1)).eq.20) iblock=2
 
 ! Regular cosine and sine terms
         do j=1,ntermd_1(itori,itori1,itori2,iblock)
 
 ! Regular cosine and sine terms
         do j=1,ntermd_1(itori,itori1,itori2,iblock)
 !      write (iout,*) "EBACK_SC_COR",itau_start,itau_end
       esccor=0.0D0
       do i=itau_start,itau_end
 !      write (iout,*) "EBACK_SC_COR",itau_start,itau_end
       esccor=0.0D0
       do i=itau_start,itau_end
-        if ((itype(i-2).eq.ntyp1).or.(itype(i-1).eq.ntyp1)) cycle
+        if ((itype(i-2,1).eq.ntyp1).or.(itype(i-1,1).eq.ntyp1)) cycle
         esccor_ii=0.0D0
         esccor_ii=0.0D0
-        isccori=isccortyp(itype(i-2))
-        isccori1=isccortyp(itype(i-1))
+        isccori=isccortyp(itype(i-2,1))
+        isccori1=isccortyp(itype(i-1,1))
 
 !      write (iout,*) "EBACK_SC_COR",i,nterm_sccor(isccori,isccori1)
         phii=phi(i)
 
 !      write (iout,*) "EBACK_SC_COR",i,nterm_sccor(isccori,isccori1)
         phii=phi(i)
 !   2 = Ca...Ca...Ca...SC
 !   3 = SC...Ca...Ca...SCi
         gloci=0.0D0
 !   2 = Ca...Ca...Ca...SC
 !   3 = SC...Ca...Ca...SCi
         gloci=0.0D0
-        if (((intertyp.eq.3).and.((itype(i-2).eq.10).or. &
-            (itype(i-1).eq.10).or.(itype(i-2).eq.ntyp1).or. &
-            (itype(i-1).eq.ntyp1))) &
-          .or. ((intertyp.eq.1).and.((itype(i-2).eq.10) &
-           .or.(itype(i-2).eq.ntyp1).or.(itype(i-1).eq.ntyp1) &
-           .or.(itype(i).eq.ntyp1))) &
-          .or.((intertyp.eq.2).and.((itype(i-1).eq.10).or. &
-            (itype(i-1).eq.ntyp1).or.(itype(i-2).eq.ntyp1).or. &
-            (itype(i-3).eq.ntyp1)))) cycle
-        if ((intertyp.eq.2).and.(i.eq.4).and.(itype(1).eq.ntyp1)) cycle
-        if ((intertyp.eq.1).and.(i.eq.nres).and.(itype(nres).eq.ntyp1)) &
+        if (((intertyp.eq.3).and.((itype(i-2,1).eq.10).or. &
+            (itype(i-1,1).eq.10).or.(itype(i-2,1).eq.ntyp1).or. &
+            (itype(i-1,1).eq.ntyp1))) &
+          .or. ((intertyp.eq.1).and.((itype(i-2,1).eq.10) &
+           .or.(itype(i-2,1).eq.ntyp1).or.(itype(i-1,1).eq.ntyp1) &
+           .or.(itype(i,1).eq.ntyp1))) &
+          .or.((intertyp.eq.2).and.((itype(i-1,1).eq.10).or. &
+            (itype(i-1,1).eq.ntyp1).or.(itype(i-2,1).eq.ntyp1).or. &
+            (itype(i-3,1).eq.ntyp1)))) cycle
+        if ((intertyp.eq.2).and.(i.eq.4).and.(itype(1,1).eq.ntyp1)) cycle
+        if ((intertyp.eq.1).and.(i.eq.nres).and.(itype(nres,1).eq.ntyp1)) &
        cycle
        do j=1,nterm_sccor(isccori,isccori1)
           v1ij=v1sccor(j,intertyp,isccori,isccori1)
        cycle
        do j=1,nterm_sccor(isccori,isccori1)
           v1ij=v1sccor(j,intertyp,isccori,isccori1)
         gloc_sc(intertyp,i-3,icg)=gloc_sc(intertyp,i-3,icg)+wsccor*gloci
         if (lprn) &
         write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)') &
         gloc_sc(intertyp,i-3,icg)=gloc_sc(intertyp,i-3,icg)+wsccor*gloci
         if (lprn) &
         write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)') &
-        restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,isccori,isccori1,&
+        restyp(itype(i-2,1),1),i-2,restyp(itype(i-1,1),1),i-1,isccori,isccori1,&
         (v1sccor(j,intertyp,isccori,isccori1),j=1,6),&
         (v2sccor(j,intertyp,isccori,isccori1),j=1,6)
         gsccor_loc(i-3)=gsccor_loc(i-3)+gloci
         (v1sccor(j,intertyp,isccori,isccori1),j=1,6),&
         (v2sccor(j,intertyp,isccori,isccori1),j=1,6)
         gsccor_loc(i-3)=gsccor_loc(i-3)+gloci
       allocate(dipderx(3,5,4,maxconts,nres))
 !
 
       allocate(dipderx(3,5,4,maxconts,nres))
 !
 
-      iti1 = itortyp(itype(i+1))
+      iti1 = itortyp(itype(i+1,1))
       if (j.lt.nres-1) then
       if (j.lt.nres-1) then
-        itj1 = itortyp(itype(j+1))
+        itj1 = itortyp(itype(j+1,1))
       else
         itj1=ntortyp+1
       endif
       else
         itj1=ntortyp+1
       endif
       if (l.eq.j+1) then
 ! parallel orientation of the two CA-CA-CA frames.
         if (i.gt.1) then
       if (l.eq.j+1) then
 ! parallel orientation of the two CA-CA-CA frames.
         if (i.gt.1) then
-          iti=itortyp(itype(i))
+          iti=itortyp(itype(i,1))
         else
           iti=ntortyp+1
         endif
         else
           iti=ntortyp+1
         endif
-        itk1=itortyp(itype(k+1))
-        itj=itortyp(itype(j))
+        itk1=itortyp(itype(k+1,1))
+        itj=itortyp(itype(j,1))
         if (l.lt.nres-1) then
         if (l.lt.nres-1) then
-          itl1=itortyp(itype(l+1))
+          itl1=itortyp(itype(l+1,1))
         else
           itl1=ntortyp+1
         endif
         else
           itl1=ntortyp+1
         endif
       else
 ! Antiparallel orientation of the two CA-CA-CA frames.
         if (i.gt.1) then
       else
 ! Antiparallel orientation of the two CA-CA-CA frames.
         if (i.gt.1) then
-          iti=itortyp(itype(i))
+          iti=itortyp(itype(i,1))
         else
           iti=ntortyp+1
         endif
         else
           iti=ntortyp+1
         endif
-        itk1=itortyp(itype(k+1))
-        itl=itortyp(itype(l))
-        itj=itortyp(itype(j))
+        itk1=itortyp(itype(k+1,1))
+        itl=itortyp(itype(l,1))
+        itj=itortyp(itype(j,1))
         if (j.lt.nres-1) then
         if (j.lt.nres-1) then
-          itj1=itortyp(itype(j+1))
+          itj1=itortyp(itype(j+1,1))
         else 
           itj1=ntortyp+1
         endif
         else 
           itj1=ntortyp+1
         endif
 !          o             o                   o             o                   C
 !         /l\           / \             \   / \           / \   /              C
 !        /   \         /   \             \ /   \         /   \ /               C
 !          o             o                   o             o                   C
 !         /l\           / \             \   / \           / \   /              C
 !        /   \         /   \             \ /   \         /   \ /               C
-!       j| o |l1       | o |             o| o |         | o |o                C
+!       j| o |l1       | o |                o| o |         | o |o                C
 !     \  |/k\|         |/ \|  /            |/ \|         |/ \|                 C
 !      \i/   \         /   \ /             /   \         /   \                 C
 !       o    k1             o                                                  C
 !     \  |/k\|         |/ \|  /            |/ \|         |/ \|                 C
 !      \i/   \         /   \ /             /   \         /   \                 C
 !       o    k1             o                                                  C
 !          o             o                   o             o                   C
 !         /j\           / \             \   / \           / \   /              C
 !        /   \         /   \             \ /   \         /   \ /               C
 !          o             o                   o             o                   C
 !         /j\           / \             \   / \           / \   /              C
 !        /   \         /   \             \ /   \         /   \ /               C
-!      j1| o |l        | o |             o| o |         | o |o                C
+!      j1| o |l        | o |                o| o |         | o |o                C
 !     \  |/k\|         |/ \|  /            |/ \|         |/ \|                 C
 !      \i/   \         /   \ /             /   \         /   \                 C
 !       o     k1            o                                                  C
 !     \  |/k\|         |/ \|  /            |/ \|         |/ \|                 C
 !      \i/   \         /   \ /             /   \         /   \                 C
 !       o     k1            o                                                  C
 !d      write (iout,*)
 !d     &   'EELLO5: Contacts have occurred for peptide groups',i,j,
 !d     &   ' and',k,l
 !d      write (iout,*)
 !d     &   'EELLO5: Contacts have occurred for peptide groups',i,j,
 !d     &   ' and',k,l
-      itk=itortyp(itype(k))
-      itl=itortyp(itype(l))
-      itj=itortyp(itype(j))
+      itk=itortyp(itype(k,1))
+      itl=itortyp(itype(l,1))
+      itj=itortyp(itype(j,1))
       eello5_1=0.0d0
       eello5_2=0.0d0
       eello5_3=0.0d0
       eello5_1=0.0d0
       eello5_2=0.0d0
       eello5_3=0.0d0
 !       i             i                                                        C
 !                                                                              C
 !CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
 !       i             i                                                        C
 !                                                                              C
 !CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
-      itk=itortyp(itype(k))
+      itk=itortyp(itype(k,1))
       s1= scalar2(AEAb1(1,2,imat),CUgb2(1,i))
       s2=-scalar2(AEAb2(1,1,imat),Ug2Db1t(1,k))
       s3= scalar2(AEAb2(1,1,imat),CUgb2(1,k))
       s1= scalar2(AEAb1(1,2,imat),CUgb2(1,i))
       s2=-scalar2(AEAb2(1,1,imat),Ug2Db1t(1,k))
       s3= scalar2(AEAb2(1,1,imat),CUgb2(1,k))
 !
 ! 4/7/01 AL Component s1 was removed, because it pertains to the respective 
 !           energy moment and not to the cluster cumulant.
 !
 ! 4/7/01 AL Component s1 was removed, because it pertains to the respective 
 !           energy moment and not to the cluster cumulant.
-      iti=itortyp(itype(i))
+      iti=itortyp(itype(i,1))
       if (j.lt.nres-1) then
       if (j.lt.nres-1) then
-        itj1=itortyp(itype(j+1))
+        itj1=itortyp(itype(j+1,1))
       else
         itj1=ntortyp+1
       endif
       else
         itj1=ntortyp+1
       endif
-      itk=itortyp(itype(k))
-      itk1=itortyp(itype(k+1))
+      itk=itortyp(itype(k,1))
+      itk1=itortyp(itype(k+1,1))
       if (l.lt.nres-1) then
       if (l.lt.nres-1) then
-        itl1=itortyp(itype(l+1))
+        itl1=itortyp(itype(l+1,1))
       else
         itl1=ntortyp+1
       endif
       else
         itl1=ntortyp+1
       endif
 ! 4/7/01 AL Component s1 was removed, because it pertains to the respective 
 !           energy moment and not to the cluster cumulant.
 !d      write (2,*) 'eello_graph4: wturn6',wturn6
 ! 4/7/01 AL Component s1 was removed, because it pertains to the respective 
 !           energy moment and not to the cluster cumulant.
 !d      write (2,*) 'eello_graph4: wturn6',wturn6
-      iti=itortyp(itype(i))
-      itj=itortyp(itype(j))
+      iti=itortyp(itype(i,1))
+      itj=itortyp(itype(j,1))
       if (j.lt.nres-1) then
       if (j.lt.nres-1) then
-        itj1=itortyp(itype(j+1))
+        itj1=itortyp(itype(j+1,1))
       else
         itj1=ntortyp+1
       endif
       else
         itj1=ntortyp+1
       endif
-      itk=itortyp(itype(k))
+      itk=itortyp(itype(k,1))
       if (k.lt.nres-1) then
       if (k.lt.nres-1) then
-        itk1=itortyp(itype(k+1))
+        itk1=itortyp(itype(k+1,1))
       else
         itk1=ntortyp+1
       endif
       else
         itk1=ntortyp+1
       endif
-      itl=itortyp(itype(l))
+      itl=itortyp(itype(l,1))
       if (l.lt.nres-1) then
       if (l.lt.nres-1) then
-        itl1=itortyp(itype(l+1))
+        itl1=itortyp(itype(l+1,1))
       else
         itl1=ntortyp+1
       endif
       else
         itl1=ntortyp+1
       endif
       j=i+4
       k=i+1
       l=i+3
       j=i+4
       k=i+1
       l=i+3
-      iti=itortyp(itype(i))
-      itk=itortyp(itype(k))
-      itk1=itortyp(itype(k+1))
-      itl=itortyp(itype(l))
-      itj=itortyp(itype(j))
+      iti=itortyp(itype(i,1))
+      itk=itortyp(itype(k,1))
+      itk1=itortyp(itype(k+1,1))
+      itl=itortyp(itype(l,1))
+      itj=itortyp(itype(j,1))
 !d      write (2,*) 'itk',itk,' itk1',itk1,' itl',itl,' itj',itj
 !d      write (2,*) 'i',i,' k',k,' j',j,' l',l
 !d      if (i.ne.1 .or. j.ne.3 .or. k.ne.2 .or. l.ne.4) then
 !d      write (2,*) 'itk',itk,' itk1',itk1,' itl',itl,' itj',itj
 !d      write (2,*) 'i',i,' k',k,' j',j,' l',l
 !d      if (i.ne.1 .or. j.ne.3 .or. k.ne.2 .or. l.ne.4) then
                       wturn6*gcorr6_turn_long(j,i)+ &
                       wstrain*ghpbc(j,i) &
                      +wliptran*gliptranc(j,i) &
                       wturn6*gcorr6_turn_long(j,i)+ &
                       wstrain*ghpbc(j,i) &
                      +wliptran*gliptranc(j,i) &
+                     +gradafm(j,i) &
                      +welec*gshieldc(j,i) &
                      +wcorr*gshieldc_ec(j,i) &
                      +wturn3*gshieldc_t3(j,i)&
                      +wturn4*gshieldc_t4(j,i)&
                      +welec*gshieldc(j,i) &
                      +wcorr*gshieldc_ec(j,i) &
                      +wturn3*gshieldc_t3(j,i)&
                      +wturn4*gshieldc_t4(j,i)&
-                     +wel_loc*gshieldc_ll(j,i) 
+                     +wel_loc*gshieldc_ll(j,i)&
+                     +wtube*gg_tube(j,i) &
+                     +wvdwpp_nucl*gvdwpp_nucl(j,i)+welpp*gelpp(j,i)+ &
+                     wvdwpsb*(gvdwpsb(j,i)+gvdwpsb1(j,i))+ &
+                     wvdwsb*gvdwsbc(j,i)+welsb*gelsbc(j,i)+ &
+                     wcorr_nucl*gradcorr_nucl(j,i)&
+                     +wcorr3_nucl*gradcorr3_nucl(j,i)+&
+                     wcatprot* gradpepcat(j,i)+ &
+                     wcatcat*gradcatcat(j,i)+   &
+                     wscbase*gvdwc_scbase(j,i)+ &
+                     wpepbase*gvdwc_pepbase(j,i)+&
+                     wscpho*gvdwc_scpho(j,i)+   &
+                     wpeppho*gvdwc_peppho(j,i)
+
+
+
 
 
         enddo
 
 
         enddo
                       wturn6*gcorr6_turn_long(j,i)+ &
                       wstrain*ghpbc(j,i) &
                      +wliptran*gliptranc(j,i) &
                       wturn6*gcorr6_turn_long(j,i)+ &
                       wstrain*ghpbc(j,i) &
                      +wliptran*gliptranc(j,i) &
+                     +gradafm(j,i) &
                      +welec*gshieldc(j,i)&
                      +wcorr*gshieldc_ec(j,i) &
                      +wturn4*gshieldc_t4(j,i) &
                      +welec*gshieldc(j,i)&
                      +wcorr*gshieldc_ec(j,i) &
                      +wturn4*gshieldc_t4(j,i) &
-                     +wel_loc*gshieldc_ll(j,i)
+                     +wel_loc*gshieldc_ll(j,i)&
+                     +wtube*gg_tube(j,i) &
+                     +wvdwpp_nucl*gvdwpp_nucl(j,i)+welpp*gelpp(j,i)+ &
+                     wvdwpsb*(gvdwpsb(j,i)+gvdwpsb1(j,i))+ &
+                     wvdwsb*gvdwsbc(j,i)+welsb*gelsbc(j,i)+ &
+                     wcorr_nucl*gradcorr_nucl(j,i) &
+                     +wcorr3_nucl*gradcorr3_nucl(j,i) +&
+                     wcatprot* gradpepcat(j,i)+ &
+                     wcatcat*gradcatcat(j,i)+   &
+                     wscbase*gvdwc_scbase(j,i)  &
+                     wpepbase*gvdwc_pepbase(j,i)+&
+                     wscpho*gvdwc_scpho(j,i)+&
+                     wpeppho*gvdwc_peppho(j,i)
 
 
         enddo
 
 
         enddo
                       wsccor*gsccorc(j,i) &
                      +wscloc*gscloc(j,i)  &
                      +wliptran*gliptranc(j,i) &
                       wsccor*gsccorc(j,i) &
                      +wscloc*gscloc(j,i)  &
                      +wliptran*gliptranc(j,i) &
+                     +gradafm(j,i) &
                      +welec*gshieldc(j,i) &
                      +welec*gshieldc_loc(j,i) &
                      +wcorr*gshieldc_ec(j,i) &
                      +welec*gshieldc(j,i) &
                      +welec*gshieldc_loc(j,i) &
                      +wcorr*gshieldc_ec(j,i) &
                      +wturn4*gshieldc_t4(j,i) &
                      +wturn4*gshieldc_loc_t4(j,i) &
                      +wel_loc*gshieldc_ll(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) 
+                     +wel_loc*gshieldc_loc_ll(j,i) &
+                     +wtube*gg_tube(j,i) &
+                     +0.5d0*(wvdwpp_nucl*gvdwpp_nucl(j,i)+welpp*gelpp(j,i)&
+                     +wvdwpsb*gvdwpsb1(j,i))&
+                     +wbond_nucl*gradb_nucl(j,i)+wsbloc*gsbloc(j,i)
+
+!                 if ((i.le.2).and.(i.ge.1))
+!                       print *,gradc(j,i,icg),&
+!                      gradbufc(j,i),welec*gelc(j,i), &
+!                      wel_loc*gel_loc(j,i), &
+!                      wscp*gvdwc_scpp(j,i), &
+!                      welec*gelc_long(j,i),wvdwpp*gvdwpp(j,i), &
+!                      wel_loc*gel_loc_long(j,i), &
+!                      wcorr*gradcorr_long(j,i), &
+!                      wcorr5*gradcorr5_long(j,i), &
+!                      wcorr6*gradcorr6_long(j,i), &
+!                      wturn6*gcorr6_turn_long(j,i), &
+!                      wbond*gradb(j,i), &
+!                      wcorr*gradcorr(j,i), &
+!                      wturn3*gcorr3_turn(j,i), &
+!                      wturn4*gcorr4_turn(j,i), &
+!                      wcorr5*gradcorr5(j,i), &
+!                      wcorr6*gradcorr6(j,i), &
+!                      wturn6*gcorr6_turn(j,i), &
+!                      wsccor*gsccorc(j,i) &
+!                     ,wscloc*gscloc(j,i)  &
+!                     ,wliptran*gliptranc(j,i) &
+!                    ,gradafm(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) &
+!                     ,wbond_nucl*gradb_nucl(j,i) &
+!                     ,wvdwpp_nucl*gvdwpp_nucl(j,i),welpp*gelpp(j,i),&
+!                     wvdwpsb*gvdwpsb1(j,i)&
+!                     ,wbond_nucl*gradb_nucl(j,i),wsbloc*gsbloc(j,i)
+!
 
 #else
           gradc(j,i,icg)=gradbufc(j,i)+welec*gelc(j,i)+ &
 
 #else
           gradc(j,i,icg)=gradbufc(j,i)+welec*gelc(j,i)+ &
                       wturn6*gcorr6_turn(j,i)+ &
                       wsccor*gsccorc(j,i) &
                      +wscloc*gscloc(j,i) &
                       wturn6*gcorr6_turn(j,i)+ &
                       wsccor*gsccorc(j,i) &
                      +wscloc*gscloc(j,i) &
+                     +gradafm(j,i) &
                      +wliptran*gliptranc(j,i) &
                      +welec*gshieldc(j,i) &
                      +welec*gshieldc_loc(j,) &
                      +wliptran*gliptranc(j,i) &
                      +welec*gshieldc(j,i) &
                      +welec*gshieldc_loc(j,) &
                      +wturn4*gshieldc_t4(j,i) &
                      +wturn4*gshieldc_loc_t4(j,i) &
                      +wel_loc*gshieldc_ll(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) 
+                     +wel_loc*gshieldc_loc_ll(j,i) &
+                     +wtube*gg_tube(j,i) &
+                     +wbond_nucl*gradb_nucl(j,i) &
+                     +0.5d0*(wvdwpp_nucl*gvdwpp_nucl(j,i)+welpp*gelpp(j,i)&
+                     +wvdwpsb*gvdwpsb1(j,i))&
+                     +wsbloc*gsbloc(j,i)
+
+
 
 
 #endif
 
 
 #endif
                        +wcorr*gshieldx_ec(j,i)  &
                        +wturn3*gshieldx_t3(j,i) &
                        +wturn4*gshieldx_t4(j,i) &
                        +wcorr*gshieldx_ec(j,i)  &
                        +wturn3*gshieldx_t3(j,i) &
                        +wturn4*gshieldx_t4(j,i) &
-                       +wel_loc*gshieldx_ll(j,i)
+                       +wel_loc*gshieldx_ll(j,i)&
+                       +wtube*gg_tube_sc(j,i)   &
+                       +wbond_nucl*gradbx_nucl(j,i) &
+                       +wvdwsb*gvdwsbx(j,i) &
+                       +welsb*gelsbx(j,i) &
+                       +wcorr_nucl*gradxorr_nucl(j,i)&
+                       +wcorr3_nucl*gradxorr3_nucl(j,i) &
+                       +wsbloc*gsblocx(j,i) &
+                       +wcatprot* gradpepcatx(j,i)&
+                       +wscbase*gvdwx_scbase(j,i) &
+                       +wpepbase*gvdwx_pepbase(j,i)&
+                       +wscpho*gvdwx_scpho(j,i)
+!              if (i.eq.3) print *,"tu?", wscpho,gvdwx_scpho(j,i)
 
         enddo
       enddo 
 
         enddo
       enddo 
 #ifdef MPI
       if (nfgtasks.gt.1) then
         do j=1,3
 #ifdef MPI
       if (nfgtasks.gt.1) then
         do j=1,3
-          do i=1,nres
+          do i=0,nres
             gradbufc(j,i)=gradc(j,i,icg)
             gradbufx(j,i)=gradx(j,i,icg)
           enddo
             gradbufc(j,i)=gradc(j,i,icg)
             gradbufx(j,i)=gradx(j,i,icg)
           enddo
         call MPI_Barrier(FG_COMM,IERR)
         time_barrier_g=time_barrier_g+MPI_Wtime()-time00
         time00=MPI_Wtime()
         call MPI_Barrier(FG_COMM,IERR)
         time_barrier_g=time_barrier_g+MPI_Wtime()-time00
         time00=MPI_Wtime()
-        call MPI_Reduce(gradbufc(1,1),gradc(1,1,icg),3*nres,&
+        call MPI_Reduce(gradbufc(1,0),gradc(1,0,icg),3*nres+3,&
           MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
           MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
-        call MPI_Reduce(gradbufx(1,1),gradx(1,1,icg),3*nres,&
+        call MPI_Reduce(gradbufx(1,0),gradx(1,0,icg),3*nres+3,&
           MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
         call MPI_Reduce(glocbuf(1),gloc(1,icg),4*nres,&
           MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
           MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
         call MPI_Reduce(glocbuf(1),gloc(1,icg),4*nres,&
           MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
           MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
         time_reduce=time_reduce+MPI_Wtime()-time00
 !#define DEBUG
           MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
         time_reduce=time_reduce+MPI_Wtime()-time00
 !#define DEBUG
+!          print *,"gradbuf",gradbufc(1,1),gradc(1,1,icg)
 #ifdef DEBUG
       write (iout,*) "gloc_sc after reduce"
       do i=1,nres
 #ifdef DEBUG
       write (iout,*) "gloc_sc after reduce"
       do i=1,nres
 !      include 'COMMON.CALC'
 !      include 'COMMON.IOUNITS'
       real(kind=8), dimension(3) :: dcosom1,dcosom2
 !      include 'COMMON.CALC'
 !      include 'COMMON.IOUNITS'
       real(kind=8), dimension(3) :: dcosom1,dcosom2
-
+!      print *,"wchodze"
       eom1=eps2der*eps2rt_om1-2.0D0*alf1*eps3der+sigder*sigsq_om1
       eom2=eps2der*eps2rt_om2+2.0D0*alf2*eps3der+sigder*sigsq_om2
       eom12=evdwij*eps1_om12+eps2der*eps2rt_om12 &
       eom1=eps2der*eps2rt_om1-2.0D0*alf1*eps3der+sigder*sigsq_om1
       eom2=eps2der*eps2rt_om2+2.0D0*alf2*eps3der+sigder*sigsq_om2
       eom12=evdwij*eps1_om12+eps2der*eps2rt_om12 &
       do k=1,3
         gg(k)=(gg(k)+eom1*dcosom1(k)+eom2*dcosom2(k))*sss_ele_cut
 !C      print *,'gg',k,gg(k)
       do k=1,3
         gg(k)=(gg(k)+eom1*dcosom1(k)+eom2*dcosom2(k))*sss_ele_cut
 !C      print *,'gg',k,gg(k)
-      enddo 
+       enddo 
+!       print *,i,j,gg_lipi(3),gg_lipj(3),sss_ele_cut
 !      write (iout,*) "gg",(gg(k),k=1,3)
       do k=1,3
         gvdwx(k,i)=gvdwx(k,i)-gg(k) +gg_lipi(k)&
 !      write (iout,*) "gg",(gg(k),k=1,3)
       do k=1,3
         gvdwx(k,i)=gvdwx(k,i)-gg(k) +gg_lipi(k)&
 !
       ind1=0
       do i=1,nres-2
 !
       ind1=0
       do i=1,nres-2
-       ind1=ind1+1
+      ind1=ind1+1
 !
 ! Derivatives of DC(i+1) in theta(i+2)
 !
 !
 ! Derivatives of DC(i+1) in theta(i+2)
 !
 ! theta(nres) and phi(i+3) thru phi(nres).
 !
         do j=i+1,nres-2
 ! theta(nres) and phi(i+3) thru phi(nres).
 !
         do j=i+1,nres-2
-         ind1=ind1+1
-         ind=indmat(i+1,j+1)
+        ind1=ind1+1
+        ind=indmat(i+1,j+1)
 !d        print *,'i=',i,' j=',j,' ind=',ind,' ind1=',ind1
           do k=1,3
             do l=1,3
 !d        print *,'i=',i,' j=',j,' ind=',ind,' ind1=',ind1
           do k=1,3
             do l=1,3
           enddo
           do k=1,3
             dcdv(k+3,ind1)=vbld(i+1)*temp(k,1)
           enddo
           do k=1,3
             dcdv(k+3,ind1)=vbld(i+1)*temp(k,1)
-         enddo
+        enddo
           do k=1,3
             dxoijk=0.0D0
             do l=1,3
           do k=1,3
             dxoijk=0.0D0
             do l=1,3
 ! Derivatives in alpha and omega:
 !
       do i=2,nres-1
 ! Derivatives in alpha and omega:
 !
       do i=2,nres-1
-!       dsci=dsc(itype(i))
+!       dsci=dsc(itype(i,1))
         dsci=vbld(i+nres)
 #ifdef OSF
         alphi=alph(i)
         dsci=vbld(i+nres)
 #ifdef OSF
         alphi=alph(i)
         if(alphi.ne.alphi) alphi=100.0 
         if(omegi.ne.omegi) omegi=-100.0
 #else
         if(alphi.ne.alphi) alphi=100.0 
         if(omegi.ne.omegi) omegi=-100.0
 #else
-       alphi=alph(i)
-       omegi=omeg(i)
+      alphi=alph(i)
+      omegi=omeg(i)
 #endif
 !d      print *,'i=',i,' dsci=',dsci,' alphi=',alphi,' omegi=',omegi
 #endif
 !d      print *,'i=',i,' dsci=',dsci,' alphi=',alphi,' omegi=',omegi
-       cosalphi=dcos(alphi)
-       sinalphi=dsin(alphi)
-       cosomegi=dcos(omegi)
-       sinomegi=dsin(omegi)
-       temp(1,1)=-dsci*sinalphi
-       temp(2,1)= dsci*cosalphi*cosomegi
-       temp(3,1)=-dsci*cosalphi*sinomegi
-       temp(1,2)=0.0D0
-       temp(2,2)=-dsci*sinalphi*sinomegi
-       temp(3,2)=-dsci*sinalphi*cosomegi
-       theta2=pi-0.5D0*theta(i+1)
-       cost2=dcos(theta2)
-       sint2=dsin(theta2)
-       jjj=0
+      cosalphi=dcos(alphi)
+      sinalphi=dsin(alphi)
+      cosomegi=dcos(omegi)
+      sinomegi=dsin(omegi)
+      temp(1,1)=-dsci*sinalphi
+      temp(2,1)= dsci*cosalphi*cosomegi
+      temp(3,1)=-dsci*cosalphi*sinomegi
+      temp(1,2)=0.0D0
+      temp(2,2)=-dsci*sinalphi*sinomegi
+      temp(3,2)=-dsci*sinalphi*cosomegi
+      theta2=pi-0.5D0*theta(i+1)
+      cost2=dcos(theta2)
+      sint2=dsin(theta2)
+      jjj=0
 !d      print *,((temp(l,k),l=1,3),k=1,2)
         do j=1,2
 !d      print *,((temp(l,k),l=1,3),k=1,2)
         do j=1,2
-         xp=temp(1,j)
-         yp=temp(2,j)
-         xxp= xp*cost2+yp*sint2
-         yyp=-xp*sint2+yp*cost2
-         zzp=temp(3,j)
-         xx(1)=xxp
-         xx(2)=yyp*r(2,2,i-1)+zzp*r(2,3,i-1)
-         xx(3)=yyp*r(3,2,i-1)+zzp*r(3,3,i-1)
-         do k=1,3
-           dj=0.0D0
-           do l=1,3
-             dj=dj+prod(k,l,i-1)*xx(l)
+        xp=temp(1,j)
+        yp=temp(2,j)
+        xxp= xp*cost2+yp*sint2
+        yyp=-xp*sint2+yp*cost2
+        zzp=temp(3,j)
+        xx(1)=xxp
+        xx(2)=yyp*r(2,2,i-1)+zzp*r(2,3,i-1)
+        xx(3)=yyp*r(3,2,i-1)+zzp*r(3,3,i-1)
+        do k=1,3
+          dj=0.0D0
+          do l=1,3
+            dj=dj+prod(k,l,i-1)*xx(l)
             enddo
             enddo
-           dxds(jjj+k,i)=dj
+          dxds(jjj+k,i)=dj
           enddo
           enddo
-         jjj=jjj+3
-       enddo
+        jjj=jjj+3
+      enddo
       enddo
       return
       end subroutine cartder
       enddo
       return
       end subroutine cartder
       write (iout,'(a)') '**************** dx/dalpha'
       write (iout,'(a)')
       do i=2,nres-1
       write (iout,'(a)') '**************** dx/dalpha'
       write (iout,'(a)')
       do i=2,nres-1
-       alphi=alph(i)
-       alph(i)=alph(i)+aincr
-       do k=1,3
-         temp(k,i)=dc(k,nres+i)
+      alphi=alph(i)
+      alph(i)=alph(i)+aincr
+      do k=1,3
+        temp(k,i)=dc(k,nres+i)
         enddo
         enddo
-       call chainbuild
-       do k=1,3
-         gg(k)=(dc(k,nres+i)-temp(k,i))/aincr
-         xx(k)=dabs((gg(k)-dxds(k,i))/(aincr*dabs(dxds(k,i))+aincr))
+      call chainbuild
+      do k=1,3
+        gg(k)=(dc(k,nres+i)-temp(k,i))/aincr
+        xx(k)=dabs((gg(k)-dxds(k,i))/(aincr*dabs(dxds(k,i))+aincr))
         enddo
         write (iout,'(i4,3e15.6/4x,3e15.6,3f9.3)') &
         i,(gg(k),k=1,3),(dxds(k,i),k=1,3),(xx(k),k=1,3)
         write (iout,'(a)')
         enddo
         write (iout,'(i4,3e15.6/4x,3e15.6,3f9.3)') &
         i,(gg(k),k=1,3),(dxds(k,i),k=1,3),(xx(k),k=1,3)
         write (iout,'(a)')
-       alph(i)=alphi
-       call chainbuild
+      alph(i)=alphi
+      call chainbuild
       enddo
       write (iout,'(a)')
       write (iout,'(a)') '**************** dx/domega'
       write (iout,'(a)')
       do i=2,nres-1
       enddo
       write (iout,'(a)')
       write (iout,'(a)') '**************** dx/domega'
       write (iout,'(a)')
       do i=2,nres-1
-       omegi=omeg(i)
-       omeg(i)=omeg(i)+aincr
-       do k=1,3
-         temp(k,i)=dc(k,nres+i)
+      omegi=omeg(i)
+      omeg(i)=omeg(i)+aincr
+      do k=1,3
+        temp(k,i)=dc(k,nres+i)
         enddo
         enddo
-       call chainbuild
-       do k=1,3
+      call chainbuild
+      do k=1,3
           gg(k)=(dc(k,nres+i)-temp(k,i))/aincr
           xx(k)=dabs((gg(k)-dxds(k+3,i))/ &
                 (aincr*dabs(dxds(k+3,i))+aincr))
           gg(k)=(dc(k,nres+i)-temp(k,i))/aincr
           xx(k)=dabs((gg(k)-dxds(k+3,i))/ &
                 (aincr*dabs(dxds(k+3,i))+aincr))
         write (iout,'(i4,3e15.6/4x,3e15.6,3f9.3)') &
             i,(gg(k),k=1,3),(dxds(k+3,i),k=1,3),(xx(k),k=1,3)
         write (iout,'(a)')
         write (iout,'(i4,3e15.6/4x,3e15.6,3f9.3)') &
             i,(gg(k),k=1,3),(dxds(k+3,i),k=1,3),(xx(k),k=1,3)
         write (iout,'(a)')
-       omeg(i)=omegi
-       call chainbuild
+      omeg(i)=omegi
+      call chainbuild
       enddo
       write (iout,'(a)')
       write (iout,'(a)') '**************** dx/dtheta'
       write (iout,'(a)')
       do i=3,nres
       enddo
       write (iout,'(a)')
       write (iout,'(a)') '**************** dx/dtheta'
       write (iout,'(a)')
       do i=3,nres
-       theti=theta(i)
+      theti=theta(i)
         theta(i)=theta(i)+aincr
         do j=i-1,nres-1
           do k=1,3
         theta(i)=theta(i)+aincr
         do j=i-1,nres-1
           do k=1,3
         enddo
         call chainbuild
         do j=i-1,nres-1
         enddo
         call chainbuild
         do j=i-1,nres-1
-         ii = indmat(i-2,j)
+        ii = indmat(i-2,j)
 !         print *,'i=',i-2,' j=',j-1,' ii=',ii
 !         print *,'i=',i-2,' j=',j-1,' ii=',ii
-         do k=1,3
-           gg(k)=(dc(k,nres+j)-temp(k,j))/aincr
-           xx(k)=dabs((gg(k)-dxdv(k,ii))/ &
+        do k=1,3
+          gg(k)=(dc(k,nres+j)-temp(k,j))/aincr
+          xx(k)=dabs((gg(k)-dxdv(k,ii))/ &
                   (aincr*dabs(dxdv(k,ii))+aincr))
           enddo
           write (iout,'(2i4,3e14.6/8x,3e14.6,3f9.3)') &
                   (aincr*dabs(dxdv(k,ii))+aincr))
           enddo
           write (iout,'(2i4,3e14.6/8x,3e14.6,3f9.3)') &
         enddo
         call chainbuild
         do j=i-1,nres-1
         enddo
         call chainbuild
         do j=i-1,nres-1
-         ii = indmat(i-2,j)
+        ii = indmat(i-2,j)
 !         print *,'ii=',ii
 !         print *,'ii=',ii
-         do k=1,3
-           gg(k)=(dc(k,nres+j)-temp(k,j))/aincr
+        do k=1,3
+          gg(k)=(dc(k,nres+j)-temp(k,j))/aincr
             xx(k)=dabs((gg(k)-dxdv(k+3,ii))/ &
                   (aincr*dabs(dxdv(k+3,ii))+aincr))
           enddo
             xx(k)=dabs((gg(k)-dxdv(k+3,ii))/ &
                   (aincr*dabs(dxdv(k+3,ii))+aincr))
           enddo
         enddo
         call chainbuild 
         do j=i+1,nres-1
         enddo
         call chainbuild 
         do j=i+1,nres-1
-         ii = indmat(i,j)
+        ii = indmat(i,j)
 !         print *,'ii=',ii
 !         print *,'ii=',ii
-         do k=1,3
-           gg(k)=(dc(k,j)-temp(k,j))/aincr
-           xx(k)=dabs((gg(k)-dcdv(k,ii))/ &
+        do k=1,3
+          gg(k)=(dc(k,j)-temp(k,j))/aincr
+          xx(k)=dabs((gg(k)-dcdv(k,ii))/ &
                  (aincr*dabs(dcdv(k,ii))+aincr))
           enddo
           write (iout,'(2i4,3e14.6/8x,3e14.6,3f9.3)') &
                  i,j,(gg(k),k=1,3),(dcdv(k,ii),k=1,3),(xx(k),k=1,3)
                  (aincr*dabs(dcdv(k,ii))+aincr))
           enddo
           write (iout,'(2i4,3e14.6/8x,3e14.6,3f9.3)') &
                  i,j,(gg(k),k=1,3),(dcdv(k,ii),k=1,3),(xx(k),k=1,3)
-         write (iout,'(a)')
+        write (iout,'(a)')
         enddo
         do j=1,nres
           do k=1,3
         enddo
         do j=1,nres
           do k=1,3
         enddo
         call chainbuild 
         do j=i+2,nres-1
         enddo
         call chainbuild 
         do j=i+2,nres-1
-         ii = indmat(i+1,j)
+        ii = indmat(i+1,j)
 !         print *,'ii=',ii
 !         print *,'ii=',ii
-         do k=1,3
-           gg(k)=(dc(k,j)-temp(k,j))/aincr
+        do k=1,3
+          gg(k)=(dc(k,j)-temp(k,j))/aincr
             xx(k)=dabs((gg(k)-dcdv(k+3,ii))/ &
                  (aincr*dabs(dcdv(k+3,ii))+aincr))
           enddo
           write (iout,'(2i4,3e14.6/8x,3e14.6,3f9.3)') &
                i,j,(gg(k),k=1,3),(dcdv(k+3,ii),k=1,3),(xx(k),k=1,3)
             xx(k)=dabs((gg(k)-dcdv(k+3,ii))/ &
                  (aincr*dabs(dcdv(k+3,ii))+aincr))
           enddo
           write (iout,'(2i4,3e14.6/8x,3e14.6,3f9.3)') &
                i,j,(gg(k),k=1,3),(dcdv(k+3,ii),k=1,3),(xx(k),k=1,3)
-         write (iout,'(a)')
+        write (iout,'(a)')
         enddo
         do j=1,nres
           do k=1,3
         enddo
         do j=1,nres
           do k=1,3
         write (iout,'(i5,3f10.5)') i,(gradxorr(j,i),j=1,3)
       enddo
       do i=1,nres
         write (iout,'(i5,3f10.5)') i,(gradxorr(j,i),j=1,3)
       enddo
       do i=1,nres
-       do j=1,3
-         grad_s(j,i)=gradc(j,i,icg)
-         grad_s(j+3,i)=gradx(j,i,icg)
+      do j=1,3
+        grad_s(j,i)=gradc(j,i,icg)
+        grad_s(j+3,i)=gradx(j,i,icg)
         enddo
       enddo
       call flush(iout)
       write (iout,'(/a/)') 'Gradient in virtual-bond and SC vectors'
       do i=1,nres
         do j=1,3
         enddo
       enddo
       call flush(iout)
       write (iout,'(/a/)') 'Gradient in virtual-bond and SC vectors'
       do i=1,nres
         do j=1,3
-         xx(j)=c(j,i+nres)
-         ddc(j)=dc(j,i) 
-         ddx(j)=dc(j,i+nres)
-        enddo
-       do j=1,3
-         dc(j,i)=dc(j,i)+aincr
-         do k=i+1,nres
-           c(j,k)=c(j,k)+aincr
-           c(j,k+nres)=c(j,k+nres)+aincr
+        xx(j)=c(j,i+nres)
+        ddc(j)=dc(j,i) 
+        ddx(j)=dc(j,i+nres)
+        enddo
+      do j=1,3
+        dc(j,i)=dc(j,i)+aincr
+        do k=i+1,nres
+          c(j,k)=c(j,k)+aincr
+          c(j,k+nres)=c(j,k+nres)+aincr
           enddo
           call etotal(energia1)
           etot1=energia1(0)
           enddo
           call etotal(energia1)
           etot1=energia1(0)
-         ggg(j)=(etot1-etot)/aincr
-         dc(j,i)=ddc(j)
-         do k=i+1,nres
-           c(j,k)=c(j,k)-aincr
-           c(j,k+nres)=c(j,k+nres)-aincr
+        ggg(j)=(etot1-etot)/aincr
+        dc(j,i)=ddc(j)
+        do k=i+1,nres
+          c(j,k)=c(j,k)-aincr
+          c(j,k+nres)=c(j,k+nres)-aincr
           enddo
         enddo
           enddo
         enddo
-       do j=1,3
-         c(j,i+nres)=c(j,i+nres)+aincr
-         dc(j,i+nres)=dc(j,i+nres)+aincr
+      do j=1,3
+        c(j,i+nres)=c(j,i+nres)+aincr
+        dc(j,i+nres)=dc(j,i+nres)+aincr
           call etotal(energia1)
           etot1=energia1(0)
           call etotal(energia1)
           etot1=energia1(0)
-         ggg(j+3)=(etot1-etot)/aincr
-         c(j,i+nres)=xx(j)
-         dc(j,i+nres)=ddx(j)
+        ggg(j+3)=(etot1-etot)/aincr
+        c(j,i+nres)=xx(j)
+        dc(j,i+nres)=ddx(j)
         enddo
         enddo
-       write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/)') &
+      write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/)') &
          i,(ggg(k),k=1,6),(grad_s(k,i),k=1,6)
       enddo
       return
          i,(ggg(k),k=1,6),(grad_s(k,i),k=1,6)
       enddo
       return
@@ -11331,7 +11858,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         enddo
         call zerograd
         call etotal_short(energia)
         enddo
         call zerograd
         call etotal_short(energia)
-!el        call enerprint(energia)
+        call enerprint(energia)
         call flush(iout)
         write (iout,*) "enter cartgrad"
         call flush(iout)
         call flush(iout)
         write (iout,*) "enter cartgrad"
         call flush(iout)
@@ -11360,14 +11887,14 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         do j=1,3
           if (nnt.gt.1 .and. i.eq.nnt) ddc1(j)=c(j,1)
           if (nct.lt.nres .and. i.eq.nct) ddcn(j)=c(j,nres)
         do j=1,3
           if (nnt.gt.1 .and. i.eq.nnt) ddc1(j)=c(j,1)
           if (nct.lt.nres .and. i.eq.nct) ddcn(j)=c(j,nres)
-         ddc(j)=c(j,i) 
-         ddx(j)=c(j,i+nres) 
+        ddc(j)=c(j,i) 
+        ddx(j)=c(j,i+nres) 
           dcnorm_safe1(j)=dc_norm(j,i-1)
           dcnorm_safe2(j)=dc_norm(j,i)
           dxnorm_safe(j)=dc_norm(j,i+nres)
         enddo
           dcnorm_safe1(j)=dc_norm(j,i-1)
           dcnorm_safe2(j)=dc_norm(j,i)
           dxnorm_safe(j)=dc_norm(j,i+nres)
         enddo
-       do j=1,3
-         c(j,i)=ddc(j)+aincr
+      do j=1,3
+        c(j,i)=ddc(j)+aincr
           if (nnt.gt.1 .and. i.eq.nnt) c(j,1)=c(j,1)+aincr
           if (nct.lt.nres .and. i.eq.nct) c(j,nres)=c(j,nres)+aincr
           if (i.gt.1) dc(j,i-1)=c(j,i)-c(j,i-1)
           if (nnt.gt.1 .and. i.eq.nnt) c(j,1)=c(j,1)+aincr
           if (nct.lt.nres .and. i.eq.nct) c(j,nres)=c(j,nres)+aincr
           if (i.gt.1) dc(j,i-1)=c(j,i)-c(j,i-1)
@@ -11387,7 +11914,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           endif
 !- end split gradient
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot1",etot1
           endif
 !- end split gradient
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot1",etot1
-         c(j,i)=ddc(j)-aincr
+        c(j,i)=ddc(j)-aincr
           if (nnt.gt.1 .and. i.eq.nnt) c(j,1)=ddc1(j)-aincr
           if (nct.lt.nres .and. i.eq.nct) c(j,nres)=ddcn(j)-aincr
           if (i.gt.1) dc(j,i-1)=c(j,i)-c(j,i-1)
           if (nnt.gt.1 .and. i.eq.nnt) c(j,1)=ddc1(j)-aincr
           if (nct.lt.nres .and. i.eq.nct) c(j,nres)=ddcn(j)-aincr
           if (i.gt.1) dc(j,i-1)=c(j,i)-c(j,i-1)
@@ -11398,20 +11925,20 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
             call etotal(energia1)
             etot2=energia1(0)
             write (iout,*) "ij",i,j," etot2",etot2
             call etotal(energia1)
             etot2=energia1(0)
             write (iout,*) "ij",i,j," etot2",etot2
-           ggg(j)=(etot1-etot2)/(2*aincr)
+          ggg(j)=(etot1-etot2)/(2*aincr)
           else
 !- split gradient
             call etotal_long(energia1)
             etot21=energia1(0)
           else
 !- split gradient
             call etotal_long(energia1)
             etot21=energia1(0)
-           ggg(j)=(etot11-etot21)/(2*aincr)
+          ggg(j)=(etot11-etot21)/(2*aincr)
             call etotal_short(energia1)
             etot22=energia1(0)
             call etotal_short(energia1)
             etot22=energia1(0)
-           ggg1(j)=(etot12-etot22)/(2*aincr)
+          ggg1(j)=(etot12-etot22)/(2*aincr)
 !- end split gradient
 !            write (iout,*) "etot21",etot21," etot22",etot22
           endif
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot2",etot2
 !- end split gradient
 !            write (iout,*) "etot21",etot21," etot22",etot22
           endif
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot2",etot2
-         c(j,i)=ddc(j)
+        c(j,i)=ddc(j)
           if (nnt.gt.1 .and. i.eq.nnt) c(j,1)=ddc1(j)
           if (nct.lt.nres .and. i.eq.nct) c(j,nres)=ddcn(j)
           if (i.gt.1) dc(j,i-1)=c(j,i)-c(j,i-1)
           if (nnt.gt.1 .and. i.eq.nnt) c(j,1)=ddc1(j)
           if (nct.lt.nres .and. i.eq.nct) c(j,nres)=ddcn(j)
           if (i.gt.1) dc(j,i-1)=c(j,i)-c(j,i-1)
@@ -11421,8 +11948,8 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           dc_norm(j,i)=dcnorm_safe2(j)
           dc_norm(j,i+nres)=dxnorm_safe(j)
         enddo
           dc_norm(j,i)=dcnorm_safe2(j)
           dc_norm(j,i+nres)=dxnorm_safe(j)
         enddo
-       do j=1,3
-         c(j,i+nres)=ddx(j)+aincr
+      do j=1,3
+        c(j,i+nres)=ddx(j)+aincr
           dc(j,i+nres)=c(j,i+nres)-c(j,i)
           call int_from_cart1(.false.)
           if (.not.split_ene) then
           dc(j,i+nres)=c(j,i+nres)-c(j,i)
           call int_from_cart1(.false.)
           if (.not.split_ene) then
@@ -11436,30 +11963,30 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
             etot12=energia1(0)
           endif
 !- end split gradient
             etot12=energia1(0)
           endif
 !- end split gradient
-         c(j,i+nres)=ddx(j)-aincr
+        c(j,i+nres)=ddx(j)-aincr
           dc(j,i+nres)=c(j,i+nres)-c(j,i)
           call int_from_cart1(.false.)
           if (.not.split_ene) then
             call etotal(energia1)
             etot2=energia1(0)
           dc(j,i+nres)=c(j,i+nres)-c(j,i)
           call int_from_cart1(.false.)
           if (.not.split_ene) then
             call etotal(energia1)
             etot2=energia1(0)
-           ggg(j+3)=(etot1-etot2)/(2*aincr)
+          ggg(j+3)=(etot1-etot2)/(2*aincr)
           else
 !- split gradient
             call etotal_long(energia1)
             etot21=energia1(0)
           else
 !- split gradient
             call etotal_long(energia1)
             etot21=energia1(0)
-           ggg(j+3)=(etot11-etot21)/(2*aincr)
+          ggg(j+3)=(etot11-etot21)/(2*aincr)
             call etotal_short(energia1)
             etot22=energia1(0)
             call etotal_short(energia1)
             etot22=energia1(0)
-           ggg1(j+3)=(etot12-etot22)/(2*aincr)
+          ggg1(j+3)=(etot12-etot22)/(2*aincr)
 !- end split gradient
           endif
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot2",etot2
 !- end split gradient
           endif
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot2",etot2
-         c(j,i+nres)=ddx(j)
+        c(j,i+nres)=ddx(j)
           dc(j,i+nres)=c(j,i+nres)-c(j,i)
           dc_norm(j,i+nres)=dxnorm_safe(j)
           call int_from_cart1(.false.)
         enddo
           dc(j,i+nres)=c(j,i+nres)-c(j,i)
           dc_norm(j,i+nres)=dxnorm_safe(j)
           call int_from_cart1(.false.)
         enddo
-       write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/3x,6(1pe12.5)/)') &
+      write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/3x,6(1pe12.5)/)') &
          i,(ggg(k),k=1,6),(grad_s(k,i),k=1,6),(ggg(k)/grad_s(k,i),k=1,6)
         if (split_ene) then
           write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/3x,6(1pe12.5)/)') &
          i,(ggg(k),k=1,6),(grad_s(k,i),k=1,6),(ggg(k)/grad_s(k,i),k=1,6)
         if (split_ene) then
           write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/3x,6(1pe12.5)/)') &
@@ -11538,6 +12065,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         do i=1,nres
           do j=1,3
             grad_s(j,i)=gcart(j,i)
         do i=1,nres
           do j=1,3
             grad_s(j,i)=gcart(j,i)
+!            if (i.le.2) print *,"tu?!",gcart(j,i),grad_s(j,i),gxcart(j,i)
             grad_s(j+3,i)=gxcart(j,i)
           enddo
         enddo
             grad_s(j+3,i)=gxcart(j,i)
           enddo
         enddo
@@ -11595,16 +12123,16 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       write (iout,'(/a/)') 'Gradient in virtual-bond and SC vectors'
       do i=0,nres
         do j=1,3
       write (iout,'(/a/)') 'Gradient in virtual-bond and SC vectors'
       do i=0,nres
         do j=1,3
-         xx(j)=c(j,i+nres)
-         ddc(j)=dc(j,i) 
-         ddx(j)=dc(j,i+nres)
+        xx(j)=c(j,i+nres)
+        ddc(j)=dc(j,i) 
+        ddx(j)=dc(j,i+nres)
           do k=1,3
             dcnorm_safe(k)=dc_norm(k,i)
             dxnorm_safe(k)=dc_norm(k,i+nres)
           enddo
         enddo
           do k=1,3
             dcnorm_safe(k)=dc_norm(k,i)
             dxnorm_safe(k)=dc_norm(k,i+nres)
           enddo
         enddo
-       do j=1,3
-         dc(j,i)=ddc(j)+aincr
+      do j=1,3
+        dc(j,i)=ddc(j)+aincr
           call chainbuild_cart
 #ifdef MPI
 ! Broadcast the order to compute internal coordinates to the slaves.
           call chainbuild_cart
 #ifdef MPI
 ! Broadcast the order to compute internal coordinates to the slaves.
@@ -11615,6 +12143,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           if (.not.split_ene) then
             call etotal(energia1)
             etot1=energia1(0)
           if (.not.split_ene) then
             call etotal(energia1)
             etot1=energia1(0)
+!            call enerprint(energia1)
           else
 !- split gradient
             call etotal_long(energia1)
           else
 !- split gradient
             call etotal_long(energia1)
@@ -11625,30 +12154,30 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           endif
 !- end split gradient
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot1",etot1
           endif
 !- end split gradient
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot1",etot1
-         dc(j,i)=ddc(j)-aincr
+        dc(j,i)=ddc(j)-aincr
           call chainbuild_cart
 !          call int_from_cart1(.false.)
           if (.not.split_ene) then
             call etotal(energia1)
             etot2=energia1(0)
           call chainbuild_cart
 !          call int_from_cart1(.false.)
           if (.not.split_ene) then
             call etotal(energia1)
             etot2=energia1(0)
-           ggg(j)=(etot1-etot2)/(2*aincr)
+          ggg(j)=(etot1-etot2)/(2*aincr)
           else
 !- split gradient
             call etotal_long(energia1)
             etot21=energia1(0)
           else
 !- split gradient
             call etotal_long(energia1)
             etot21=energia1(0)
-           ggg(j)=(etot11-etot21)/(2*aincr)
+          ggg(j)=(etot11-etot21)/(2*aincr)
             call etotal_short(energia1)
             etot22=energia1(0)
             call etotal_short(energia1)
             etot22=energia1(0)
-           ggg1(j)=(etot12-etot22)/(2*aincr)
+          ggg1(j)=(etot12-etot22)/(2*aincr)
 !- end split gradient
 !            write (iout,*) "etot21",etot21," etot22",etot22
           endif
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot2",etot2
 !- end split gradient
 !            write (iout,*) "etot21",etot21," etot22",etot22
           endif
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot2",etot2
-         dc(j,i)=ddc(j)
+        dc(j,i)=ddc(j)
           call chainbuild_cart
         enddo
           call chainbuild_cart
         enddo
-       do j=1,3
-         dc(j,i+nres)=ddx(j)+aincr
+      do j=1,3
+        dc(j,i+nres)=ddx(j)+aincr
           call chainbuild_cart
 !          write (iout,*) "i",i," j",j," dxnorm+ and dxnorm"
 !          write (iout,'(3f15.10)') (dc_norm(k,i+nres),k=1,3)
           call chainbuild_cart
 !          write (iout,*) "i",i," j",j," dxnorm+ and dxnorm"
 !          write (iout,'(3f15.10)') (dc_norm(k,i+nres),k=1,3)
@@ -11670,7 +12199,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           endif
 !- end split gradient
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot1",etot1
           endif
 !- end split gradient
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot1",etot1
-         dc(j,i+nres)=ddx(j)-aincr
+        dc(j,i+nres)=ddx(j)-aincr
           call chainbuild_cart
 !          write (iout,*) "i",i," j",j," dxnorm- and dxnorm"
 !          write (iout,'(3f15.10)') (dc_norm(k,i+nres),k=1,3)
           call chainbuild_cart
 !          write (iout,*) "i",i," j",j," dxnorm- and dxnorm"
 !          write (iout,'(3f15.10)') (dc_norm(k,i+nres),k=1,3)
@@ -11683,22 +12212,22 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           if (.not.split_ene) then
             call etotal(energia1)
             etot2=energia1(0)
           if (.not.split_ene) then
             call etotal(energia1)
             etot2=energia1(0)
-           ggg(j+3)=(etot1-etot2)/(2*aincr)
+          ggg(j+3)=(etot1-etot2)/(2*aincr)
           else
 !- split gradient
             call etotal_long(energia1)
             etot21=energia1(0)
           else
 !- split gradient
             call etotal_long(energia1)
             etot21=energia1(0)
-           ggg(j+3)=(etot11-etot21)/(2*aincr)
+          ggg(j+3)=(etot11-etot21)/(2*aincr)
             call etotal_short(energia1)
             etot22=energia1(0)
             call etotal_short(energia1)
             etot22=energia1(0)
-           ggg1(j+3)=(etot12-etot22)/(2*aincr)
+          ggg1(j+3)=(etot12-etot22)/(2*aincr)
 !- end split gradient
           endif
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot2",etot2
 !- end split gradient
           endif
 !          write(iout,'(2i5,2(a,f15.10))')i,j," etot",etot," etot2",etot2
-         dc(j,i+nres)=ddx(j)
+        dc(j,i+nres)=ddx(j)
           call chainbuild_cart
         enddo
           call chainbuild_cart
         enddo
-       write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/3x,6(1pe12.5)/)') &
+      write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/3x,6(1pe12.5)/)') &
          i,(ggg(k),k=1,6),(grad_s(k,i),k=1,6),(ggg(k)/grad_s(k,i),k=1,6)
         if (split_ene) then
           write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/3x,6(1pe12.5)/)') &
          i,(ggg(k),k=1,6),(grad_s(k,i),k=1,6),(ggg(k)/grad_s(k,i),k=1,6)
         if (split_ene) then
           write (iout,'(i3,6(1pe12.5)/3x,6(1pe12.5)/3x,6(1pe12.5)/)') &
@@ -11743,11 +12272,11 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       call var_to_geom(nvar,x)
       call chainbuild
       icall=1
       call var_to_geom(nvar,x)
       call chainbuild
       icall=1
-      print *,'ICG=',ICG
+!      print *,'ICG=',ICG
       call etotal(energia)
       etot = energia(0)
 !el      call enerprint(energia)
       call etotal(energia)
       etot = energia(0)
 !el      call enerprint(energia)
-      print *,'ICG=',ICG
+!      print *,'ICG=',ICG
 #ifdef MPL
       if (MyID.ne.BossID) then
         call mp_bcast(x(1),8*(nvar+3),BossID,fgGroupID)
 #ifdef MPL
       if (MyID.ne.BossID) then
         call mp_bcast(x(1),8*(nvar+3),BossID,fgGroupID)
@@ -12001,9 +12530,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !      write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
 !      write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -12014,7 +12543,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !d        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 !d   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
 !d        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 !d   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
@@ -12091,9 +12620,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !      write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
 !      write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -12106,7 +12635,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !d        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 !d   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
 !d        write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
 !d   &                  'iend=',iend(i,iint)
           do j=istart(i,iint),iend(i,iint)
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
@@ -12181,9 +12710,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
 !     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -12192,7 +12721,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
@@ -12212,7 +12741,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !d            sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 !d            epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 !d            write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
 !d            sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 !d            epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 !d            write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
-!d   &          restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
+!d   &          restyp(itypi,1),i,restyp(itypj,1),j,aa(itypi,itypj),
 !d   &          bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
 !d   &          sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
 !d   &          (c(k,i),k=1,3),(c(k,j),k=1,3)
 !d   &          bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
 !d   &          sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
 !d   &          (c(k,i),k=1,3),(c(k,j),k=1,3)
@@ -12268,9 +12797,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
 !     print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
       evdw=0.0D0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -12279,7 +12808,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
             if (itypj.eq.ntyp1) cycle
             xj=c(1,nres+j)-xi
             yj=c(2,nres+j)-yi
@@ -12299,7 +12828,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !d            sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 !d            epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 !d            write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
 !d            sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
 !d            epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
 !d            write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
-!d   &          restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
+!d   &          restyp(itypi,1),i,restyp(itypj,1),j,aa(itypi,itypj),
 !d   &          bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
 !d   &          sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
 !d   &          (c(k,i),k=1,3),(c(k,j),k=1,3)
 !d   &          bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
 !d   &          sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
 !d   &          (c(k,i),k=1,3),(c(k,j),k=1,3)
@@ -12367,9 +12896,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     endif
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     endif
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -12384,7 +12913,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
@@ -12425,7 +12954,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
 !d              write (iout,'(2(a3,i3,2x),15(0pf7.3))')
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
 !d              write (iout,'(2(a3,i3,2x),15(0pf7.3))')
-!d     &          restyp(itypi),i,restyp(itypj),j,
+!d     &          restyp(itypi,1),i,restyp(itypj,1),j,
 !d     &          epsi,sigm,chi1,chi2,chip1,chip2,
 !d     &          eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
 !d     &          om1,om2,om12,1.0D0/dsqrt(rrij),
 !d     &          epsi,sigm,chi1,chi2,chip1,chip2,
 !d     &          eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
 !d     &          om1,om2,om12,1.0D0/dsqrt(rrij),
@@ -12487,9 +13016,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     endif
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     endif
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -12504,7 +13033,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
@@ -12545,7 +13074,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
 !d              write (iout,'(2(a3,i3,2x),15(0pf7.3))')
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
 !d              write (iout,'(2(a3,i3,2x),15(0pf7.3))')
-!d     &          restyp(itypi),i,restyp(itypj),j,
+!d     &          restyp(itypi,1),i,restyp(itypj,1),j,
 !d     &          epsi,sigm,chi1,chi2,chip1,chip2,
 !d     &          eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
 !d     &          om1,om2,om12,1.0D0/dsqrt(rrij),
 !d     &          epsi,sigm,chi1,chi2,chip1,chip2,
 !d     &          eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
 !d     &          om1,om2,om12,1.0D0/dsqrt(rrij),
@@ -12607,9 +13136,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     if (icall.eq.0) lprn=.false.
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     if (icall.eq.0) lprn=.false.
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -12655,21 +13184,43 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         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
         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
-              if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') &
-                              'evdw',i,j,evdwij,' ss'
+!              call dyn_ssbond_ene(i,j,evdwij)
+!              evdw=evdw+evdwij
+!              if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') &
+!                              'evdw',i,j,evdwij,' ss'
 !              if (energy_dec) write (iout,*) &
 !                              'evdw',i,j,evdwij,' ss'
 !              if (energy_dec) write (iout,*) &
 !                              'evdw',i,j,evdwij,' ss'
+!             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
+
+!c              write(iout,*) "PRZED TRI", evdwij
+!               evdwij_przed_tri=evdwij
+!              call triple_ssbond_ene(i,j,k,evdwij)
+!c               if(evdwij_przed_tri.ne.evdwij) then
+!c                 write (iout,*) "TRI:", evdwij, evdwij_przed_tri
+!c               endif
+
+!c              write(iout,*) "PO TRI", evdwij
+!C call the energy function that removes the artifical triple disulfide
+!C bond the soubroutine is located in ssMD.F
+!              evdw=evdw+evdwij
+              if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') &
+                            'evdw',i,j,evdwij,'tss'
+!              endif!dyn_ss_mask(k)
+!             enddo! k
+
             ELSE
 !el            ind=ind+1
             ELSE
 !el            ind=ind+1
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
 !            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
 !     &       1.0d0/vbld(j+nres)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
 !            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
 !     &       1.0d0/vbld(j+nres)
-!            write (iout,*) "i",i," j", j," itype",itype(i),itype(j)
+!            write (iout,*) "i",i," j", j," itype",itype(i,1),itype(j,1)
             sig0ij=sigma(itypi,itypj)
             chi1=chi(itypi,itypj)
             chi2=chi(itypj,itypi)
             sig0ij=sigma(itypi,itypj)
             chi1=chi(itypi,itypj)
             chi2=chi(itypj,itypi)
@@ -12773,7 +13324,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               if (rij_shift.le.0.0D0) then
                 evdw=1.0D20
 !d                write (iout,'(2(a3,i3,2x),17(0pf7.3))')
               if (rij_shift.le.0.0D0) then
                 evdw=1.0D20
 !d                write (iout,'(2(a3,i3,2x),17(0pf7.3))')
-!d     &          restyp(itypi),i,restyp(itypj),j,
+!d     &          restyp(itypi,1),i,restyp(itypj,1),j,
 !d     &          rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq) 
                 return
               endif
 !d     &          rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq) 
                 return
               endif
@@ -12794,7 +13345,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
               write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
               write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
-                restyp(itypi),i,restyp(itypj),j,&
+                restyp(itypi,1),i,restyp(itypj,1),j,&
                 epsi,sigm,chi1,chi2,chip1,chip2,&
                 eps1,eps2rt**2,eps3rt**2,sig,sig0ij,&
                 om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,&
                 epsi,sigm,chi1,chi2,chip1,chip2,&
                 eps1,eps2rt**2,eps3rt**2,sig,sig0ij,&
                 om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,&
@@ -12865,9 +13416,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     if (icall.eq.0) lprn=.false.
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     if (icall.eq.0) lprn=.false.
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -12923,17 +13474,39 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               evdw=evdw+evdwij
               if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') &
                               'evdw',i,j,evdwij,' ss'
               evdw=evdw+evdwij
               if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') &
                               'evdw',i,j,evdwij,' ss'
+             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
+
+!c              write(iout,*) "PRZED TRI", evdwij
+!               evdwij_przed_tri=evdwij
+              call triple_ssbond_ene(i,j,k,evdwij)
+!c               if(evdwij_przed_tri.ne.evdwij) then
+!c                 write (iout,*) "TRI:", evdwij, evdwij_przed_tri
+!c               endif
+
+!c              write(iout,*) "PO TRI", evdwij
+!C call the energy function that removes the artifical triple disulfide
+!C bond the soubroutine is located in ssMD.F
+              evdw=evdw+evdwij
+              if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)') &
+                            'evdw',i,j,evdwij,'tss'
+              endif!dyn_ss_mask(k)
+             enddo! k
+
 !              if (energy_dec) write (iout,*) &
 !                              'evdw',i,j,evdwij,' ss'
             ELSE
 !el            ind=ind+1
 !              if (energy_dec) write (iout,*) &
 !                              'evdw',i,j,evdwij,' ss'
             ELSE
 !el            ind=ind+1
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
 !            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
 !     &       1.0d0/vbld(j+nres)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
 !            write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
 !     &       1.0d0/vbld(j+nres)
-!            write (iout,*) "i",i," j", j," itype",itype(i),itype(j)
+!            write (iout,*) "i",i," j", j," itype",itype(i,1),itype(j,1)
             sig0ij=sigma(itypi,itypj)
             chi1=chi(itypi,itypj)
             chi2=chi(itypj,itypi)
             sig0ij=sigma(itypi,itypj)
             chi1=chi(itypi,itypj)
             chi2=chi(itypj,itypi)
@@ -13042,7 +13615,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               if (rij_shift.le.0.0D0) then
                 evdw=1.0D20
 !d                write (iout,'(2(a3,i3,2x),17(0pf7.3))')
               if (rij_shift.le.0.0D0) then
                 evdw=1.0D20
 !d                write (iout,'(2(a3,i3,2x),17(0pf7.3))')
-!d     &          restyp(itypi),i,restyp(itypj),j,
+!d     &          restyp(itypi,1),i,restyp(itypj,1),j,
 !d     &          rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq) 
                 return
               endif
 !d     &          rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq) 
                 return
               endif
@@ -13063,7 +13636,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
               write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
               write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
-                restyp(itypi),i,restyp(itypj),j,&
+                restyp(itypi,1),i,restyp(itypj,1),j,&
                 epsi,sigm,chi1,chi2,chip1,chip2,&
                 eps1,eps2rt**2,eps3rt**2,sig,sig0ij,&
                 om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,&
                 epsi,sigm,chi1,chi2,chip1,chip2,&
                 eps1,eps2rt**2,eps3rt**2,sig,sig0ij,&
                 om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,&
@@ -13133,9 +13706,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     if (icall.eq.0) lprn=.true.
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     if (icall.eq.0) lprn=.true.
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -13150,7 +13723,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
@@ -13206,7 +13779,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
               write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
               write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
-                restyp(itypi),i,restyp(itypj),j,&
+                restyp(itypi,1),i,restyp(itypj,1),j,&
                 epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),&
                 chi1,chi2,chip1,chip2,&
                 eps1,eps2rt**2,eps3rt**2,&
                 epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),&
                 chi1,chi2,chip1,chip2,&
                 eps1,eps2rt**2,eps3rt**2,&
@@ -13262,9 +13835,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     if (icall.eq.0) lprn=.true.
 !el      ind=0
       do i=iatsc_s,iatsc_e
 !     if (icall.eq.0) lprn=.true.
 !el      ind=0
       do i=iatsc_s,iatsc_e
-        itypi=itype(i)
+        itypi=itype(i,1)
         if (itypi.eq.ntyp1) cycle
         if (itypi.eq.ntyp1) cycle
-        itypi1=itype(i+1)
+        itypi1=itype(i+1,1)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
         xi=c(1,nres+i)
         yi=c(2,nres+i)
         zi=c(3,nres+i)
@@ -13279,7 +13852,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
         do iint=1,nint_gr(i)
           do j=istart(i,iint),iend(i,iint)
 !el            ind=ind+1
-            itypj=itype(j)
+            itypj=itype(j,1)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
             if (itypj.eq.ntyp1) cycle
 !            dscj_inv=dsc_inv(itypj)
             dscj_inv=vbld_inv(j+nres)
@@ -13335,7 +13908,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
               write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
               sigm=dabs(aa_aq(itypi,itypj)/bb_aq(itypi,itypj))**(1.0D0/6.0D0)
               epsi=bb_aq(itypi,itypj)**2/aa_aq(itypi,itypj)
               write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
-                restyp(itypi),i,restyp(itypj),j,&
+                restyp(itypi,1),i,restyp(itypj,1),j,&
                 epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),&
                 chi1,chi2,chip1,chip2,&
                 eps1,eps2rt**2,eps3rt**2,&
                 epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),&
                 chi1,chi2,chip1,chip2,&
                 eps1,eps2rt**2,eps3rt**2,&
@@ -13486,8 +14059,8 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 ! Loop over i,i+2 and i,i+3 pairs of the peptide groups
 !
       do i=iturn3_start,iturn3_end
 ! Loop over i,i+2 and i,i+3 pairs of the peptide groups
 !
       do i=iturn3_start,iturn3_end
-        if (itype(i).eq.ntyp1.or. itype(i+1).eq.ntyp1 &
-        .or. itype(i+2).eq.ntyp1 .or. itype(i+3).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1.or. itype(i+1,1).eq.ntyp1 &
+        .or. itype(i+2,1).eq.ntyp1 .or. itype(i+3,1).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
@@ -13509,9 +14082,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         num_cont_hb(i)=num_conti
       enddo
       do i=iturn4_start,iturn4_end
         num_cont_hb(i)=num_conti
       enddo
       do i=iturn4_start,iturn4_end
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1 &
-          .or. itype(i+3).eq.ntyp1 &
-          .or. itype(i+4).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1 &
+          .or. itype(i+3,1).eq.ntyp1 &
+          .or. itype(i+4,1).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
@@ -13529,7 +14102,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           if (zmedi.lt.0) zmedi=zmedi+boxzsize
         num_conti=num_cont_hb(i)
         call eelecij_scale(i,i+3,ees,evdw1,eel_loc)
           if (zmedi.lt.0) zmedi=zmedi+boxzsize
         num_conti=num_cont_hb(i)
         call eelecij_scale(i,i+3,ees,evdw1,eel_loc)
-        if (wturn4.gt.0.0d0 .and. itype(i+2).ne.ntyp1) &
+        if (wturn4.gt.0.0d0 .and. itype(i+2,1).ne.ntyp1) &
           call eturn4(i,eello_turn4)
         num_cont_hb(i)=num_conti
       enddo   ! i
           call eturn4(i,eello_turn4)
         num_cont_hb(i)=num_conti
       enddo   ! i
@@ -13537,7 +14110,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 ! Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
 !
       do i=iatel_s,iatel_e
 ! Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
 !
       do i=iatel_s,iatel_e
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
@@ -13556,7 +14129,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         num_conti=num_cont_hb(i)
         do j=ielstart(i),ielend(i)
 !        write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
         num_conti=num_cont_hb(i)
         do j=ielstart(i),ielend(i)
-          if (itype(j).eq.ntyp1 .or. itype(j+1).eq.ntyp1) cycle
+          if (itype(j,1).eq.ntyp1 .or. itype(j+1,1).eq.ntyp1) cycle
           call eelecij_scale(i,j,ees,evdw1,eel_loc)
         enddo ! j
         num_cont_hb(i)=num_conti
           call eelecij_scale(i,j,ees,evdw1,eel_loc)
         enddo ! j
         num_cont_hb(i)=num_conti
@@ -13648,8 +14221,8 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !      allocate(d_cont(maxconts,nres)) !(maxconts,maxres)
 !      allocate(jcont_hb(maxconts,nres)) !(maxconts,maxres)
 
 !      allocate(d_cont(maxconts,nres)) !(maxconts,maxres)
 !      allocate(jcont_hb(maxconts,nres)) !(maxconts,maxres)
 
-!      allocate(a_chuj(2,2,maxconts,nres))     !(2,2,maxconts,maxres)
-!      allocate(a_chuj_der(2,2,3,5,maxconts,nres))     !(2,2,3,5,maxconts,maxres)
+!      allocate(a_chuj(2,2,maxconts,nres))      !(2,2,maxconts,maxres)
+!      allocate(a_chuj_der(2,2,3,5,maxconts,nres))      !(2,2,3,5,maxconts,maxres)
 
 #ifdef MPI
           time00=MPI_Wtime()
 
 #ifdef MPI
           time00=MPI_Wtime()
@@ -13940,7 +14513,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           a32=a32*fac
           a33=a33*fac
 !d          write (iout,'(4i5,4f10.5)')
           a32=a32*fac
           a33=a33*fac
 !d          write (iout,'(4i5,4f10.5)')
-!d     &     i,itortyp(itype(i)),j,itortyp(itype(j)),a22,a23,a32,a33
+!d     &     i,itortyp(itype(i,1)),j,itortyp(itype(j,1)),a22,a23,a32,a33
 !d          write (iout,'(6f10.5)') (muij(k),k=1,4),fac,eel_loc_ij
 !d          write (iout,'(2(3f10.5,5x)/2(3f10.5,5x))') uy(:,i),uz(:,i),
 !d     &      uy(:,j),uz(:,j)
 !d          write (iout,'(6f10.5)') (muij(k),k=1,4),fac,eel_loc_ij
 !d          write (iout,'(2(3f10.5,5x)/2(3f10.5,5x))') uy(:,i),uz(:,i),
 !d     &      uy(:,j),uz(:,j)
@@ -14417,7 +14990,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     & " iatel_e_vdw",iatel_e_vdw
       call flush(iout)
       do i=iatel_s_vdw,iatel_e_vdw
 !     & " iatel_e_vdw",iatel_e_vdw
       call flush(iout)
       do i=iatel_s_vdw,iatel_e_vdw
-        if (itype(i).eq.ntyp1.or. itype(i+1).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1.or. itype(i+1,1).eq.ntyp1) cycle
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
         dxi=dc(1,i)
         dyi=dc(2,i)
         dzi=dc(3,i)
@@ -14438,7 +15011,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !     &   ' ielend',ielend_vdw(i)
         call flush(iout)
         do j=ielstart_vdw(i),ielend_vdw(i)
 !     &   ' ielend',ielend_vdw(i)
         call flush(iout)
         do j=ielstart_vdw(i),ielend_vdw(i)
-          if (itype(j).eq.ntyp1 .or. itype(j+1).eq.ntyp1) cycle
+          if (itype(j,1).eq.ntyp1 .or. itype(j+1,1).eq.ntyp1) cycle
 !el          ind=ind+1
           iteli=itel(i)
           itelj=itel(j)
 !el          ind=ind+1
           iteli=itel(i)
           itelj=itel(j)
@@ -14571,7 +15144,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !d    print '(a)','Enter ESCP'
 !d    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       do i=iatscp_s,iatscp_e
 !d    print '(a)','Enter ESCP'
 !d    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       do i=iatscp_s,iatscp_e
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) cycle
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
@@ -14586,7 +15159,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
-          itypj=itype(j)
+          itypj=itype(j,1)
           if (itypj.eq.ntyp1) cycle
 ! Uncomment following three lines for SC-p interactions
 !         xj=c(1,nres+j)-xi
           if (itypj.eq.ntyp1) cycle
 ! Uncomment following three lines for SC-p interactions
 !         xj=c(1,nres+j)-xi
@@ -14730,7 +15303,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !d    print '(a)','Enter ESCP'
 !d    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       do i=iatscp_s,iatscp_e
 !d    print '(a)','Enter ESCP'
 !d    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
       do i=iatscp_s,iatscp_e
-        if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
+        if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) cycle
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
         iteli=itel(i)
         xi=0.5D0*(c(1,i)+c(1,i+1))
         yi=0.5D0*(c(2,i)+c(2,i+1))
@@ -14745,7 +15318,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
         do iint=1,nscp_gr(i)
 
         do j=iscpstart(i,iint),iscpend(i,iint)
-          itypj=itype(j)
+          itypj=itype(j,1)
           if (itypj.eq.ntyp1) cycle
 ! Uncomment following three lines for SC-p interactions
 !         xj=c(1,nres+j)-xi
           if (itypj.eq.ntyp1) cycle
 ! Uncomment following three lines for SC-p interactions
 !         xj=c(1,nres+j)-xi
@@ -15205,7 +15778,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !el local variables
       integer :: i,nres6
       real(kind=8) :: evdw,evdw1,evdw2,evdw2_14,esccor,etors_d,etors
 !el local variables
       integer :: i,nres6
       real(kind=8) :: evdw,evdw1,evdw2,evdw2_14,esccor,etors_d,etors
-      real(kind=8) :: ehpb,escloc,estr,ebe,edihcnstr
+      real(kind=8) :: ehpb,escloc,estr,ebe,edihcnstr,ethetacnstr
       nres6=6*nres
 
 !      write(iout,'(a,i2)')'Calling etotal_short ipot=',ipot
       nres6=6*nres
 
 !      write(iout,'(a,i2)')'Calling etotal_short ipot=',ipot
@@ -15360,7 +15933,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !
 ! Calculate the virtual-bond-angle energy.
 !
 !
 ! Calculate the virtual-bond-angle energy.
 !
-      call ebend(ebe)
+      call ebend(ebe,ethetacnstr)
 !
 ! Calculate the SC local energy.
 !
 !
 ! Calculate the SC local energy.
 !
@@ -15446,7 +16019,35 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       endif
       return
       end function gnmr1prim
       endif
       return
       end function gnmr1prim
-!-----------------------------------------------------------------------------
+!----------------------------------------------------------------------------
+      real(kind=8) function rlornmr1(y,ymin,ymax,sigma)
+      real(kind=8) y,ymin,ymax,sigma
+      real(kind=8) wykl /4.0d0/
+      if (y.lt.ymin) then
+        rlornmr1=(ymin-y)**wykl/((ymin-y)**wykl+sigma**wykl)
+      else if (y.gt.ymax) then
+        rlornmr1=(y-ymax)**wykl/((y-ymax)**wykl+sigma**wykl)
+      else
+        rlornmr1=0.0d0
+      endif
+      return
+      end function rlornmr1
+!------------------------------------------------------------------------------
+      real(kind=8) function rlornmr1prim(y,ymin,ymax,sigma)
+      real(kind=8) y,ymin,ymax,sigma
+      real(kind=8) wykl /4.0d0/
+      if (y.lt.ymin) then
+        rlornmr1prim=-(ymin-y)**(wykl-1)*sigma**wykl*wykl/ &
+        ((ymin-y)**wykl+sigma**wykl)**2
+      else if (y.gt.ymax) then
+        rlornmr1prim=(y-ymax)**(wykl-1)*sigma**wykl*wykl/ &
+        ((y-ymax)**wykl+sigma**wykl)**2
+      else
+        rlornmr1prim=0.0d0
+      endif
+      return
+      end function rlornmr1prim
+
       real(kind=8) function harmonic(y,ymax)
 !      implicit none
       real(kind=8) :: y,ymax
       real(kind=8) function harmonic(y,ymax)
 !      implicit none
       real(kind=8) :: y,ymax
@@ -15514,44 +16115,44 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       ind=0
       ind1=0
       do i=1,nres-2
       ind=0
       ind1=0
       do i=1,nres-2
-       gthetai=0.0D0
-       gphii=0.0D0
-       do j=i+1,nres-1
+      gthetai=0.0D0
+      gphii=0.0D0
+      do j=i+1,nres-1
           ind=ind+1
 !         ind=indmat(i,j)
 !         print *,'GRAD: i=',i,' jc=',j,' ind=',ind
           ind=ind+1
 !         ind=indmat(i,j)
 !         print *,'GRAD: i=',i,' jc=',j,' ind=',ind
-         do k=1,3
+        do k=1,3
             gthetai=gthetai+dcdv(k,ind)*gradc(k,j,icg)
           enddo
             gthetai=gthetai+dcdv(k,ind)*gradc(k,j,icg)
           enddo
-         do k=1,3
-           gphii=gphii+dcdv(k+3,ind)*gradc(k,j,icg)
+        do k=1,3
+          gphii=gphii+dcdv(k+3,ind)*gradc(k,j,icg)
           enddo
         enddo
           enddo
         enddo
-       do j=i+1,nres-1
+      do j=i+1,nres-1
           ind1=ind1+1
 !         ind1=indmat(i,j)
 !         print *,'GRAD: i=',i,' jx=',j,' ind1=',ind1
           ind1=ind1+1
 !         ind1=indmat(i,j)
 !         print *,'GRAD: i=',i,' jx=',j,' ind1=',ind1
-         do k=1,3
-           gthetai=gthetai+dxdv(k,ind1)*gradx(k,j,icg)
-           gphii=gphii+dxdv(k+3,ind1)*gradx(k,j,icg)
+        do k=1,3
+          gthetai=gthetai+dxdv(k,ind1)*gradx(k,j,icg)
+          gphii=gphii+dxdv(k+3,ind1)*gradx(k,j,icg)
           enddo
         enddo
           enddo
         enddo
-       if (i.gt.1) g(i-1)=gphii
-       if (n.gt.nphi) g(nphi+i)=gthetai
+      if (i.gt.1) g(i-1)=gphii
+      if (n.gt.nphi) g(nphi+i)=gthetai
       enddo
       if (n.le.nphi+ntheta) goto 10
       do i=2,nres-1
       enddo
       if (n.le.nphi+ntheta) goto 10
       do i=2,nres-1
-       if (itype(i).ne.10) then
+      if (itype(i,1).ne.10) then
           galphai=0.0D0
           galphai=0.0D0
-         gomegai=0.0D0
-         do k=1,3
-           galphai=galphai+dxds(k,i)*gradx(k,i,icg)
+        gomegai=0.0D0
+        do k=1,3
+          galphai=galphai+dxds(k,i)*gradx(k,i,icg)
           enddo
           enddo
-         do k=1,3
-           gomegai=gomegai+dxds(k+3,i)*gradx(k,i,icg)
+        do k=1,3
+          gomegai=gomegai+dxds(k+3,i)*gradx(k,i,icg)
           enddo
           g(ialph(i,1))=galphai
           enddo
           g(ialph(i,1))=galphai
-         g(ialph(i,1)+nside)=gomegai
+        g(ialph(i,1)+nside)=gomegai
         endif
       enddo
 !
         endif
       enddo
 !
@@ -15586,7 +16187,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       real(kind=8) :: urparm(1)     
       real(kind=8) :: f
       real(kind=8),external :: ufparm                     
       real(kind=8) :: urparm(1)     
       real(kind=8) :: f
       real(kind=8),external :: ufparm                     
-      real(kind=8),dimension(6*nres) :: x      !(maxvar) (maxvar=6*maxres)
+      real(kind=8),dimension(6*nres) :: x      !(maxvar) (maxvar=6*maxres)
 !     if (jjj.gt.0) then
 !       write (iout,'(10f8.3)') (rad2deg*x(i),i=1,n)
 !     endif
 !     if (jjj.gt.0) then
 !       write (iout,'(10f8.3)') (rad2deg*x(i),i=1,n)
 !     endif
@@ -15675,10 +16276,11 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 #ifdef DEBUG
       write (iout,*) "gcart, gxcart, gloc before int_to_cart"
 #endif
 #ifdef DEBUG
       write (iout,*) "gcart, gxcart, gloc before int_to_cart"
 #endif
-      do i=1,nct
+      do i=0,nct
         do j=1,3
           gcart(j,i)=gradc(j,i,icg)
           gxcart(j,i)=gradx(j,i,icg)
         do j=1,3
           gcart(j,i)=gradc(j,i,icg)
           gxcart(j,i)=gradx(j,i,icg)
+!          if (i.le.2) print *,"gcart_one",gcart(j,i),gradc(j,i,icg)
         enddo
 #ifdef DEBUG
         write (iout,'(i5,2(3f10.5,5x),f10.5)') i,(gcart(j,i),j=1,3),&
         enddo
 #ifdef DEBUG
         write (iout,'(i5,2(3f10.5,5x),f10.5)') i,(gcart(j,i),j=1,3),&
@@ -15688,815 +16290,853 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 #ifdef TIMING
       time01=MPI_Wtime()
 #endif
 #ifdef TIMING
       time01=MPI_Wtime()
 #endif
+!       print *,"gcart_two",gxcart(2,2),gradx(2,2,icg)
       call int_to_cart
       call int_to_cart
+!             print *,"gcart_two",gxcart(2,2),gradx(2,2,icg)
+
 #ifdef TIMING
 #ifdef TIMING
-      time_inttocart=time_inttocart+MPI_Wtime()-time01
+            time_inttocart=time_inttocart+MPI_Wtime()-time01
 #endif
 #ifdef DEBUG
 #endif
 #ifdef DEBUG
-      write (iout,*) "gcart and gxcart after int_to_cart"
-      do i=0,nres-1
-        write (iout,'(i5,3f10.5,5x,3f10.5)') i,(gcart(j,i),j=1,3),&
-            (gxcart(j,i),j=1,3)
-      enddo
+            write (iout,*) "gcart and gxcart after int_to_cart"
+            do i=0,nres-1
+            write (iout,'(i5,3f10.5,5x,3f10.5)') i,(gcart(j,i),j=1,3),&
+                (gxcart(j,i),j=1,3)
+            enddo
 #endif
 #ifdef CARGRAD
 #ifdef DEBUG
 #endif
 #ifdef CARGRAD
 #ifdef DEBUG
-      write (iout,*) "CARGRAD"
+            write (iout,*) "CARGRAD"
 #endif
 #endif
-      do i=nres,1,-1
-        do j=1,3
-          gcart(j,i)=-gcart(j,i)+gcart(j,i-1)-gxcart(j,i)
-!          gcart_new(j,i)=-gcart(j,i)+gcart(j,i-1)-gxcart(j,i)
-        enddo
-!        write (iout,'(i5,3f10.5,5x,3f10.5,5x,3f10.5)') i,(gcart(j,i),j=1,3), &
-!            (gcart_new(j,i),j=1,3),(gxcart(j,i),j=1,3)
-      enddo    
-! Correction: dummy residues
-        if (nnt.gt.1) then
-          do j=1,3
-!            gcart_new(j,nnt)=gcart_new(j,nnt)+gcart_new(j,1)
-            gcart(j,nnt)=gcart(j,nnt)+gcart(j,1)
-          enddo
-        endif
-        if (nct.lt.nres) then
-          do j=1,3
-!            gcart_new(j,nct)=gcart_new(j,nct)+gcart_new(j,nres)
-            gcart(j,nct)=gcart(j,nct)+gcart(j,nres)
-          enddo
-        endif
+            do i=nres,0,-1
+            do j=1,3
+              gcart(j,i)=-gcart(j,i)+gcart(j,i-1)-gxcart(j,i)
+      !          gcart_new(j,i)=-gcart(j,i)+gcart(j,i-1)-gxcart(j,i)
+            enddo
+      !        write (iout,'(i5,3f10.5,5x,3f10.5,5x,3f10.5)') i,(gcart(j,i),j=1,3), &
+      !            (gcart_new(j,i),j=1,3),(gxcart(j,i),j=1,3)
+            enddo    
+      ! Correction: dummy residues
+            if (nnt.gt.1) then
+              do j=1,3
+      !            gcart_new(j,nnt)=gcart_new(j,nnt)+gcart_new(j,1)
+                gcart(j,nnt)=gcart(j,nnt)+gcart(j,1)
+              enddo
+            endif
+            if (nct.lt.nres) then
+              do j=1,3
+      !            gcart_new(j,nct)=gcart_new(j,nct)+gcart_new(j,nres)
+                gcart(j,nct)=gcart(j,nct)+gcart(j,nres)
+              enddo
+            endif
 #endif
 #ifdef TIMING
 #endif
 #ifdef TIMING
-      time_cartgrad=time_cartgrad+MPI_Wtime()-time00
+            time_cartgrad=time_cartgrad+MPI_Wtime()-time00
 #endif
 #endif
-!el#undef DEBUG
-      return
-      end subroutine cartgrad
-!-----------------------------------------------------------------------------
-      subroutine zerograd
-!      implicit real*8 (a-h,o-z)
-!      include 'DIMENSIONS'
-!      include 'COMMON.DERIV'
-!      include 'COMMON.CHAIN'
-!      include 'COMMON.VAR'
-!      include 'COMMON.MD'
-!      include 'COMMON.SCCOR'
-!
-!el local variables
-      integer :: i,j,intertyp,k
-! Initialize Cartesian-coordinate gradient
-!
-!      if (.not.allocated(gradx)) allocate(gradx(3,nres,2)) !(3,maxres,2)
-!      if (.not.allocated(gradc)) allocate(gradc(3,nres,2)) !(3,maxres,2)
-
-!      allocate(gvdwx(3,nres),gvdwc(3,nres),gelc(3,nres),gelc_long(3,nres))
-!      allocate(gvdwpp(3,nres),gvdwc_scpp(3,nres),gradx_scp(3,nres))
-!      allocate(gvdwc_scp(3,nres),ghpbx(3,nres),ghpbc(3,nres))
-!      allocate(gradcorr_long(3,nres))
-!      allocate(gradcorr5_long(3,nres),gradcorr6_long(3,nres))
-!      allocate(gcorr6_turn_long(3,nres))
-!      allocate(gradcorr5(3,nres),gradcorr6(3,nres)) !(3,maxres)
-
-!      if (.not.allocated(gradcorr)) allocate(gradcorr(3,nres)) !(3,maxres)
-
-!      allocate(gel_loc(3,nres),gel_loc_long(3,nres),gcorr3_turn(3,nres))
-!      allocate(gcorr4_turn(3,nres),gcorr6_turn(3,nres))
-
-!      if (.not.allocated(gradb)) allocate(gradb(3,nres)) !(3,maxres)
-!      if (.not.allocated(gradbx)) allocate(gradbx(3,nres)) !(3,maxres)
+      !el#undef DEBUG
+            return
+            end subroutine cartgrad
+      !-----------------------------------------------------------------------------
+            subroutine zerograd
+      !      implicit real*8 (a-h,o-z)
+      !      include 'DIMENSIONS'
+      !      include 'COMMON.DERIV'
+      !      include 'COMMON.CHAIN'
+      !      include 'COMMON.VAR'
+      !      include 'COMMON.MD'
+      !      include 'COMMON.SCCOR'
+      !
+      !el local variables
+            integer :: i,j,intertyp,k
+      ! Initialize Cartesian-coordinate gradient
+      !
+      !      if (.not.allocated(gradx)) allocate(gradx(3,nres,2)) !(3,maxres,2)
+      !      if (.not.allocated(gradc)) allocate(gradc(3,nres,2)) !(3,maxres,2)
+
+      !      allocate(gvdwx(3,nres),gvdwc(3,nres),gelc(3,nres),gelc_long(3,nres))
+      !      allocate(gvdwpp(3,nres),gvdwc_scpp(3,nres),gradx_scp(3,nres))
+      !      allocate(gvdwc_scp(3,nres),ghpbx(3,nres),ghpbc(3,nres))
+      !      allocate(gradcorr_long(3,nres))
+      !      allocate(gradcorr5_long(3,nres),gradcorr6_long(3,nres))
+      !      allocate(gcorr6_turn_long(3,nres))
+      !      allocate(gradcorr5(3,nres),gradcorr6(3,nres)) !(3,maxres)
+
+      !      if (.not.allocated(gradcorr)) allocate(gradcorr(3,nres)) !(3,maxres)
+
+      !      allocate(gel_loc(3,nres),gel_loc_long(3,nres),gcorr3_turn(3,nres))
+      !      allocate(gcorr4_turn(3,nres),gcorr6_turn(3,nres))
+
+      !      if (.not.allocated(gradb)) allocate(gradb(3,nres)) !(3,maxres)
+      !      if (.not.allocated(gradbx)) allocate(gradbx(3,nres)) !(3,maxres)
+
+      !      allocate(gsccorc(3,nres),gsccorx(3,nres)) !(3,maxres)
+      !      allocate(gscloc(3,nres)) !(3,maxres)
+      !      if (.not.allocated(gsclocx)) allocate(gsclocx(3,nres)) !(3,maxres)
+
+
+
+      !      common /deriv_scloc/
+      !      allocate(dXX_C1tab(3,nres),dYY_C1tab(3,nres),dZZ_C1tab(3,nres))
+      !      allocate(dXX_Ctab(3,nres),dYY_Ctab(3,nres),dZZ_Ctab(3,nres))
+      !      allocate(dXX_XYZtab(3,nres),dYY_XYZtab(3,nres),dZZ_XYZtab(3,nres))      !(3,maxres)
+      !      common /mpgrad/
+      !      allocate(jgrad_start(nres),jgrad_end(nres)) !(maxres)
+              
+              
+
+      !          gradc(j,i,icg)=0.0d0
+      !          gradx(j,i,icg)=0.0d0
+
+      !      allocate(gloc_sc(3,nres,10)) !(3,0:maxres2,10)maxres2=2*maxres
+      !elwrite(iout,*) "icg",icg
+            do i=-1,nres
+            do j=1,3
+              gvdwx(j,i)=0.0D0
+              gradx_scp(j,i)=0.0D0
+              gvdwc(j,i)=0.0D0
+              gvdwc_scp(j,i)=0.0D0
+              gvdwc_scpp(j,i)=0.0d0
+              gelc(j,i)=0.0D0
+              gelc_long(j,i)=0.0D0
+              gradb(j,i)=0.0d0
+              gradbx(j,i)=0.0d0
+              gvdwpp(j,i)=0.0d0
+              gel_loc(j,i)=0.0d0
+              gel_loc_long(j,i)=0.0d0
+              ghpbc(j,i)=0.0D0
+              ghpbx(j,i)=0.0D0
+              gcorr3_turn(j,i)=0.0d0
+              gcorr4_turn(j,i)=0.0d0
+              gradcorr(j,i)=0.0d0
+              gradcorr_long(j,i)=0.0d0
+              gradcorr5_long(j,i)=0.0d0
+              gradcorr6_long(j,i)=0.0d0
+              gcorr6_turn_long(j,i)=0.0d0
+              gradcorr5(j,i)=0.0d0
+              gradcorr6(j,i)=0.0d0
+              gcorr6_turn(j,i)=0.0d0
+              gsccorc(j,i)=0.0d0
+              gsccorx(j,i)=0.0d0
+              gradc(j,i,icg)=0.0d0
+              gradx(j,i,icg)=0.0d0
+              gscloc(j,i)=0.0d0
+              gsclocx(j,i)=0.0d0
+              gliptran(j,i)=0.0d0
+              gliptranx(j,i)=0.0d0
+              gliptranc(j,i)=0.0d0
+              gshieldx(j,i)=0.0d0
+              gshieldc(j,i)=0.0d0
+              gshieldc_loc(j,i)=0.0d0
+              gshieldx_ec(j,i)=0.0d0
+              gshieldc_ec(j,i)=0.0d0
+              gshieldc_loc_ec(j,i)=0.0d0
+              gshieldx_t3(j,i)=0.0d0
+              gshieldc_t3(j,i)=0.0d0
+              gshieldc_loc_t3(j,i)=0.0d0
+              gshieldx_t4(j,i)=0.0d0
+              gshieldc_t4(j,i)=0.0d0
+              gshieldc_loc_t4(j,i)=0.0d0
+              gshieldx_ll(j,i)=0.0d0
+              gshieldc_ll(j,i)=0.0d0
+              gshieldc_loc_ll(j,i)=0.0d0
+              gg_tube(j,i)=0.0d0
+              gg_tube_sc(j,i)=0.0d0
+              gradafm(j,i)=0.0d0
+              gradb_nucl(j,i)=0.0d0
+              gradbx_nucl(j,i)=0.0d0
+              gvdwpp_nucl(j,i)=0.0d0
+              gvdwpp(j,i)=0.0d0
+              gelpp(j,i)=0.0d0
+              gvdwpsb(j,i)=0.0d0
+              gvdwpsb1(j,i)=0.0d0
+              gvdwsbc(j,i)=0.0d0
+              gvdwsbx(j,i)=0.0d0
+              gelsbc(j,i)=0.0d0
+              gradcorr_nucl(j,i)=0.0d0
+              gradcorr3_nucl(j,i)=0.0d0
+              gradxorr_nucl(j,i)=0.0d0
+              gradxorr3_nucl(j,i)=0.0d0
+              gelsbx(j,i)=0.0d0
+              gsbloc(j,i)=0.0d0
+              gsblocx(j,i)=0.0d0
+              gradpepcat(j,i)=0.0d0
+              gradpepcatx(j,i)=0.0d0
+              gradcatcat(j,i)=0.0d0
+              gvdwx_scbase(j,i)=0.0d0
+              gvdwc_scbase(j,i)=0.0d0
+              gvdwx_pepbase(j,i)=0.0d0
+              gvdwc_pepbase(j,i)=0.0d0
+              gvdwx_scpho(j,i)=0.0d0
+              gvdwc_scpho(j,i)=0.0d0
+              gvdwc_peppho(j,i)=0.0d0
+            enddo
+             enddo
+            do i=0,nres
+            do j=1,3
+              do intertyp=1,3
+               gloc_sc(intertyp,i,icg)=0.0d0
+              enddo
+            enddo
+            enddo
+            do i=1,nres
+             do j=1,maxcontsshi
+             shield_list(j,i)=0
+            do k=1,3
+      !C           print *,i,j,k
+               grad_shield_side(k,j,i)=0.0d0
+               grad_shield_loc(k,j,i)=0.0d0
+             enddo
+             enddo
+             ishield_list(i)=0
+            enddo
 
 
-!      allocate(gsccorc(3,nres),gsccorx(3,nres)) !(3,maxres)
-!      allocate(gscloc(3,nres)) !(3,maxres)
-!      if (.not.allocated(gsclocx)) allocate(gsclocx(3,nres)) !(3,maxres)
+      !
+      ! Initialize the gradient of local energy terms.
+      !
+      !      allocate(gloc(4*nres,2))      !!(maxvar,2)(maxvar=6*maxres)
+      !      if (.not.allocated(gel_loc_loc)) allocate(gel_loc_loc(nres)) !(maxvar)(maxvar=6*maxres)
+      !      if (.not.allocated(gcorr_loc)) allocate(gcorr_loc(nres)) !(maxvar)(maxvar=6*maxres)
+      !      allocate(g_corr5_loc(nres),g_corr6_loc(nres))      !(maxvar)(maxvar=6*maxres)
+      !      allocate(gel_loc_turn3(nres))
+      !      allocate(gel_loc_turn4(nres),gel_loc_turn6(nres))  !(maxvar)(maxvar=6*maxres)
+      !      allocate(gsccor_loc(nres))      !(maxres)
+
+            do i=1,4*nres
+            gloc(i,icg)=0.0D0
+            enddo
+            do i=1,nres
+            gel_loc_loc(i)=0.0d0
+            gcorr_loc(i)=0.0d0
+            g_corr5_loc(i)=0.0d0
+            g_corr6_loc(i)=0.0d0
+            gel_loc_turn3(i)=0.0d0
+            gel_loc_turn4(i)=0.0d0
+            gel_loc_turn6(i)=0.0d0
+            gsccor_loc(i)=0.0d0
+            enddo
+      ! initialize gcart and gxcart
+      !      allocate(gcart(3,0:nres),gxcart(3,0:nres)) !(3,0:MAXRES)
+            do i=0,nres
+            do j=1,3
+              gcart(j,i)=0.0d0
+              gxcart(j,i)=0.0d0
+            enddo
+            enddo
+            return
+            end subroutine zerograd
+      !-----------------------------------------------------------------------------
+            real(kind=8) function fdum()
+            fdum=0.0D0
+            return
+            end function fdum
+      !-----------------------------------------------------------------------------
+      ! intcartderiv.F
+      !-----------------------------------------------------------------------------
+            subroutine intcartderiv
+      !      implicit real*8 (a-h,o-z)
+      !      include 'DIMENSIONS'
+#ifdef MPI
+            include 'mpif.h'
+#endif
+      !      include 'COMMON.SETUP'
+      !      include 'COMMON.CHAIN' 
+      !      include 'COMMON.VAR'
+      !      include 'COMMON.GEO'
+      !      include 'COMMON.INTERACT'
+      !      include 'COMMON.DERIV'
+      !      include 'COMMON.IOUNITS'
+      !      include 'COMMON.LOCAL'
+      !      include 'COMMON.SCCOR'
+            real(kind=8) :: pi4,pi34
+            real(kind=8),dimension(3,2,nres) :: dcostheta ! (3,2,maxres)
+            real(kind=8),dimension(3,3,nres) :: dcosphi,dsinphi,dcosalpha,&
+                      dcosomega,dsinomega !(3,3,maxres)
+            real(kind=8),dimension(3) :: vo1,vo2,vo3,dummy,vp1,vp2,vp3,vpp1,n
+          
+            integer :: i,j,k
+            real(kind=8) :: cost,sint,cost1,sint1,cost2,sint2,sing,cosg,scalp,&
+                    fac0,fac1,fac2,fac3,fac4,fac5,fac6,ctgt,ctgt1,cosg_inv,&
+                    fac7,fac8,fac9,scala1,scala2,cosa,sina,sino,fac15,fac16,&
+                    fac17,coso_inv,fac10,fac11,fac12,fac13,fac14
+            integer :: nres2
+            nres2=2*nres
 
 
+      !el from module energy-------------
+      !el      allocate(dcostau(3,3,3,itau_start:itau_end)) !(3,3,3,maxres2)maxres2=2*maxres
+      !el      allocate(dsintau(3,3,3,itau_start:itau_end))
+      !el      allocate(dtauangle(3,3,3,itau_start:itau_end))
 
 
+      !el      allocate(dcostau(3,3,3,0:nres2)) !(3,3,3,maxres2)maxres2=2*maxres
+      !el      allocate(dsintau(3,3,3,0:nres2))
+      !el      allocate(dtauangle(3,3,3,0:nres2))
+      !el      allocate(domicron(3,2,2,0:nres2))
+      !el      allocate(dcosomicron(3,2,2,0:nres2))
 
 
-!      common /deriv_scloc/
-!      allocate(dXX_C1tab(3,nres),dYY_C1tab(3,nres),dZZ_C1tab(3,nres))
-!      allocate(dXX_Ctab(3,nres),dYY_Ctab(3,nres),dZZ_Ctab(3,nres))
-!      allocate(dXX_XYZtab(3,nres),dYY_XYZtab(3,nres),dZZ_XYZtab(3,nres))      !(3,maxres)
-!      common /mpgrad/
-!      allocate(jgrad_start(nres),jgrad_end(nres)) !(maxres)
-         
-         
 
 
-!          gradc(j,i,icg)=0.0d0
-!          gradx(j,i,icg)=0.0d0
 
 
-!      allocate(gloc_sc(3,nres,10)) !(3,0:maxres2,10)maxres2=2*maxres
-!elwrite(iout,*) "icg",icg
-      do i=-1,nres
-       do j=1,3
-         gvdwx(j,i)=0.0D0
-          gradx_scp(j,i)=0.0D0
-         gvdwc(j,i)=0.0D0
-          gvdwc_scp(j,i)=0.0D0
-          gvdwc_scpp(j,i)=0.0d0
-         gelc(j,i)=0.0D0
-         gelc_long(j,i)=0.0D0
-          gradb(j,i)=0.0d0
-          gradbx(j,i)=0.0d0
-          gvdwpp(j,i)=0.0d0
-          gel_loc(j,i)=0.0d0
-          gel_loc_long(j,i)=0.0d0
-         ghpbc(j,i)=0.0D0
-         ghpbx(j,i)=0.0D0
-          gcorr3_turn(j,i)=0.0d0
-          gcorr4_turn(j,i)=0.0d0
-          gradcorr(j,i)=0.0d0
-          gradcorr_long(j,i)=0.0d0
-          gradcorr5_long(j,i)=0.0d0
-          gradcorr6_long(j,i)=0.0d0
-          gcorr6_turn_long(j,i)=0.0d0
-          gradcorr5(j,i)=0.0d0
-          gradcorr6(j,i)=0.0d0
-          gcorr6_turn(j,i)=0.0d0
-          gsccorc(j,i)=0.0d0
-          gsccorx(j,i)=0.0d0
-          gradc(j,i,icg)=0.0d0
-          gradx(j,i,icg)=0.0d0
-          gscloc(j,i)=0.0d0
-          gsclocx(j,i)=0.0d0
-          gliptran(j,i)=0.0d0
-          gshieldx(j,i)=0.0d0
-          gshieldc(j,i)=0.0d0
-          gshieldc_loc(j,i)=0.0d0
-          gshieldx_ec(j,i)=0.0d0
-          gshieldc_ec(j,i)=0.0d0
-          gshieldc_loc_ec(j,i)=0.0d0
-          gshieldx_t3(j,i)=0.0d0
-          gshieldc_t3(j,i)=0.0d0
-          gshieldc_loc_t3(j,i)=0.0d0
-          gshieldx_t4(j,i)=0.0d0
-          gshieldc_t4(j,i)=0.0d0
-          gshieldc_loc_t4(j,i)=0.0d0
-          gshieldx_ll(j,i)=0.0d0
-          gshieldc_ll(j,i)=0.0d0
-          gshieldc_loc_ll(j,i)=0.0d0
-
-          do intertyp=1,3
-           gloc_sc(intertyp,i,icg)=0.0d0
-          enddo
-        enddo
-      enddo
-      do i=1,nres
-       do j=1,maxcontsshi
-       shield_list(j,i)=0
-        do k=1,3
-!C           print *,i,j,k
-           grad_shield_side(k,j,i)=0.0d0
-           grad_shield_loc(k,j,i)=0.0d0
-         enddo
-       enddo
-       ishield_list(i)=0
-      enddo
+#if defined(MPI) && defined(PARINTDER)
+            if (nfgtasks.gt.1 .and. me.eq.king) &
+            call MPI_Bcast(8,1,MPI_INTEGER,king,FG_COMM,IERROR)
+#endif
+            pi4 = 0.5d0*pipol
+            pi34 = 3*pi4
 
 
-!
-! Initialize the gradient of local energy terms.
-!
-!      allocate(gloc(4*nres,2))        !!(maxvar,2)(maxvar=6*maxres)
-!      if (.not.allocated(gel_loc_loc)) allocate(gel_loc_loc(nres)) !(maxvar)(maxvar=6*maxres)
-!      if (.not.allocated(gcorr_loc)) allocate(gcorr_loc(nres)) !(maxvar)(maxvar=6*maxres)
-!      allocate(g_corr5_loc(nres),g_corr6_loc(nres))   !(maxvar)(maxvar=6*maxres)
-!      allocate(gel_loc_turn3(nres))
-!      allocate(gel_loc_turn4(nres),gel_loc_turn6(nres))  !(maxvar)(maxvar=6*maxres)
-!      allocate(gsccor_loc(nres))      !(maxres)
+      !      allocate(dtheta(3,2,nres))      !(3,2,maxres)
+      !      allocate(dphi(3,3,nres),dalpha(3,3,nres),domega(3,3,nres)) !(3,3,maxres)
 
 
-      do i=1,4*nres
-        gloc(i,icg)=0.0D0
-      enddo
-      do i=1,nres
-        gel_loc_loc(i)=0.0d0
-        gcorr_loc(i)=0.0d0
-        g_corr5_loc(i)=0.0d0
-        g_corr6_loc(i)=0.0d0
-        gel_loc_turn3(i)=0.0d0
-        gel_loc_turn4(i)=0.0d0
-        gel_loc_turn6(i)=0.0d0
-        gsccor_loc(i)=0.0d0
-      enddo
-! initialize gcart and gxcart
-!      allocate(gcart(3,0:nres),gxcart(3,0:nres)) !(3,0:MAXRES)
-      do i=0,nres
-        do j=1,3
-          gcart(j,i)=0.0d0
-          gxcart(j,i)=0.0d0
-        enddo
-      enddo
-      return
-      end subroutine zerograd
-!-----------------------------------------------------------------------------
-      real(kind=8) function fdum()
-      fdum=0.0D0
-      return
-      end function fdum
-!-----------------------------------------------------------------------------
-! intcartderiv.F
-!-----------------------------------------------------------------------------
-      subroutine intcartderiv
-!      implicit real*8 (a-h,o-z)
-!      include 'DIMENSIONS'
-#ifdef MPI
-      include 'mpif.h'
-#endif
-!      include 'COMMON.SETUP'
-!      include 'COMMON.CHAIN' 
-!      include 'COMMON.VAR'
-!      include 'COMMON.GEO'
-!      include 'COMMON.INTERACT'
-!      include 'COMMON.DERIV'
-!      include 'COMMON.IOUNITS'
-!      include 'COMMON.LOCAL'
-!      include 'COMMON.SCCOR'
-      real(kind=8) :: pi4,pi34
-      real(kind=8),dimension(3,2,nres) :: dcostheta ! (3,2,maxres)
-      real(kind=8),dimension(3,3,nres) :: dcosphi,dsinphi,dcosalpha,&
-                    dcosomega,dsinomega !(3,3,maxres)
-      real(kind=8),dimension(3) :: vo1,vo2,vo3,dummy,vp1,vp2,vp3,vpp1,n
-    
-      integer :: i,j,k
-      real(kind=8) :: cost,sint,cost1,sint1,cost2,sint2,sing,cosg,scalp,&
-                  fac0,fac1,fac2,fac3,fac4,fac5,fac6,ctgt,ctgt1,cosg_inv,&
-                  fac7,fac8,fac9,scala1,scala2,cosa,sina,sino,fac15,fac16,&
-                  fac17,coso_inv,fac10,fac11,fac12,fac13,fac14
-      integer :: nres2
-      nres2=2*nres
-
-!el from module energy-------------
-!el      allocate(dcostau(3,3,3,itau_start:itau_end)) !(3,3,3,maxres2)maxres2=2*maxres
-!el      allocate(dsintau(3,3,3,itau_start:itau_end))
-!el      allocate(dtauangle(3,3,3,itau_start:itau_end))
-
-!el      allocate(dcostau(3,3,3,0:nres2)) !(3,3,3,maxres2)maxres2=2*maxres
-!el      allocate(dsintau(3,3,3,0:nres2))
-!el      allocate(dtauangle(3,3,3,0:nres2))
-!el      allocate(domicron(3,2,2,0:nres2))
-!el      allocate(dcosomicron(3,2,2,0:nres2))
-
-
-
-#if defined(MPI) && defined(PARINTDER)
-      if (nfgtasks.gt.1 .and. me.eq.king) &
-        call MPI_Bcast(8,1,MPI_INTEGER,king,FG_COMM,IERROR)
-#endif
-      pi4 = 0.5d0*pipol
-      pi34 = 3*pi4
-
-!      allocate(dtheta(3,2,nres))      !(3,2,maxres)
-!      allocate(dphi(3,3,nres),dalpha(3,3,nres),domega(3,3,nres)) !(3,3,maxres)
-
-!     write (iout,*) "iphi1_start",iphi1_start," iphi1_end",iphi1_end
-      do i=1,nres
-        do j=1,3
-          dtheta(j,1,i)=0.0d0
-          dtheta(j,2,i)=0.0d0
-          dphi(j,1,i)=0.0d0
-          dphi(j,2,i)=0.0d0
-          dphi(j,3,i)=0.0d0
-        enddo
-      enddo
-! Derivatives of theta's
+      !     write (iout,*) "iphi1_start",iphi1_start," iphi1_end",iphi1_end
+            do i=1,nres
+            do j=1,3
+              dtheta(j,1,i)=0.0d0
+              dtheta(j,2,i)=0.0d0
+              dphi(j,1,i)=0.0d0
+              dphi(j,2,i)=0.0d0
+              dphi(j,3,i)=0.0d0
+            enddo
+            enddo
+      ! Derivatives of theta's
 #if defined(MPI) && defined(PARINTDER)
 #if defined(MPI) && defined(PARINTDER)
-! We need dtheta(:,:,i-1) to compute dphi(:,:,i)
-      do i=max0(ithet_start-1,3),ithet_end
+      ! We need dtheta(:,:,i-1) to compute dphi(:,:,i)
+            do i=max0(ithet_start-1,3),ithet_end
 #else
 #else
-      do i=3,nres
+            do i=3,nres
 #endif
 #endif
-        cost=dcos(theta(i))
-       sint=sqrt(1-cost*cost)
-        do j=1,3
-          dcostheta(j,1,i)=-(dc_norm(j,i-1)+cost*dc_norm(j,i-2))/&
-         vbld(i-1)
-          if (itype(i-1).ne.ntyp1) dtheta(j,1,i)=-dcostheta(j,1,i)/sint
-          dcostheta(j,2,i)=-(dc_norm(j,i-2)+cost*dc_norm(j,i-1))/&
-         vbld(i)
-          if (itype(i-1).ne.ntyp1) dtheta(j,2,i)=-dcostheta(j,2,i)/sint
-        enddo
-      enddo
+            cost=dcos(theta(i))
+            sint=sqrt(1-cost*cost)
+            do j=1,3
+              dcostheta(j,1,i)=-(dc_norm(j,i-1)+cost*dc_norm(j,i-2))/&
+              vbld(i-1)
+              if (itype(i-1,1).ne.ntyp1) dtheta(j,1,i)=-dcostheta(j,1,i)/sint
+              dcostheta(j,2,i)=-(dc_norm(j,i-2)+cost*dc_norm(j,i-1))/&
+              vbld(i)
+              if (itype(i-1,1).ne.ntyp1) dtheta(j,2,i)=-dcostheta(j,2,i)/sint
+            enddo
+            enddo
 #if defined(MPI) && defined(PARINTDER)
 #if defined(MPI) && defined(PARINTDER)
-! We need dtheta(:,:,i-1) to compute dphi(:,:,i)
-      do i=max0(ithet_start-1,3),ithet_end
+      ! We need dtheta(:,:,i-1) to compute dphi(:,:,i)
+            do i=max0(ithet_start-1,3),ithet_end
 #else
 #else
-      do i=3,nres
+            do i=3,nres
 #endif
 #endif
-      if ((itype(i-1).ne.10).and.(itype(i-1).ne.ntyp1)) then
-        cost1=dcos(omicron(1,i))
-        sint1=sqrt(1-cost1*cost1)
-        cost2=dcos(omicron(2,i))
-        sint2=sqrt(1-cost2*cost2)
-       do j=1,3
-!C Calculate derivative over first omicron (Cai-2,Cai-1,SCi-1) 
-          dcosomicron(j,1,1,i)=-(dc_norm(j,i-1+nres)+ &
-          cost1*dc_norm(j,i-2))/ &
-          vbld(i-1)
-          domicron(j,1,1,i)=-1/sint1*dcosomicron(j,1,1,i)
-          dcosomicron(j,1,2,i)=-(dc_norm(j,i-2) &
-          +cost1*(dc_norm(j,i-1+nres)))/ &
-          vbld(i-1+nres)
-          domicron(j,1,2,i)=-1/sint1*dcosomicron(j,1,2,i)
-!C Calculate derivative over second omicron Sci-1,Cai-1 Cai
-!C Looks messy but better than if in loop
-          dcosomicron(j,2,1,i)=-(-dc_norm(j,i-1+nres) &
-          +cost2*dc_norm(j,i-1))/ &
-          vbld(i)
-          domicron(j,2,1,i)=-1/sint2*dcosomicron(j,2,1,i)
-          dcosomicron(j,2,2,i)=-(dc_norm(j,i-1) &
-           +cost2*(-dc_norm(j,i-1+nres)))/ &
-          vbld(i-1+nres)
-!          write(iout,*) "vbld", i,itype(i),vbld(i-1+nres)
-          domicron(j,2,2,i)=-1/sint2*dcosomicron(j,2,2,i)
-        enddo
-       endif
-      enddo
-!elwrite(iout,*) "after vbld write"
-! Derivatives of phi:
-! If phi is 0 or 180 degrees, then the formulas 
-! have to be derived by power series expansion of the
-! conventional formulas around 0 and 180.
+            if ((itype(i-1,1).ne.10).and.(itype(i-1,1).ne.ntyp1)) then
+            cost1=dcos(omicron(1,i))
+            sint1=sqrt(1-cost1*cost1)
+            cost2=dcos(omicron(2,i))
+            sint2=sqrt(1-cost2*cost2)
+             do j=1,3
+      !C Calculate derivative over first omicron (Cai-2,Cai-1,SCi-1) 
+              dcosomicron(j,1,1,i)=-(dc_norm(j,i-1+nres)+ &
+              cost1*dc_norm(j,i-2))/ &
+              vbld(i-1)
+              domicron(j,1,1,i)=-1/sint1*dcosomicron(j,1,1,i)
+              dcosomicron(j,1,2,i)=-(dc_norm(j,i-2) &
+              +cost1*(dc_norm(j,i-1+nres)))/ &
+              vbld(i-1+nres)
+              domicron(j,1,2,i)=-1/sint1*dcosomicron(j,1,2,i)
+      !C Calculate derivative over second omicron Sci-1,Cai-1 Cai
+      !C Looks messy but better than if in loop
+              dcosomicron(j,2,1,i)=-(-dc_norm(j,i-1+nres) &
+              +cost2*dc_norm(j,i-1))/ &
+              vbld(i)
+              domicron(j,2,1,i)=-1/sint2*dcosomicron(j,2,1,i)
+              dcosomicron(j,2,2,i)=-(dc_norm(j,i-1) &
+               +cost2*(-dc_norm(j,i-1+nres)))/ &
+              vbld(i-1+nres)
+      !          write(iout,*) "vbld", i,itype(i,1),vbld(i-1+nres)
+              domicron(j,2,2,i)=-1/sint2*dcosomicron(j,2,2,i)
+            enddo
+             endif
+            enddo
+      !elwrite(iout,*) "after vbld write"
+      ! Derivatives of phi:
+      ! If phi is 0 or 180 degrees, then the formulas 
+      ! have to be derived by power series expansion of the
+      ! conventional formulas around 0 and 180.
 #ifdef PARINTDER
 #ifdef PARINTDER
-      do i=iphi1_start,iphi1_end
+            do i=iphi1_start,iphi1_end
 #else
 #else
-      do i=4,nres      
+            do i=4,nres      
 #endif
 #endif
-!        if (itype(i-1).eq.21 .or. itype(i-2).eq.21 ) cycle
-! the conventional case
-        sint=dsin(theta(i))
-       sint1=dsin(theta(i-1))
-        sing=dsin(phi(i))
-       cost=dcos(theta(i))
-        cost1=dcos(theta(i-1))
-       cosg=dcos(phi(i))
-        scalp=scalar(dc_norm(1,i-3),dc_norm(1,i-1))
-        fac0=1.0d0/(sint1*sint)
-        fac1=cost*fac0
-        fac2=cost1*fac0
-        fac3=cosg*cost1/(sint1*sint1)
-        fac4=cosg*cost/(sint*sint)
-!    Obtaining the gamma derivatives from sine derivative                               
-       if (phi(i).gt.-pi4.and.phi(i).le.pi4.or. &
-           phi(i).gt.pi34.and.phi(i).le.pi.or. &
-           phi(i).ge.-pi.and.phi(i).le.-pi34) then
-         call vecpr(dc_norm(1,i-1),dc_norm(1,i-2),vp1)
-         call vecpr(dc_norm(1,i-3),dc_norm(1,i-1),vp2)
-         call vecpr(dc_norm(1,i-3),dc_norm(1,i-2),vp3) 
-         do j=1,3
-            ctgt=cost/sint
-            ctgt1=cost1/sint1
-            cosg_inv=1.0d0/cosg
-            if (itype(i-1).ne.ntyp1 .and. itype(i-2).ne.ntyp1) then
-           dsinphi(j,1,i)=-sing*ctgt1*dtheta(j,1,i-1) &
-              -(fac0*vp1(j)+sing*dc_norm(j,i-3))*vbld_inv(i-2)
-            dphi(j,1,i)=cosg_inv*dsinphi(j,1,i)
-            dsinphi(j,2,i)= &
-              -sing*(ctgt1*dtheta(j,2,i-1)+ctgt*dtheta(j,1,i)) &
-              -(fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
-            dphi(j,2,i)=cosg_inv*dsinphi(j,2,i)
-            dsinphi(j,3,i)=-sing*ctgt*dtheta(j,2,i) &
-              +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i)
-!     &        +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i-1)
-            dphi(j,3,i)=cosg_inv*dsinphi(j,3,i)
-            endif
-! Bug fixed 3/24/05 (AL)
-        enddo                                              
-!   Obtaining the gamma derivatives from cosine derivative
-        else
-           do j=1,3
-           if (itype(i-1).ne.ntyp1 .and. itype(i-2).ne.ntyp1) then
-           dcosphi(j,1,i)=fac1*dcostheta(j,1,i-1)+fac3* &
-          dcostheta(j,1,i-1)-fac0*(dc_norm(j,i-1)-scalp* &
-           dc_norm(j,i-3))/vbld(i-2)
-           dphi(j,1,i)=-1/sing*dcosphi(j,1,i)       
-           dcosphi(j,2,i)=fac1*dcostheta(j,2,i-1)+fac2* &
-          dcostheta(j,1,i)+fac3*dcostheta(j,2,i-1)+fac4* &
-           dcostheta(j,1,i)
-           dphi(j,2,i)=-1/sing*dcosphi(j,2,i)      
-           dcosphi(j,3,i)=fac2*dcostheta(j,2,i)+fac4* &
-          dcostheta(j,2,i)-fac0*(dc_norm(j,i-3)-scalp* &
-           dc_norm(j,i-1))/vbld(i)
-           dphi(j,3,i)=-1/sing*dcosphi(j,3,i)       
-           endif
-         enddo
-        endif                                                                                           
-      enddo
-!alculate derivative of Tauangle
+      !        if (itype(i-1,1).eq.21 .or. itype(i-2,1).eq.21 ) cycle
+      ! the conventional case
+            sint=dsin(theta(i))
+            sint1=dsin(theta(i-1))
+            sing=dsin(phi(i))
+            cost=dcos(theta(i))
+            cost1=dcos(theta(i-1))
+            cosg=dcos(phi(i))
+            scalp=scalar(dc_norm(1,i-3),dc_norm(1,i-1))
+            fac0=1.0d0/(sint1*sint)
+            fac1=cost*fac0
+            fac2=cost1*fac0
+            fac3=cosg*cost1/(sint1*sint1)
+            fac4=cosg*cost/(sint*sint)
+      !    Obtaining the gamma derivatives from sine derivative                           
+             if (phi(i).gt.-pi4.and.phi(i).le.pi4.or. &
+               phi(i).gt.pi34.and.phi(i).le.pi.or. &
+               phi(i).ge.-pi.and.phi(i).le.-pi34) then
+             call vecpr(dc_norm(1,i-1),dc_norm(1,i-2),vp1)
+             call vecpr(dc_norm(1,i-3),dc_norm(1,i-1),vp2)
+             call vecpr(dc_norm(1,i-3),dc_norm(1,i-2),vp3) 
+             do j=1,3
+                ctgt=cost/sint
+                ctgt1=cost1/sint1
+                cosg_inv=1.0d0/cosg
+                if (itype(i-1,1).ne.ntyp1 .and. itype(i-2,1).ne.ntyp1) then
+                dsinphi(j,1,i)=-sing*ctgt1*dtheta(j,1,i-1) &
+                  -(fac0*vp1(j)+sing*dc_norm(j,i-3))*vbld_inv(i-2)
+                dphi(j,1,i)=cosg_inv*dsinphi(j,1,i)
+                dsinphi(j,2,i)= &
+                  -sing*(ctgt1*dtheta(j,2,i-1)+ctgt*dtheta(j,1,i)) &
+                  -(fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
+                dphi(j,2,i)=cosg_inv*dsinphi(j,2,i)
+                dsinphi(j,3,i)=-sing*ctgt*dtheta(j,2,i) &
+                  +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i)
+      !     &        +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i-1)
+                dphi(j,3,i)=cosg_inv*dsinphi(j,3,i)
+                endif
+      ! Bug fixed 3/24/05 (AL)
+             enddo                                                        
+      !   Obtaining the gamma derivatives from cosine derivative
+            else
+               do j=1,3
+               if (itype(i-1,1).ne.ntyp1 .and. itype(i-2,1).ne.ntyp1) then
+               dcosphi(j,1,i)=fac1*dcostheta(j,1,i-1)+fac3* &
+               dcostheta(j,1,i-1)-fac0*(dc_norm(j,i-1)-scalp* &
+               dc_norm(j,i-3))/vbld(i-2)
+               dphi(j,1,i)=-1/sing*dcosphi(j,1,i)       
+               dcosphi(j,2,i)=fac1*dcostheta(j,2,i-1)+fac2* &
+               dcostheta(j,1,i)+fac3*dcostheta(j,2,i-1)+fac4* &
+               dcostheta(j,1,i)
+               dphi(j,2,i)=-1/sing*dcosphi(j,2,i)      
+               dcosphi(j,3,i)=fac2*dcostheta(j,2,i)+fac4* &
+               dcostheta(j,2,i)-fac0*(dc_norm(j,i-3)-scalp* &
+               dc_norm(j,i-1))/vbld(i)
+               dphi(j,3,i)=-1/sing*dcosphi(j,3,i)       
+               endif
+             enddo
+            endif                                                                                                         
+            enddo
+      !alculate derivative of Tauangle
 #ifdef PARINTDER
 #ifdef PARINTDER
-      do i=itau_start,itau_end
+            do i=itau_start,itau_end
 #else
 #else
-      do i=3,nres
-!elwrite(iout,*) " vecpr",i,nres
+            do i=3,nres
+      !elwrite(iout,*) " vecpr",i,nres
 #endif
 #endif
-       if ((itype(i-2).eq.ntyp1).or.(itype(i-2).eq.10)) cycle
-!       if ((itype(i-2).eq.ntyp1).or.(itype(i-2).eq.10).or.
-!     &     (itype(i-1).eq.ntyp1).or.(itype(i).eq.ntyp1)) cycle
-!c dtauangle(j,intertyp,dervityp,residue number)
-!c INTERTYP=1 SC...Ca...Ca..Ca
-! the conventional case
-        sint=dsin(theta(i))
-        sint1=dsin(omicron(2,i-1))
-        sing=dsin(tauangle(1,i))
-        cost=dcos(theta(i))
-        cost1=dcos(omicron(2,i-1))
-        cosg=dcos(tauangle(1,i))
-!elwrite(iout,*) " vecpr5",i,nres
-        do j=1,3
-!elwrite(iout,*) " vecpreee",i,nres,j,i-2+nres
-!elwrite(iout,*) " vecpr5",dc_norm2(1,1)
-        dc_norm2(j,i-2+nres)=-dc_norm(j,i-2+nres)
-!       write(iout,*) dc_norm2(j,i-2+nres),"dcnorm"
-        enddo
-        scalp=scalar(dc_norm2(1,i-2+nres),dc_norm(1,i-1))
-        fac0=1.0d0/(sint1*sint)
-        fac1=cost*fac0
-        fac2=cost1*fac0
-        fac3=cosg*cost1/(sint1*sint1)
-        fac4=cosg*cost/(sint*sint)
-!        write(iout,*) "faki",fac0,fac1,fac2,fac3,fac4
-!    Obtaining the gamma derivatives from sine derivative                                
-       if (tauangle(1,i).gt.-pi4.and.tauangle(1,i).le.pi4.or. &
-           tauangle(1,i).gt.pi34.and.tauangle(1,i).le.pi.or. &
-           tauangle(1,i).gt.-pi.and.tauangle(1,i).le.-pi34) then
-         call vecpr(dc_norm(1,i-1),dc_norm(1,i-2),vp1)
-         call vecpr(dc_norm2(1,i-2+nres),dc_norm(1,i-1),vp2)
-         call vecpr(dc_norm2(1,i-2+nres),dc_norm(1,i-2),vp3)
-        do j=1,3
-            ctgt=cost/sint
-            ctgt1=cost1/sint1
-            cosg_inv=1.0d0/cosg
-            dsintau(j,1,1,i)=-sing*ctgt1*domicron(j,2,2,i-1) &
-       -(fac0*vp1(j)+sing*(dc_norm2(j,i-2+nres))) &
-       *vbld_inv(i-2+nres)
-            dtauangle(j,1,1,i)=cosg_inv*dsintau(j,1,1,i)
-            dsintau(j,1,2,i)= &
-              -sing*(ctgt1*domicron(j,2,1,i-1)+ctgt*dtheta(j,1,i)) &
-              -(fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
-!            write(iout,*) "dsintau", dsintau(j,1,2,i)
-            dtauangle(j,1,2,i)=cosg_inv*dsintau(j,1,2,i)
-! Bug fixed 3/24/05 (AL)
-            dsintau(j,1,3,i)=-sing*ctgt*dtheta(j,2,i) &
-              +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i)
-!     &        +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i-1)
-            dtauangle(j,1,3,i)=cosg_inv*dsintau(j,1,3,i)
-         enddo
-!   Obtaining the gamma derivatives from cosine derivative
-        else
-           do j=1,3
-           dcostau(j,1,1,i)=fac1*dcosomicron(j,2,2,i-1)+fac3* &
-           dcosomicron(j,2,2,i-1)-fac0*(dc_norm(j,i-1)-scalp* &
-           (dc_norm2(j,i-2+nres)))/vbld(i-2+nres)
-           dtauangle(j,1,1,i)=-1/sing*dcostau(j,1,1,i)
-           dcostau(j,1,2,i)=fac1*dcosomicron(j,2,1,i-1)+fac2* &
-           dcostheta(j,1,i)+fac3*dcosomicron(j,2,1,i-1)+fac4* &
-           dcostheta(j,1,i)
-           dtauangle(j,1,2,i)=-1/sing*dcostau(j,1,2,i)
-           dcostau(j,1,3,i)=fac2*dcostheta(j,2,i)+fac4* &
-           dcostheta(j,2,i)-fac0*(-dc_norm(j,i-2+nres)-scalp* &
-           dc_norm(j,i-1))/vbld(i)
-           dtauangle(j,1,3,i)=-1/sing*dcostau(j,1,3,i)
-!         write (iout,*) "else",i
-         enddo
-        endif
-!        do k=1,3                 
-!        write(iout,*) "tu",i,k,(dtauangle(j,1,k,i),j=1,3)        
-!        enddo                
-      enddo
-!C Second case Ca...Ca...Ca...SC
+             if ((itype(i-2,1).eq.ntyp1).or.(itype(i-2,1).eq.10)) cycle
+      !       if ((itype(i-2,1).eq.ntyp1).or.(itype(i-2,1).eq.10).or.
+      !     &     (itype(i-1,1).eq.ntyp1).or.(itype(i,1).eq.ntyp1)) cycle
+      !c dtauangle(j,intertyp,dervityp,residue number)
+      !c INTERTYP=1 SC...Ca...Ca..Ca
+      ! the conventional case
+            sint=dsin(theta(i))
+            sint1=dsin(omicron(2,i-1))
+            sing=dsin(tauangle(1,i))
+            cost=dcos(theta(i))
+            cost1=dcos(omicron(2,i-1))
+            cosg=dcos(tauangle(1,i))
+      !elwrite(iout,*) " vecpr5",i,nres
+            do j=1,3
+      !elwrite(iout,*) " vecpreee",i,nres,j,i-2+nres
+      !elwrite(iout,*) " vecpr5",dc_norm2(1,1)
+            dc_norm2(j,i-2+nres)=-dc_norm(j,i-2+nres)
+      !       write(iout,*) dc_norm2(j,i-2+nres),"dcnorm"
+            enddo
+            scalp=scalar(dc_norm2(1,i-2+nres),dc_norm(1,i-1))
+            fac0=1.0d0/(sint1*sint)
+            fac1=cost*fac0
+            fac2=cost1*fac0
+            fac3=cosg*cost1/(sint1*sint1)
+            fac4=cosg*cost/(sint*sint)
+      !        write(iout,*) "faki",fac0,fac1,fac2,fac3,fac4
+      !    Obtaining the gamma derivatives from sine derivative                                
+             if (tauangle(1,i).gt.-pi4.and.tauangle(1,i).le.pi4.or. &
+               tauangle(1,i).gt.pi34.and.tauangle(1,i).le.pi.or. &
+               tauangle(1,i).gt.-pi.and.tauangle(1,i).le.-pi34) then
+             call vecpr(dc_norm(1,i-1),dc_norm(1,i-2),vp1)
+             call vecpr(dc_norm2(1,i-2+nres),dc_norm(1,i-1),vp2)
+             call vecpr(dc_norm2(1,i-2+nres),dc_norm(1,i-2),vp3)
+            do j=1,3
+                ctgt=cost/sint
+                ctgt1=cost1/sint1
+                cosg_inv=1.0d0/cosg
+                dsintau(j,1,1,i)=-sing*ctgt1*domicron(j,2,2,i-1) &
+             -(fac0*vp1(j)+sing*(dc_norm2(j,i-2+nres))) &
+             *vbld_inv(i-2+nres)
+                dtauangle(j,1,1,i)=cosg_inv*dsintau(j,1,1,i)
+                dsintau(j,1,2,i)= &
+                  -sing*(ctgt1*domicron(j,2,1,i-1)+ctgt*dtheta(j,1,i)) &
+                  -(fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
+      !            write(iout,*) "dsintau", dsintau(j,1,2,i)
+                dtauangle(j,1,2,i)=cosg_inv*dsintau(j,1,2,i)
+      ! Bug fixed 3/24/05 (AL)
+                dsintau(j,1,3,i)=-sing*ctgt*dtheta(j,2,i) &
+                  +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i)
+      !     &        +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i-1)
+                dtauangle(j,1,3,i)=cosg_inv*dsintau(j,1,3,i)
+             enddo
+      !   Obtaining the gamma derivatives from cosine derivative
+            else
+               do j=1,3
+               dcostau(j,1,1,i)=fac1*dcosomicron(j,2,2,i-1)+fac3* &
+               dcosomicron(j,2,2,i-1)-fac0*(dc_norm(j,i-1)-scalp* &
+               (dc_norm2(j,i-2+nres)))/vbld(i-2+nres)
+               dtauangle(j,1,1,i)=-1/sing*dcostau(j,1,1,i)
+               dcostau(j,1,2,i)=fac1*dcosomicron(j,2,1,i-1)+fac2* &
+               dcostheta(j,1,i)+fac3*dcosomicron(j,2,1,i-1)+fac4* &
+               dcostheta(j,1,i)
+               dtauangle(j,1,2,i)=-1/sing*dcostau(j,1,2,i)
+               dcostau(j,1,3,i)=fac2*dcostheta(j,2,i)+fac4* &
+               dcostheta(j,2,i)-fac0*(-dc_norm(j,i-2+nres)-scalp* &
+               dc_norm(j,i-1))/vbld(i)
+               dtauangle(j,1,3,i)=-1/sing*dcostau(j,1,3,i)
+      !         write (iout,*) "else",i
+             enddo
+            endif
+      !        do k=1,3                 
+      !        write(iout,*) "tu",i,k,(dtauangle(j,1,k,i),j=1,3)        
+      !        enddo                
+            enddo
+      !C Second case Ca...Ca...Ca...SC
 #ifdef PARINTDER
 #ifdef PARINTDER
-      do i=itau_start,itau_end
+            do i=itau_start,itau_end
 #else
 #else
-      do i=4,nres
+            do i=4,nres
 #endif
 #endif
-       if ((itype(i-1).eq.ntyp1).or.(itype(i-1).eq.10).or. &
-          (itype(i-2).eq.ntyp1).or.(itype(i-3).eq.ntyp1)) cycle
-! the conventional case
-        sint=dsin(omicron(1,i))
-        sint1=dsin(theta(i-1))
-        sing=dsin(tauangle(2,i))
-        cost=dcos(omicron(1,i))
-        cost1=dcos(theta(i-1))
-        cosg=dcos(tauangle(2,i))
-!        do j=1,3
-!        dc_norm2(j,i-1+nres)=-dc_norm(j,i-1+nres)
-!        enddo
-        scalp=scalar(dc_norm(1,i-3),dc_norm(1,i-1+nres))
-        fac0=1.0d0/(sint1*sint)
-        fac1=cost*fac0
-        fac2=cost1*fac0
-        fac3=cosg*cost1/(sint1*sint1)
-        fac4=cosg*cost/(sint*sint)
-!    Obtaining the gamma derivatives from sine derivative                                
-       if (tauangle(2,i).gt.-pi4.and.tauangle(2,i).le.pi4.or. &
-           tauangle(2,i).gt.pi34.and.tauangle(2,i).le.pi.or. &
-           tauangle(2,i).gt.-pi.and.tauangle(2,i).le.-pi34) then
-         call vecpr(dc_norm2(1,i-1+nres),dc_norm(1,i-2),vp1)
-         call vecpr(dc_norm(1,i-3),dc_norm(1,i-1+nres),vp2)
-         call vecpr(dc_norm(1,i-3),dc_norm(1,i-2),vp3)
-        do j=1,3
-            ctgt=cost/sint
-            ctgt1=cost1/sint1
-            cosg_inv=1.0d0/cosg
-            dsintau(j,2,1,i)=-sing*ctgt1*dtheta(j,1,i-1) &
-              +(fac0*vp1(j)-sing*dc_norm(j,i-3))*vbld_inv(i-2)
-!       write(iout,*) i,j,dsintau(j,2,1,i),sing*ctgt1*dtheta(j,1,i-1),
-!     &fac0*vp1(j),sing*dc_norm(j,i-3),vbld_inv(i-2),"dsintau(2,1)"
-            dtauangle(j,2,1,i)=cosg_inv*dsintau(j,2,1,i)
-            dsintau(j,2,2,i)= &
-              -sing*(ctgt1*dtheta(j,2,i-1)+ctgt*domicron(j,1,1,i)) &
-              -(fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
-!            write(iout,*) "sprawdzenie",i,j,sing*ctgt1*dtheta(j,2,i-1),
-!     & sing*ctgt*domicron(j,1,2,i),
-!     & (fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
-            dtauangle(j,2,2,i)=cosg_inv*dsintau(j,2,2,i)
-! Bug fixed 3/24/05 (AL)
-            dsintau(j,2,3,i)=-sing*ctgt*domicron(j,1,2,i) &
-             +(fac0*vp3(j)-sing*dc_norm(j,i-1+nres))*vbld_inv(i-1+nres)
-!     &        +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i-1)
-            dtauangle(j,2,3,i)=cosg_inv*dsintau(j,2,3,i)
-         enddo
-!   Obtaining the gamma derivatives from cosine derivative
-        else
-           do j=1,3
-           dcostau(j,2,1,i)=fac1*dcostheta(j,1,i-1)+fac3* &
-           dcostheta(j,1,i-1)-fac0*(dc_norm(j,i-1+nres)-scalp* &
-           dc_norm(j,i-3))/vbld(i-2)
-           dtauangle(j,2,1,i)=-1/sing*dcostau(j,2,1,i)
-           dcostau(j,2,2,i)=fac1*dcostheta(j,2,i-1)+fac2* &
-           dcosomicron(j,1,1,i)+fac3*dcostheta(j,2,i-1)+fac4* &
-           dcosomicron(j,1,1,i)
-           dtauangle(j,2,2,i)=-1/sing*dcostau(j,2,2,i)
-           dcostau(j,2,3,i)=fac2*dcosomicron(j,1,2,i)+fac4* &
-           dcosomicron(j,1,2,i)-fac0*(dc_norm(j,i-3)-scalp* &
-           dc_norm(j,i-1+nres))/vbld(i-1+nres)
-           dtauangle(j,2,3,i)=-1/sing*dcostau(j,2,3,i)
-!        write(iout,*) i,j,"else", dtauangle(j,2,3,i) 
-         enddo
-        endif                                    
-      enddo
+             if ((itype(i-1,1).eq.ntyp1).or.(itype(i-1,1).eq.10).or. &
+              (itype(i-2,1).eq.ntyp1).or.(itype(i-3,1).eq.ntyp1)) cycle
+      ! the conventional case
+            sint=dsin(omicron(1,i))
+            sint1=dsin(theta(i-1))
+            sing=dsin(tauangle(2,i))
+            cost=dcos(omicron(1,i))
+            cost1=dcos(theta(i-1))
+            cosg=dcos(tauangle(2,i))
+      !        do j=1,3
+      !        dc_norm2(j,i-1+nres)=-dc_norm(j,i-1+nres)
+      !        enddo
+            scalp=scalar(dc_norm(1,i-3),dc_norm(1,i-1+nres))
+            fac0=1.0d0/(sint1*sint)
+            fac1=cost*fac0
+            fac2=cost1*fac0
+            fac3=cosg*cost1/(sint1*sint1)
+            fac4=cosg*cost/(sint*sint)
+      !    Obtaining the gamma derivatives from sine derivative                                
+             if (tauangle(2,i).gt.-pi4.and.tauangle(2,i).le.pi4.or. &
+               tauangle(2,i).gt.pi34.and.tauangle(2,i).le.pi.or. &
+               tauangle(2,i).gt.-pi.and.tauangle(2,i).le.-pi34) then
+             call vecpr(dc_norm2(1,i-1+nres),dc_norm(1,i-2),vp1)
+             call vecpr(dc_norm(1,i-3),dc_norm(1,i-1+nres),vp2)
+             call vecpr(dc_norm(1,i-3),dc_norm(1,i-2),vp3)
+            do j=1,3
+                ctgt=cost/sint
+                ctgt1=cost1/sint1
+                cosg_inv=1.0d0/cosg
+                dsintau(j,2,1,i)=-sing*ctgt1*dtheta(j,1,i-1) &
+                  +(fac0*vp1(j)-sing*dc_norm(j,i-3))*vbld_inv(i-2)
+      !       write(iout,*) i,j,dsintau(j,2,1,i),sing*ctgt1*dtheta(j,1,i-1),
+      !     &fac0*vp1(j),sing*dc_norm(j,i-3),vbld_inv(i-2),"dsintau(2,1)"
+                dtauangle(j,2,1,i)=cosg_inv*dsintau(j,2,1,i)
+                dsintau(j,2,2,i)= &
+                  -sing*(ctgt1*dtheta(j,2,i-1)+ctgt*domicron(j,1,1,i)) &
+                  -(fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
+      !            write(iout,*) "sprawdzenie",i,j,sing*ctgt1*dtheta(j,2,i-1),
+      !     & sing*ctgt*domicron(j,1,2,i),
+      !     & (fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
+                dtauangle(j,2,2,i)=cosg_inv*dsintau(j,2,2,i)
+      ! Bug fixed 3/24/05 (AL)
+                dsintau(j,2,3,i)=-sing*ctgt*domicron(j,1,2,i) &
+                 +(fac0*vp3(j)-sing*dc_norm(j,i-1+nres))*vbld_inv(i-1+nres)
+      !     &        +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i-1)
+                dtauangle(j,2,3,i)=cosg_inv*dsintau(j,2,3,i)
+             enddo
+      !   Obtaining the gamma derivatives from cosine derivative
+            else
+               do j=1,3
+               dcostau(j,2,1,i)=fac1*dcostheta(j,1,i-1)+fac3* &
+               dcostheta(j,1,i-1)-fac0*(dc_norm(j,i-1+nres)-scalp* &
+               dc_norm(j,i-3))/vbld(i-2)
+               dtauangle(j,2,1,i)=-1/sing*dcostau(j,2,1,i)
+               dcostau(j,2,2,i)=fac1*dcostheta(j,2,i-1)+fac2* &
+               dcosomicron(j,1,1,i)+fac3*dcostheta(j,2,i-1)+fac4* &
+               dcosomicron(j,1,1,i)
+               dtauangle(j,2,2,i)=-1/sing*dcostau(j,2,2,i)
+               dcostau(j,2,3,i)=fac2*dcosomicron(j,1,2,i)+fac4* &
+               dcosomicron(j,1,2,i)-fac0*(dc_norm(j,i-3)-scalp* &
+               dc_norm(j,i-1+nres))/vbld(i-1+nres)
+               dtauangle(j,2,3,i)=-1/sing*dcostau(j,2,3,i)
+      !        write(iout,*) i,j,"else", dtauangle(j,2,3,i) 
+             enddo
+            endif                                    
+            enddo
 
 
-!CC third case SC...Ca...Ca...SC
+      !CC third case SC...Ca...Ca...SC
 #ifdef PARINTDER
 
 #ifdef PARINTDER
 
-      do i=itau_start,itau_end
+            do i=itau_start,itau_end
 #else
 #else
-      do i=3,nres
+            do i=3,nres
 #endif
 #endif
-! the conventional case
-      if ((itype(i-1).eq.ntyp1).or.(itype(i-1).eq.10).or. &
-      (itype(i-2).eq.ntyp1).or.(itype(i-2).eq.10)) cycle
-        sint=dsin(omicron(1,i))
-        sint1=dsin(omicron(2,i-1))
-        sing=dsin(tauangle(3,i))
-        cost=dcos(omicron(1,i))
-        cost1=dcos(omicron(2,i-1))
-        cosg=dcos(tauangle(3,i))
-        do j=1,3
-        dc_norm2(j,i-2+nres)=-dc_norm(j,i-2+nres)
-!        dc_norm2(j,i-1+nres)=-dc_norm(j,i-1+nres)
-        enddo
-        scalp=scalar(dc_norm2(1,i-2+nres),dc_norm(1,i-1+nres))
-        fac0=1.0d0/(sint1*sint)
-        fac1=cost*fac0
-        fac2=cost1*fac0
-        fac3=cosg*cost1/(sint1*sint1)
-        fac4=cosg*cost/(sint*sint)
-!    Obtaining the gamma derivatives from sine derivative                                
-       if (tauangle(3,i).gt.-pi4.and.tauangle(3,i).le.pi4.or. &
-           tauangle(3,i).gt.pi34.and.tauangle(3,i).le.pi.or. &
-           tauangle(3,i).gt.-pi.and.tauangle(3,i).le.-pi34) then
-         call vecpr(dc_norm(1,i-1+nres),dc_norm(1,i-2),vp1)
-         call vecpr(dc_norm2(1,i-2+nres),dc_norm(1,i-1+nres),vp2)
-         call vecpr(dc_norm2(1,i-2+nres),dc_norm(1,i-2),vp3)
-        do j=1,3
-            ctgt=cost/sint
-            ctgt1=cost1/sint1
-            cosg_inv=1.0d0/cosg
-            dsintau(j,3,1,i)=-sing*ctgt1*domicron(j,2,2,i-1) &
-              -(fac0*vp1(j)-sing*dc_norm(j,i-2+nres)) &
-              *vbld_inv(i-2+nres)
-            dtauangle(j,3,1,i)=cosg_inv*dsintau(j,3,1,i)
-            dsintau(j,3,2,i)= &
-              -sing*(ctgt1*domicron(j,2,1,i-1)+ctgt*domicron(j,1,1,i)) &
-              -(fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
-            dtauangle(j,3,2,i)=cosg_inv*dsintau(j,3,2,i)
-! Bug fixed 3/24/05 (AL)
-            dsintau(j,3,3,i)=-sing*ctgt*domicron(j,1,2,i) &
-              +(fac0*vp3(j)-sing*dc_norm(j,i-1+nres)) &
-              *vbld_inv(i-1+nres)
-!     &        +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i-1)
-            dtauangle(j,3,3,i)=cosg_inv*dsintau(j,3,3,i)
-         enddo
-!   Obtaining the gamma derivatives from cosine derivative
-        else
-           do j=1,3
-           dcostau(j,3,1,i)=fac1*dcosomicron(j,2,2,i-1)+fac3* &
-           dcosomicron(j,2,2,i-1)-fac0*(dc_norm(j,i-1+nres)-scalp* &
-           dc_norm2(j,i-2+nres))/vbld(i-2+nres)
-           dtauangle(j,3,1,i)=-1/sing*dcostau(j,3,1,i)
-           dcostau(j,3,2,i)=fac1*dcosomicron(j,2,1,i-1)+fac2* &
-           dcosomicron(j,1,1,i)+fac3*dcosomicron(j,2,1,i-1)+fac4* &
-           dcosomicron(j,1,1,i)
-           dtauangle(j,3,2,i)=-1/sing*dcostau(j,3,2,i)
-           dcostau(j,3,3,i)=fac2*dcosomicron(j,1,2,i)+fac4* &
-           dcosomicron(j,1,2,i)-fac0*(dc_norm2(j,i-2+nres)-scalp* &
-           dc_norm(j,i-1+nres))/vbld(i-1+nres)
-           dtauangle(j,3,3,i)=-1/sing*dcostau(j,3,3,i)
-!          write(iout,*) "else",i 
-         enddo
-        endif                                                                                            
-      enddo
+      ! the conventional case
+            if ((itype(i-1,1).eq.ntyp1).or.(itype(i-1,1).eq.10).or. &
+            (itype(i-2,1).eq.ntyp1).or.(itype(i-2,1).eq.10)) cycle
+            sint=dsin(omicron(1,i))
+            sint1=dsin(omicron(2,i-1))
+            sing=dsin(tauangle(3,i))
+            cost=dcos(omicron(1,i))
+            cost1=dcos(omicron(2,i-1))
+            cosg=dcos(tauangle(3,i))
+            do j=1,3
+            dc_norm2(j,i-2+nres)=-dc_norm(j,i-2+nres)
+      !        dc_norm2(j,i-1+nres)=-dc_norm(j,i-1+nres)
+            enddo
+            scalp=scalar(dc_norm2(1,i-2+nres),dc_norm(1,i-1+nres))
+            fac0=1.0d0/(sint1*sint)
+            fac1=cost*fac0
+            fac2=cost1*fac0
+            fac3=cosg*cost1/(sint1*sint1)
+            fac4=cosg*cost/(sint*sint)
+      !    Obtaining the gamma derivatives from sine derivative                                
+             if (tauangle(3,i).gt.-pi4.and.tauangle(3,i).le.pi4.or. &
+               tauangle(3,i).gt.pi34.and.tauangle(3,i).le.pi.or. &
+               tauangle(3,i).gt.-pi.and.tauangle(3,i).le.-pi34) then
+             call vecpr(dc_norm(1,i-1+nres),dc_norm(1,i-2),vp1)
+             call vecpr(dc_norm2(1,i-2+nres),dc_norm(1,i-1+nres),vp2)
+             call vecpr(dc_norm2(1,i-2+nres),dc_norm(1,i-2),vp3)
+            do j=1,3
+                ctgt=cost/sint
+                ctgt1=cost1/sint1
+                cosg_inv=1.0d0/cosg
+                dsintau(j,3,1,i)=-sing*ctgt1*domicron(j,2,2,i-1) &
+                  -(fac0*vp1(j)-sing*dc_norm(j,i-2+nres)) &
+                  *vbld_inv(i-2+nres)
+                dtauangle(j,3,1,i)=cosg_inv*dsintau(j,3,1,i)
+                dsintau(j,3,2,i)= &
+                  -sing*(ctgt1*domicron(j,2,1,i-1)+ctgt*domicron(j,1,1,i)) &
+                  -(fac0*vp2(j)+sing*dc_norm(j,i-2))*vbld_inv(i-1)
+                dtauangle(j,3,2,i)=cosg_inv*dsintau(j,3,2,i)
+      ! Bug fixed 3/24/05 (AL)
+                dsintau(j,3,3,i)=-sing*ctgt*domicron(j,1,2,i) &
+                  +(fac0*vp3(j)-sing*dc_norm(j,i-1+nres)) &
+                  *vbld_inv(i-1+nres)
+      !     &        +(fac0*vp3(j)-sing*dc_norm(j,i-1))*vbld_inv(i-1)
+                dtauangle(j,3,3,i)=cosg_inv*dsintau(j,3,3,i)
+             enddo
+      !   Obtaining the gamma derivatives from cosine derivative
+            else
+               do j=1,3
+               dcostau(j,3,1,i)=fac1*dcosomicron(j,2,2,i-1)+fac3* &
+               dcosomicron(j,2,2,i-1)-fac0*(dc_norm(j,i-1+nres)-scalp* &
+               dc_norm2(j,i-2+nres))/vbld(i-2+nres)
+               dtauangle(j,3,1,i)=-1/sing*dcostau(j,3,1,i)
+               dcostau(j,3,2,i)=fac1*dcosomicron(j,2,1,i-1)+fac2* &
+               dcosomicron(j,1,1,i)+fac3*dcosomicron(j,2,1,i-1)+fac4* &
+               dcosomicron(j,1,1,i)
+               dtauangle(j,3,2,i)=-1/sing*dcostau(j,3,2,i)
+               dcostau(j,3,3,i)=fac2*dcosomicron(j,1,2,i)+fac4* &
+               dcosomicron(j,1,2,i)-fac0*(dc_norm2(j,i-2+nres)-scalp* &
+               dc_norm(j,i-1+nres))/vbld(i-1+nres)
+               dtauangle(j,3,3,i)=-1/sing*dcostau(j,3,3,i)
+      !          write(iout,*) "else",i 
+             enddo
+            endif                                                                                            
+            enddo
 
 #ifdef CRYST_SC
 
 #ifdef CRYST_SC
-!   Derivatives of side-chain angles alpha and omega
+      !   Derivatives of side-chain angles alpha and omega
 #if defined(MPI) && defined(PARINTDER)
 #if defined(MPI) && defined(PARINTDER)
-        do i=ibond_start,ibond_end
+            do i=ibond_start,ibond_end
 #else
 #else
-        do i=2,nres-1          
+            do i=2,nres-1          
 #endif
 #endif
-          if(itype(i).ne.10 .and. itype(i).ne.ntyp1) then        
-             fac5=1.0d0/dsqrt(2*(1+dcos(theta(i+1))))
-             fac6=fac5/vbld(i)
-             fac7=fac5*fac5
-             fac8=fac5/vbld(i+1)     
-             fac9=fac5/vbld(i+nres)                 
-             scala1=scalar(dc_norm(1,i-1),dc_norm(1,i+nres))
-            scala2=scalar(dc_norm(1,i),dc_norm(1,i+nres))
-            cosa=dsqrt(0.5d0/(1.0d0+dcos(theta(i+1))))* &
-             (scalar(dC_norm(1,i),dC_norm(1,i+nres)) &
-             -scalar(dC_norm(1,i-1),dC_norm(1,i+nres)))
-             sina=sqrt(1-cosa*cosa)
-             sino=dsin(omeg(i))                                                                                                     
-!             write (iout,*) "i",i," cosa",cosa," sina",sina," sino",sino
-             do j=1,3    
-                dcosalpha(j,1,i)=fac6*(scala1*dc_norm(j,i-1)- &
-                dc_norm(j,i+nres))-cosa*fac7*dcostheta(j,1,i+1)
-                dalpha(j,1,i)=-1/sina*dcosalpha(j,1,i)
-                dcosalpha(j,2,i)=fac8*(dc_norm(j,i+nres)- &
-                scala2*dc_norm(j,i))-cosa*fac7*dcostheta(j,2,i+1)
-                dalpha(j,2,i)=-1/sina*dcosalpha(j,2,i)
-                dcosalpha(j,3,i)=(fac9*(dc_norm(j,i)- &
-               dc_norm(j,i-1))-(cosa*dc_norm(j,i+nres))/ &
-                vbld(i+nres))
-                dalpha(j,3,i)=-1/sina*dcosalpha(j,3,i)
-                   enddo
-! obtaining the derivatives of omega from sines            
-            if(omeg(i).gt.-pi4.and.omeg(i).le.pi4.or. &
-               omeg(i).gt.pi34.and.omeg(i).le.pi.or. &
-               omeg(i).gt.-pi.and.omeg(i).le.-pi34) then
-               fac15=dcos(theta(i+1))/(dsin(theta(i+1))* &
-              dsin(theta(i+1)))
-               fac16=dcos(alph(i))/(dsin(alph(i))*dsin(alph(i)))
-               fac17=1.0d0/(dsin(theta(i+1))*dsin(alph(i)))            
-               call vecpr(dc_norm(1,i+nres),dc_norm(1,i),vo1)
-               call vecpr(dc_norm(1,i+nres),dc_norm(1,i-1),vo2)
-               call vecpr(dc_norm(1,i),dc_norm(1,i-1),vo3)
-               coso_inv=1.0d0/dcos(omeg(i))                           
+              if(itype(i,1).ne.10 .and. itype(i,1).ne.ntyp1) then        
+                 fac5=1.0d0/dsqrt(2*(1+dcos(theta(i+1))))
+                 fac6=fac5/vbld(i)
+                 fac7=fac5*fac5
+                 fac8=fac5/vbld(i+1)     
+                 fac9=fac5/vbld(i+nres)                      
+                 scala1=scalar(dc_norm(1,i-1),dc_norm(1,i+nres))
+                 scala2=scalar(dc_norm(1,i),dc_norm(1,i+nres))
+                 cosa=dsqrt(0.5d0/(1.0d0+dcos(theta(i+1))))* &
+                 (scalar(dC_norm(1,i),dC_norm(1,i+nres)) &
+                 -scalar(dC_norm(1,i-1),dC_norm(1,i+nres)))
+                 sina=sqrt(1-cosa*cosa)
+                 sino=dsin(omeg(i))                                                                                                                                
+      !             write (iout,*) "i",i," cosa",cosa," sina",sina," sino",sino
+                 do j=1,3        
+                  dcosalpha(j,1,i)=fac6*(scala1*dc_norm(j,i-1)- &
+                  dc_norm(j,i+nres))-cosa*fac7*dcostheta(j,1,i+1)
+                  dalpha(j,1,i)=-1/sina*dcosalpha(j,1,i)
+                  dcosalpha(j,2,i)=fac8*(dc_norm(j,i+nres)- &
+                  scala2*dc_norm(j,i))-cosa*fac7*dcostheta(j,2,i+1)
+                  dalpha(j,2,i)=-1/sina*dcosalpha(j,2,i)
+                  dcosalpha(j,3,i)=(fac9*(dc_norm(j,i)- &
+                  dc_norm(j,i-1))-(cosa*dc_norm(j,i+nres))/ &
+                  vbld(i+nres))
+                  dalpha(j,3,i)=-1/sina*dcosalpha(j,3,i)
+                enddo
+      ! obtaining the derivatives of omega from sines          
+                if(omeg(i).gt.-pi4.and.omeg(i).le.pi4.or. &
+                   omeg(i).gt.pi34.and.omeg(i).le.pi.or. &
+                   omeg(i).gt.-pi.and.omeg(i).le.-pi34) then
+                   fac15=dcos(theta(i+1))/(dsin(theta(i+1))* &
+                   dsin(theta(i+1)))
+                   fac16=dcos(alph(i))/(dsin(alph(i))*dsin(alph(i)))
+                   fac17=1.0d0/(dsin(theta(i+1))*dsin(alph(i)))                   
+                   call vecpr(dc_norm(1,i+nres),dc_norm(1,i),vo1)
+                   call vecpr(dc_norm(1,i+nres),dc_norm(1,i-1),vo2)
+                   call vecpr(dc_norm(1,i),dc_norm(1,i-1),vo3)
+                   coso_inv=1.0d0/dcos(omeg(i))                                       
+                   do j=1,3
+                   dsinomega(j,1,i)=sino*(fac15*dcostheta(j,1,i+1) &
+                   +fac16*dcosalpha(j,1,i))-fac17/vbld(i)*vo1(j)- &
+                   (sino*dc_norm(j,i-1))/vbld(i)
+                   domega(j,1,i)=coso_inv*dsinomega(j,1,i)
+                   dsinomega(j,2,i)=sino*(fac15*dcostheta(j,2,i+1) &
+                   +fac16*dcosalpha(j,2,i))+fac17/vbld(i+1)*vo2(j) &
+                   -sino*dc_norm(j,i)/vbld(i+1)
+                   domega(j,2,i)=coso_inv*dsinomega(j,2,i)                                               
+                   dsinomega(j,3,i)=sino*fac16*dcosalpha(j,3,i)- &
+                   fac17/vbld(i+nres)*vo3(j)-sino*dc_norm(j,i+nres)/ &
+                   vbld(i+nres)
+                   domega(j,3,i)=coso_inv*dsinomega(j,3,i)
+                  enddo                           
+               else
+      !   obtaining the derivatives of omega from cosines
+                 fac10=sqrt(0.5d0*(1-dcos(theta(i+1))))
+                 fac11=sqrt(0.5d0*(1+dcos(theta(i+1))))
+                 fac12=fac10*sina
+                 fac13=fac12*fac12
+                 fac14=sina*sina
+                 do j=1,3                                     
+                  dcosomega(j,1,i)=(-(0.25d0*cosa/fac11* &
+                  dcostheta(j,1,i+1)+fac11*dcosalpha(j,1,i))*fac12+ &
+                  (0.25d0/fac10*sina*dcostheta(j,1,i+1)+cosa/sina* &
+                  fac10*dcosalpha(j,1,i))*(scala2-fac11*cosa))/fac13
+                  domega(j,1,i)=-1/sino*dcosomega(j,1,i)
+                  dcosomega(j,2,i)=(((dc_norm(j,i+nres)-scala2* &
+                  dc_norm(j,i))/vbld(i+1)-0.25d0*cosa/fac11* &
+                  dcostheta(j,2,i+1)-fac11*dcosalpha(j,2,i))*fac12+ &
+                  (scala2-fac11*cosa)*(0.25d0*sina/fac10* &
+                  dcostheta(j,2,i+1)+fac10*cosa/sina*dcosalpha(j,2,i)))/fac13
+                  domega(j,2,i)=-1/sino*dcosomega(j,2,i)             
+                  dcosomega(j,3,i)=1/fac10*((1/vbld(i+nres)*(dc_norm(j,i)- &
+                  scala2*dc_norm(j,i+nres))-fac11*dcosalpha(j,3,i))*sina+ &
+                  (scala2-fac11*cosa)*(cosa/sina*dcosalpha(j,3,i)))/fac14
+                  domega(j,3,i)=-1/sino*dcosomega(j,3,i)                         
+                enddo           
+              endif
+             else
                do j=1,3
                do j=1,3
-                 dsinomega(j,1,i)=sino*(fac15*dcostheta(j,1,i+1) &
-                 +fac16*dcosalpha(j,1,i))-fac17/vbld(i)*vo1(j)- &
-                 (sino*dc_norm(j,i-1))/vbld(i)
-                 domega(j,1,i)=coso_inv*dsinomega(j,1,i)
-                 dsinomega(j,2,i)=sino*(fac15*dcostheta(j,2,i+1) &
-                 +fac16*dcosalpha(j,2,i))+fac17/vbld(i+1)*vo2(j) &
-                 -sino*dc_norm(j,i)/vbld(i+1)
-                 domega(j,2,i)=coso_inv*dsinomega(j,2,i)                                                      
-                 dsinomega(j,3,i)=sino*fac16*dcosalpha(j,3,i)- &
-                 fac17/vbld(i+nres)*vo3(j)-sino*dc_norm(j,i+nres)/ &
-                 vbld(i+nres)
-                 domega(j,3,i)=coso_inv*dsinomega(j,3,i)
-              enddo                             
-           else
-!   obtaining the derivatives of omega from cosines
-             fac10=sqrt(0.5d0*(1-dcos(theta(i+1))))
-             fac11=sqrt(0.5d0*(1+dcos(theta(i+1))))
-             fac12=fac10*sina
-             fac13=fac12*fac12
-             fac14=sina*sina
-             do j=1,3                                   
-                dcosomega(j,1,i)=(-(0.25d0*cosa/fac11* &
-               dcostheta(j,1,i+1)+fac11*dcosalpha(j,1,i))*fac12+ &
-                (0.25d0/fac10*sina*dcostheta(j,1,i+1)+cosa/sina* &
-                fac10*dcosalpha(j,1,i))*(scala2-fac11*cosa))/fac13
-                domega(j,1,i)=-1/sino*dcosomega(j,1,i)
-                dcosomega(j,2,i)=(((dc_norm(j,i+nres)-scala2* &
-               dc_norm(j,i))/vbld(i+1)-0.25d0*cosa/fac11* &
-                dcostheta(j,2,i+1)-fac11*dcosalpha(j,2,i))*fac12+ &
-                (scala2-fac11*cosa)*(0.25d0*sina/fac10* &
-                dcostheta(j,2,i+1)+fac10*cosa/sina*dcosalpha(j,2,i)))/fac13
-                domega(j,2,i)=-1/sino*dcosomega(j,2,i)                 
-                dcosomega(j,3,i)=1/fac10*((1/vbld(i+nres)*(dc_norm(j,i)- &
-                scala2*dc_norm(j,i+nres))-fac11*dcosalpha(j,3,i))*sina+ &
-                (scala2-fac11*cosa)*(cosa/sina*dcosalpha(j,3,i)))/fac14
-                domega(j,3,i)=-1/sino*dcosomega(j,3,i)                         
-            enddo          
-         endif
-         else
-           do j=1,3
-             do k=1,3
-               dalpha(k,j,i)=0.0d0
-               domega(k,j,i)=0.0d0
-             enddo
-           enddo
-         endif
-       enddo                                         
+                 do k=1,3
+                   dalpha(k,j,i)=0.0d0
+                   domega(k,j,i)=0.0d0
+                 enddo
+               enddo
+             endif
+             enddo                                     
 #endif
 #if defined(MPI) && defined(PARINTDER)
 #endif
 #if defined(MPI) && defined(PARINTDER)
-      if (nfgtasks.gt.1) then
+            if (nfgtasks.gt.1) then
 #ifdef DEBUG
 #ifdef DEBUG
-!d      write (iout,*) "Gather dtheta"
-!d      call flush(iout)
-      write (iout,*) "dtheta before gather"
-      do i=1,nres
-        write (iout,'(i3,3(3f8.5,3x))') i,((dtheta(j,k,i),k=1,3),j=1,2)
-      enddo
+      !d      write (iout,*) "Gather dtheta"
+      !d      call flush(iout)
+            write (iout,*) "dtheta before gather"
+            do i=1,nres
+            write (iout,'(i3,3(3f8.5,3x))') i,((dtheta(j,k,i),k=1,3),j=1,2)
+            enddo
 #endif
 #endif
-      call MPI_Gatherv(dtheta(1,1,ithet_start),ithet_count(fg_rank),&
-        MPI_THET,dtheta(1,1,1),ithet_count(0),ithet_displ(0),MPI_THET,&
-        king,FG_COMM,IERROR)
+            call MPI_Gatherv(dtheta(1,1,ithet_start),ithet_count(fg_rank),&
+            MPI_THET,dtheta(1,1,1),ithet_count(0),ithet_displ(0),MPI_THET,&
+            king,FG_COMM,IERROR)
 #ifdef DEBUG
 #ifdef DEBUG
-!d      write (iout,*) "Gather dphi"
-!d      call flush(iout)
-      write (iout,*) "dphi before gather"
-      do i=1,nres
-        write (iout,'(i3,3(3f8.5,3x))') i,((dphi(j,k,i),k=1,3),j=1,3)
-      enddo
+      !d      write (iout,*) "Gather dphi"
+      !d      call flush(iout)
+            write (iout,*) "dphi before gather"
+            do i=1,nres
+            write (iout,'(i3,3(3f8.5,3x))') i,((dphi(j,k,i),k=1,3),j=1,3)
+            enddo
 #endif
 #endif
-      call MPI_Gatherv(dphi(1,1,iphi1_start),iphi1_count(fg_rank),&
-        MPI_GAM,dphi(1,1,1),iphi1_count(0),iphi1_displ(0),MPI_GAM,&
-        king,FG_COMM,IERROR)
-!d      write (iout,*) "Gather dalpha"
-!d      call flush(iout)
+            call MPI_Gatherv(dphi(1,1,iphi1_start),iphi1_count(fg_rank),&
+            MPI_GAM,dphi(1,1,1),iphi1_count(0),iphi1_displ(0),MPI_GAM,&
+            king,FG_COMM,IERROR)
+      !d      write (iout,*) "Gather dalpha"
+      !d      call flush(iout)
 #ifdef CRYST_SC
 #ifdef CRYST_SC
-      call MPI_Gatherv(dalpha(1,1,ibond_start),ibond_count(fg_rank),&
-        MPI_GAM,dalpha(1,1,1),ibond_count(0),ibond_displ(0),MPI_GAM,&
-        king,FG_COMM,IERROR)
-!d      write (iout,*) "Gather domega"
-!d      call flush(iout)
-      call MPI_Gatherv(domega(1,1,ibond_start),ibond_count(fg_rank),&
-        MPI_GAM,domega(1,1,1),ibond_count(0),ibond_displ(0),MPI_GAM,&
-        king,FG_COMM,IERROR)
+            call MPI_Gatherv(dalpha(1,1,ibond_start),ibond_count(fg_rank),&
+            MPI_GAM,dalpha(1,1,1),ibond_count(0),ibond_displ(0),MPI_GAM,&
+            king,FG_COMM,IERROR)
+      !d      write (iout,*) "Gather domega"
+      !d      call flush(iout)
+            call MPI_Gatherv(domega(1,1,ibond_start),ibond_count(fg_rank),&
+            MPI_GAM,domega(1,1,1),ibond_count(0),ibond_displ(0),MPI_GAM,&
+            king,FG_COMM,IERROR)
 #endif
 #endif
-      endif
+            endif
 #endif
 #ifdef DEBUG
 #endif
 #ifdef DEBUG
-      write (iout,*) "dtheta after gather"
-      do i=1,nres
-        write (iout,'(i3,3(3f8.5,3x))') i,((dtheta(j,k,i),j=1,3),k=1,2)
-      enddo
-      write (iout,*) "dphi after gather"
-      do i=1,nres
-        write (iout,'(i3,3(3f8.5,3x))') i,((dphi(j,k,i),j=1,3),k=1,3)
-      enddo
-      write (iout,*) "dalpha after gather"
-      do i=1,nres
-        write (iout,'(i3,3(3f8.5,3x))') i,((dalpha(j,k,i),j=1,3),k=1,3)
-      enddo
-      write (iout,*) "domega after gather"
-      do i=1,nres
-        write (iout,'(i3,3(3f8.5,3x))') i,((domega(j,k,i),j=1,3),k=1,3)
-      enddo
+            write (iout,*) "dtheta after gather"
+            do i=1,nres
+            write (iout,'(i3,3(3f8.5,3x))') i,((dtheta(j,k,i),j=1,3),k=1,2)
+            enddo
+            write (iout,*) "dphi after gather"
+            do i=1,nres
+            write (iout,'(i3,3(3f8.5,3x))') i,((dphi(j,k,i),j=1,3),k=1,3)
+            enddo
+            write (iout,*) "dalpha after gather"
+            do i=1,nres
+            write (iout,'(i3,3(3f8.5,3x))') i,((dalpha(j,k,i),j=1,3),k=1,3)
+            enddo
+            write (iout,*) "domega after gather"
+            do i=1,nres
+            write (iout,'(i3,3(3f8.5,3x))') i,((domega(j,k,i),j=1,3),k=1,3)
+            enddo
 #endif
 #endif
-      return
-      end subroutine intcartderiv
-!-----------------------------------------------------------------------------
-      subroutine checkintcartgrad
-!      implicit real*8 (a-h,o-z)
-!      include 'DIMENSIONS'
+            return
+            end subroutine intcartderiv
+      !-----------------------------------------------------------------------------
+            subroutine checkintcartgrad
+      !      implicit real*8 (a-h,o-z)
+      !      include 'DIMENSIONS'
 #ifdef MPI
 #ifdef MPI
-      include 'mpif.h'
+            include 'mpif.h'
 #endif
 #endif
-!      include 'COMMON.CHAIN' 
-!      include 'COMMON.VAR'
-!      include 'COMMON.GEO'
-!      include 'COMMON.INTERACT'
-!      include 'COMMON.DERIV'
-!      include 'COMMON.IOUNITS'
-!      include 'COMMON.SETUP'
-      real(kind=8),dimension(3,2,nres) :: dthetanum !(3,2,maxres)
-      real(kind=8),dimension(3,3,nres) :: dphinum,dalphanum,domeganum !(3,3,maxres)
-      real(kind=8),dimension(nres) :: theta_s,phi_s,alph_s,omeg_s !(maxres)
-      real(kind=8),dimension(3) :: dc_norm_s
-      real(kind=8) :: aincr=1.0d-5
-      integer :: i,j 
-      real(kind=8) :: dcji
-      do i=1,nres
-        phi_s(i)=phi(i)
-        theta_s(i)=theta(i)    
-        alph_s(i)=alph(i)
-        omeg_s(i)=omeg(i)
-      enddo
-! Check theta gradient
-      write (iout,*) &
-       "Analytical (upper) and numerical (lower) gradient of theta"
-      write (iout,*) 
-      do i=3,nres
-        do j=1,3
-          dcji=dc(j,i-2)
-          dc(j,i-2)=dcji+aincr
-          call chainbuild_cart
-          call int_from_cart1(.false.)
+      !      include 'COMMON.CHAIN' 
+      !      include 'COMMON.VAR'
+      !      include 'COMMON.GEO'
+      !      include 'COMMON.INTERACT'
+      !      include 'COMMON.DERIV'
+      !      include 'COMMON.IOUNITS'
+      !      include 'COMMON.SETUP'
+            real(kind=8),dimension(3,2,nres) :: dthetanum !(3,2,maxres)
+            real(kind=8),dimension(3,3,nres) :: dphinum,dalphanum,domeganum !(3,3,maxres)
+            real(kind=8),dimension(nres) :: theta_s,phi_s,alph_s,omeg_s !(maxres)
+            real(kind=8),dimension(3) :: dc_norm_s
+            real(kind=8) :: aincr=1.0d-5
+            integer :: i,j 
+            real(kind=8) :: dcji
+            do i=1,nres
+            phi_s(i)=phi(i)
+            theta_s(i)=theta(i)       
+            alph_s(i)=alph(i)
+            omeg_s(i)=omeg(i)
+            enddo
+      ! Check theta gradient
+            write (iout,*) &
+             "Analytical (upper) and numerical (lower) gradient of theta"
+            write (iout,*) 
+            do i=3,nres
+            do j=1,3
+              dcji=dc(j,i-2)
+              dc(j,i-2)=dcji+aincr
+              call chainbuild_cart
+              call int_from_cart1(.false.)
           dthetanum(j,1,i)=(theta(i)-theta_s(i))/aincr 
           dc(j,i-2)=dcji
           dcji=dc(j,i-1)
           dc(j,i-1)=dc(j,i-1)+aincr
           dthetanum(j,1,i)=(theta(i)-theta_s(i))/aincr 
           dc(j,i-2)=dcji
           dcji=dc(j,i-1)
           dc(j,i-1)=dc(j,i-1)+aincr
-          call chainbuild_cart   
+          call chainbuild_cart        
           dthetanum(j,2,i)=(theta(i)-theta_s(i))/aincr
           dc(j,i-1)=dcji
         enddo 
           dthetanum(j,2,i)=(theta(i)-theta_s(i))/aincr
           dc(j,i-1)=dcji
         enddo 
@@ -16518,7 +17158,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
           dc(j,i-3)=dcji+aincr
           call chainbuild_cart
           dphinum(j,1,i)=(phi(i)-phi_s(i))/aincr  
           dc(j,i-3)=dcji+aincr
           call chainbuild_cart
           dphinum(j,1,i)=(phi(i)-phi_s(i))/aincr  
-         dc(j,i-3)=dcji
+              dc(j,i-3)=dcji
           dcji=dc(j,i-2)
           dc(j,i-2)=dcji+aincr
           call chainbuild_cart
           dcji=dc(j,i-2)
           dc(j,i-2)=dcji+aincr
           call chainbuild_cart
@@ -16544,28 +17184,28 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       write (iout,*) &
        "Analytical (upper) and numerical (lower) gradient of alpha"
       do i=2,nres-1
       write (iout,*) &
        "Analytical (upper) and numerical (lower) gradient of alpha"
       do i=2,nres-1
-       if(itype(i).ne.10) then
-                   do j=1,3
-             dcji=dc(j,i-1)
-                     dc(j,i-1)=dcji+aincr
+       if(itype(i,1).ne.10) then
+                 do j=1,3
+                  dcji=dc(j,i-1)
+                   dc(j,i-1)=dcji+aincr
               call chainbuild_cart
               dalphanum(j,1,i)=(alph(i)-alph_s(i)) &
               call chainbuild_cart
               dalphanum(j,1,i)=(alph(i)-alph_s(i)) &
-             /aincr  
-             dc(j,i-1)=dcji
+                 /aincr  
+                  dc(j,i-1)=dcji
               dcji=dc(j,i)
               dc(j,i)=dcji+aincr
               call chainbuild_cart
               dalphanum(j,2,i)=(alph(i)-alph_s(i)) &
               dcji=dc(j,i)
               dc(j,i)=dcji+aincr
               call chainbuild_cart
               dalphanum(j,2,i)=(alph(i)-alph_s(i)) &
-             /aincr 
+                 /aincr 
               dc(j,i)=dcji
               dcji=dc(j,i+nres)
               dc(j,i+nres)=dc(j,i+nres)+aincr
               call chainbuild_cart
               dalphanum(j,3,i)=(alph(i)-alph_s(i)) &
               dc(j,i)=dcji
               dcji=dc(j,i+nres)
               dc(j,i+nres)=dc(j,i+nres)+aincr
               call chainbuild_cart
               dalphanum(j,3,i)=(alph(i)-alph_s(i)) &
-             /aincr
+                 /aincr
              dc(j,i+nres)=dcji
             enddo
              dc(j,i+nres)=dcji
             enddo
-          endif             
+          endif           
 !el        write (iout,'(i5,3(3f10.5,5x))') i,(dalpha(j,1,i),j=1,3),&
 !el          (dalpha(j,2,i),j=1,3),(dalpha(j,3,i),j=1,3)
 !el        write (iout,'(5x,3(3f10.5,5x))') (dalphanum(j,1,i),j=1,3),&
 !el        write (iout,'(i5,3(3f10.5,5x))') i,(dalpha(j,1,i),j=1,3),&
 !el          (dalpha(j,2,i),j=1,3),(dalpha(j,3,i),j=1,3)
 !el        write (iout,'(5x,3(3f10.5,5x))') (dalphanum(j,1,i),j=1,3),&
@@ -16580,28 +17220,28 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       write (iout,*) &
        "Analytical (upper) and numerical (lower) gradient of omega"
       do i=2,nres-1
       write (iout,*) &
        "Analytical (upper) and numerical (lower) gradient of omega"
       do i=2,nres-1
-       if(itype(i).ne.10) then
-                   do j=1,3
-             dcji=dc(j,i-1)
-                     dc(j,i-1)=dcji+aincr
+       if(itype(i,1).ne.10) then
+                 do j=1,3
+                  dcji=dc(j,i-1)
+                   dc(j,i-1)=dcji+aincr
               call chainbuild_cart
               domeganum(j,1,i)=(omeg(i)-omeg_s(i)) &
               call chainbuild_cart
               domeganum(j,1,i)=(omeg(i)-omeg_s(i)) &
-             /aincr  
-             dc(j,i-1)=dcji
+                 /aincr  
+                  dc(j,i-1)=dcji
               dcji=dc(j,i)
               dc(j,i)=dcji+aincr
               call chainbuild_cart
               domeganum(j,2,i)=(omeg(i)-omeg_s(i)) &
               dcji=dc(j,i)
               dc(j,i)=dcji+aincr
               call chainbuild_cart
               domeganum(j,2,i)=(omeg(i)-omeg_s(i)) &
-             /aincr 
+                 /aincr 
               dc(j,i)=dcji
               dcji=dc(j,i+nres)
               dc(j,i+nres)=dc(j,i+nres)+aincr
               call chainbuild_cart
               domeganum(j,3,i)=(omeg(i)-omeg_s(i)) &
               dc(j,i)=dcji
               dcji=dc(j,i+nres)
               dc(j,i+nres)=dc(j,i+nres)+aincr
               call chainbuild_cart
               domeganum(j,3,i)=(omeg(i)-omeg_s(i)) &
-             /aincr
+                 /aincr
              dc(j,i+nres)=dcji
             enddo
              dc(j,i+nres)=dcji
             enddo
-          endif             
+          endif           
 !el        write (iout,'(i5,3(3f10.5,5x))') i,(domega(j,1,i),j=1,3),&
 !el          (domega(j,2,i),j=1,3),(domega(j,3,i),j=1,3)
 !el        write (iout,'(5x,3(3f10.5,5x))') (domeganum(j,1,i),j=1,3),&
 !el        write (iout,'(i5,3(3f10.5,5x))') i,(domega(j,1,i),j=1,3),&
 !el          (domega(j,2,i),j=1,3),(domega(j,3,i),j=1,3)
 !el        write (iout,'(5x,3(3f10.5,5x))') (domeganum(j,1,i),j=1,3),&
@@ -16626,7 +17266,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !      include 'COMMON.VAR'
       integer :: i,j,jl,k,l,il,kl,nl,np,ip,kp,seg1,seg2,seg3,seg4,secseg
       integer :: kkk,nsep=3
 !      include 'COMMON.VAR'
       integer :: i,j,jl,k,l,il,kl,nl,np,ip,kp,seg1,seg2,seg3,seg4,secseg
       integer :: kkk,nsep=3
-      real(kind=8) :: qm       !dist,
+      real(kind=8) :: qm      !dist,
       real(kind=8) :: qq,qqij,qqijCM,dij,d0ij,dijCM,d0ijCM,qqmax
       logical :: lprn=.false.
       logical :: flag
       real(kind=8) :: qq,qqij,qqijCM,dij,d0ij,dijCM,d0ijCM,qqmax
       logical :: lprn=.false.
       logical :: flag
@@ -16646,7 +17286,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
                        (cref(3,jl,kkk)-cref(3,il,kkk))**2)
             dij=dist(il,jl)
             qqij = dexp(-0.5d0*((dij-d0ij)/(sigm(d0ij)))**2)
                        (cref(3,jl,kkk)-cref(3,il,kkk))**2)
             dij=dist(il,jl)
             qqij = dexp(-0.5d0*((dij-d0ij)/(sigm(d0ij)))**2)
-            if (itype(il).ne.10 .or. itype(jl).ne.10) then
+            if (itype(il,1).ne.10 .or. itype(jl,1).ne.10) then
               nl=nl+1
               d0ijCM=dsqrt( &
                      (cref(1,jl+nres,kkk)-cref(1,il+nres,kkk))**2+ &
               nl=nl+1
               d0ijCM=dsqrt( &
                      (cref(1,jl+nres,kkk)-cref(1,il+nres,kkk))**2+ &
@@ -16657,7 +17297,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
             endif
             qq = qq+qqij+qqijCM
           enddo
             endif
             qq = qq+qqij+qqijCM
           enddo
-        enddo  
+        enddo       
         qq = qq/nl
       else
       do il=seg1,seg2
         qq = qq/nl
       else
       do il=seg1,seg2
@@ -16673,7 +17313,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
                        (cref(3,jl,kkk)-cref(3,il,kkk))**2)
             dij=dist(il,jl)
             qqij = dexp(-0.5d0*((dij-d0ij)/(sigm(d0ij)))**2)
                        (cref(3,jl,kkk)-cref(3,il,kkk))**2)
             dij=dist(il,jl)
             qqij = dexp(-0.5d0*((dij-d0ij)/(sigm(d0ij)))**2)
-            if (itype(il).ne.10 .or. itype(jl).ne.10) then
+            if (itype(il,1).ne.10 .or. itype(jl,1).ne.10) then
               nl=nl+1
               d0ijCM=dsqrt( &
                      (cref(1,jl+nres,kkk)-cref(1,il+nres,kkk))**2+ &
               nl=nl+1
               d0ijCM=dsqrt( &
                      (cref(1,jl+nres,kkk)-cref(1,il+nres,kkk))**2+ &
@@ -16708,12 +17348,12 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       logical :: lprn=.false.
       logical :: flag
       real(kind=8) :: sim,dd0,fac,ddqij
       logical :: lprn=.false.
       logical :: flag
       real(kind=8) :: sim,dd0,fac,ddqij
-!el      sigm(x)=0.25d0*x           ! local function
+!el      sigm(x)=0.25d0*x           ! local function
       do kkk=1,nperm 
       do i=0,nres
         do j=1,3
           dqwol(j,i)=0.0d0
       do kkk=1,nperm 
       do i=0,nres
         do j=1,3
           dqwol(j,i)=0.0d0
-          dxqwol(j,i)=0.0d0      
+          dxqwol(j,i)=0.0d0        
         enddo
       enddo
       nl=0 
         enddo
       enddo
       nl=0 
@@ -16729,13 +17369,13 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
             sim = sim*sim
             dd0 = dij-d0ij
             fac = dd0*sim/dij*dexp(-0.5d0*dd0*dd0*sim)
             sim = sim*sim
             dd0 = dij-d0ij
             fac = dd0*sim/dij*dexp(-0.5d0*dd0*dd0*sim)
-           do k=1,3
+          do k=1,3
               ddqij = (c(k,il)-c(k,jl))*fac
               dqwol(k,il)=dqwol(k,il)+ddqij
               dqwol(k,jl)=dqwol(k,jl)-ddqij
             enddo
               ddqij = (c(k,il)-c(k,jl))*fac
               dqwol(k,il)=dqwol(k,il)+ddqij
               dqwol(k,jl)=dqwol(k,jl)-ddqij
             enddo
-                    
-            if (itype(il).ne.10 .or. itype(jl).ne.10) then
+                       
+            if (itype(il,1).ne.10 .or. itype(jl,1).ne.10) then
               nl=nl+1
               d0ijCM=dsqrt( &
                      (cref(1,jl+nres,kkk)-cref(1,il+nres,kkk))**2+ &
               nl=nl+1
               d0ijCM=dsqrt( &
                      (cref(1,jl+nres,kkk)-cref(1,il+nres,kkk))**2+ &
@@ -16751,9 +17391,9 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
                 dxqwol(k,il)=dxqwol(k,il)+ddqij
                 dxqwol(k,jl)=dxqwol(k,jl)-ddqij
               enddo
                 dxqwol(k,il)=dxqwol(k,il)+ddqij
                 dxqwol(k,jl)=dxqwol(k,jl)-ddqij
               enddo
-            endif          
+            endif           
           enddo
           enddo
-        enddo  
+        enddo       
        else
         do il=seg1,seg2
         if((seg3-il).lt.3) then
        else
         do il=seg1,seg2
         if((seg3-il).lt.3) then
@@ -16776,7 +17416,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               dqwol(k,il)=dqwol(k,il)+ddqij
               dqwol(k,jl)=dqwol(k,jl)-ddqij
             enddo
               dqwol(k,il)=dqwol(k,il)+ddqij
               dqwol(k,jl)=dqwol(k,jl)-ddqij
             enddo
-            if (itype(il).ne.10 .or. itype(jl).ne.10) then
+            if (itype(il,1).ne.10 .or. itype(jl,1).ne.10) then
               nl=nl+1
               d0ijCM=dsqrt( &
                      (cref(1,jl+nres,kkk)-cref(1,il+nres,kkk))**2+ &
               nl=nl+1
               d0ijCM=dsqrt( &
                      (cref(1,jl+nres,kkk)-cref(1,il+nres,kkk))**2+ &
@@ -16794,7 +17434,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
               enddo
             endif 
           enddo
               enddo
             endif 
           enddo
-        enddo               
+        enddo                   
       endif
       enddo
        do i=0,nres
       endif
       enddo
        do i=0,nres
@@ -16896,11 +17536,11 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
          Ucdfrag=wfrag(i,iset)*harmonicprim(qfrag(i),&
            qinfrag(i,iset))
 !         hm1=harmonic(qfrag(i,iset),qinfrag(i,iset))
          Ucdfrag=wfrag(i,iset)*harmonicprim(qfrag(i),&
            qinfrag(i,iset))
 !         hm1=harmonic(qfrag(i,iset),qinfrag(i,iset))
-!               hm2=harmonic(qfrag(i,iset)+delta,qinfrag(i,iset))
-!         hmnum=(hm2-hm1)/delta                 
+!             hm2=harmonic(qfrag(i,iset)+delta,qinfrag(i,iset))
+!         hmnum=(hm2-hm1)/delta              
 !         write(iout,*) "harmonicprim frag",harmonicprim(qfrag(i,iset),
 !     &   qinfrag(i,iset))
 !         write(iout,*) "harmonicprim frag",harmonicprim(qfrag(i,iset),
 !     &   qinfrag(i,iset))
-!         write(iout,*) "harmonicnum frag", hmnum               
+!         write(iout,*) "harmonicnum frag", hmnum               
 ! Calculating the derivatives of Q with respect to cartesian coordinates
          call qwolynes_prim(ifrag(1,i,iset),ifrag(2,i,iset),.true.,&
           idummy,idummy)
 ! Calculating the derivatives of Q with respect to cartesian coordinates
          call qwolynes_prim(ifrag(1,i,iset),ifrag(2,i,iset),.true.,&
           idummy,idummy)
@@ -16922,7 +17562,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
                dUxconst(j,ii)=dUxconst(j,ii)+ucdfrag*dxqwol(j,ii)
             enddo
          enddo
                dUxconst(j,ii)=dUxconst(j,ii)+ucdfrag*dxqwol(j,ii)
             enddo
          enddo
-      enddo    
+      enddo      
       do i=1,npair
          kstart=ifrag(1,ipair(1,i,iset),iset)
          kend=ifrag(2,ipair(1,i,iset),iset)
       do i=1,npair
          kstart=ifrag(1,ipair(1,i,iset),iset)
          kend=ifrag(2,ipair(1,i,iset),iset)
@@ -16933,11 +17573,11 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !  Calculating dU/dQ
          Ucdpair=wpair(i,iset)*harmonicprim(qpair(i),qinpair(i,iset))
 !         hm1=harmonic(qpair(i),qinpair(i,iset))
 !  Calculating dU/dQ
          Ucdpair=wpair(i,iset)*harmonicprim(qpair(i),qinpair(i,iset))
 !         hm1=harmonic(qpair(i),qinpair(i,iset))
-!               hm2=harmonic(qpair(i)+delta,qinpair(i,iset))
-!         hmnum=(hm2-hm1)/delta                 
+!             hm2=harmonic(qpair(i)+delta,qinpair(i,iset))
+!         hmnum=(hm2-hm1)/delta              
 !         write(iout,*) "harmonicprim pair ",harmonicprim(qpair(i),
 !     &   qinpair(i,iset))
 !         write(iout,*) "harmonicprim pair ",harmonicprim(qpair(i),
 !     &   qinpair(i,iset))
-!         write(iout,*) "harmonicnum pair ", hmnum      
+!         write(iout,*) "harmonicnum pair ", hmnum       
 ! Calculating dQ/dXi
          call qwolynes_prim(kstart,kend,.false.,&
           lstart,lend)
 ! Calculating dQ/dXi
          call qwolynes_prim(kstart,kend,.false.,&
           lstart,lend)
@@ -16974,7 +17614,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
          do j=1,3
            dudxconst(j,i)=duxconst(j,i)
          enddo
          do j=1,3
            dudxconst(j,i)=duxconst(j,i)
          enddo
-      enddo                     
+      enddo                       
 !      write(iout,*) "dU/ddc backbone "
 !       do ii=0,nres
 !        write(iout,'(i5,3e15.5)') ii, (dudconst(j,ii),j=1,3)
 !      write(iout,*) "dU/ddc backbone "
 !       do ii=0,nres
 !        write(iout,'(i5,3e15.5)') ii, (dudconst(j,ii),j=1,3)
@@ -17023,7 +17663,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
             cdummy(j,i)=dc(j,i)
             dc(j,i)=dc(j,i)+delta
             call chainbuild_cart
             cdummy(j,i)=dc(j,i)
             dc(j,i)=dc(j,i)+delta
             call chainbuild_cart
-           uzap2=0.0d0
+          uzap2=0.0d0
             do ii=1,nfrag
              qfrag(ii)=qwolynes(ifrag(1,ii,iset),ifrag(2,ii,iset),.true.,&
                 idummy,idummy)
             do ii=1,nfrag
              qfrag(ii)=qwolynes(ifrag(1,ii,iset),ifrag(2,ii,iset),.true.,&
                 idummy,idummy)
@@ -17057,7 +17697,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
                uzap1=uzap1+wpair(ii,iset)*harmonic(qpair(ii),&
                 qinpair(ii,iset))
             enddo
                uzap1=uzap1+wpair(ii,iset)*harmonic(qpair(ii),&
                 qinpair(ii,iset))
             enddo
-            ducartan(j,i)=(uzap2-uzap1)/(delta)            
+            ducartan(j,i)=(uzap2-uzap1)/(delta)          
          enddo
       enddo
 ! Calculating numerical gradients for dU/ddx
          enddo
       enddo
 ! Calculating numerical gradients for dU/ddx
@@ -17067,7 +17707,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
             cdummy(j,i)=dc(j,i+nres)
             dc(j,i+nres)=dc(j,i+nres)+delta
             call chainbuild_cart
             cdummy(j,i)=dc(j,i+nres)
             dc(j,i+nres)=dc(j,i+nres)+delta
             call chainbuild_cart
-           uzap2=0.0d0
+          uzap2=0.0d0
             do ii=1,nfrag
              qfrag(ii)=qwolynes(ifrag(1,ii,iset),ifrag(2,ii,iset),.true.,&
                 idummy,idummy)
             do ii=1,nfrag
              qfrag(ii)=qwolynes(ifrag(1,ii,iset),ifrag(2,ii,iset),.true.,&
                 idummy,idummy)
@@ -17101,7 +17741,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
                uzap1=uzap1+wpair(ii,iset)*harmonic(qpair(ii),&
                 qinpair(ii,iset))
             enddo
                uzap1=uzap1+wpair(ii,iset)*harmonic(qpair(ii),&
                 qinpair(ii,iset))
             enddo
-            duxcartan(j,i)=(uzap2-uzap1)/(delta)           
+            duxcartan(j,i)=(uzap2-uzap1)/(delta)          
          enddo
       enddo    
       write(iout,*) "Numerical dUconst/ddc backbone "
          enddo
       enddo    
       write(iout,*) "Numerical dUconst/ddc backbone "
@@ -17267,13 +17907,13 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !el      allocate(dyn_ssbond_ij(iatsc_s:iatsc_e,nres))
 !el      allocate(dyn_ssbond_ij(0:nres+4,nres))
 
 !el      allocate(dyn_ssbond_ij(iatsc_s:iatsc_e,nres))
 !el      allocate(dyn_ssbond_ij(0:nres+4,nres))
 
-      itypi=itype(i)
+      itypi=itype(i,1)
       dxi=dc_norm(1,nres+i)
       dyi=dc_norm(2,nres+i)
       dzi=dc_norm(3,nres+i)
       dsci_inv=vbld_inv(i+nres)
 
       dxi=dc_norm(1,nres+i)
       dyi=dc_norm(2,nres+i)
       dzi=dc_norm(3,nres+i)
       dsci_inv=vbld_inv(i+nres)
 
-      itypj=itype(j)
+      itypj=itype(j,1)
       xj=c(1,nres+j)-c(1,nres+i)
       yj=c(2,nres+j)-c(2,nres+i)
       zj=c(3,nres+j)-c(3,nres+i)
       xj=c(1,nres+j)-c(1,nres+i)
       yj=c(2,nres+j)-c(2,nres+i)
       zj=c(3,nres+j)-c(3,nres+i)
@@ -17584,6 +18224,176 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 
       return
       end subroutine dyn_ssbond_ene
 
       return
       end subroutine dyn_ssbond_ene
+!--------------------------------------------------------------------------
+         subroutine triple_ssbond_ene(resi,resj,resk,eij)
+!      implicit none
+!      Includes
+      use calc_data
+      use comm_sschecks
+!      include 'DIMENSIONS'
+!      include 'COMMON.SBRIDGE'
+!      include 'COMMON.CHAIN'
+!      include 'COMMON.DERIV'
+!      include 'COMMON.LOCAL'
+!      include 'COMMON.INTERACT'
+!      include 'COMMON.VAR'
+!      include 'COMMON.IOUNITS'
+!      include 'COMMON.CALC'
+#ifndef CLUST
+#ifndef WHAM
+       use MD_data
+!      include 'COMMON.MD'
+!      use MD, only: totT,t_bath
+#endif
+#endif
+      double precision h_base
+      external h_base
+
+!c     Input arguments
+      integer resi,resj,resk,m,itypi,itypj,itypk
+
+!c     Output arguments
+      double precision eij,eij1,eij2,eij3
+
+!c     Local variables
+      logical havebond
+!c      integer itypi,itypj,k,l
+      double precision rrij,ssd,deltat1,deltat2,deltat12,cosphi
+      double precision rrik,rrjk,rik,rjk,xi,xk,yi,yk,zi,zk,xij,yij,zij
+      double precision xik,yik,zik,xjk,yjk,zjk,dxk,dyk,dzk
+      double precision sig0ij,ljd,sig,fac,e1,e2
+      double precision dcosom1(3),dcosom2(3),ed
+      double precision pom1,pom2
+      double precision ljA,ljB,ljXs
+      double precision d_ljB(1:3)
+      double precision ssA,ssB,ssC,ssXs
+      double precision ssxm,ljxm,ssm,ljm
+      double precision d_ssxm(1:3),d_ljxm(1:3),d_ssm(1:3),d_ljm(1:3)
+      eij=0.0
+      if (dtriss.eq.0) return
+      i=resi
+      j=resj
+      k=resk
+!C      write(iout,*) resi,resj,resk
+      itypi=itype(i,1)
+      dxi=dc_norm(1,nres+i)
+      dyi=dc_norm(2,nres+i)
+      dzi=dc_norm(3,nres+i)
+      dsci_inv=vbld_inv(i+nres)
+      xi=c(1,nres+i)
+      yi=c(2,nres+i)
+      zi=c(3,nres+i)
+      itypj=itype(j,1)
+      xj=c(1,nres+j)
+      yj=c(2,nres+j)
+      zj=c(3,nres+j)
+
+      dxj=dc_norm(1,nres+j)
+      dyj=dc_norm(2,nres+j)
+      dzj=dc_norm(3,nres+j)
+      dscj_inv=vbld_inv(j+nres)
+      itypk=itype(k,1)
+      xk=c(1,nres+k)
+      yk=c(2,nres+k)
+      zk=c(3,nres+k)
+
+      dxk=dc_norm(1,nres+k)
+      dyk=dc_norm(2,nres+k)
+      dzk=dc_norm(3,nres+k)
+      dscj_inv=vbld_inv(k+nres)
+      xij=xj-xi
+      xik=xk-xi
+      xjk=xk-xj
+      yij=yj-yi
+      yik=yk-yi
+      yjk=yk-yj
+      zij=zj-zi
+      zik=zk-zi
+      zjk=zk-zj
+      rrij=(xij*xij+yij*yij+zij*zij)
+      rij=dsqrt(rrij)  ! sc_angular needs rij to really be the inverse
+      rrik=(xik*xik+yik*yik+zik*zik)
+      rik=dsqrt(rrik)
+      rrjk=(xjk*xjk+yjk*yjk+zjk*zjk)
+      rjk=dsqrt(rrjk)
+!C there are three combination of distances for each trisulfide bonds
+!C The first case the ith atom is the center
+!C Energy function is E=d/(a*(x-y)**2+b*(x+y)**2+c) where x is first
+!C distance y is second distance the a,b,c,d are parameters derived for
+!C this problem d parameter was set as a penalty currenlty set to 1.
+      if ((iabs(j-i).le.2).or.(iabs(i-k).le.2)) then
+      eij1=0.0d0
+      else
+      eij1=dtriss/(atriss*(rij-rik)**2+btriss*(rij+rik)**6+ctriss)
+      endif
+!C second case jth atom is center
+      if ((iabs(j-i).le.2).or.(iabs(j-k).le.2)) then
+      eij2=0.0d0
+      else
+      eij2=dtriss/(atriss*(rij-rjk)**2+btriss*(rij+rjk)**6+ctriss)
+      endif
+!C the third case kth atom is the center
+      if ((iabs(i-k).le.2).or.(iabs(j-k).le.2)) then
+      eij3=0.0d0
+      else
+      eij3=dtriss/(atriss*(rik-rjk)**2+btriss*(rik+rjk)**6+ctriss)
+      endif
+!C      eij2=0.0
+!C      eij3=0.0
+!C      eij1=0.0
+      eij=eij1+eij2+eij3
+!C      write(iout,*)i,j,k,eij
+!C The energy penalty calculated now time for the gradient part 
+!C derivative over rij
+      fac=-eij1**2/dtriss*(2.0*atriss*(rij-rik)+6.0*btriss*(rij+rik)**5) &
+      -eij2**2/dtriss*(2.0*atriss*(rij-rjk)+6.0*btriss*(rij+rjk)**5)
+            gg(1)=xij*fac/rij
+            gg(2)=yij*fac/rij
+            gg(3)=zij*fac/rij
+      do m=1,3
+        gvdwx(m,i)=gvdwx(m,i)-gg(m)
+        gvdwx(m,j)=gvdwx(m,j)+gg(m)
+      enddo
+
+      do l=1,3
+        gvdwc(l,i)=gvdwc(l,i)-gg(l)
+        gvdwc(l,j)=gvdwc(l,j)+gg(l)
+      enddo
+!C now derivative over rik
+      fac=-eij1**2/dtriss* &
+      (-2.0*atriss*(rij-rik)+6.0*btriss*(rij+rik)**5) &
+      -eij3**2/dtriss*(2.0*atriss*(rik-rjk)+6.0*btriss*(rik+rjk)**5)
+            gg(1)=xik*fac/rik
+            gg(2)=yik*fac/rik
+            gg(3)=zik*fac/rik
+      do m=1,3
+        gvdwx(m,i)=gvdwx(m,i)-gg(m)
+        gvdwx(m,k)=gvdwx(m,k)+gg(m)
+      enddo
+      do l=1,3
+        gvdwc(l,i)=gvdwc(l,i)-gg(l)
+        gvdwc(l,k)=gvdwc(l,k)+gg(l)
+      enddo
+!C now derivative over rjk
+      fac=-eij2**2/dtriss* &
+      (-2.0*atriss*(rij-rjk)+6.0*btriss*(rij+rjk)**5)- &
+      eij3**2/dtriss*(-2.0*atriss*(rik-rjk)+6.0*btriss*(rik+rjk)**5)
+            gg(1)=xjk*fac/rjk
+            gg(2)=yjk*fac/rjk
+            gg(3)=zjk*fac/rjk
+      do m=1,3
+        gvdwx(m,j)=gvdwx(m,j)-gg(m)
+        gvdwx(m,k)=gvdwx(m,k)+gg(m)
+      enddo
+      do l=1,3
+        gvdwc(l,j)=gvdwc(l,j)-gg(l)
+        gvdwc(l,k)=gvdwc(l,k)+gg(l)
+      enddo
+      return
+      end subroutine triple_ssbond_ene
+
+
+
 !-----------------------------------------------------------------------------
       real(kind=8) function h_base(x,deriv)
 !     A smooth function going 0->1 in range [0,1]
 !-----------------------------------------------------------------------------
       real(kind=8) function h_base(x,deriv)
 !     A smooth function going 0->1 in range [0,1]
@@ -17730,15 +18540,18 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       diff=newnss-nss
 
 !mc      write(iout,*)"NEWNSS ",newnss,(newihpb(i),newjhpb(i),i=1,newnss)
       diff=newnss-nss
 
 !mc      write(iout,*)"NEWNSS ",newnss,(newihpb(i),newjhpb(i),i=1,newnss)
-
+!       print *,newnss,nss,maxdim
       do i=1,nss
         found=.false.
       do i=1,nss
         found=.false.
+!        print *,newnss
         do j=1,newnss
         do j=1,newnss
+!!          print *,j
           if (idssb(i).eq.newihpb(j) .and. &
                jdssb(i).eq.newjhpb(j)) found=.true.
         enddo
 #ifndef CLUST
 #ifndef WHAM
           if (idssb(i).eq.newihpb(j) .and. &
                jdssb(i).eq.newjhpb(j)) found=.true.
         enddo
 #ifndef CLUST
 #ifndef WHAM
+!        write(iout,*) "found",found,i,j
         if (.not.found.and.fg_rank.eq.0) &
             write(iout,'(a15,f12.2,f8.1,2i5)') &
              "SSBOND_BREAK",totT,t_bath,idssb(i),jdssb(i)
         if (.not.found.and.fg_rank.eq.0) &
             write(iout,'(a15,f12.2,f8.1,2i5)') &
              "SSBOND_BREAK",totT,t_bath,idssb(i),jdssb(i)
@@ -17749,11 +18562,13 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       do i=1,newnss
         found=.false.
         do j=1,nss
       do i=1,newnss
         found=.false.
         do j=1,nss
+!          print *,i,j
           if (newihpb(i).eq.idssb(j) .and. &
                newjhpb(i).eq.jdssb(j)) found=.true.
         enddo
 #ifndef CLUST
 #ifndef WHAM
           if (newihpb(i).eq.idssb(j) .and. &
                newjhpb(i).eq.jdssb(j)) found=.true.
         enddo
 #ifndef CLUST
 #ifndef WHAM
+!        write(iout,*) "found",found,i,j
         if (.not.found.and.fg_rank.eq.0) &
             write(iout,'(a15,f12.2,f8.1,2i5)') &
              "SSBOND_FORM",totT,t_bath,newihpb(i),newjhpb(i)
         if (.not.found.and.fg_rank.eq.0) &
             write(iout,'(a15,f12.2,f8.1,2i5)') &
              "SSBOND_FORM",totT,t_bath,newihpb(i),newjhpb(i)
@@ -17783,10 +18598,10 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       real(kind=8) :: fracinbuf,eliptran,sslip,positi,ssgradlip
       integer :: i
       eliptran=0.0
       real(kind=8) :: fracinbuf,eliptran,sslip,positi,ssgradlip
       integer :: i
       eliptran=0.0
-      print *, "I am in eliptran"
+!      print *, "I am in eliptran"
       do i=ilip_start,ilip_end
 !C       do i=1,1
       do i=ilip_start,ilip_end
 !C       do i=1,1
-        if ((itype(i).eq.ntyp1).or.(itype(i+1).eq.ntyp1).or.(i.eq.nres))&
+        if ((itype(i,1).eq.ntyp1).or.(itype(i+1,1).eq.ntyp1).or.(i.eq.nres))&
          cycle
 
         positi=(mod(((c(3,i)+c(3,i+1))/2.0d0),boxzsize))
          cycle
 
         positi=(mod(((c(3,i)+c(3,i+1))/2.0d0),boxzsize))
@@ -17832,7 +18647,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
        enddo
 ! here starts the side chain transfer
        do i=ilip_start,ilip_end
        enddo
 ! here starts the side chain transfer
        do i=ilip_start,ilip_end
-        if (itype(i).eq.ntyp1) cycle
+        if (itype(i,1).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
         positi=(mod(c(3,i+nres),boxzsize))
         if (positi.le.0) positi=positi+boxzsize
 !C       print *,mod(c(3,i+nres),boxzsize),bordlipbot,bordliptop
@@ -17848,25 +18663,25 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !C lipbufthick is thickenes of lipid buffore
          sslip=sscalelip(fracinbuf)
          ssgradlip=-sscagradlip(fracinbuf)/lipbufthick
 !C lipbufthick is thickenes of lipid buffore
          sslip=sscalelip(fracinbuf)
          ssgradlip=-sscagradlip(fracinbuf)/lipbufthick
-         eliptran=eliptran+sslip*liptranene(itype(i))
+         eliptran=eliptran+sslip*liptranene(itype(i,1))
          gliptranx(3,i)=gliptranx(3,i) &
          gliptranx(3,i)=gliptranx(3,i) &
-      +ssgradlip*liptranene(itype(i))
+      +ssgradlip*liptranene(itype(i,1))
          gliptranc(3,i-1)= gliptranc(3,i-1) &
          gliptranc(3,i-1)= gliptranc(3,i-1) &
-      +ssgradlip*liptranene(itype(i))
+      +ssgradlip*liptranene(itype(i,1))
 !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
 !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))
+         eliptran=eliptran+sslip*liptranene(itype(i,1))
          gliptranx(3,i)=gliptranx(3,i)  &
          gliptranx(3,i)=gliptranx(3,i)  &
-       +ssgradlip*liptranene(itype(i))
+       +ssgradlip*liptranene(itype(i,1))
          gliptranc(3,i-1)= gliptranc(3,i-1) &
          gliptranc(3,i-1)= gliptranc(3,i-1) &
-      +ssgradlip*liptranene(itype(i))
+      +ssgradlip*liptranene(itype(i,1))
 !C          print *, "doing sscalefor top part",sslip,fracinbuf
         else
 !C          print *, "doing sscalefor top part",sslip,fracinbuf
         else
-         eliptran=eliptran+liptranene(itype(i))
+         eliptran=eliptran+liptranene(itype(i,1))
 !C         print *,"I am in true lipid"
         endif
         endif ! if in lipid or buffor
 !C         print *,"I am in true lipid"
         endif
         endif ! if in lipid or buffor
@@ -17876,39 +18691,685 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
        enddo
        return
        end  subroutine Eliptransfer
        enddo
        return
        end  subroutine Eliptransfer
-!--------------------------------------------------------------------------------
-!C first for shielding is setting of function of side-chains
-
-       subroutine set_shield_fac2
-       real(kind=8) :: div77_81=0.974996043d0, &
-        div4_81=0.2222222222d0
-       real (kind=8) :: dist_pep_side,dist_side_calf,dist_pept_group, &
-         scale_fac_dist,fac_help_scale,VofOverlap,VolumeTotal,costhet,&
-         short,long,sinthet,costhet_fac,sh_frac_dist,rkprim,cosphi,   &
-         sinphi,cosphi_fac,pep_side0pept_group,cosalfa,fac_alfa_sin
-!C the vector between center of side_chain and peptide group
-       real(kind=8),dimension(3) :: pep_side_long,side_calf, &
-         pept_group,costhet_grad,cosphi_grad_long, &
-         cosphi_grad_loc,pep_side_norm,side_calf_norm, &
-         sh_frac_dist_grad,pep_side
-        integer i,j,k
-!C      write(2,*) "ivec",ivec_start,ivec_end
-      do i=1,nres
-        fac_shield(i)=0.0d0
+!----------------------------------NANO FUNCTIONS
+!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)
+      real(kind=8),dimension(3) :: vectube
+      real(kind=8) :: Etube,xtemp,xminact,yminact,& 
+       ytemp,xmin,ymin,tub_r,rdiff,rdiff6,fac,positi, &
+       sc_aa_tube,sc_bb_tube
+      integer :: i,j,iti
+      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 for UNRES
+       do i=itube_start,itube_end
+!C lets ommit dummy atoms for now
+       if ((itype(i,1).eq.ntyp1).or.(itype(i+1,1).eq.ntyp1)) cycle
+!C now calculate distance from center of tube and direction vectors
+      xmin=boxxsize
+      ymin=boxysize
+! Find minimum distance in periodic box
+        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
         do j=1,3
-        grad_shield(j,i)=0.0d0
+        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,1)
+!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
+       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 subroutine calctube
+!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       7) allocate matrices
+
+
+!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)
+            real(kind=8),dimension(3) :: vectube
+      real(kind=8) :: Etube,xtemp,xminact,yminact,&
+       ytemp,xmin,ymin,tub_r,rdiff,rdiff6,fac,positi,fracinbuf,&
+       sstube,ssgradtube,sc_aa_tube,sc_bb_tube
+      integer:: i,j,iti
+      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,1).eq.ntyp1).or.(itype(i+1,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)
+!C       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
+!C         print *,ssgradtube, sstube,tubetranene(itype(i,1))
+         enetube(i)=enetube(i)+sstube*tubetranenepep
+!C         gg_tube_SC(3,i)=gg_tube_SC(3,i)
+!C     &+ssgradtube*tubetranene(itype(i,1))
+!C         gg_tube(3,i-1)= gg_tube(3,i-1)
+!C     &+ssgradtube*tubetranene(itype(i,1))
+!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,1))
+!C         gg_tube(3,i-1)= gg_tube(3,i-1)
+!C     &+ssgradtube*tubetranene(itype(i,1))
+!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,1)
+!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)
+!C       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
+!C         print *,ssgradtube, sstube,tubetranene(itype(i,1))
+         enetube(i+nres)=enetube(i+nres)+sstube*tubetranene(itype(i,1))
+!C         gg_tube_SC(3,i)=gg_tube_SC(3,i)
+!C     &+ssgradtube*tubetranene(itype(i,1))
+!C         gg_tube(3,i-1)= gg_tube(3,i-1)
+!C     &+ssgradtube*tubetranene(itype(i,1))
+!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,1))
+!C         gg_tube_SC(3,i)=gg_tube_SC(3,i)
+!C     &+ssgradtube*tubetranene(itype(i,1))
+!C         gg_tube(3,i-1)= gg_tube(3,i-1)
+!C     &+ssgradtube*tubetranene(itype(i,1))
+!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,1))
+!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 subroutine calctube2
+!=====================================================================================================================================
+      subroutine calcnano(Etube)
+      real(kind=8),dimension(3) :: vectube
+      
+      real(kind=8) :: Etube,xtemp,xminact,yminact,&
+       ytemp,xmin,ymin,tub_r,rdiff,rdiff6,fac,denominator,faccav,&
+       sc_aa_tube,sc_bb_tube,zmin,ztemp,zminact
+       integer:: i,j,iti,r
+
+      Etube=0.0d0
+!      print *,itube_start,itube_end,"poczatek"
+      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,1).eq.ntyp1).or.(itype(i+1,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)=dmod((c(1,i)+c(1,i+1))/2.0d0,boxxsize)
+         vectube(1)=vectube(1)+boxxsize*j
+         vectube(2)=dmod((c(2,i)+c(2,i+1))/2.0d0,boxysize)
+         vectube(2)=vectube(2)+boxysize*j
+         vectube(3)=dmod((c(3,i)+c(3,i+1))/2.0d0,boxzsize)
+         vectube(3)=vectube(3)+boxzsize*j
+
+
+         xminact=dabs(vectube(1)-tubecenter(1))
+         yminact=dabs(vectube(2)-tubecenter(2))
+         zminact=dabs(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.0d0+dcavtubpep*rdiff6*rdiff6)
+         enecavtube(i)=  &
+        (bcavtubpep*rdiff+acavtubpep*dsqrt(rdiff)+ccavtubpep) &
+        /denominator
+         enecavtube(i)=0.0
+         faccav=((bcavtubpep*1.0d0+acavtubpep/2.0d0/dsqrt(rdiff)) &
+        *denominator-(bcavtubpep*rdiff+acavtubpep*dsqrt(rdiff)   &
+        +ccavtubpep)*rdiff6**2.0d0/rdiff*dcavtubpep*12.0d0)      &
+        /denominator**2.0d0
+!C         faccav=0.0
+!C         fac=fac+faccav
+!C 667     continue
+         endif
+          if (energy_dec) write(iout,*),i,rdiff,enetube(i),enecavtube(i)
+        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.0d0
+!C Lets not jump over memory as we use many times iti
+         iti=itype(i,1)
+!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)=dmod((c(1,i+nres)),boxxsize)
+         vectube(1)=vectube(1)+boxxsize*j
+         vectube(2)=dmod((c(2,i+nres)),boxysize)
+         vectube(2)=vectube(2)+boxysize*j
+         vectube(3)=dmod((c(3,i+nres)),boxzsize)
+         vectube(3)=vectube(3)+boxzsize*j
+
+
+         xminact=dabs(vectube(1)-tubecenter(1))
+         yminact=dabs(vectube(2)-tubecenter(2))
+         zminact=dabs(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
+       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.0d0
+         faccav=0.0d0
+         else
+         denominator=(1.0d0+dcavtub(iti)*rdiff6*rdiff6)
+         enecavtube(i+nres)=   &
+        (bcavtub(iti)*rdiff+acavtub(iti)*dsqrt(rdiff)+ccavtub(iti)) &
+        /denominator
+!C         enecavtube(i)=0.0
+         faccav=((bcavtub(iti)*1.0d0+acavtub(iti)/2.0d0/dsqrt(rdiff)) &
+        *denominator-(bcavtub(iti)*rdiff+acavtub(iti)*dsqrt(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
+          if (energy_dec) write(iout,*),i,rdiff,enetube(i+nres),enecavtube(i+nres)
+        enddo
+
+
+
+        do i=itube_start,itube_end
+          Etube=Etube+enetube(i)+enetube(i+nres)+enecavtube(i) &
+         +enecavtube(i+nres)
+        enddo
+!        do i=1,20
+!         print *,"begin", i,"a"
+!         do r=1,10000
+!          rdiff=r/100.0d0
+!          rdiff6=rdiff**6.0d0
+!          sc_aa_tube=sc_aa_tube_par(i)
+!          sc_bb_tube=sc_bb_tube_par(i)
+!          enetube(i)=sc_aa_tube/rdiff6**2.0d0+sc_bb_tube/rdiff6
+!          denominator=(1.0d0+dcavtub(i)*rdiff6*rdiff6)
+!          enecavtube(i)=   &
+!         (bcavtub(i)*rdiff+acavtub(i)*dsqrt(rdiff)+ccavtub(i)) &
+!         /denominator
+
+!          print '(5(f10.3,1x))',rdiff,enetube(i),enecavtube(i),enecavtube(i)+enetube(i)
+!         enddo
+!         print *,"end",i,"a"
+!        enddo
+!C        print *,"ETUBE", etube
+        return
+        end subroutine calcnano
+
+!===============================================
+!--------------------------------------------------------------------------------
+!C first for shielding is setting of function of side-chains
+
+       subroutine set_shield_fac2
+       real(kind=8) :: div77_81=0.974996043d0, &
+        div4_81=0.2222222222d0
+       real (kind=8) :: dist_pep_side,dist_side_calf,dist_pept_group, &
+         scale_fac_dist,fac_help_scale,VofOverlap,VolumeTotal,costhet,&
+         short,long,sinthet,costhet_fac,sh_frac_dist,rkprim,cosphi,   &
+         sinphi,cosphi_fac,pep_side0pept_group,cosalfa,fac_alfa_sin
+!C the vector between center of side_chain and peptide group
+       real(kind=8),dimension(3) :: pep_side_long,side_calf, &
+         pept_group,costhet_grad,cosphi_grad_long, &
+         cosphi_grad_loc,pep_side_norm,side_calf_norm, &
+         sh_frac_dist_grad,pep_side
+        integer i,j,k
+!C      write(2,*) "ivec",ivec_start,ivec_end
+      do i=1,nres
+        fac_shield(i)=0.0d0
+        do j=1,3
+        grad_shield(j,i)=0.0d0
         enddo
       enddo
       do i=ivec_start,ivec_end
 !C      do i=1,nres-1
         enddo
       enddo
       do i=ivec_start,ivec_end
 !C      do i=1,nres-1
-!C      if ((itype(i).eq.ntyp1).and.itype(i+1).eq.ntyp1) cycle
+!C      if ((itype(i,1).eq.ntyp1).and.itype(i+1,1).eq.ntyp1) cycle
       ishield_list(i)=0
       ishield_list(i)=0
-      if ((itype(i).eq.ntyp1).and.itype(i+1).eq.ntyp1) cycle
+      if ((itype(i,1).eq.ntyp1).and.itype(i+1,1).eq.ntyp1) cycle
 !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
 !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
+       if ((itype(k,1).eq.ntyp1).or.(itype(k,1).eq.10)) cycle
        dist_pep_side=0.0
        dist_side_calf=0.0
        do j=1,3
        dist_pep_side=0.0
        dist_side_calf=0.0
        do j=1,3
@@ -17963,8 +19424,8 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
          enddo
         endif
 !C this is what is now we have the distance scaling now volume...
          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))
+      short=short_r_sidechain(itype(k,1))
+      long=long_r_sidechain(itype(k,1))
       costhet=1.0d0/dsqrt(1.0d0+short**2/dist_pep_side**2)
       sinthet=short/dist_pep_side*costhet
 !C now costhet_grad
       costhet=1.0d0/dsqrt(1.0d0+short**2/dist_pep_side**2)
       sinthet=short/dist_pep_side*costhet
 !C now costhet_grad
@@ -18050,10 +19511,66 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       enddo
       fac_shield(i)=VolumeTotal*wshield+(1.0d0-wshield)
      
       enddo
       fac_shield(i)=VolumeTotal*wshield+(1.0d0-wshield)
      
-      write(2,*) "TOTAL VOLUME",i,itype(i),fac_shield(i)
+!C      write(2,*) "TOTAL VOLUME",i,itype(i,1),fac_shield(i)
       enddo
       return
       end subroutine set_shield_fac2
       enddo
       return
       end subroutine set_shield_fac2
+!----------------------------------------------------------------------------
+! SOUBROUTINE FOR AFM
+       subroutine AFMvel(Eafmforce)
+       use MD_data, only:totTafm
+      real(kind=8),dimension(3) :: diffafm
+      real(kind=8) :: afmdist,Eafmforce
+       integer :: i
+!C Only for check grad COMMENT if not used for checkgrad
+!C      totT=3.0d0
+!C--------------------------------------------------------
+!C      print *,"wchodze"
+      afmdist=0.0d0
+      Eafmforce=0.0d0
+      do i=1,3
+      diffafm(i)=c(i,afmend)-c(i,afmbeg)
+      afmdist=afmdist+diffafm(i)**2
+      enddo
+      afmdist=dsqrt(afmdist)
+!      totTafm=3.0
+      Eafmforce=0.5d0*forceAFMconst &
+      *(distafminit+totTafm*velAFMconst-afmdist)**2
+!C      Eafmforce=-forceAFMconst*(dist-distafminit)
+      do i=1,3
+      gradafm(i,afmend-1)=-forceAFMconst* &
+       (distafminit+totTafm*velAFMconst-afmdist) &
+       *diffafm(i)/afmdist
+      gradafm(i,afmbeg-1)=forceAFMconst* &
+      (distafminit+totTafm*velAFMconst-afmdist) &
+      *diffafm(i)/afmdist
+      enddo
+!      print *,'AFM',Eafmforce,totTafm*velAFMconst,afmdist
+      return
+      end subroutine AFMvel
+!---------------------------------------------------------
+       subroutine AFMforce(Eafmforce)
+
+      real(kind=8),dimension(3) :: diffafm
+!      real(kind=8) ::afmdist
+      real(kind=8) :: afmdist,Eafmforce
+      integer :: i
+      afmdist=0.0d0
+      Eafmforce=0.0d0
+      do i=1,3
+      diffafm(i)=c(i,afmend)-c(i,afmbeg)
+      afmdist=afmdist+diffafm(i)**2
+      enddo
+      afmdist=dsqrt(afmdist)
+!      print *,afmdist,distafminit
+      Eafmforce=-forceAFMconst*(afmdist-distafminit)
+      do i=1,3
+      gradafm(i,afmend-1)=-forceAFMconst*diffafm(i)/afmdist
+      gradafm(i,afmbeg-1)=forceAFMconst*diffafm(i)/afmdist
+      enddo
+!C      print *,'AFM',Eafmforce
+      return
+      end subroutine AFMforce
 
 !-----------------------------------------------------------------------------
 #ifdef WHAM
 
 !-----------------------------------------------------------------------------
 #ifdef WHAM
@@ -18104,12 +19621,12 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       if(nres.lt.100) then
         maxconts=nres
       elseif(nres.lt.200) then
       if(nres.lt.100) then
         maxconts=nres
       elseif(nres.lt.200) then
-        maxconts=0.8*nres      ! Max. number of contacts per residue
+        maxconts=0.8*nres      ! Max. number of contacts per residue
       else
         maxconts=0.6*nres ! (maxconts=maxres/4)
       endif
       else
         maxconts=0.6*nres ! (maxconts=maxres/4)
       endif
-      maxcont=12*nres  ! Max. number of SC contacts
-      maxvar=6*nres    ! Max. number of variables
+      maxcont=12*nres      ! Max. number of SC contacts
+      maxvar=6*nres      ! Max. number of variables
 !el      maxdim=(nres-1)*(nres-2)/2 ! Max. number of derivatives of virtual-bond
       maxdim=nres*(nres-2)/2 ! Max. number of derivatives of virtual-bond
 !----------------------
 !el      maxdim=(nres-1)*(nres-2)/2 ! Max. number of derivatives of virtual-bond
       maxdim=nres*(nres-2)/2 ! Max. number of derivatives of virtual-bond
 !----------------------
@@ -18132,6 +19649,19 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       allocate(ielstart_vdw(nres))
       allocate(ielend_vdw(nres))
 !(maxres)
       allocate(ielstart_vdw(nres))
       allocate(ielend_vdw(nres))
 !(maxres)
+      allocate(nint_gr_nucl(nres))
+      allocate(nscp_gr_nucl(nres))
+      allocate(ielstart_nucl(nres))
+      allocate(ielend_nucl(nres))
+!(maxres)
+      allocate(istart_nucl(nres,maxint_gr))
+      allocate(iend_nucl(nres,maxint_gr))
+!(maxres,maxint_gr)
+      allocate(iscpstart_nucl(nres,maxint_gr))
+      allocate(iscpend_nucl(nres,maxint_gr))
+!(maxres,maxint_gr)
+      allocate(ielstart_vdw_nucl(nres))
+      allocate(ielend_vdw_nucl(nres))
 
       allocate(lentyp(0:nfgtasks-1))
 !(0:maxprocs-1)
 
       allocate(lentyp(0:nfgtasks-1))
 !(0:maxprocs-1)
@@ -18299,6 +19829,28 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
       allocate(gshieldc_ll(3,-1:nres))
       allocate(gshieldc_loc_ll(3,-1:nres))
       allocate(grad_shield(3,-1:nres))
       allocate(gshieldc_ll(3,-1:nres))
       allocate(gshieldc_loc_ll(3,-1:nres))
       allocate(grad_shield(3,-1:nres))
+      allocate(gg_tube_sc(3,-1:nres))
+      allocate(gg_tube(3,-1:nres))
+      allocate(gradafm(3,-1:nres))
+      allocate(gradb_nucl(3,-1:nres))
+      allocate(gradbx_nucl(3,-1:nres))
+      allocate(gvdwpsb1(3,-1:nres))
+      allocate(gelpp(3,-1:nres))
+      allocate(gvdwpsb(3,-1:nres))
+      allocate(gelsbc(3,-1:nres))
+      allocate(gelsbx(3,-1:nres))
+      allocate(gvdwsbx(3,-1:nres))
+      allocate(gvdwsbc(3,-1:nres))
+      allocate(gsbloc(3,-1:nres))
+      allocate(gsblocx(3,-1:nres))
+      allocate(gradcorr_nucl(3,-1:nres))
+      allocate(gradxorr_nucl(3,-1:nres))
+      allocate(gradcorr3_nucl(3,-1:nres))
+      allocate(gradxorr3_nucl(3,-1:nres))
+      allocate(gvdwpp_nucl(3,-1:nres))
+      allocate(gradpepcat(3,-1:nres))
+      allocate(gradpepcatx(3,-1:nres))
+      allocate(gradcatcat(3,-1:nres))
 !(3,maxres)
       allocate(grad_shield_side(3,50,nres))
       allocate(grad_shield_loc(3,50,nres))
 !(3,maxres)
       allocate(grad_shield_side(3,50,nres))
       allocate(grad_shield_loc(3,50,nres))
@@ -18327,6 +19879,14 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !(3,maxres)
       allocate(gsccor_loc(-1:nres))
 !(maxres)
 !(3,maxres)
       allocate(gsccor_loc(-1:nres))
 !(maxres)
+      allocate(gvdwx_scbase(3,-1:nres))
+      allocate(gvdwc_scbase(3,-1:nres))
+      allocate(gvdwx_pepbase(3,-1:nres))
+      allocate(gvdwc_pepbase(3,-1:nres))
+      allocate(gvdwx_scpho(3,-1:nres))
+      allocate(gvdwc_scpho(3,-1:nres))
+      allocate(gvdwc_peppho(3,-1:nres))
+
       allocate(dtheta(3,2,-1:nres))
 !(3,2,maxres)
       allocate(gscloc(3,-1:nres))
       allocate(dtheta(3,2,-1:nres))
 !(3,2,maxres)
       allocate(gscloc(3,-1:nres))
@@ -18404,7 +19964,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !----------------------
 ! common.sbridge
 !      common /sbridge/ in io_common: read_bridge
 !----------------------
 ! common.sbridge
 !      common /sbridge/ in io_common: read_bridge
-!el    allocate((:),allocatable :: iss !(maxss)
+!el    allocate((:),allocatable :: iss      !(maxss)
 !      common /links/  in io_common: read_bridge
 !el      real(kind=8),dimension(:),allocatable :: dhpb,forcon,dhpb1 !(maxdim) !el dhpb1 !!! nie używane
 !el      integer,dimension(:),allocatable :: ihpb,jhpb,ibecarb !(maxdim) !el ibecarb !!! nie używane
 !      common /links/  in io_common: read_bridge
 !el      real(kind=8),dimension(:),allocatable :: dhpb,forcon,dhpb1 !(maxdim) !el dhpb1 !!! nie używane
 !el      integer,dimension(:),allocatable :: ihpb,jhpb,ibecarb !(maxdim) !el ibecarb !!! nie używane
@@ -18418,14 +19978,18 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !        enddo
 !      enddo
 
 !        enddo
 !      enddo
 
-      if (nss.gt.0) then
-        allocate(idssb(nss),jdssb(nss))
+!      if (nss.gt.0) then
+        allocate(idssb(maxdim),jdssb(maxdim))
+!        allocate(newihpb(nss),newjhpb(nss))
 !(maxdim)
 !(maxdim)
-      endif
+!      endif
       allocate(ishield_list(nres))
       allocate(shield_list(50,nres))
       allocate(dyn_ss_mask(nres))
       allocate(fac_shield(nres))
       allocate(ishield_list(nres))
       allocate(shield_list(50,nres))
       allocate(dyn_ss_mask(nres))
       allocate(fac_shield(nres))
+      allocate(enetube(nres*2))
+      allocate(enecavtube(nres*2))
+
 !(maxres)
       dyn_ss_mask(:)=.false.
 !----------------------
 !(maxres)
       dyn_ss_mask(:)=.false.
 !----------------------
@@ -18441,7 +20005,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !      allocate(nlor_sccor(-ntyp:ntyp,-ntyp:ntyp)) !(-ntyp:ntyp,-ntyp:ntyp)
 !      allocate(vlor1sccor(maxterm_sccor,20,20))
 !      allocate(vlor2sccor(maxterm_sccor,20,20))
 !      allocate(nlor_sccor(-ntyp:ntyp,-ntyp:ntyp)) !(-ntyp:ntyp,-ntyp:ntyp)
 !      allocate(vlor1sccor(maxterm_sccor,20,20))
 !      allocate(vlor2sccor(maxterm_sccor,20,20))
-!      allocate(vlor3sccor(maxterm_sccor,20,20))       !(maxterm_sccor,20,20)
+!      allocate(vlor3sccor(maxterm_sccor,20,20))      !(maxterm_sccor,20,20)
 !----------------
       allocate(gloc_sc(3,0:2*nres,0:10))
 !(3,0:maxres2,10)maxres2=2*maxres
 !----------------
       allocate(gloc_sc(3,0:2*nres,0:10))
 !(3,0:maxres2,10)maxres2=2*maxres
@@ -18472,6 +20036,4070 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 
       return
       end subroutine alloc_ener_arrays
 
       return
       end subroutine alloc_ener_arrays
+!-----------------------------------------------------------------
+      subroutine ebond_nucl(estr_nucl)
+!c
+!c Evaluate the energy of stretching of the CA-CA and CA-SC virtual bonds
+!c 
+      
+      real(kind=8),dimension(3) :: u,ud
+      real(kind=8) :: usum,uprod,uprod1,uprod2,usumsqder
+      real(kind=8) :: estr_nucl,diff
+      integer :: iti,i,j,k,nbi
+      estr_nucl=0.0d0
+!C      print *,"I enter ebond"
+      if (energy_dec) &
+      write (iout,*) "ibondp_start,ibondp_end",&
+       ibondp_nucl_start,ibondp_nucl_end
+      do i=ibondp_nucl_start,ibondp_nucl_end
+        if (itype(i-1,2).eq.ntyp1_molec(2) .or. &
+         itype(i,2).eq.ntyp1_molec(2)) cycle
+!          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)
+
+          diff = vbld(i)-vbldp0_nucl
+          if(energy_dec)write(iout,*) "estr_nucl_bb" , i,vbld(i),&
+          vbldp0_nucl,diff,AKP_nucl*diff*diff
+          estr_nucl=estr_nucl+diff*diff
+!          print *,estr_nucl
+          do j=1,3
+            gradb_nucl(j,i-1)=AKP_nucl*diff*dc(j,i-1)/vbld(i)
+          enddo
+!c          write (iout,'(i5,3f10.5)') i,(gradb(j,i-1),j=1,3)
+      enddo
+      estr_nucl=0.5d0*AKP_nucl*estr_nucl
+!      print *,"partial sum", estr_nucl,AKP_nucl
+
+      if (energy_dec) &
+      write (iout,*) "ibondp_start,ibondp_end",&
+       ibond_nucl_start,ibond_nucl_end
+
+      do i=ibond_nucl_start,ibond_nucl_end
+!C        print *, "I am stuck",i
+        iti=itype(i,2)
+        if (iti.eq.ntyp1_molec(2)) cycle
+          nbi=nbondterm_nucl(iti)
+!C        print *,iti,nbi
+          if (nbi.eq.1) then
+            diff=vbld(i+nres)-vbldsc0_nucl(1,iti)
+
+            if (energy_dec) &
+           write (iout,*) "estr_nucl_sc", i,iti,vbld(i+nres),vbldsc0_nucl(1,iti),diff, &
+           AKSC_nucl(1,iti),AKSC_nucl(1,iti)*diff*diff
+            estr_nucl=estr_nucl+0.5d0*AKSC_nucl(1,iti)*diff*diff
+!            print *,estr_nucl
+            do j=1,3
+              gradbx_nucl(j,i)=AKSC_nucl(1,iti)*diff*dc(j,i+nres)/vbld(i+nres)
+            enddo
+          else
+            do j=1,nbi
+              diff=vbld(i+nres)-vbldsc0_nucl(j,iti)
+              ud(j)=aksc_nucl(j,iti)*diff
+              u(j)=abond0_nucl(j,iti)+0.5d0*ud(j)*diff
+            enddo
+            uprod=u(1)
+            do j=2,nbi
+              uprod=uprod*u(j)
+            enddo
+            usum=0.0d0
+            usumsqder=0.0d0
+            do j=1,nbi
+              uprod1=1.0d0
+              uprod2=1.0d0
+              do k=1,nbi
+                if (k.ne.j) then
+                  uprod1=uprod1*u(k)
+                  uprod2=uprod2*u(k)*u(k)
+                endif
+              enddo
+              usum=usum+uprod1
+              usumsqder=usumsqder+ud(j)*uprod2
+            enddo
+            estr_nucl=estr_nucl+uprod/usum
+            do j=1,3
+             gradbx_nucl(j,i)=usumsqder/(usum*usum)*dc(j,i+nres)/vbld(i+nres)
+            enddo
+        endif
+      enddo
+!C      print *,"I am about to leave ebond"
+      return
+      end subroutine ebond_nucl
+
 !-----------------------------------------------------------------------------
 !-----------------------------------------------------------------------------
-!-----------------------------------------------------------------------------
+      subroutine ebend_nucl(etheta_nucl)
+      real(kind=8),dimension(nntheterm_nucl+1) :: coskt,sinkt !mmaxtheterm
+      real(kind=8),dimension(nsingle_nucl+1) :: cosph1,sinph1,cosph2,sinph2 !maxsingle
+      real(kind=8),dimension(ndouble_nucl+1,ndouble_nucl+1) :: cosph1ph2,sinph1ph2 !maxdouble,maxdouble
+      logical :: lprn=.false., lprn1=.false.
+!el local variables
+      integer :: i,k,iblock,ityp1,ityp2,ityp3,l,m
+      real(kind=8) :: dethetai,dephii,dephii1,theti2,phii,phii1,ethetai
+      real(kind=8) :: aux,etheta_nucl,ccl,ssl,scl,csl,ethetacnstr
+! local variables for constrains
+      real(kind=8) :: difi,thetiii
+       integer itheta
+      etheta_nucl=0.0D0
+!      print *,"ithet_start",ithet_nucl_start," ithet_end",ithet_nucl_end,nres
+      do i=ithet_nucl_start,ithet_nucl_end
+        if ((itype(i-1,2).eq.ntyp1_molec(2)).or.&
+        (itype(i-2,2).eq.ntyp1_molec(2)).or.     &
+        (itype(i,2).eq.ntyp1_molec(2))) cycle
+        dethetai=0.0d0
+        dephii=0.0d0
+        dephii1=0.0d0
+        theti2=0.5d0*theta(i)
+        ityp2=ithetyp_nucl(itype(i-1,2))
+        do k=1,nntheterm_nucl
+          coskt(k)=dcos(k*theti2)
+          sinkt(k)=dsin(k*theti2)
+        enddo
+        if (i.gt.3 .and. itype(i-2,2).ne.ntyp1_molec(2)) then
+#ifdef OSF
+          phii=phi(i)
+          if (phii.ne.phii) phii=150.0
+#else
+          phii=phi(i)
+#endif
+          ityp1=ithetyp_nucl(itype(i-2,2))
+          do k=1,nsingle_nucl
+            cosph1(k)=dcos(k*phii)
+            sinph1(k)=dsin(k*phii)
+          enddo
+        else
+          phii=0.0d0
+          ityp1=nthetyp_nucl+1
+          do k=1,nsingle_nucl
+            cosph1(k)=0.0d0
+            sinph1(k)=0.0d0
+          enddo
+        endif
+
+        if (i.lt.nres .and. itype(i,2).ne.ntyp1_molec(2)) then
+#ifdef OSF
+          phii1=phi(i+1)
+          if (phii1.ne.phii1) phii1=150.0
+          phii1=pinorm(phii1)
+#else
+          phii1=phi(i+1)
+#endif
+          ityp3=ithetyp_nucl(itype(i,2))
+          do k=1,nsingle_nucl
+            cosph2(k)=dcos(k*phii1)
+            sinph2(k)=dsin(k*phii1)
+          enddo
+        else
+          phii1=0.0d0
+          ityp3=nthetyp_nucl+1
+          do k=1,nsingle_nucl
+            cosph2(k)=0.0d0
+            sinph2(k)=0.0d0
+          enddo
+        endif
+        ethetai=aa0thet_nucl(ityp1,ityp2,ityp3)
+        do k=1,ndouble_nucl
+          do l=1,k-1
+            ccl=cosph1(l)*cosph2(k-l)
+            ssl=sinph1(l)*sinph2(k-l)
+            scl=sinph1(l)*cosph2(k-l)
+            csl=cosph1(l)*sinph2(k-l)
+            cosph1ph2(l,k)=ccl-ssl
+            cosph1ph2(k,l)=ccl+ssl
+            sinph1ph2(l,k)=scl+csl
+            sinph1ph2(k,l)=scl-csl
+          enddo
+        enddo
+        if (lprn) then
+        write (iout,*) "i",i," ityp1",ityp1," ityp2",ityp2,&
+         " ityp3",ityp3," theti2",theti2," phii",phii," phii1",phii1
+        write (iout,*) "coskt and sinkt",nntheterm_nucl
+        do k=1,nntheterm_nucl
+          write (iout,*) k,coskt(k),sinkt(k)
+        enddo
+        endif
+        do k=1,ntheterm_nucl
+          ethetai=ethetai+aathet_nucl(k,ityp1,ityp2,ityp3)*sinkt(k)
+          dethetai=dethetai+0.5d0*k*aathet_nucl(k,ityp1,ityp2,ityp3)&
+           *coskt(k)
+          if (lprn)&
+         write (iout,*) "k",k," aathet",aathet_nucl(k,ityp1,ityp2,ityp3),&
+          " ethetai",ethetai
+        enddo
+        if (lprn) then
+        write (iout,*) "cosph and sinph"
+        do k=1,nsingle_nucl
+          write (iout,*) k,cosph1(k),sinph1(k),cosph2(k),sinph2(k)
+        enddo
+        write (iout,*) "cosph1ph2 and sinph2ph2"
+        do k=2,ndouble_nucl
+          do l=1,k-1
+            write (iout,*) l,k,cosph1ph2(l,k),cosph1ph2(k,l),&
+              sinph1ph2(l,k),sinph1ph2(k,l)
+          enddo
+        enddo
+        write(iout,*) "ethetai",ethetai
+        endif
+        do m=1,ntheterm2_nucl
+          do k=1,nsingle_nucl
+            aux=bbthet_nucl(k,m,ityp1,ityp2,ityp3)*cosph1(k)&
+              +ccthet_nucl(k,m,ityp1,ityp2,ityp3)*sinph1(k)&
+              +ddthet_nucl(k,m,ityp1,ityp2,ityp3)*cosph2(k)&
+              +eethet_nucl(k,m,ityp1,ityp2,ityp3)*sinph2(k)
+            ethetai=ethetai+sinkt(m)*aux
+            dethetai=dethetai+0.5d0*m*aux*coskt(m)
+            dephii=dephii+k*sinkt(m)*(&
+               ccthet_nucl(k,m,ityp1,ityp2,ityp3)*cosph1(k)-&
+               bbthet_nucl(k,m,ityp1,ityp2,ityp3)*sinph1(k))
+            dephii1=dephii1+k*sinkt(m)*(&
+               eethet_nucl(k,m,ityp1,ityp2,ityp3)*cosph2(k)-&
+               ddthet_nucl(k,m,ityp1,ityp2,ityp3)*sinph2(k))
+            if (lprn) &
+           write (iout,*) "m",m," k",k," bbthet",&
+              bbthet_nucl(k,m,ityp1,ityp2,ityp3)," ccthet",&
+              ccthet_nucl(k,m,ityp1,ityp2,ityp3)," ddthet",&
+              ddthet_nucl(k,m,ityp1,ityp2,ityp3)," eethet",&
+              eethet_nucl(k,m,ityp1,ityp2,ityp3)," ethetai",ethetai
+          enddo
+        enddo
+        if (lprn) &
+        write(iout,*) "ethetai",ethetai
+        do m=1,ntheterm3_nucl
+          do k=2,ndouble_nucl
+            do l=1,k-1
+              aux=ffthet_nucl(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)+&
+                 ffthet_nucl(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l)+&
+                 ggthet_nucl(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)+&
+                 ggthet_nucl(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)
+              ethetai=ethetai+sinkt(m)*aux
+              dethetai=dethetai+0.5d0*m*coskt(m)*aux
+              dephii=dephii+l*sinkt(m)*(&
+                -ffthet_nucl(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)-&
+                 ffthet_nucl(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)+&
+                 ggthet_nucl(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)+&
+                 ggthet_nucl(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l))
+              dephii1=dephii1+(k-l)*sinkt(m)*( &
+                -ffthet_nucl(l,k,m,ityp1,ityp2,ityp3)*sinph1ph2(l,k)+&
+                 ffthet_nucl(k,l,m,ityp1,ityp2,ityp3)*sinph1ph2(k,l)+&
+                 ggthet_nucl(l,k,m,ityp1,ityp2,ityp3)*cosph1ph2(l,k)-&
+                 ggthet_nucl(k,l,m,ityp1,ityp2,ityp3)*cosph1ph2(k,l))
+              if (lprn) then
+              write (iout,*) "m",m," k",k," l",l," ffthet", &
+                 ffthet_nucl(l,k,m,ityp1,ityp2,ityp3), &
+                 ffthet_nucl(k,l,m,ityp1,ityp2,ityp3)," ggthet",&
+                 ggthet_nucl(l,k,m,ityp1,ityp2,ityp3),&
+                 ggthet_nucl(k,l,m,ityp1,ityp2,ityp3)," ethetai",ethetai
+              write (iout,*) cosph1ph2(l,k)*sinkt(m), &
+                 cosph1ph2(k,l)*sinkt(m),&
+                 sinph1ph2(l,k)*sinkt(m),sinph1ph2(k,l)*sinkt(m)
+              endif
+            enddo
+          enddo
+        enddo
+10      continue
+        if (lprn1) write (iout,'(i2,3f8.1,9h ethetai ,f10.5)') &
+        i,theta(i)*rad2deg,phii*rad2deg, &
+        phii1*rad2deg,ethetai
+        etheta_nucl=etheta_nucl+ethetai
+!        print *,i,"partial sum",etheta_nucl
+        if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang_nucl*dephii
+        if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang_nucl*dephii1
+        gloc(nphi+i-2,icg)=wang_nucl*dethetai
+      enddo
+      return
+      end subroutine ebend_nucl
+!----------------------------------------------------
+      subroutine etor_nucl(etors_nucl)
+!      implicit real*8 (a-h,o-z)
+!      include 'DIMENSIONS'
+!      include 'COMMON.VAR'
+!      include 'COMMON.GEO'
+!      include 'COMMON.LOCAL'
+!      include 'COMMON.TORSION'
+!      include 'COMMON.INTERACT'
+!      include 'COMMON.DERIV'
+!      include 'COMMON.CHAIN'
+!      include 'COMMON.NAMES'
+!      include 'COMMON.IOUNITS'
+!      include 'COMMON.FFIELD'
+!      include 'COMMON.TORCNSTR'
+!      include 'COMMON.CONTROL'
+      real(kind=8) :: etors_nucl,edihcnstr
+      logical :: lprn
+!el local variables
+      integer :: i,j,iblock,itori,itori1
+      real(kind=8) :: phii,gloci,v1ij,v2ij,cosphi,sinphi,&
+                   vl1ij,vl2ij,vl3ij,pom1,difi,etors_ii,pom
+! Set lprn=.true. for debugging
+      lprn=.false.
+!     lprn=.true.
+      etors_nucl=0.0D0
+!      print *,"iphi_nucl_start/end", iphi_nucl_start,iphi_nucl_end
+      do i=iphi_nucl_start,iphi_nucl_end
+        if (itype(i-2,2).eq.ntyp1_molec(2) .or. itype(i-1,2).eq.ntyp1_molec(2) &
+             .or. itype(i-3,2).eq.ntyp1_molec(2) &
+             .or. itype(i,2).eq.ntyp1_molec(2)) cycle
+        etors_ii=0.0D0
+        itori=itortyp_nucl(itype(i-2,2))
+        itori1=itortyp_nucl(itype(i-1,2))
+        phii=phi(i)
+!         print *,i,itori,itori1
+        gloci=0.0D0
+!C Regular cosine and sine terms
+        do j=1,nterm_nucl(itori,itori1)
+          v1ij=v1_nucl(j,itori,itori1)
+          v2ij=v2_nucl(j,itori,itori1)
+          cosphi=dcos(j*phii)
+          sinphi=dsin(j*phii)
+          etors_nucl=etors_nucl+v1ij*cosphi+v2ij*sinphi
+          if (energy_dec) etors_ii=etors_ii+&
+                     v1ij*cosphi+v2ij*sinphi
+          gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
+        enddo
+!C Lorentz terms
+!C                         v1
+!C  E = SUM ----------------------------------- - v1
+!C          [v2 cos(phi/2)+v3 sin(phi/2)]^2 + 1
+!C
+        cosphi=dcos(0.5d0*phii)
+        sinphi=dsin(0.5d0*phii)
+        do j=1,nlor_nucl(itori,itori1)
+          vl1ij=vlor1_nucl(j,itori,itori1)
+          vl2ij=vlor2_nucl(j,itori,itori1)
+          vl3ij=vlor3_nucl(j,itori,itori1)
+          pom=vl2ij*cosphi+vl3ij*sinphi
+          pom1=1.0d0/(pom*pom+1.0d0)
+          etors_nucl=etors_nucl+vl1ij*pom1
+          if (energy_dec) etors_ii=etors_ii+ &
+                     vl1ij*pom1
+          pom=-pom*pom1*pom1
+          gloci=gloci+vl1ij*(vl3ij*cosphi-vl2ij*sinphi)*pom
+        enddo
+!C Subtract the constant term
+        etors_nucl=etors_nucl-v0_nucl(itori,itori1)
+          if (energy_dec) write (iout,'(a6,i5,0pf7.3)') &
+              'etor',i,etors_ii-v0_nucl(itori,itori1)
+        if (lprn) &
+       write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)') &
+       restyp(itype(i-2,2),2),i-2,restyp(itype(i-1,2),2),i-1,itori,itori1, &
+       (v1_nucl(j,itori,itori1),j=1,6),(v2_nucl(j,itori,itori1),j=1,6)
+        gloc(i-3,icg)=gloc(i-3,icg)+wtor_nucl*gloci
+!c       write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
+      enddo
+      return
+      end subroutine etor_nucl
+!------------------------------------------------------------
+      subroutine epp_nucl_sub(evdw1,ees)
+!C
+!C This subroutine calculates the average interaction energy and its gradient
+!C in the virtual-bond vectors between non-adjacent peptide groups, based on 
+!C the potential described in Liwo et al., Protein Sci., 1993, 2, 1715. 
+!C The potential depends both on the distance of peptide-group centers and on 
+!C the orientation of the CA-CA virtual bonds.
+!C 
+      integer :: i,j,k,iteli,itelj,num_conti,isubchap,ind
+      real(kind=8) :: dxi,dyi,dzi,dxj,dyj,dzj,aaa,bbb
+      real(kind=8) :: xj,yj,zj,rij,rrmij,sss,r3ij,r6ij,evdw1,&
+                 dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,&
+                 dx_normj,dy_normj,dz_normj,rmij,ev1,ev2,evdwij,facvdw
+      real(kind=8) :: xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,&
+                    dist_temp, dist_init,sss_grad,fac,evdw1ij
+      integer xshift,yshift,zshift
+      real(kind=8),dimension(3):: ggg,gggp,gggm,erij
+      real(kind=8) :: ees,eesij
+!c 4/26/02 - AL scaling factor for 1,4 repulsive VDW interactions
+      real(kind=8) scal_el /0.5d0/
+      t_eelecij=0.0d0
+      ees=0.0D0
+      evdw1=0.0D0
+      ind=0
+!c
+!c Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
+!c
+!      print *,"iatel_s_nucl,iatel_e_nucl",iatel_s_nucl,iatel_e_nucl
+      do i=iatel_s_nucl,iatel_e_nucl
+        if (itype(i,2).eq.ntyp1_molec(2) .or. itype(i+1,2).eq.ntyp1_molec(2)) cycle
+        dxi=dc(1,i)
+        dyi=dc(2,i)
+        dzi=dc(3,i)
+        dx_normi=dc_norm(1,i)
+        dy_normi=dc_norm(2,i)
+        dz_normi=dc_norm(3,i)
+        xmedi=c(1,i)+0.5d0*dxi
+        ymedi=c(2,i)+0.5d0*dyi
+        zmedi=c(3,i)+0.5d0*dzi
+          xmedi=dmod(xmedi,boxxsize)
+          if (xmedi.lt.0) xmedi=xmedi+boxxsize
+          ymedi=dmod(ymedi,boxysize)
+          if (ymedi.lt.0) ymedi=ymedi+boxysize
+          zmedi=dmod(zmedi,boxzsize)
+          if (zmedi.lt.0) zmedi=zmedi+boxzsize
+
+        do j=ielstart_nucl(i),ielend_nucl(i)
+          if (itype(j,2).eq.ntyp1_molec(2) .or. itype(j+1,2).eq.ntyp1_molec(2)) cycle
+          ind=ind+1
+          dxj=dc(1,j)
+          dyj=dc(2,j)
+          dzj=dc(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
+      isubchap=0
+      dist_init=(xj-xmedi)**2+(yj-ymedi)**2+(zj-zmedi)**2
+      xj_safe=xj
+      yj_safe=yj
+      zj_safe=zj
+      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
+!C          print *,i,j
+          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
+!c          write (2,*)"ij",i,j," r0pp",r0pp," rij",rij," epspp",epspp
+          fac=(r0pp**2/rij)**3
+          ev1=epspp*fac*fac
+          ev2=epspp*fac
+          evdw1ij=ev1-2*ev2
+          fac=(-ev1-evdw1ij)/rij
+!          write (2,*)"fac",fac," ev1",ev1," ev2",ev2," evdw1ij",evdw1ij
+          if (energy_dec) write(iout,'(2i5,a9,f10.4)') i,j,"evdw1ij",evdw1ij
+          evdw1=evdw1+evdw1ij
+!C
+!C Calculate contributions to the Cartesian gradient.
+!C
+          ggg(1)=fac*xj
+          ggg(2)=fac*yj
+          ggg(3)=fac*zj
+          do k=1,3
+            gvdwpp_nucl(k,i)=gvdwpp_nucl(k,i)-ggg(k)
+            gvdwpp_nucl(k,j)=gvdwpp_nucl(k,j)+ggg(k)
+          enddo
+!c phoshate-phosphate electrostatic interactions
+          rij=dsqrt(rij)
+          fac=1.0d0/rij
+          eesij=dexp(-BEES*rij)*fac
+!          write (2,*)"fac",fac," eesijpp",eesij
+          if (energy_dec) write(iout,'(2i5,a9,f10.4)') i,j,"eesijpp",eesij
+          ees=ees+eesij
+!c          fac=-eesij*fac
+          fac=-(fac+BEES)*eesij*fac
+          ggg(1)=fac*xj
+          ggg(2)=fac*yj
+          ggg(3)=fac*zj
+!c          write(2,*) "ggg",i,j,ggg(1),ggg(2),ggg(3)
+!c          write(2,*) "gelpp",i,(gelpp(k,i),k=1,3)
+!c          write(2,*) "gelpp",j,(gelpp(k,j),k=1,3)
+          do k=1,3
+            gelpp(k,i)=gelpp(k,i)-ggg(k)
+            gelpp(k,j)=gelpp(k,j)+ggg(k)
+          enddo
+        enddo ! j
+      enddo   ! i
+!c      ees=332.0d0*ees 
+      ees=AEES*ees
+      do i=nnt,nct
+!c        write (2,*) "i",i," gelpp",(gelpp(k,i),k=1,3)
+        do k=1,3
+          gvdwpp_nucl(k,i)=6*gvdwpp_nucl(k,i)
+!c          gelpp(k,i)=332.0d0*gelpp(k,i)
+          gelpp(k,i)=AEES*gelpp(k,i)
+        enddo
+!c        write (2,*) "i",i," gelpp",(gelpp(k,i),k=1,3)
+      enddo
+!c      write (2,*) "total EES",ees
+      return
+      end subroutine epp_nucl_sub
+!---------------------------------------------------------------------
+      subroutine epsb(evdwpsb,eelpsb)
+!      use comm_locel
+!C
+!C This subroutine calculates the excluded-volume interaction energy between
+!C peptide-group centers and side chains and its gradient in virtual-bond and
+!C side-chain vectors.
+!C
+      real(kind=8),dimension(3):: ggg
+      integer :: i,iint,j,k,iteli,itypj,subchap
+      real(kind=8) :: evdw2,evdw2_14,xi,yi,zi,xj,yj,zj,rrij,fac,&
+                   e1,e2,evdwij,rij,evdwpsb,eelpsb
+      real(kind=8) :: xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,&
+                    dist_temp, dist_init
+      integer xshift,yshift,zshift
+
+!cd    print '(a)','Enter ESCP'
+!cd    write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
+      eelpsb=0.0d0
+      evdwpsb=0.0d0
+!      print *,"iatscp_s_nucl,iatscp_e_nucl",iatscp_s_nucl,iatscp_e_nucl
+      do i=iatscp_s_nucl,iatscp_e_nucl
+        if (itype(i,2).eq.ntyp1_molec(2) &
+         .or. itype(i+1,2).eq.ntyp1_molec(2)) cycle
+        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))
+          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_nucl(i)
+
+        do j=iscpstart_nucl(i,iint),iscpend_nucl(i,iint)
+          itypj=itype(j,2)
+          if (itypj.eq.ntyp1_molec(2)) cycle
+!C Uncomment following three lines for SC-p interactions
+!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)
+          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
+      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)
+          fac=rrij**expon2
+          e1=fac*fac*aad_nucl(itypj)
+          e2=fac*bad_nucl(itypj)
+          if (iabs(j-i) .le. 2) then
+            e1=scal14*e1
+            e2=scal14*e2
+          endif
+          evdwij=e1+e2
+          evdwpsb=evdwpsb+evdwij
+          if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a4)') &
+             'evdw2',i,j,evdwij,"tu4"
+!C
+!C Calculate contributions to the gradient in the virtual-bond and SC vectors.
+!C
+          fac=-(evdwij+e1)*rrij
+          ggg(1)=xj*fac
+          ggg(2)=yj*fac
+          ggg(3)=zj*fac
+          do k=1,3
+            gvdwpsb1(k,i)=gvdwpsb1(k,i)-ggg(k)
+            gvdwpsb(k,j)=gvdwpsb(k,j)+ggg(k)
+          enddo
+        enddo
+
+        enddo ! iint
+      enddo ! i
+      do i=1,nct
+        do j=1,3
+          gvdwpsb(j,i)=expon*gvdwpsb(j,i)
+          gvdwpsb1(j,i)=expon*gvdwpsb1(j,i)
+        enddo
+      enddo
+      return
+      end subroutine epsb
+
+!------------------------------------------------------
+      subroutine esb_gb(evdwsb,eelsb)
+      use comm_locel
+      use calc_data_nucl
+      integer :: iint,itypi,itypi1,itypj,subchap,num_conti2
+      real(kind=8) :: xi,yi,zi,sig,rij_shift,fac,e1,e2,sigm,epsi
+      real(kind=8) :: evdw,sig0iji,evdwsb,eelsb,ecorr,eelij
+      real(kind=8) :: xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,&
+                    dist_temp, dist_init,aa,bb,faclip,sig0ij
+      integer :: ii
+      logical lprn
+      evdw=0.0D0
+      eelsb=0.0d0
+      ecorr=0.0d0
+      evdwsb=0.0D0
+      lprn=.false.
+      ind=0
+!      print *,"iastsc_nucl",iatsc_s_nucl,iatsc_e_nucl
+      do i=iatsc_s_nucl,iatsc_e_nucl
+        num_conti=0
+        num_conti2=0
+        itypi=itype(i,2)
+!        PRINT *,"I=",i,itypi
+        if (itypi.eq.ntyp1_molec(2)) cycle
+        itypi1=itype(i+1,2)
+        xi=c(1,nres+i)
+        yi=c(2,nres+i)
+        zi=c(3,nres+i)
+          xi=dmod(xi,boxxsize)
+          if (xi.lt.0) xi=xi+boxxsize
+          yi=dmod(yi,boxysize)
+          if (yi.lt.0) yi=yi+boxysize
+          zi=dmod(zi,boxzsize)
+          if (zi.lt.0) zi=zi+boxzsize
+
+        dxi=dc_norm(1,nres+i)
+        dyi=dc_norm(2,nres+i)
+        dzi=dc_norm(3,nres+i)
+        dsci_inv=vbld_inv(i+nres)
+!C
+!C Calculate SC interaction energy.
+!C
+        do iint=1,nint_gr_nucl(i)
+!          print *,"tu?",i,istart_nucl(i,iint),iend_nucl(i,iint) 
+          do j=istart_nucl(i,iint),iend_nucl(i,iint)
+            ind=ind+1
+!            print *,"JESTEM"
+            itypj=itype(j,2)
+            if (itypj.eq.ntyp1_molec(2)) cycle
+            dscj_inv=vbld_inv(j+nres)
+            sig0ij=sigma_nucl(itypi,itypj)
+            chi1=chi_nucl(itypi,itypj)
+            chi2=chi_nucl(itypj,itypi)
+            chi12=chi1*chi2
+            chip1=chip_nucl(itypi,itypj)
+            chip2=chip_nucl(itypj,itypi)
+            chip12=chip1*chip2
+!            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)
+          xj=dmod(xj,boxxsize)
+          if (xj.lt.0) xj=xj+boxxsize
+          yj=dmod(yj,boxysize)
+          if (yj.lt.0) yj=yj+boxysize
+          zj=dmod(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
+      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)
+            rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
+            rij=dsqrt(rrij)
+!C Calculate angle-dependent terms of energy and contributions to their
+!C derivatives.
+            erij(1)=xj*rij
+            erij(2)=yj*rij
+            erij(3)=zj*rij
+            om1=dxi*erij(1)+dyi*erij(2)+dzi*erij(3)
+            om2=dxj*erij(1)+dyj*erij(2)+dzj*erij(3)
+            om12=dxi*dxj+dyi*dyj+dzi*dzj
+            call sc_angular_nucl
+            sigsq=1.0D0/sigsq
+            sig=sig0ij*dsqrt(sigsq)
+            rij_shift=1.0D0/rij-sig+sig0ij
+!            print *,rij_shift,"rij_shift"
+!c            write (2,*) " rij",1.0D0/rij," sig",sig," sig0ij",sig0ij,
+!c     &       " rij_shift",rij_shift
+            if (rij_shift.le.0.0D0) then
+              evdw=1.0D20
+              return
+            endif
+            sigder=-sig*sigsq
+!c---------------------------------------------------------------
+            rij_shift=1.0D0/rij_shift
+            fac=rij_shift**expon
+            e1=fac*fac*aa_nucl(itypi,itypj)
+            e2=fac*bb_nucl(itypi,itypj)
+            evdwij=eps1*eps2rt*(e1+e2)
+!c            write (2,*) "eps1",eps1," eps2rt",eps2rt,
+!c     &       " e1",e1," e2",e2," evdwij",evdwij
+            eps2der=evdwij
+            evdwij=evdwij*eps2rt
+            evdwsb=evdwsb+evdwij
+            if (lprn) then
+            sigm=dabs(aa_nucl(itypi,itypj)/bb_nucl(itypi,itypj))**(1.0D0/6.0D0)
+            epsi=bb_nucl(itypi,itypj)**2/aa_nucl(itypi,itypj)
+            write (iout,'(2(a3,i3,2x),17(0pf7.3))') &
+             restyp(itypi,2),i,restyp(itypj,2),j, &
+             epsi,sigm,chi1,chi2,chip1,chip2, &
+             eps1,eps2rt**2,sig,sig0ij, &
+             om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,&
+            evdwij
+            write (iout,*) "aa",aa_nucl(itypi,itypj)," bb",bb_nucl(itypi,itypj)
+            endif
+
+            if (energy_dec) write (iout,'(a6,2i5,e15.3,a4)') &
+                             'evdw',i,j,evdwij,"tu3"
+
+
+!C Calculate gradient components.
+            e1=e1*eps1*eps2rt**2
+            fac=-expon*(e1+evdwij)*rij_shift
+            sigder=fac*sigder
+            fac=rij*fac
+!c            fac=0.0d0
+!C Calculate the radial part of the gradient
+            gg(1)=xj*fac
+            gg(2)=yj*fac
+            gg(3)=zj*fac
+!C Calculate angular part of the gradient.
+            call sc_grad_nucl
+            call eelsbij(eelij,num_conti2)
+            if (energy_dec .and. &
+           (j.eq.i+1.or.j.eq.nres-i+1.or.j.eq.nres-i.or.j.eq.nres-i+2)) &
+          write (istat,'(e14.5)') evdwij
+            eelsb=eelsb+eelij
+          enddo      ! j
+        enddo        ! iint
+        num_cont_hb(i)=num_conti2
+      enddo          ! i
+!c      write (iout,*) "Number of loop steps in EGB:",ind
+!cccc      energy_dec=.false.
+      return
+      end subroutine esb_gb
+!-------------------------------------------------------------------------------
+      subroutine eelsbij(eesij,num_conti2)
+      use comm_locel
+      use calc_data_nucl
+      real(kind=8),dimension(3) :: ggg,gggp,gggm,dcosb,dcosg
+      real(kind=8),dimension(3,3) :: erder,uryg,urzg,vryg,vrzg
+      real(kind=8) :: xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,&
+                    dist_temp, dist_init,rlocshield,fracinbuf
+      integer xshift,yshift,zshift,ilist,iresshield,num_conti2
+
+!c 4/26/02 - AL scaling factor for 1,4 repulsive VDW interactions
+      real(kind=8) scal_el /0.5d0/
+      integer :: iteli,itelj,kkk,kkll,m,isubchap
+      real(kind=8) :: ael6i,rrmij,rmij,r0ij,fcont,fprimcont,ees0tmp,facfac
+      real(kind=8) :: ees,evdw1,eel_loc,aaa,bbb,ael3i,ael63i,ael32i
+      real(kind=8) :: dx_normj,dy_normj,dz_normj,&
+                  r3ij,r6ij,cosa,cosb,cosg,fac,ev1,ev2,fac3,fac4,fac5,fac6,&
+                  el1,el2,el3,el4,eesij,ees0ij,facvdw,facel,fac1,ecosa,&
+                  ecosb,ecosg,ury,urz,vry,vrz,facr,a22der,a23der,a32der,&
+                  a33der,eel_loc_ij,cosa4,wij,cosbg1,cosbg2,ees0pij,&
+                  ees0pij1,ees0mij,ees0mij1,fac3p,ees0mijp,ees0pijp,&
+                  ecosa1,ecosb1,ecosg1,ecosa2,ecosb2,ecosg2,ecosap,ecosbp,&
+                  ecosgp,ecosam,ecosbm,ecosgm,ghalf,itypi,itypj
+      ind=ind+1
+      itypi=itype(i,2)
+      itypj=itype(j,2)
+!      print *,i,j,itypi,itypj,istype(i),istype(j),"????"
+      ael6i=ael6_nucl(itypi,itypj)
+      ael3i=ael3_nucl(itypi,itypj)
+      ael63i=ael63_nucl(itypi,itypj)
+      ael32i=ael32_nucl(itypi,itypj)
+!c      write (iout,*) "eelecij",i,j,itype(i),itype(j),
+!c     &  ael6i,ael3i,ael63i,al32i,rij,rrij
+      dxj=dc(1,j+nres)
+      dyj=dc(2,j+nres)
+      dzj=dc(3,j+nres)
+      dx_normi=dc_norm(1,i+nres)
+      dy_normi=dc_norm(2,i+nres)
+      dz_normi=dc_norm(3,i+nres)
+      dx_normj=dc_norm(1,j+nres)
+      dy_normj=dc_norm(2,j+nres)
+      dz_normj=dc_norm(3,j+nres)
+!c      xj=c(1,j)+0.5D0*dxj-xmedi
+!c      yj=c(2,j)+0.5D0*dyj-ymedi
+!c      zj=c(3,j)+0.5D0*dzj-zmedi
+      if (ipot_nucl.ne.2) then
+        cosa=dx_normi*dx_normj+dy_normi*dy_normj+dz_normi*dz_normj
+        cosb=(xj*dx_normi+yj*dy_normi+zj*dz_normi)*rmij
+        cosg=(xj*dx_normj+yj*dy_normj+zj*dz_normj)*rmij
+      else
+        cosa=om12
+        cosb=om1
+        cosg=om2
+      endif
+      r3ij=rij*rrij
+      r6ij=r3ij*r3ij
+      fac=cosa-3.0D0*cosb*cosg
+      facfac=fac*fac
+      fac1=3.0d0*(cosb*cosb+cosg*cosg)
+      fac3=ael6i*r6ij
+      fac4=ael3i*r3ij
+      fac5=ael63i*r6ij
+      fac6=ael32i*r6ij
+!c      write (iout,*) "r3ij",r3ij," r6ij",r6ij," fac",fac," fac1",fac1,
+!c     &  " fac2",fac2," fac3",fac3," fac4",fac4," fac5",fac5," fac6",fac6
+      el1=fac3*(4.0D0+facfac-fac1)
+      el2=fac4*fac
+      el3=fac5*(2.0d0-2.0d0*facfac+fac1)
+      el4=fac6*facfac
+      eesij=el1+el2+el3+el4
+!C 12/26/95 - for the evaluation of multi-body H-bonding interactions
+      ees0ij=4.0D0+facfac-fac1
+
+      if (energy_dec) then
+          if(j.eq.i+1.or.j.eq.nres-i+1.or.j.eq.nres-i.or.j.eq.nres-i+2) &
+          write (istat,'(2a1,i4,1x,2a1,i4,4f10.5,3e12.5,$)') &
+           sugartyp(istype(i)),restyp(itypi,2),i,sugartyp(istype(j)),&
+           restyp(itypj,2),j,1.0d0/rij,cosa,cosb,cosg,fac*r3ij, &
+           (4.0D0+facfac-fac1)*r6ij,(2.0d0-2.0d0*facfac+fac1)*r6ij 
+          write (iout,'(a6,2i5,e15.3)') 'ees',i,j,eesij
+      endif
+
+!C
+!C Calculate contributions to the Cartesian gradient.
+!C
+      facel=-3.0d0*rrij*(eesij+el1+el3+el4)
+      fac1=fac
+!c      erij(1)=xj*rmij
+!c      erij(2)=yj*rmij
+!c      erij(3)=zj*rmij
+!*
+!* Radial derivatives. First process both termini of the fragment (i,j)
+!*
+      ggg(1)=facel*xj
+      ggg(2)=facel*yj
+      ggg(3)=facel*zj
+      do k=1,3
+        gelsbc(k,j)=gelsbc(k,j)+ggg(k)
+        gelsbc(k,i)=gelsbc(k,i)-ggg(k)
+        gelsbx(k,j)=gelsbx(k,j)+ggg(k)
+        gelsbx(k,i)=gelsbx(k,i)-ggg(k)
+      enddo
+!*
+!* Angular part
+!*          
+      ecosa=2.0D0*fac3*fac1+fac4+(-4.0d0*fac5+2.0d0*fac6)*fac1
+      fac4=-3.0D0*fac4
+      fac3=-6.0D0*fac3
+      fac5= 6.0d0*fac5
+      fac6=-6.0d0*fac6
+      ecosb=fac3*(fac1*cosg+cosb)+cosg*fac4+(cosb+2*fac1*cosg)*fac5+&
+       fac6*fac1*cosg
+      ecosg=fac3*(fac1*cosb+cosg)+cosb*fac4+(cosg+2*fac1*cosb)*fac5+&
+       fac6*fac1*cosb
+      do k=1,3
+        dcosb(k)=rij*(dc_norm(k,i+nres)-erij(k)*cosb)
+        dcosg(k)=rij*(dc_norm(k,j+nres)-erij(k)*cosg)
+      enddo
+      do k=1,3
+        ggg(k)=ecosb*dcosb(k)+ecosg*dcosg(k)
+      enddo
+      do k=1,3
+        gelsbx(k,i)=gelsbx(k,i)-ggg(k) &
+             +(ecosa*(dc_norm(k,j+nres)-cosa*dc_norm(k,i+nres))&
+             + ecosb*(erij(k)-cosb*dc_norm(k,i+nres)))*vbld_inv(i+nres)
+        gelsbx(k,j)=gelsbx(k,j)+ggg(k) &
+             +(ecosa*(dc_norm(k,i+nres)-cosa*dc_norm(k,j+nres))&
+             + ecosg*(erij(k)-cosg*dc_norm(k,j+nres)))*vbld_inv(j+nres)
+        gelsbc(k,j)=gelsbc(k,j)+ggg(k)
+        gelsbc(k,i)=gelsbc(k,i)-ggg(k)
+      enddo
+!      IF ( (wcorr_nucl.gt.0.0d0.or.wcorr3_nucl.gt.0.0d0) .and.
+       IF ( j.gt.i+1 .and.&
+          num_conti.le.maxconts) THEN
+!C
+!C Calculate the contact function. The ith column of the array JCONT will 
+!C contain the numbers of atoms that make contacts with the atom I (of numbers
+!C greater than I). The arrays FACONT and GACONT will contain the values of
+!C the contact function and its derivative.
+        r0ij=2.20D0*sigma(itypi,itypj)
+!c        write (2,*) "ij",i,j," rij",1.0d0/rij," r0ij",r0ij
+        call gcont(rij,r0ij,1.0D0,0.2d0/r0ij,fcont,fprimcont)
+!c        write (2,*) "fcont",fcont
+        if (fcont.gt.0.0D0) then
+          num_conti=num_conti+1
+          num_conti2=num_conti2+1
+
+          if (num_conti.gt.maxconts) then
+            write (iout,*) 'WARNING - max. # of contacts exceeded;',&
+                          ' will skip next contacts for this conf.'
+          else
+            jcont_hb(num_conti,i)=j
+!c            write (iout,*) "num_conti",num_conti,
+!c     &        " jcont_hb",jcont_hb(num_conti,i)
+!C Calculate contact energies
+            cosa4=4.0D0*cosa
+            wij=cosa-3.0D0*cosb*cosg
+            cosbg1=cosb+cosg
+            cosbg2=cosb-cosg
+            fac3=dsqrt(-ael6i)*r3ij
+!c            write (2,*) "ael6i",ael6i," r3ij",r3ij," fac3",fac3
+            ees0tmp=4.0D0+cosa4+wij*wij-3.0D0*cosbg1*cosbg1
+            if (ees0tmp.gt.0) then
+              ees0pij=dsqrt(ees0tmp)
+            else
+              ees0pij=0
+            endif
+            ees0tmp=4.0D0-cosa4+wij*wij-3.0D0*cosbg2*cosbg2
+            if (ees0tmp.gt.0) then
+              ees0mij=dsqrt(ees0tmp)
+            else
+              ees0mij=0
+            endif
+            ees0p(num_conti,i)=0.5D0*fac3*(ees0pij+ees0mij)
+            ees0m(num_conti,i)=0.5D0*fac3*(ees0pij-ees0mij)
+!c            write (iout,*) "i",i," j",j,
+!c     &         " ees0m",ees0m(num_conti,i)," ees0p",ees0p(num_conti,i)
+            ees0pij1=fac3/ees0pij
+            ees0mij1=fac3/ees0mij
+            fac3p=-3.0D0*fac3*rrij
+            ees0pijp=0.5D0*fac3p*(ees0pij+ees0mij)
+            ees0mijp=0.5D0*fac3p*(ees0pij-ees0mij)
+            ecosa1=       ees0pij1*( 1.0D0+0.5D0*wij)
+            ecosb1=-1.5D0*ees0pij1*(wij*cosg+cosbg1)
+            ecosg1=-1.5D0*ees0pij1*(wij*cosb+cosbg1)
+            ecosa2=       ees0mij1*(-1.0D0+0.5D0*wij)
+            ecosb2=-1.5D0*ees0mij1*(wij*cosg+cosbg2)
+            ecosg2=-1.5D0*ees0mij1*(wij*cosb-cosbg2)
+            ecosap=ecosa1+ecosa2
+            ecosbp=ecosb1+ecosb2
+            ecosgp=ecosg1+ecosg2
+            ecosam=ecosa1-ecosa2
+            ecosbm=ecosb1-ecosb2
+            ecosgm=ecosg1-ecosg2
+!C End diagnostics
+            facont_hb(num_conti,i)=fcont
+            fprimcont=fprimcont/rij
+            do k=1,3
+              gggp(k)=ecosbp*dcosb(k)+ecosgp*dcosg(k)
+              gggm(k)=ecosbm*dcosb(k)+ecosgm*dcosg(k)
+            enddo
+            gggp(1)=gggp(1)+ees0pijp*xj
+            gggp(2)=gggp(2)+ees0pijp*yj
+            gggp(3)=gggp(3)+ees0pijp*zj
+            gggm(1)=gggm(1)+ees0mijp*xj
+            gggm(2)=gggm(2)+ees0mijp*yj
+            gggm(3)=gggm(3)+ees0mijp*zj
+!C Derivatives due to the contact function
+            gacont_hbr(1,num_conti,i)=fprimcont*xj
+            gacont_hbr(2,num_conti,i)=fprimcont*yj
+            gacont_hbr(3,num_conti,i)=fprimcont*zj
+            do k=1,3
+!c
+!c Gradient of the correlation terms
+!c
+              gacontp_hb1(k,num_conti,i)= &
+             (ecosap*(dc_norm(k,j+nres)-cosa*dc_norm(k,i+nres)) &
+            + ecosbp*(erij(k)-cosb*dc_norm(k,i+nres)))*vbld_inv(i+nres)
+              gacontp_hb2(k,num_conti,i)= &
+             (ecosap*(dc_norm(k,i+nres)-cosa*dc_norm(k,j+nres)) &
+            + ecosgp*(erij(k)-cosg*dc_norm(k,j+nres)))*vbld_inv(j+nres)
+              gacontp_hb3(k,num_conti,i)=gggp(k)
+              gacontm_hb1(k,num_conti,i)= &
+             (ecosam*(dc_norm(k,j+nres)-cosa*dc_norm(k,i+nres)) &
+            + ecosbm*(erij(k)-cosb*dc_norm(k,i+nres)))*vbld_inv(i+nres)
+              gacontm_hb2(k,num_conti,i)= &
+             (ecosam*(dc_norm(k,i+nres)-cosa*dc_norm(k,j+nres))&
+            + ecosgm*(erij(k)-cosg*dc_norm(k,j+nres)))*vbld_inv(j+nres)
+              gacontm_hb3(k,num_conti,i)=gggm(k)
+            enddo
+          endif
+        endif
+      ENDIF
+      return
+      end subroutine eelsbij
+!------------------------------------------------------------------
+      subroutine sc_grad_nucl
+      use comm_locel
+      use calc_data_nucl
+      real(kind=8),dimension(3) :: dcosom1,dcosom2
+      eom1=eps2der*eps2rt_om1+sigder*sigsq_om1
+      eom2=eps2der*eps2rt_om2+sigder*sigsq_om2
+      eom12=evdwij*eps1_om12+eps2der*eps2rt_om12+sigder*sigsq_om12
+      do k=1,3
+        dcosom1(k)=rij*(dc_norm(k,nres+i)-om1*erij(k))
+        dcosom2(k)=rij*(dc_norm(k,nres+j)-om2*erij(k))
+      enddo
+      do k=1,3
+        gg(k)=gg(k)+eom1*dcosom1(k)+eom2*dcosom2(k)
+      enddo
+      do k=1,3
+        gvdwsbx(k,i)=gvdwsbx(k,i)-gg(k) &
+                 +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i))&
+                 +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
+        gvdwsbx(k,j)=gvdwsbx(k,j)+gg(k) &
+                 +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j)) &
+                 +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
+      enddo
+!C 
+!C Calculate the components of the gradient in DC and X
+!C
+      do l=1,3
+        gvdwsbc(l,i)=gvdwsbc(l,i)-gg(l)
+        gvdwsbc(l,j)=gvdwsbc(l,j)+gg(l)
+      enddo
+      return
+      end subroutine sc_grad_nucl
+!-----------------------------------------------------------------------
+      subroutine esb(esbloc)
+!C Calculate the local energy of a side chain and its derivatives in the
+!C corresponding virtual-bond valence angles THETA and the spherical angles 
+!C ALPHA and OMEGA derived from AM1 all-atom calculations.
+!C added by Urszula Kozlowska. 07/11/2007
+!C
+      real(kind=8),dimension(3):: x_prime,y_prime,z_prime
+      real(kind=8),dimension(9):: x
+     real(kind=8) :: sumene,dsc_i,dp2_i,xx,yy,zz,sumene1, &
+      sumene2,sumene3,sumene4,s1,s1_6,s2,s2_6,&
+      de_dxx,de_dyy,de_dzz,de_dt,s1_t,s1_6_t,s2_t,s2_6_t
+      real(kind=8),dimension(3):: dXX_Ci1,dYY_Ci1,dZZ_Ci1,dXX_Ci,&
+       dYY_Ci,dZZ_Ci,dXX_XYZ,dYY_XYZ,dZZ_XYZ,dt_dCi,dt_dCi1
+       real(kind=8) :: esbloc,delta,cosfac2,cosfac,sinfac2,sinfac,de_dtt,&
+       cossc,cossc1,cosfac2xx,sinfac2yy,pom1,pom
+       integer::it,nlobit,i,j,k
+!      common /sccalc/ time11,time12,time112,theti,it,nlobit
+      delta=0.02d0*pi
+      esbloc=0.0D0
+      do i=loc_start_nucl,loc_end_nucl
+        if (itype(i,2).eq.ntyp1_molec(2)) cycle
+        costtab(i+1) =dcos(theta(i+1))
+        sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
+        cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
+        sint2tab(i+1)=dsqrt(0.5d0*(1.0d0-costtab(i+1)))
+        cosfac2=0.5d0/(1.0d0+costtab(i+1))
+        cosfac=dsqrt(cosfac2)
+        sinfac2=0.5d0/(1.0d0-costtab(i+1))
+        sinfac=dsqrt(sinfac2)
+        it=itype(i,2)
+        if (it.eq.10) goto 1
+
+!c
+!C  Compute the axes of tghe local cartesian coordinates system; store in
+!c   x_prime, y_prime and z_prime 
+!c
+        do j=1,3
+          x_prime(j) = 0.00
+          y_prime(j) = 0.00
+          z_prime(j) = 0.00
+        enddo
+!C        write(2,*) "dc_norm", dc_norm(1,i+nres),dc_norm(2,i+nres),
+!C     &   dc_norm(3,i+nres)
+        do j = 1,3
+          x_prime(j) = (dc_norm(j,i) - dc_norm(j,i-1))*cosfac
+          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)
+!           z_prime(j)=0.0
+        enddo
+       
+        xx=0.0d0
+        yy=0.0d0
+        zz=0.0d0
+        do j = 1,3
+          xx = xx + x_prime(j)*dc_norm(j,i+nres)
+          yy = yy + y_prime(j)*dc_norm(j,i+nres)
+          zz = zz + z_prime(j)*dc_norm(j,i+nres)
+        enddo
+
+        xxtab(i)=xx
+        yytab(i)=yy
+        zztab(i)=zz
+         it=itype(i,2)
+        do j = 1,9
+          x(j) = sc_parmin_nucl(j,it)
+        enddo
+#ifdef CHECK_COORD
+!Cc diagnostics - remove later
+        xx1 = dcos(alph(2))
+        yy1 = dsin(alph(2))*dcos(omeg(2))
+        zz1 = -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
+!C,"  --- ", xx_w,yy_w,zz_w
+!c end diagnostics
+#endif
+        sumene = enesc_nucl(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
+        esbloc = esbloc + sumene
+        sumene2= enesc_nucl(x,xx,yy,0.0d0,cost2tab(i+1),sint2tab(i+1))
+!        print *,"enecomp",sumene,sumene2
+!        if (energy_dec) write(iout,*) "i",i," esbloc",sumene,esbloc,xx,yy,zz
+!        if (energy_dec) write(iout,*) "x",(x(k),k=1,9)
+#ifdef DEBUG
+        write (2,*) "x",(x(k),k=1,9)
+!C
+!C This section to check the numerical derivatives of the energy of ith side
+!C chain in xx, yy, zz, and theta. Use the -DDEBUG compiler option or insert
+!C #define DEBUG in the code to turn it on.
+!C
+        write (2,*) "sumene               =",sumene
+        aincr=1.0d-7
+        xxsave=xx
+        xx=xx+aincr
+        write (2,*) xx,yy,zz
+        sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
+        de_dxx_num=(sumenep-sumene)/aincr
+        xx=xxsave
+        write (2,*) "xx+ sumene from enesc=",sumenep,sumene
+        yysave=yy
+        yy=yy+aincr
+        write (2,*) xx,yy,zz
+        sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
+        de_dyy_num=(sumenep-sumene)/aincr
+        yy=yysave
+        write (2,*) "yy+ sumene from enesc=",sumenep,sumene
+        zzsave=zz
+        zz=zz+aincr
+        write (2,*) xx,yy,zz
+        sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
+        de_dzz_num=(sumenep-sumene)/aincr
+        zz=zzsave
+        write (2,*) "zz+ sumene from enesc=",sumenep,sumene
+        costsave=cost2tab(i+1)
+        sintsave=sint2tab(i+1)
+        cost2tab(i+1)=dcos(0.5d0*(theta(i+1)+aincr))
+        sint2tab(i+1)=dsin(0.5d0*(theta(i+1)+aincr))
+        sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
+        de_dt_num=(sumenep-sumene)/aincr
+        write (2,*) " t+ sumene from enesc=",sumenep,sumene
+        cost2tab(i+1)=costsave
+        sint2tab(i+1)=sintsave
+!C End of diagnostics section.
+#endif
+!C        
+!C Compute the gradient of esc
+!C
+        de_dxx=x(1)+2*x(4)*xx+x(7)*zz+x(8)*yy
+        de_dyy=x(2)+2*x(5)*yy+x(8)*xx+x(9)*zz
+        de_dzz=x(3)+2*x(6)*zz+x(7)*xx+x(9)*yy
+        de_dtt=0.0d0
+#ifdef DEBUG
+        write (2,*) "x",(x(k),k=1,9)
+        write (2,*) "xx",xx," yy",yy," zz",zz
+        write (2,*) "de_xx   ",de_xx," de_yy   ",de_yy,&
+          " de_zz   ",de_zz," de_tt   ",de_tt
+        write (2,*) "de_xx_num",de_dxx_num," de_yy_num",de_dyy_num,&
+          " de_zz_num",de_dzz_num," de_dt_num",de_dt_num
+#endif
+!C
+       cossc=scalar(dc_norm(1,i),dc_norm(1,i+nres))
+       cossc1=scalar(dc_norm(1,i-1),dc_norm(1,i+nres))
+       cosfac2xx=cosfac2*xx
+       sinfac2yy=sinfac2*yy
+       do k = 1,3
+         dt_dCi(k) = -(dc_norm(k,i-1)+costtab(i+1)*dc_norm(k,i))*&
+           vbld_inv(i+1)
+         dt_dCi1(k)= -(dc_norm(k,i)+costtab(i+1)*dc_norm(k,i-1))*&
+           vbld_inv(i)
+         pom=(dC_norm(k,i+nres)-cossc*dC_norm(k,i))*vbld_inv(i+1)
+         pom1=(dC_norm(k,i+nres)-cossc1*dC_norm(k,i-1))*vbld_inv(i)
+!c         write (iout,*) "i",i," k",k," pom",pom," pom1",pom1,
+!c     &    " dt_dCi",dt_dCi(k)," dt_dCi1",dt_dCi1(k)
+!c         write (iout,*) "dC_norm",(dC_norm(j,i),j=1,3),
+!c     &   (dC_norm(j,i-1),j=1,3)," vbld_inv",vbld_inv(i+1),vbld_inv(i)
+         dXX_Ci(k)=pom*cosfac-dt_dCi(k)*cosfac2xx
+         dXX_Ci1(k)=-pom1*cosfac-dt_dCi1(k)*cosfac2xx
+         dYY_Ci(k)=pom*sinfac+dt_dCi(k)*sinfac2yy
+         dYY_Ci1(k)=pom1*sinfac+dt_dCi1(k)*sinfac2yy
+         dZZ_Ci1(k)=0.0d0
+         dZZ_Ci(k)=0.0d0
+         do j=1,3
+           dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1)*dC_norm(j,i+nres)
+           dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1)*dC_norm(j,i+nres)
+         enddo
+
+         dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
+         dYY_XYZ(k)=vbld_inv(i+nres)*(y_prime(k)-yy*dC_norm(k,i+nres))
+         dZZ_XYZ(k)=vbld_inv(i+nres)*(z_prime(k)-zz*dC_norm(k,i+nres))
+!c
+         dt_dCi(k) = -dt_dCi(k)/sinttab(i+1)
+         dt_dCi1(k)= -dt_dCi1(k)/sinttab(i+1)
+       enddo
+
+       do k=1,3
+         dXX_Ctab(k,i)=dXX_Ci(k)
+         dXX_C1tab(k,i)=dXX_Ci1(k)
+         dYY_Ctab(k,i)=dYY_Ci(k)
+         dYY_C1tab(k,i)=dYY_Ci1(k)
+         dZZ_Ctab(k,i)=dZZ_Ci(k)
+         dZZ_C1tab(k,i)=dZZ_Ci1(k)
+         dXX_XYZtab(k,i)=dXX_XYZ(k)
+         dYY_XYZtab(k,i)=dYY_XYZ(k)
+         dZZ_XYZtab(k,i)=dZZ_XYZ(k)
+       enddo
+       do k = 1,3
+!c         write (iout,*) "k",k," dxx_ci1",dxx_ci1(k)," dyy_ci1",
+!c     &    dyy_ci1(k)," dzz_ci1",dzz_ci1(k)
+!c         write (iout,*) "k",k," dxx_ci",dxx_ci(k)," dyy_ci",
+!c     &    dyy_ci(k)," dzz_ci",dzz_ci(k)
+!c         write (iout,*) "k",k," dt_dci",dt_dci(k)," dt_dci",
+!c     &    dt_dci(k)
+!c         write (iout,*) "k",k," dxx_XYZ",dxx_XYZ(k)," dyy_XYZ",
+!c     &    dyy_XYZ(k)," dzz_XYZ",dzz_XYZ(k) 
+         gsbloc(k,i-1)=gsbloc(k,i-1)+(de_dxx*dxx_ci1(k) &
+         +de_dyy*dyy_ci1(k)+de_dzz*dzz_ci1(k)+de_dt*dt_dCi1(k))
+         gsbloc(k,i)=gsbloc(k,i)+(de_dxx*dxx_Ci(k) &
+         +de_dyy*dyy_Ci(k)+de_dzz*dzz_Ci(k)+de_dt*dt_dCi(k))
+         gsblocx(k,i)=                 de_dxx*dxx_XYZ(k)&
+         +de_dyy*dyy_XYZ(k)+de_dzz*dzz_XYZ(k)
+!         print *,i,de_dxx*dxx_ci1(k)+de_dyy*dyy_ci1(k),de_dzz*dzz_ci1(k)*2
+       enddo
+!c       write(iout,*) "ENERGY GRAD = ", (gsbloc(k,i-1),k=1,3),
+!c     &  (gsbloc(k,i),k=1,3),(gsblocx(k,i),k=1,3)  
+
+!C to check gradient call subroutine check_grad
+
+    1 continue
+      enddo
+      return
+      end subroutine esb
+!=-------------------------------------------------------
+      real(kind=8) function enesc_nucl(x,xx,yy,zz,cost2,sint2)
+!      implicit none
+      real(kind=8),dimension(9):: x(9)
+       real(kind=8) :: xx,yy,zz,cost2,sint2,sumene1,sumene2, &
+      sumene3,sumene4,sumene,dsc_i,dp2_i,dscp1,dscp2,s1,s1_6,s2,s2_6
+      integer i
+!c      write (2,*) "enesc"
+!c      write (2,*) "x",(x(i),i=1,9)
+!c      write(2,*)"xx",xx," yy",yy," zz",zz," cost2",cost2," sint2",sint2
+      sumene=x(1)*xx+x(2)*yy+x(3)*zz+x(4)*xx**2 &
+        + x(5)*yy**2+x(6)*zz**2+x(7)*xx*zz+x(8)*xx*yy &
+        + x(9)*yy*zz
+      enesc_nucl=sumene
+      return
+      end function enesc_nucl
+!-----------------------------------------------------------------------------
+      subroutine multibody_hb_nucl(ecorr,ecorr3,n_corr,n_corr1)
+#ifdef MPI
+      include 'mpif.h'
+      integer,parameter :: max_cont=2000
+      integer,parameter:: max_dim=2*(8*3+6)
+      integer, parameter :: msglen1=max_cont*max_dim
+      integer,parameter :: msglen2=2*msglen1
+      integer source,CorrelType,CorrelID,Error
+      real(kind=8) :: buffer(max_cont,max_dim)
+      integer status(MPI_STATUS_SIZE)
+      integer :: ierror,nbytes
+#endif
+      real(kind=8),dimension(3):: gx(3),gx1(3)
+      real(kind=8) :: time00
+      logical lprn,ldone
+      integer i,j,i1,j1,jj,kk,num_conti,num_conti1,nn
+      real(kind=8) ecorr,ecorr3
+      integer :: n_corr,n_corr1,mm,msglen
+!C Set lprn=.true. for debugging
+      lprn=.false.
+      n_corr=0
+      n_corr1=0
+#ifdef MPI
+      if(.not.allocated(zapas2)) allocate(zapas2(3,maxconts,nres,8))
+
+      if (nfgtasks.le.1) goto 30
+      if (lprn) then
+        write (iout,'(a)') 'Contact function values:'
+        do i=nnt,nct-1
+          write (iout,'(2i3,50(1x,i2,f5.2))')  &
+         i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i), &
+         j=1,num_cont_hb(i))
+        enddo
+      endif
+!C Caution! Following code assumes that electrostatic interactions concerning
+!C a given atom are split among at most two processors!
+      CorrelType=477
+      CorrelID=fg_rank+1
+      ldone=.false.
+      do i=1,max_cont
+        do j=1,max_dim
+          buffer(i,j)=0.0D0
+        enddo
+      enddo
+      mm=mod(fg_rank,2)
+!c      write (*,*) 'MyRank',MyRank,' mm',mm
+      if (mm) 20,20,10 
+   10 continue
+!c      write (*,*) 'Sending: MyRank',MyRank,' mm',mm,' ldone',ldone
+      if (fg_rank.gt.0) then
+!C Send correlation contributions to the preceding processor
+        msglen=msglen1
+        nn=num_cont_hb(iatel_s_nucl)
+        call pack_buffer(max_cont,max_dim,iatel_s,0,buffer)
+!c        write (*,*) 'The BUFFER array:'
+!c        do i=1,nn
+!c          write (*,'(i2,9(3f8.3,2x))') i,(buffer(i,j),j=1,30)
+!c        enddo
+        if (ielstart_nucl(iatel_s_nucl).gt.iatel_s_nucl+ispp) then
+          msglen=msglen2
+          call pack_buffer(max_cont,max_dim,iatel_s+1,30,buffer)
+!C Clear the contacts of the atom passed to the neighboring processor
+        nn=num_cont_hb(iatel_s_nucl+1)
+!c        do i=1,nn
+!c          write (*,'(i2,9(3f8.3,2x))') i,(buffer(i,j+30),j=1,30)
+!c        enddo
+            num_cont_hb(iatel_s_nucl)=0
+        endif
+!cd      write (iout,*) 'Processor ',fg_rank,MyRank,
+!cd   & ' is sending correlation contribution to processor',fg_rank-1,
+!cd   & ' msglen=',msglen
+!c        write (*,*) 'Processor ',fg_rank,MyRank,
+!c     & ' is sending correlation contribution to processor',fg_rank-1,
+!c     & ' msglen=',msglen,' CorrelType=',CorrelType
+        time00=MPI_Wtime()
+        call MPI_Send(buffer,msglen,MPI_DOUBLE_PRECISION,fg_rank-1, &
+         CorrelType,FG_COMM,IERROR)
+        time_sendrecv=time_sendrecv+MPI_Wtime()-time00
+!cd      write (iout,*) 'Processor ',fg_rank,
+!cd   & ' has sent correlation contribution to processor',fg_rank-1,
+!cd   & ' msglen=',msglen,' CorrelID=',CorrelID
+!c        write (*,*) 'Processor ',fg_rank,
+!c     & ' has sent correlation contribution to processor',fg_rank-1,
+!c     & ' msglen=',msglen,' CorrelID=',CorrelID
+!c        msglen=msglen1
+      endif ! (fg_rank.gt.0)
+      if (ldone) goto 30
+      ldone=.true.
+   20 continue
+!c      write (*,*) 'Receiving: MyRank',MyRank,' mm',mm,' ldone',ldone
+      if (fg_rank.lt.nfgtasks-1) then
+!C Receive correlation contributions from the next processor
+        msglen=msglen1
+        if (ielend_nucl(iatel_e_nucl).lt.nct_molec(2)-1) msglen=msglen2
+!cd      write (iout,*) 'Processor',fg_rank,
+!cd   & ' is receiving correlation contribution from processor',fg_rank+1,
+!cd   & ' msglen=',msglen,' CorrelType=',CorrelType
+!c        write (*,*) 'Processor',fg_rank,
+!c     &' is receiving correlation contribution from processor',fg_rank+1,
+!c     & ' msglen=',msglen,' CorrelType=',CorrelType
+        time00=MPI_Wtime()
+        nbytes=-1
+        do while (nbytes.le.0)
+          call MPI_Probe(fg_rank+1,CorrelType,FG_COMM,status,IERROR)
+          call MPI_Get_count(status,MPI_DOUBLE_PRECISION,nbytes,IERROR)
+        enddo
+!c        print *,'Processor',myrank,' msglen',msglen,' nbytes',nbytes
+        call MPI_Recv(buffer,nbytes,MPI_DOUBLE_PRECISION, &
+         fg_rank+1,CorrelType,FG_COMM,status,IERROR)
+        time_sendrecv=time_sendrecv+MPI_Wtime()-time00
+!c        write (*,*) 'Processor',fg_rank,
+!c     &' has received correlation contribution from processor',fg_rank+1,
+!c     & ' msglen=',msglen,' nbytes=',nbytes
+!c        write (*,*) 'The received BUFFER array:'
+!c        do i=1,max_cont
+!c          write (*,'(i2,9(3f8.3,2x))') i,(buffer(i,j),j=1,60)
+!c        enddo
+        if (msglen.eq.msglen1) then
+          call unpack_buffer(max_cont,max_dim,iatel_e_nucl+1,0,buffer)
+        else if (msglen.eq.msglen2)  then
+          call unpack_buffer(max_cont,max_dim,iatel_e_nucl,0,buffer)
+          call unpack_buffer(max_cont,max_dim,iatel_e_nucl+1,30,buffer)
+        else
+          write (iout,*) &
+      'ERROR!!!! message length changed while processing correlations.'
+          write (*,*) &
+      'ERROR!!!! message length changed while processing correlations.'
+          call MPI_Abort(MPI_COMM_WORLD,Error,IERROR)
+        endif ! msglen.eq.msglen1
+      endif ! fg_rank.lt.nfgtasks-1
+      if (ldone) goto 30
+      ldone=.true.
+      goto 10
+   30 continue
+#endif
+      if (lprn) then
+        write (iout,'(a)') 'Contact function values:'
+        do i=nnt_molec(2),nct_molec(2)-1
+          write (iout,'(2i3,50(1x,i2,f5.2))') &
+         i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i), &
+         j=1,num_cont_hb(i))
+        enddo
+      endif
+      ecorr=0.0D0
+      ecorr3=0.0d0
+!C Remove the loop below after debugging !!!
+!      do i=nnt_molec(2),nct_molec(2)
+!        do j=1,3
+!          gradcorr_nucl(j,i)=0.0D0
+!          gradxorr_nucl(j,i)=0.0D0
+!          gradcorr3_nucl(j,i)=0.0D0
+!          gradxorr3_nucl(j,i)=0.0D0
+!        enddo
+!      enddo
+!      print *,"iatsc_s_nucl,iatsc_e_nucl",iatsc_s_nucl,iatsc_e_nucl
+!C Calculate the local-electrostatic correlation terms
+      do i=iatsc_s_nucl,iatsc_e_nucl
+        i1=i+1
+        num_conti=num_cont_hb(i)
+        num_conti1=num_cont_hb(i+1)
+!        print *,i,num_conti,num_conti1
+        do jj=1,num_conti
+          j=jcont_hb(jj,i)
+          do kk=1,num_conti1
+            j1=jcont_hb(kk,i1)
+!c            write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
+!c     &         ' jj=',jj,' kk=',kk
+            if (j1.eq.j+1 .or. j1.eq.j-1) then
+!C
+!C Contacts I-J and (I+1)-(J+1) or (I+1)-(J-1) occur simultaneously. 
+!C The system gains extra energy.
+!C Tentative expression & coefficients; assumed d(stacking)=4.5 A,
+!C parallel dipoles of stacknig bases and sin(mui)sin(muj)/eps/d^3=0.7
+!C Need to implement full formulas 34 and 35 from Liwo et al., 1998.
+!C
+              ecorr=ecorr+ehbcorr_nucl(i,j,i+1,j1,jj,kk,0.528D0,0.132D0)
+              if (energy_dec) write (iout,'(a6,2i5,0pf7.3)') &
+                 'ecorrh',i,j,ehbcorr_nucl(i,j,i+1,j1,jj,kk,0.528D0,0.132D0) 
+              n_corr=n_corr+1
+            else if (j1.eq.j) then
+!C
+!C Contacts I-J and I-(J+1) occur simultaneously. 
+!C The system loses extra energy.
+!C Tentative expression & c?oefficients; assumed d(stacking)=4.5 A,
+!C parallel dipoles of stacknig bases and sin(mui)sin(muj)/eps/d^3=0.7
+!C Need to implement full formulas 32 from Liwo et al., 1998.
+!C
+!c              write (iout,*) 'ecorr3: i=',i,' j=',j,' i1=',i1,' j1=',j1,
+!c     &         ' jj=',jj,' kk=',kk
+              ecorr3=ecorr3+ehbcorr3_nucl(i,j,i+1,j,jj,kk,0.310D0,-0.155D0)
+            endif
+          enddo ! kk
+          do kk=1,num_conti
+            j1=jcont_hb(kk,i)
+!c            write (iout,*) 'ecorr3: i=',i,' j=',j,' i1=',i1,' j1=',j1,
+!c     &         ' jj=',jj,' kk=',kk
+            if (j1.eq.j+1) then
+!C Contacts I-J and (I+1)-J occur simultaneously. 
+!C The system loses extra energy.
+              ecorr3=ecorr3+ehbcorr3_nucl(i,j,i,j+1,jj,kk,0.310D0,-0.155D0)
+            endif ! j1==j+1
+          enddo ! kk
+        enddo ! jj
+      enddo ! i
+      return
+      end subroutine multibody_hb_nucl
+!-----------------------------------------------------------
+      real(kind=8) function ehbcorr_nucl(i,j,k,l,jj,kk,coeffp,coeffm)
+!      implicit real*8 (a-h,o-z)
+!      include 'DIMENSIONS'
+!      include 'COMMON.IOUNITS'
+!      include 'COMMON.DERIV'
+!      include 'COMMON.INTERACT'
+!      include 'COMMON.CONTACTS'
+      real(kind=8),dimension(3) :: gx,gx1
+      logical :: lprn
+!el local variables
+      integer :: i,j,k,l,jj,kk,ll,ilist,m, iresshield
+      real(kind=8) :: coeffp,coeffm,eij,ekl,ees0pij,ees0pkl,ees0mij,&
+                   ees0mkl,ees,coeffpees0pij,coeffmees0mij,&
+                   coeffpees0pkl,coeffmees0mkl,gradlongij,gradlongkl, &
+                   rlocshield
+
+      lprn=.false.
+      eij=facont_hb(jj,i)
+      ekl=facont_hb(kk,k)
+      ees0pij=ees0p(jj,i)
+      ees0pkl=ees0p(kk,k)
+      ees0mij=ees0m(jj,i)
+      ees0mkl=ees0m(kk,k)
+      ekont=eij*ekl
+      ees=-(coeffp*ees0pij*ees0pkl+coeffm*ees0mij*ees0mkl)
+!      print *,"ehbcorr_nucl",ekont,ees
+!cd    ees=-(coeffp*ees0pkl+coeffm*ees0mkl)
+!C Following 4 lines for diagnostics.
+!cd    ees0pkl=0.0D0
+!cd    ees0pij=1.0D0
+!cd    ees0mkl=0.0D0
+!cd    ees0mij=1.0D0
+!cd      write (iout,*)'Contacts have occurred for nucleic bases',
+!cd     &  i,j,' fcont:',eij,' eij',' eesij',ees0pij,ees0mij,' and ',k,l
+!cd     & ,' fcont ',ekl,' eeskl',ees0pkl,ees0mkl,' ees=',ees
+!C Calculate the multi-body contribution to energy.
+!      ecorr_nucl=ecorr_nucl+ekont*ees
+!C Calculate multi-body contributions to the gradient.
+      coeffpees0pij=coeffp*ees0pij
+      coeffmees0mij=coeffm*ees0mij
+      coeffpees0pkl=coeffp*ees0pkl
+      coeffmees0mkl=coeffm*ees0mkl
+      do ll=1,3
+        gradxorr_nucl(ll,i)=gradxorr_nucl(ll,i) &
+       -ekont*(coeffpees0pkl*gacontp_hb1(ll,jj,i)+&
+       coeffmees0mkl*gacontm_hb1(ll,jj,i))
+        gradxorr_nucl(ll,j)=gradxorr_nucl(ll,j) &
+        -ekont*(coeffpees0pkl*gacontp_hb2(ll,jj,i)+&
+        coeffmees0mkl*gacontm_hb2(ll,jj,i))
+        gradxorr_nucl(ll,k)=gradxorr_nucl(ll,k) &
+        -ekont*(coeffpees0pij*gacontp_hb1(ll,kk,k)+&
+        coeffmees0mij*gacontm_hb1(ll,kk,k))
+        gradxorr_nucl(ll,l)=gradxorr_nucl(ll,l) &
+        -ekont*(coeffpees0pij*gacontp_hb2(ll,kk,k)+ &
+        coeffmees0mij*gacontm_hb2(ll,kk,k))
+        gradlongij=ees*ekl*gacont_hbr(ll,jj,i)- &
+          ekont*(coeffpees0pkl*gacontp_hb3(ll,jj,i)+ &
+          coeffmees0mkl*gacontm_hb3(ll,jj,i))
+        gradcorr_nucl(ll,j)=gradcorr_nucl(ll,j)+gradlongij
+        gradcorr_nucl(ll,i)=gradcorr_nucl(ll,i)-gradlongij
+        gradlongkl=ees*eij*gacont_hbr(ll,kk,k)- &
+          ekont*(coeffpees0pij*gacontp_hb3(ll,kk,k)+ &
+          coeffmees0mij*gacontm_hb3(ll,kk,k))
+        gradcorr_nucl(ll,l)=gradcorr_nucl(ll,l)+gradlongkl
+        gradcorr_nucl(ll,k)=gradcorr_nucl(ll,k)-gradlongkl
+        gradxorr_nucl(ll,i)=gradxorr_nucl(ll,i)-gradlongij
+        gradxorr_nucl(ll,j)=gradxorr_nucl(ll,j)+gradlongij
+        gradxorr_nucl(ll,k)=gradxorr_nucl(ll,k)-gradlongkl
+        gradxorr_nucl(ll,l)=gradxorr_nucl(ll,l)+gradlongkl
+      enddo
+      ehbcorr_nucl=ekont*ees
+      return
+      end function ehbcorr_nucl
+!-------------------------------------------------------------------------
+
+     real(kind=8) function ehbcorr3_nucl(i,j,k,l,jj,kk,coeffp,coeffm)
+!      implicit real*8 (a-h,o-z)
+!      include 'DIMENSIONS'
+!      include 'COMMON.IOUNITS'
+!      include 'COMMON.DERIV'
+!      include 'COMMON.INTERACT'
+!      include 'COMMON.CONTACTS'
+      real(kind=8),dimension(3) :: gx,gx1
+      logical :: lprn
+!el local variables
+      integer :: i,j,k,l,jj,kk,ll,ilist,m, iresshield
+      real(kind=8) :: coeffp,coeffm,eij,ekl,ees0pij,ees0pkl,ees0mij,&
+                   ees0mkl,ees,coeffpees0pij,coeffmees0mij,&
+                   coeffpees0pkl,coeffmees0mkl,gradlongij,gradlongkl, &
+                   rlocshield
+
+      lprn=.false.
+      eij=facont_hb(jj,i)
+      ekl=facont_hb(kk,k)
+      ees0pij=ees0p(jj,i)
+      ees0pkl=ees0p(kk,k)
+      ees0mij=ees0m(jj,i)
+      ees0mkl=ees0m(kk,k)
+      ekont=eij*ekl
+      ees=-(coeffp*ees0pij*ees0pkl+coeffm*ees0mij*ees0mkl)
+!cd    ees=-(coeffp*ees0pkl+coeffm*ees0mkl)
+!C Following 4 lines for diagnostics.
+!cd    ees0pkl=0.0D0
+!cd    ees0pij=1.0D0
+!cd    ees0mkl=0.0D0
+!cd    ees0mij=1.0D0
+!cd      write (iout,*)'Contacts have occurred for nucleic bases',
+!cd     &  i,j,' fcont:',eij,' eij',' eesij',ees0pij,ees0mij,' and ',k,l
+!cd     & ,' fcont ',ekl,' eeskl',ees0pkl,ees0mkl,' ees=',ees
+!C Calculate the multi-body contribution to energy.
+!      ecorr=ecorr+ekont*ees
+!C Calculate multi-body contributions to the gradient.
+      coeffpees0pij=coeffp*ees0pij
+      coeffmees0mij=coeffm*ees0mij
+      coeffpees0pkl=coeffp*ees0pkl
+      coeffmees0mkl=coeffm*ees0mkl
+      do ll=1,3
+        gradxorr3_nucl(ll,i)=gradxorr3_nucl(ll,i) &
+       -ekont*(coeffpees0pkl*gacontp_hb1(ll,jj,i)+&
+       coeffmees0mkl*gacontm_hb1(ll,jj,i))
+        gradxorr3_nucl(ll,j)=gradxorr3_nucl(ll,j) &
+        -ekont*(coeffpees0pkl*gacontp_hb2(ll,jj,i)+ &
+        coeffmees0mkl*gacontm_hb2(ll,jj,i))
+        gradxorr3_nucl(ll,k)=gradxorr3_nucl(ll,k) &
+        -ekont*(coeffpees0pij*gacontp_hb1(ll,kk,k)+ &
+        coeffmees0mij*gacontm_hb1(ll,kk,k))
+        gradxorr3_nucl(ll,l)=gradxorr3_nucl(ll,l) &
+        -ekont*(coeffpees0pij*gacontp_hb2(ll,kk,k)+ &
+        coeffmees0mij*gacontm_hb2(ll,kk,k))
+        gradlongij=ees*ekl*gacont_hbr(ll,jj,i)- &
+          ekont*(coeffpees0pkl*gacontp_hb3(ll,jj,i)+ &
+          coeffmees0mkl*gacontm_hb3(ll,jj,i))
+        gradcorr3_nucl(ll,j)=gradcorr3_nucl(ll,j)+gradlongij
+        gradcorr3_nucl(ll,i)=gradcorr3_nucl(ll,i)-gradlongij
+        gradlongkl=ees*eij*gacont_hbr(ll,kk,k)- &
+          ekont*(coeffpees0pij*gacontp_hb3(ll,kk,k)+ &
+          coeffmees0mij*gacontm_hb3(ll,kk,k))
+        gradcorr3_nucl(ll,l)=gradcorr3_nucl(ll,l)+gradlongkl
+        gradcorr3_nucl(ll,k)=gradcorr3_nucl(ll,k)-gradlongkl
+        gradxorr3_nucl(ll,i)=gradxorr3_nucl(ll,i)-gradlongij
+        gradxorr3_nucl(ll,j)=gradxorr3_nucl(ll,j)+gradlongij
+        gradxorr3_nucl(ll,k)=gradxorr3_nucl(ll,k)-gradlongkl
+        gradxorr3_nucl(ll,l)=gradxorr3_nucl(ll,l)+gradlongkl
+      enddo
+      ehbcorr3_nucl=ekont*ees
+      return
+      end function ehbcorr3_nucl
+#ifdef MPI
+      subroutine pack_buffer(dimen1,dimen2,atom,indx,buffer)
+      integer dimen1,dimen2,atom,indx,numcont,i,ii,k,j,num_kont,num_kont_old
+      real(kind=8):: buffer(dimen1,dimen2)
+      num_kont=num_cont_hb(atom)
+      do i=1,num_kont
+        do k=1,8
+          do j=1,3
+            buffer(i,indx+(k-1)*3+j)=zapas2(j,i,atom,k)
+          enddo ! j
+        enddo ! k
+        buffer(i,indx+25)=facont_hb(i,atom)
+        buffer(i,indx+26)=ees0p(i,atom)
+        buffer(i,indx+27)=ees0m(i,atom)
+        buffer(i,indx+28)=d_cont(i,atom)
+        buffer(i,indx+29)=dfloat(jcont_hb(i,atom))
+      enddo ! i
+      buffer(1,indx+30)=dfloat(num_kont)
+      return
+      end subroutine pack_buffer
+!c------------------------------------------------------------------------------
+      subroutine unpack_buffer(dimen1,dimen2,atom,indx,buffer)
+      integer dimen1,dimen2,atom,indx,numcont,i,ii,k,j,num_kont,num_kont_old
+      real(kind=8):: buffer(dimen1,dimen2)
+!      double precision zapas
+!      common /contacts_hb/ zapas(3,maxconts,maxres,8),
+!     &   facont_hb(maxconts,maxres),ees0p(maxconts,maxres),
+!     &         ees0m(maxconts,maxres),d_cont(maxconts,maxres),
+!     &         num_cont_hb(maxres),jcont_hb(maxconts,maxres)
+      num_kont=buffer(1,indx+30)
+      num_kont_old=num_cont_hb(atom)
+      num_cont_hb(atom)=num_kont+num_kont_old
+      do i=1,num_kont
+        ii=i+num_kont_old
+        do k=1,8
+          do j=1,3
+            zapas2(j,ii,atom,k)=buffer(i,indx+(k-1)*3+j)
+          enddo ! j 
+        enddo ! k 
+        facont_hb(ii,atom)=buffer(i,indx+25)
+        ees0p(ii,atom)=buffer(i,indx+26)
+        ees0m(ii,atom)=buffer(i,indx+27)
+        d_cont(i,atom)=buffer(i,indx+28)
+        jcont_hb(ii,atom)=buffer(i,indx+29)
+      enddo ! i
+      return
+      end subroutine unpack_buffer
+!c------------------------------------------------------------------------------
+#endif
+      subroutine ecatcat(ecationcation)
+        integer :: i,j,itmp,xshift,yshift,zshift,subchap,k
+        real(kind=8) :: xi,yi,zi,xj,yj,zj,ract,rcat0,epscalc,r06,r012,&
+        r7,r4,ecationcation,k0,rcal
+        real(kind=8) xj_temp,yj_temp,zj_temp,xj_safe,yj_safe,zj_safe, &
+        dist_init,dist_temp,Evan1cat,Evan2cat,Eeleccat
+        real(kind=8),dimension(3) ::dEvan1Cmcat,dEvan2Cmcat,dEeleccat,&
+        gg,r
+
+        ecationcation=0.0d0
+        if (nres_molec(5).eq.0) return
+        rcat0=3.472
+        epscalc=0.05
+        r06 = rcat0**6
+        r012 = r06**2
+        k0 = 332.0*(2.0*2.0)/80.0
+        itmp=0
+        
+        do i=1,4
+        itmp=itmp+nres_molec(i)
+        enddo
+!        write(iout,*) "itmp",itmp
+        do i=itmp+1,itmp+nres_molec(5)-1
+       
+        xi=c(1,i)
+        yi=c(2,i)
+        zi=c(3,i)
+         
+          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 j=i+1,itmp+nres_molec(5)
+!           print *,i,j,'catcat'
+           xj=c(1,j)
+           yj=c(2,j)
+           zj=c(3,j)
+          xj=dmod(xj,boxxsize)
+          if (xj.lt.0) xj=xj+boxxsize
+          yj=dmod(yj,boxysize)
+          if (yj.lt.0) yj=yj+boxysize
+          zj=dmod(zj,boxzsize)
+          if (zj.lt.0) zj=zj+boxzsize
+!          write(iout,*) c(1,i),xi,xj,"xy",boxxsize
+      dist_init=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
+      xj_safe=xj
+      yj_safe=yj
+      zj_safe=zj
+      subchap=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-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
+       rcal =xj**2+yj**2+zj**2
+        ract=sqrt(rcal)
+!        rcat0=3.472
+!        epscalc=0.05
+!        r06 = rcat0**6
+!        r012 = r06**2
+!        k0 = 332*(2*2)/80
+        Evan1cat=epscalc*(r012/rcal**6)
+        Evan2cat=epscalc*2*(r06/rcal**3)
+        Eeleccat=k0/ract
+        r7 = rcal**7
+        r4 = rcal**4
+        r(1)=xj
+        r(2)=yj
+        r(3)=zj
+        do k=1,3
+          dEvan1Cmcat(k)=-12*r(k)*epscalc*r012/r7
+          dEvan2Cmcat(k)=-12*r(k)*epscalc*r06/r4
+          dEeleccat(k)=-k0*r(k)/ract**3
+        enddo
+        do k=1,3
+          gg(k) = dEvan1Cmcat(k)+dEvan2Cmcat(k)+dEeleccat(k)
+          gradcatcat(k,i)=gradcatcat(k,i)-gg(k)
+          gradcatcat(k,j)=gradcatcat(k,j)+gg(k)
+        enddo
+
+!        write(iout,*) "ecatcat",i,j, ecationcation,xj,yj,zj
+        ecationcation=ecationcation+Evan1cat+Evan2cat+Eeleccat
+       enddo
+       enddo
+       return 
+       end subroutine ecatcat
+!---------------------------------------------------------------------------
+       subroutine ecat_prot(ecation_prot)
+       integer i,j,k,subchap,itmp,inum
+        real(kind=8) :: xi,yi,zi,xj,yj,zj,ract,rcat0,epscalc,r06,r012,&
+        r7,r4,ecationcation
+        real(kind=8) xj_temp,yj_temp,zj_temp,xj_safe,yj_safe,zj_safe, &
+        dist_init,dist_temp,ecation_prot,rcal,rocal,   &
+        Evan1,Evan2,EC,cm1mag,DASGL,delta,r0p,Epepcat, &
+        catl,cml,calpl, Etotal_p, Etotal_m,rtab,wdip,wmodquad,wquad1, &
+        wquad2,wvan1,E1,E2,wconst,wvan2,rcpm,dcmag,sin2thet,sinthet,  &
+        costhet,v1m,v2m,wh2o,wc,rsecp,Ir,Irsecp,Irthrp,Irfourp,Irfiftp,&
+        Irsistp,Irseven,Irtwelv,Irthir,dE1dr,dE2dr,dEdcos,wquad2p,opt, &
+        rs,rthrp,rfourp,rsixp,reight,Irsixp,Ireight,Irtw,Irfourt,      &
+        opt1,opt2,opt3,opt4,opt5,opt6,opt7,opt8,opt9,opt10,opt11,opt12,&
+        opt13,opt14,opt15,opt16,opt17,opt18,opt19, &
+        Equad1,Equad2,dscmag,v1dpv2,dscmag3,constA,constB,Edip
+        real(kind=8),dimension(3) ::dEvan1Cmcat,dEvan2Cmcat,dEeleccat,&
+        gg,r,EtotalCat,dEtotalCm,dEtotalCalp,dEvan1Cm,dEvan2Cm, &
+        dEtotalpep,dEtotalcat_num,dEddci,dEtotalcm_num,dEtotalcalp_num, &
+        tab1,tab2,tab3,diff,cm1,sc,p,tcat,talp,cm,drcp,drcp_norm,vcat,  &
+        v1,v2,v3,myd_norm,dx,vcm,valpha,drdpep,dcosdpep,dcosddci,dEdpep,&
+        dEcCat,dEdipCm,dEdipCalp,dEquad1Cat,dEquad1Cm,dEquad1Calp,      &
+        dEquad2Cat,dEquad2Cm,dEquad2Calpd,Evan1Cat,dEvan1Calp,dEvan2Cat,&
+        dEvan2Calp,dEtotalCat,dscvec,dEcCm,dEcCalp,dEdipCat,dEquad2Calp,&
+        dEvan1Cat
+        real(kind=8),dimension(6) :: vcatprm
+        ecation_prot=0.0d0
+! first lets calculate interaction with peptide groups
+        if (nres_molec(5).eq.0) return
+         wconst=78
+        wdip =1.092777950857032D2
+        wdip=wdip/wconst
+        wmodquad=-2.174122713004870D4
+        wmodquad=wmodquad/wconst
+        wquad1 = 3.901232068562804D1
+        wquad1=wquad1/wconst
+        wquad2 = 3
+        wquad2=wquad2/wconst
+        wvan1 = 0.1
+        wvan2 = 6
+        itmp=0
+        do i=1,4
+        itmp=itmp+nres_molec(i)
+        enddo
+!        do i=1,nres_molec(1)-1  ! loop over all peptide groups needs parralelization
+        do i=ibond_start,ibond_end
+!         cycle
+         if ((itype(i,1).eq.ntyp1).or.(itype(i+1,1).eq.ntyp1)) cycle ! leave dummy atoms
+        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))
+          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 j=itmp+1,itmp+nres_molec(5)
+           xj=c(1,j)
+           yj=c(2,j)
+           zj=c(3,j)
+          xj=dmod(xj,boxxsize)
+          if (xj.lt.0) xj=xj+boxxsize
+          yj=dmod(yj,boxysize)
+          if (yj.lt.0) yj=yj+boxysize
+          zj=dmod(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
+      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
+!       enddo
+!       enddo
+       rcpm = sqrt(xj**2+yj**2+zj**2)
+       drcp_norm(1)=xj/rcpm
+       drcp_norm(2)=yj/rcpm
+       drcp_norm(3)=zj/rcpm
+       dcmag=0.0
+       do k=1,3
+       dcmag=dcmag+dc(k,i)**2
+       enddo
+       dcmag=dsqrt(dcmag)
+       do k=1,3
+         myd_norm(k)=dc(k,i)/dcmag
+       enddo
+        costhet=drcp_norm(1)*myd_norm(1)+drcp_norm(2)*myd_norm(2)+&
+        drcp_norm(3)*myd_norm(3)
+        rsecp = rcpm**2
+        Ir = 1.0d0/rcpm
+        Irsecp = 1.0d0/rsecp
+        Irthrp = Irsecp/rcpm
+        Irfourp = Irthrp/rcpm
+        Irfiftp = Irfourp/rcpm
+        Irsistp=Irfiftp/rcpm
+        Irseven=Irsistp/rcpm
+        Irtwelv=Irsistp*Irsistp
+        Irthir=Irtwelv/rcpm
+        sin2thet = (1-costhet*costhet)
+        sinthet=sqrt(sin2thet)
+        E1 = wdip*Irsecp*costhet+(wmodquad*Irfourp+wquad1*Irthrp)&
+             *sin2thet
+        E2 = -wquad1*Irthrp*wquad2+wvan1*(wvan2**12*Irtwelv-&
+             2*wvan2**6*Irsistp)
+        ecation_prot = ecation_prot+E1+E2
+        dE1dr = -2*costhet*wdip*Irthrp-& 
+         (4*wmodquad*Irfiftp+3*wquad1*Irfourp)*sin2thet
+        dE2dr = 3*wquad1*wquad2*Irfourp-     &
+          12*wvan1*wvan2**6*(wvan2**6*Irthir-Irseven)
+        dEdcos = wdip*Irsecp-2*(wmodquad*Irfourp+wquad1*Irthrp)*costhet
+        do k=1,3
+          drdpep(k) = -drcp_norm(k)
+          dcosdpep(k) = Ir*(costhet*drcp_norm(k)-myd_norm(k))
+          dcosddci(k) = drcp_norm(k)/dcmag-costhet*myd_norm(k)/dcmag
+          dEdpep(k) = (dE1dr+dE2dr)*drdpep(k)+dEdcos*dcosdpep(k)
+          dEddci(k) = dEdcos*dcosddci(k)
+        enddo
+        do k=1,3
+        gradpepcat(k,i)=gradpepcat(k,i)+0.5D0*dEdpep(k)-dEddci(k)
+        gradpepcat(k,i+1)=gradpepcat(k,i+1)+0.5D0*dEdpep(k)+dEddci(k)
+        gradpepcat(k,j)=gradpepcat(k,j)-dEdpep(k)
+        enddo
+       enddo ! j
+       enddo ! i
+!------------------------------------------sidechains
+!        do i=1,nres_molec(1)
+        do i=ibond_start,ibond_end
+         if ((itype(i,1).eq.ntyp1)) cycle ! leave dummy atoms
+!         cycle
+!        print *,i,ecation_prot
+        xi=(c(1,i+nres))
+        yi=(c(2,i+nres))
+        zi=(c(3,i+nres))
+          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 k=1,3
+            cm1(k)=dc(k,i+nres)
+          enddo
+           cm1mag=sqrt(cm1(1)**2+cm1(2)**2+cm1(3)**2)
+         do j=itmp+1,itmp+nres_molec(5)
+           xj=c(1,j)
+           yj=c(2,j)
+           zj=c(3,j)
+          xj=dmod(xj,boxxsize)
+          if (xj.lt.0) xj=xj+boxxsize
+          yj=dmod(yj,boxysize)
+          if (yj.lt.0) yj=yj+boxysize
+          zj=dmod(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
+      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
+!       enddo
+!       enddo
+         if(itype(i,1).eq.15.or.itype(i,1).eq.16) then
+            if(itype(i,1).eq.16) then
+            inum=1
+            else
+            inum=2
+            endif
+            do k=1,6
+            vcatprm(k)=catprm(k,inum)
+            enddo
+            dASGL=catprm(7,inum)
+             do k=1,3
+                vcm(k)=(cm1(k)/cm1mag)*dASGL+c(k,i+nres)
+                valpha(k)=c(k,i)
+                vcat(k)=c(k,j)
+              enddo
+                      do k=1,3
+          dx(k) = vcat(k)-vcm(k)
+        enddo
+        do k=1,3
+          v1(k)=(vcm(k)-valpha(k))
+          v2(k)=(vcat(k)-valpha(k))
+        enddo
+        v1m = sqrt(v1(1)**2+v1(2)**2+v1(3)**2)
+        v2m = sqrt(v2(1)**2+v2(2)**2+v2(3)**2)
+        v1dpv2 = v1(1)*v2(1)+v1(2)*v2(2)+v1(3)*v2(3)
+
+!  The weights of the energy function calculated from
+!The quantum mechanical GAMESS simulations of calcium with ASP/GLU
+        wh2o=78
+        wc = vcatprm(1)
+        wc=wc/wh2o
+        wdip =vcatprm(2)
+        wdip=wdip/wh2o
+        wquad1 =vcatprm(3)
+        wquad1=wquad1/wh2o
+        wquad2 = vcatprm(4)
+        wquad2=wquad2/wh2o
+        wquad2p = 1-wquad2
+        wvan1 = vcatprm(5)
+        wvan2 =vcatprm(6)
+        opt = dx(1)**2+dx(2)**2
+        rsecp = opt+dx(3)**2
+        rs = sqrt(rsecp)
+        rthrp = rsecp*rs
+        rfourp = rthrp*rs
+        rsixp = rfourp*rsecp
+        reight=rsixp*rsecp
+        Ir = 1.0d0/rs
+        Irsecp = 1/rsecp
+        Irthrp = Irsecp/rs
+        Irfourp = Irthrp/rs
+        Irsixp = 1/rsixp
+        Ireight=1/reight
+        Irtw=Irsixp*Irsixp
+        Irthir=Irtw/rs
+        Irfourt=Irthir/rs
+        opt1 = (4*rs*dx(3)*wdip)
+        opt2 = 6*rsecp*wquad1*opt
+        opt3 = wquad1*wquad2p*Irsixp
+        opt4 = (wvan1*wvan2**12)
+        opt5 = opt4*12*Irfourt
+        opt6 = 2*wvan1*wvan2**6
+        opt7 = 6*opt6*Ireight
+        opt8 = wdip/v1m
+        opt10 = wdip/v2m
+        opt11 = (rsecp*v2m)**2
+        opt12 = (rsecp*v1m)**2
+        opt14 = (v1m*v2m*rsecp)**2
+        opt15 = -wquad1/v2m**2
+        opt16 = (rthrp*(v1m*v2m)**2)**2
+        opt17 = (v1m**2*rthrp)**2
+        opt18 = -wquad1/rthrp
+        opt19 = (v1m**2*v2m**2)**2
+        Ec = wc*Ir
+        do k=1,3
+          dEcCat(k) = -(dx(k)*wc)*Irthrp
+          dEcCm(k)=(dx(k)*wc)*Irthrp
+          dEcCalp(k)=0.0d0
+        enddo
+        Edip=opt8*(v1dpv2)/(rsecp*v2m)
+        do k=1,3
+          dEdipCat(k)=opt8*(v1(k)*rsecp*v2m-((v2(k)/v2m &
+                     *rsecp+2*dx(k)*v2m)*v1dpv2))/opt11
+          dEdipCm(k)=opt10*(v2(k)*rsecp*v1m-((v1(k)/v1m &
+                    *rsecp-2*dx(k)*v1m)*v1dpv2))/opt12
+          dEdipCalp(k)=wdip*((-v1(k)-v2(k))*rsecp*v1m &
+                      *v2m-(-v1(k)/v1m*v2m*rsecp-v2(k)/v2m*v1m*rsecp) &
+                      *v1dpv2)/opt14
+        enddo
+        Equad1=-wquad1*v1dpv2**2/(rthrp*(v1m*v2m)**2)
+        do k=1,3
+          dEquad1Cat(k)=-wquad1*(2*v1(k)*v1dpv2*(rthrp* &
+                       (v1m*v2m)**2)-(3*dx(k)*rs*(v1m*v2m)**2+2*v1m*2* &
+                       v2(k)*1/2*1/v2m*v1m*v2m*rthrp)*v1dpv2**2)/opt16
+          dEquad1Cm(k)=-wquad1*(2*v2(k)*v1dpv2*(rthrp* &
+                      (v1m*v2m)**2)-(-3*dx(k)*rs*(v1m*v2m)**2+2*v2m*2* &
+                      v1(k)*1/2*1/v1m*v2m*v1m*rthrp)*v1dpv2**2)/opt16
+          dEquad1Calp(k)=opt18*(2*(-v1(k)-v2(k))*v1dpv2* &
+                        v1m**2*v2m**2-(-2*v1(k)*v2m**2-2*v2(k)*v1m**2)* &
+                        v1dpv2**2)/opt19
+        enddo
+        Equad2=wquad1*wquad2p*Irthrp
+        do k=1,3
+          dEquad2Cat(k)=-3*dx(k)*rs*opt3
+          dEquad2Cm(k)=3*dx(k)*rs*opt3
+          dEquad2Calp(k)=0.0d0
+        enddo
+        Evan1=opt4*Irtw
+        do k=1,3
+          dEvan1Cat(k)=-dx(k)*opt5
+          dEvan1Cm(k)=dx(k)*opt5
+          dEvan1Calp(k)=0.0d0
+        enddo
+        Evan2=-opt6*Irsixp
+        do k=1,3
+          dEvan2Cat(k)=dx(k)*opt7
+          dEvan2Cm(k)=-dx(k)*opt7
+          dEvan2Calp(k)=0.0d0
+        enddo
+        ecation_prot=ecation_prot+Ec+Edip+Equad1+Equad2+Evan1+Evan2
+!        print *,ecation_prot,Ec+Edip+Equad1+Equad2+Evan1+Evan2
+        
+        do k=1,3
+          dEtotalCat(k)=dEcCat(k)+dEdipCat(k)+dEquad1Cat(k)+ &
+                       dEquad2Cat(k)+dEvan1Cat(k)+dEvan2Cat(k)
+!c             write(*,*) 'dEtotalCat inside', (dEtotalCat(l),l=1,3)
+          dEtotalCm(k)=dEcCm(k)+dEdipCm(k)+dEquad1Cm(k)+ &
+                      dEquad2Cm(k)+dEvan1Cm(k)+dEvan2Cm(k)
+          dEtotalCalp(k)=dEcCalp(k)+dEdipCalp(k)+dEquad1Calp(k) &
+                        +dEquad2Calp(k)+dEvan1Calp(k)+dEvan2Calp(k)
+        enddo
+            dscmag = 0.0d0
+            do k=1,3
+              dscvec(k) = dc(k,i+nres)
+              dscmag = dscmag+dscvec(k)*dscvec(k)
+            enddo
+            dscmag3 = dscmag
+            dscmag = sqrt(dscmag)
+            dscmag3 = dscmag3*dscmag
+            constA = 1.0d0+dASGL/dscmag
+            constB = 0.0d0
+            do k=1,3
+              constB = constB+dscvec(k)*dEtotalCm(k)
+            enddo
+            constB = constB*dASGL/dscmag3
+            do k=1,3
+              gg(k) = dEtotalCm(k)+dEtotalCalp(k)
+              gradpepcatx(k,i)=gradpepcatx(k,i)+ &
+               constA*dEtotalCm(k)-constB*dscvec(k)
+!            print *,j,constA,dEtotalCm(k),constB,dscvec(k)
+              gradpepcat(k,i)=gradpepcat(k,i)+gg(k)
+              gradpepcat(k,j)=gradpepcat(k,j)+dEtotalCat(k)
+             enddo
+        else if (itype(i,1).eq.13.or.itype(i,1).eq.14) then
+           if(itype(i,1).eq.14) then
+            inum=3
+            else
+            inum=4
+            endif
+            do k=1,6
+            vcatprm(k)=catprm(k,inum)
+            enddo
+            dASGL=catprm(7,inum)
+             do k=1,3
+                vcm(k)=(cm1(k)/cm1mag)*dASGL+c(k,i+nres)
+                valpha(k)=c(k,i)
+                vcat(k)=c(k,j)
+              enddo
+
+        do k=1,3
+          dx(k) = vcat(k)-vcm(k)
+        enddo
+        do k=1,3
+          v1(k)=(vcm(k)-valpha(k))
+          v2(k)=(vcat(k)-valpha(k))
+        enddo
+        v1m = sqrt(v1(1)**2+v1(2)**2+v1(3)**2)
+        v2m = sqrt(v2(1)**2+v2(2)**2+v2(3)**2)
+        v1dpv2 = v1(1)*v2(1)+v1(2)*v2(2)+v1(3)*v2(3)
+!  The weights of the energy function calculated from
+!The quantum mechanical GAMESS simulations of ASN/GLN with calcium
+        wh2o=78
+        wdip =vcatprm(2)
+        wdip=wdip/wh2o
+        wquad1 =vcatprm(3)
+        wquad1=wquad1/wh2o
+        wquad2 = vcatprm(4)
+        wquad2=wquad2/wh2o
+        wquad2p = 1-wquad2
+        wvan1 = vcatprm(5)
+        wvan2 =vcatprm(6)
+        opt = dx(1)**2+dx(2)**2
+        rsecp = opt+dx(3)**2
+        rs = sqrt(rsecp)
+        rthrp = rsecp*rs
+        rfourp = rthrp*rs
+        rsixp = rfourp*rsecp
+        reight=rsixp*rsecp
+        Ir = 1.0d0/rs
+        Irsecp = 1/rsecp
+        Irthrp = Irsecp/rs
+        Irfourp = Irthrp/rs
+        Irsixp = 1/rsixp
+        Ireight=1/reight
+        Irtw=Irsixp*Irsixp
+        Irthir=Irtw/rs
+        Irfourt=Irthir/rs
+        opt1 = (4*rs*dx(3)*wdip)
+        opt2 = 6*rsecp*wquad1*opt
+        opt3 = wquad1*wquad2p*Irsixp
+        opt4 = (wvan1*wvan2**12)
+        opt5 = opt4*12*Irfourt
+        opt6 = 2*wvan1*wvan2**6
+        opt7 = 6*opt6*Ireight
+        opt8 = wdip/v1m
+        opt10 = wdip/v2m
+        opt11 = (rsecp*v2m)**2
+        opt12 = (rsecp*v1m)**2
+        opt14 = (v1m*v2m*rsecp)**2
+        opt15 = -wquad1/v2m**2
+        opt16 = (rthrp*(v1m*v2m)**2)**2
+        opt17 = (v1m**2*rthrp)**2
+        opt18 = -wquad1/rthrp
+        opt19 = (v1m**2*v2m**2)**2
+        Edip=opt8*(v1dpv2)/(rsecp*v2m)
+        do k=1,3
+          dEdipCat(k)=opt8*(v1(k)*rsecp*v2m-((v2(k)/v2m&
+                     *rsecp+2*dx(k)*v2m)*v1dpv2))/opt11
+         dEdipCm(k)=opt10*(v2(k)*rsecp*v1m-((v1(k)/v1m&
+                    *rsecp-2*dx(k)*v1m)*v1dpv2))/opt12
+          dEdipCalp(k)=wdip*((-v1(k)-v2(k))*rsecp*v1m&
+                      *v2m-(-v1(k)/v1m*v2m*rsecp-v2(k)/v2m*v1m*rsecp)&
+                      *v1dpv2)/opt14
+        enddo
+        Equad1=-wquad1*v1dpv2**2/(rthrp*(v1m*v2m)**2)
+        do k=1,3
+          dEquad1Cat(k)=-wquad1*(2*v1(k)*v1dpv2*(rthrp*&
+                       (v1m*v2m)**2)-(3*dx(k)*rs*(v1m*v2m)**2+2*v1m*2*&
+                       v2(k)*1/2*1/v2m*v1m*v2m*rthrp)*v1dpv2**2)/opt16
+          dEquad1Cm(k)=-wquad1*(2*v2(k)*v1dpv2*(rthrp*&
+                      (v1m*v2m)**2)-(-3*dx(k)*rs*(v1m*v2m)**2+2*v2m*2*&
+                       v1(k)*1/2*1/v1m*v2m*v1m*rthrp)*v1dpv2**2)/opt16
+          dEquad1Calp(k)=opt18*(2*(-v1(k)-v2(k))*v1dpv2* &
+                        v1m**2*v2m**2-(-2*v1(k)*v2m**2-2*v2(k)*v1m**2)*&
+                        v1dpv2**2)/opt19
+        enddo
+        Equad2=wquad1*wquad2p*Irthrp
+        do k=1,3
+          dEquad2Cat(k)=-3*dx(k)*rs*opt3
+          dEquad2Cm(k)=3*dx(k)*rs*opt3
+          dEquad2Calp(k)=0.0d0
+        enddo
+        Evan1=opt4*Irtw
+        do k=1,3
+          dEvan1Cat(k)=-dx(k)*opt5
+          dEvan1Cm(k)=dx(k)*opt5
+          dEvan1Calp(k)=0.0d0
+        enddo
+        Evan2=-opt6*Irsixp
+        do k=1,3
+          dEvan2Cat(k)=dx(k)*opt7
+          dEvan2Cm(k)=-dx(k)*opt7
+          dEvan2Calp(k)=0.0d0
+        enddo
+         ecation_prot = ecation_prot+Edip+Equad1+Equad2+Evan1+Evan2
+        do k=1,3
+          dEtotalCat(k)=dEdipCat(k)+dEquad1Cat(k)+ &
+                       dEquad2Cat(k)+dEvan1Cat(k)+dEvan2Cat(k)
+          dEtotalCm(k)=dEdipCm(k)+dEquad1Cm(k)+ &
+                      dEquad2Cm(k)+dEvan1Cm(k)+dEvan2Cm(k)
+          dEtotalCalp(k)=dEdipCalp(k)+dEquad1Calp(k) &
+                        +dEquad2Calp(k)+dEvan1Calp(k)+dEvan2Calp(k)
+        enddo
+            dscmag = 0.0d0
+            do k=1,3
+              dscvec(k) = c(k,i+nres)-c(k,i)
+              dscmag = dscmag+dscvec(k)*dscvec(k)
+            enddo
+            dscmag3 = dscmag
+            dscmag = sqrt(dscmag)
+            dscmag3 = dscmag3*dscmag
+            constA = 1+dASGL/dscmag
+            constB = 0.0d0
+            do k=1,3
+              constB = constB+dscvec(k)*dEtotalCm(k)
+            enddo
+            constB = constB*dASGL/dscmag3
+            do k=1,3
+              gg(k) = dEtotalCm(k)+dEtotalCalp(k)
+              gradpepcatx(k,i)=gradpepcatx(k,i)+ &
+               constA*dEtotalCm(k)-constB*dscvec(k)
+              gradpepcat(k,i)=gradpepcat(k,i)+gg(k)
+              gradpepcat(k,j)=gradpepcat(k,j)+dEtotalCat(k)
+             enddo
+           else
+            rcal = 0.0d0
+            do k=1,3
+              r(k) = c(k,j)-c(k,i+nres)
+              rcal = rcal+r(k)*r(k)
+            enddo
+            ract=sqrt(rcal)
+            rocal=1.5
+            epscalc=0.2
+            r0p=0.5*(rocal+sig0(itype(i,1)))
+            r06 = r0p**6
+            r012 = r06*r06
+            Evan1=epscalc*(r012/rcal**6)
+            Evan2=epscalc*2*(r06/rcal**3)
+            r4 = rcal**4
+            r7 = rcal**7
+            do k=1,3
+              dEvan1Cm(k) = 12*r(k)*epscalc*r012/r7
+              dEvan2Cm(k) = 12*r(k)*epscalc*r06/r4
+            enddo
+            do k=1,3
+              dEtotalCm(k)=dEvan1Cm(k)+dEvan2Cm(k)
+            enddo
+                 ecation_prot = ecation_prot+ Evan1+Evan2
+            do  k=1,3
+               gradpepcatx(k,i)=gradpepcatx(k,i)+ & 
+               dEtotalCm(k)
+              gradpepcat(k,i)=gradpepcat(k,i)+dEtotalCm(k)
+              gradpepcat(k,j)=gradpepcat(k,j)-dEtotalCm(k)
+             enddo
+         endif ! 13-16 residues
+       enddo !j
+       enddo !i
+       return
+       end subroutine ecat_prot
+
+!----------------------------------------------------------------------------
+!-----------------------------------------------------------------------------
+!-----------------------------------------------------------------------------
+      subroutine eprot_sc_base(escbase)
+      use calc_data
+!      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.NAMES'
+!      include 'COMMON.INTERACT'
+!      include 'COMMON.IOUNITS'
+!      include 'COMMON.CALC'
+!      include 'COMMON.CONTROL'
+!      include 'COMMON.SBRIDGE'
+      logical :: lprn
+!el local variables
+      integer :: iint,itypi,itypi1,itypj,subchap
+      real(kind=8) :: rrij,xi,yi,zi,sig,rij_shift,fac,e1,e2,sigm,epsi
+      real(kind=8) :: evdw,sig0ij
+      real(kind=8) :: xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,&
+                    dist_temp, dist_init,aa,bb,ssgradlipi,ssgradlipj, &
+                    sslipi,sslipj,faclip
+      integer :: ii
+      real(kind=8) :: fracinbuf
+       real (kind=8) :: escbase
+       real (kind=8),dimension(4):: ener
+       real(kind=8) :: b1,b2,b3,b4,egb,eps_in,eps_inout_fac,eps_out
+       real(kind=8) :: ECL,Elj,Equad,Epol,eheadtail,rhead,dGCLOM2,&
+        sqom1,sqom2,sqom12,c1,c2,c3,pom,Lambf,sparrow,&
+        Chif,ChiLambf,bat,eagle,top,bot,botsq,Fcav,dtop,dFdR,dFdOM1,&
+        dFdOM2,w1,w2,w3,dGCLdR,dFdL,dFdOM12,dbot ,&
+        r1,eps_head,alphapol1,pis,facd2,d2,facd1,d1,erdxj,erdxi,federmaus,&
+        dPOLdR1,dFGBdOM2,dFGBdR1,dPOLdFGB1,RR1,MomoFac1,hawk,d1i,d1j,&
+        sig1,sig2,chis12,chis2,ee1,fgb1,a12sq,chis1
+       real(kind=8),dimension(3,2)::chead,erhead_tail
+       real(kind=8),dimension(3) :: Rhead_distance,ertail,erhead
+       integer troll
+       eps_out=80.0d0
+       escbase=0.0d0
+!       do i=1,nres_molec(1)
+        do i=ibond_start,ibond_end
+        if (itype(i,1).eq.ntyp1_molec(1)) cycle
+        itypi  = itype(i,1)
+        dxi    = dc_norm(1,nres+i)
+        dyi    = dc_norm(2,nres+i)
+        dzi    = dc_norm(3,nres+i)
+        dsci_inv = vbld_inv(i+nres)
+        xi=c(1,nres+i)
+        yi=c(2,nres+i)
+        zi=c(3,nres+i)
+        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 j=nres_molec(1)+1,nres_molec(2)+nres_molec(1)
+           itypj= itype(j,2)
+           if (itype(j,2).eq.ntyp1_molec(2))cycle
+           xj=c(1,j+nres)
+           yj=c(2,j+nres)
+           zj=c(3,j+nres)
+           xj=dmod(xj,boxxsize)
+           if (xj.lt.0) xj=xj+boxxsize
+           yj=dmod(yj,boxysize)
+           if (yj.lt.0) yj=yj+boxysize
+           zj=dmod(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
+
+          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 )
+!          print *,i,j,itypi,itypj
+          d1i = dhead_scbasei(itypi,itypj) !this is shift of dipole/charge
+          d1j = dhead_scbasej(itypi,itypj) !this is shift of dipole/charge
+!          d1i=0.0d0
+!          d1j=0.0d0
+!          BetaT = 1.0d0 / (298.0d0 * Rb)
+! Gay-berne var's
+          sig0ij = sigma_scbase( itypi,itypj )
+          chi1   = chi_scbase( itypi, itypj,1 )
+          chi2   = chi_scbase( itypi, itypj,2 )
+!          chi1=0.0d0
+!          chi2=0.0d0
+          chi12  = chi1 * chi2
+          chip1  = chipp_scbase( itypi, itypj,1 )
+          chip2  = chipp_scbase( itypi, itypj,2 )
+!          chip1=0.0d0
+!          chip2=0.0d0
+          chip12 = chip1 * chip2
+! not used by momo potential, but needed by sc_angular which is shared
+! by all energy_potential subroutines
+          alf1   = 0.0d0
+          alf2   = 0.0d0
+          alf12  = 0.0d0
+          a12sq = rborn_scbasei(itypi,itypj) * rborn_scbasej(itypi,itypj)
+!       a12sq = a12sq * a12sq
+! charge of amino acid itypi is...
+          chis1 = chis_scbase(itypi,itypj,1)
+          chis2 = chis_scbase(itypi,itypj,2)
+          chis12 = chis1 * chis2
+          sig1 = sigmap1_scbase(itypi,itypj)
+          sig2 = sigmap2_scbase(itypi,itypj)
+!       write (*,*) "sig1 = ", sig1
+!       write (*,*) "sig2 = ", sig2
+! alpha factors from Fcav/Gcav
+          b1 = alphasur_scbase(1,itypi,itypj)
+!          b1=0.0d0
+          b2 = alphasur_scbase(2,itypi,itypj)
+          b3 = alphasur_scbase(3,itypi,itypj)
+          b4 = alphasur_scbase(4,itypi,itypj)
+! used to determine whether we want to do quadrupole calculations
+! used by Fgb
+       eps_in = epsintab_scbase(itypi,itypj)
+       if (eps_in.eq.0.0) eps_in=1.0
+       eps_inout_fac = ( (1.0d0/eps_in) - (1.0d0/eps_out))
+!       write (*,*) "eps_inout_fac = ", eps_inout_fac
+!-------------------------------------------------------------------
+! tail location and distance calculations
+       DO k = 1,3
+! location of polar head is computed by taking hydrophobic centre
+! and moving by a d1 * dc_norm vector
+! see unres publications for very informative images
+        chead(k,1) = c(k, i+nres) + d1i * dc_norm(k, i+nres)
+        chead(k,2) = c(k, j+nres) + d1j * dc_norm(k, j+nres)
+! distance 
+!        Rsc_distance(k) = dabs(c(k, i+nres) - c(k, j+nres))
+!        Rsc(k) = Rsc_distance(k) * Rsc_distance(k)
+        Rhead_distance(k) = chead(k,2) - chead(k,1)
+       END DO
+! pitagoras (root of sum of squares)
+       Rhead = dsqrt( &
+          (Rhead_distance(1)*Rhead_distance(1)) &
+        + (Rhead_distance(2)*Rhead_distance(2)) &
+        + (Rhead_distance(3)*Rhead_distance(3)))
+!-------------------------------------------------------------------
+! zero everything that should be zero'ed
+       evdwij = 0.0d0
+       ECL = 0.0d0
+       Elj = 0.0d0
+       Equad = 0.0d0
+       Epol = 0.0d0
+       Fcav=0.0d0
+       eheadtail = 0.0d0
+       dGCLdOM1 = 0.0d0
+       dGCLdOM2 = 0.0d0
+       dGCLdOM12 = 0.0d0
+       dPOLdOM1 = 0.0d0
+       dPOLdOM2 = 0.0d0
+          Fcav = 0.0d0
+          dFdR = 0.0d0
+          dCAVdOM1  = 0.0d0
+          dCAVdOM2  = 0.0d0
+          dCAVdOM12 = 0.0d0
+          dscj_inv = vbld_inv(j+nres)
+!          print *,i,j,dscj_inv,dsci_inv
+! rij holds 1/(distance of Calpha atoms)
+          rrij = 1.0D0 / ( xj*xj + yj*yj + zj*zj)
+          rij  = dsqrt(rrij)
+!----------------------------
+          CALL sc_angular
+! this should be in elgrad_init but om's are calculated by sc_angular
+! which in turn is used by older potentials
+! om = omega, sqom = om^2
+          sqom1  = om1 * om1
+          sqom2  = om2 * om2
+          sqom12 = om12 * om12
+
+! now we calculate EGB - Gey-Berne
+! It will be summed up in evdwij and saved in evdw
+          sigsq     = 1.0D0  / sigsq
+          sig       = sig0ij * dsqrt(sigsq)
+!          rij_shift = 1.0D0  / rij - sig + sig0ij
+          rij_shift = 1.0/rij - sig + sig0ij
+          IF (rij_shift.le.0.0D0) THEN
+           evdw = 1.0D20
+           RETURN
+          END IF
+          sigder = -sig * sigsq
+          rij_shift = 1.0D0 / rij_shift
+          fac       = rij_shift**expon
+          c1        = fac  * fac * aa_scbase(itypi,itypj)
+!          c1        = 0.0d0
+          c2        = fac  * bb_scbase(itypi,itypj)
+!          c2        = 0.0d0
+          evdwij    = eps1 * eps2rt * eps3rt * ( c1 + c2 )
+          eps2der   = eps3rt * evdwij
+          eps3der   = eps2rt * evdwij
+!          evdwij    = 4.0d0 * eps2rt * eps3rt * evdwij
+          evdwij    = eps2rt * eps3rt * evdwij
+          c1     = c1 * eps1 * eps2rt**2 * eps3rt**2
+          fac    = -expon * (c1 + evdwij) * rij_shift
+          sigder = fac * sigder
+!          fac    = rij * fac
+! Calculate distance derivative
+          gg(1) =  fac
+          gg(2) =  fac
+          gg(3) =  fac
+!          if (b2.gt.0.0) then
+          fac = chis1 * sqom1 + chis2 * sqom2 &
+          - 2.0d0 * chis12 * om1 * om2 * om12
+! we will use pom later in Gcav, so dont mess with it!
+          pom = 1.0d0 - chis1 * chis2 * sqom12
+          Lambf = (1.0d0 - (fac / pom))
+          Lambf = dsqrt(Lambf)
+          sparrow = 1.0d0 / dsqrt(sig1**2.0d0 + sig2**2.0d0)
+!       write (*,*) "sparrow = ", sparrow
+          Chif = 1.0d0/rij * sparrow
+          ChiLambf = Chif * Lambf
+          eagle = dsqrt(ChiLambf)
+          bat = ChiLambf ** 11.0d0
+          top = b1 * ( eagle + b2 * ChiLambf - b3 )
+          bot = 1.0d0 + b4 * (ChiLambf ** 12.0d0)
+          botsq = bot * bot
+          Fcav = top / bot
+!          print *,i,j,Fcav
+          dtop = b1 * ((Lambf / (2.0d0 * eagle)) + (b2 * Lambf))
+          dbot = 12.0d0 * b4 * bat * Lambf
+          dFdR = ((dtop * bot - top * dbot) / botsq) * sparrow
+!       dFdR = 0.0d0
+!      write (*,*) "dFcav/dR = ", dFdR
+          dtop = b1 * ((Chif / (2.0d0 * eagle)) + (b2 * Chif))
+          dbot = 12.0d0 * b4 * bat * Chif
+          eagle = Lambf * pom
+          dFdOM1  = -(chis1 * om1 - chis12 * om2 * om12) / (eagle)
+          dFdOM2  = -(chis2 * om2 - chis12 * om1 * om12) / (eagle)
+          dFdOM12 = chis12 * (chis1 * om1 * om12 - om2) &
+              * (chis2 * om2 * om12 - om1) / (eagle * pom)
+
+          dFdL = ((dtop * bot - top * dbot) / botsq)
+!       dFdL = 0.0d0
+          dCAVdOM1  = dFdL * ( dFdOM1 )
+          dCAVdOM2  = dFdL * ( dFdOM2 )
+          dCAVdOM12 = dFdL * ( dFdOM12 )
+          
+          ertail(1) = xj*rij
+          ertail(2) = yj*rij
+          ertail(3) = zj*rij
+!      eom1=eps2der*eps2rt_om1-2.0D0*alf1*eps3der+sigder*sigsq_om1
+!      eom2=eps2der*eps2rt_om2+2.0D0*alf2*eps3der+sigder*sigsq_om2
+!      eom12=evdwij*eps1_om12+eps2der*eps2rt_om12 &
+!          -2.0D0*alf12*eps3der+sigder*sigsq_om12
+!           print *,"EOMY",eom1,eom2,eom12
+!          erdxi = scalar( ertail(1), dC_norm(1,i+nres) )
+!          erdxj = scalar( ertail(1), dC_norm(1,j+nres) )
+! here dtail=0.0
+!          facd1 = dtail(1,itypi,itypj) * vbld_inv(i+nres)
+!          facd2 = dtail(2,itypi,itypj) * vbld_inv(j+nres)
+       DO k = 1, 3
+!      write (*,*) "Gvdwc(",k,",",i,")=", gvdwc(k,i)
+!      write (*,*) "Gvdwc(",k,",",j,")=", gvdwc(k,j)
+        pom = ertail(k)
+!-facd1*(ertail(k)-erdxi*dC_norm(k,i+nres))
+        gvdwx_scbase(k,i) = gvdwx_scbase(k,i) &
+                  - (( dFdR + gg(k) ) * pom)  
+!                 +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i)) &
+!                 +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
+!     &             - ( dFdR * pom )
+        pom = ertail(k)
+!-facd2*(ertail(k)-erdxj*dC_norm(k,j+nres))
+        gvdwx_scbase(k,j) = gvdwx_scbase(k,j) &
+                  + (( dFdR + gg(k) ) * pom)  
+!                 +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j)) &
+!                 +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
+!c!     &             + ( dFdR * pom )
+
+        gvdwc_scbase(k,i) = gvdwc_scbase(k,i) &
+                  - (( dFdR + gg(k) ) * ertail(k))
+!c!     &             - ( dFdR * ertail(k))
+
+        gvdwc_scbase(k,j) = gvdwc_scbase(k,j) &
+                  + (( dFdR + gg(k) ) * ertail(k))
+!c!     &             + ( dFdR * ertail(k))
+
+        gg(k) = 0.0d0
+!c!      write (*,*) "Gvdwc(",k,",",i,")=", gvdwc(k,i)
+!c!      write (*,*) "Gvdwc(",k,",",j,")=", gvdwc(k,j)
+      END DO
+
+!          else
+
+!          endif
+!Now dipole-dipole
+         if (wdipdip_scbase(2,itypi,itypj).gt.0.0d0) then
+       w1 = wdipdip_scbase(1,itypi,itypj)
+       w2 = -wdipdip_scbase(3,itypi,itypj)/2.0
+       w3 = wdipdip_scbase(2,itypi,itypj)
+!c!-------------------------------------------------------------------
+!c! ECL
+       fac = (om12 - 3.0d0 * om1 * om2)
+       c1 = (w1 / (Rhead**3.0d0)) * fac
+       c2 = (w2 / Rhead ** 6.0d0)  &
+         * (4.0d0 + fac * fac -3.0d0 * (sqom1 + sqom2))
+       c3= (w3/ Rhead ** 6.0d0)  &
+         * (2.0d0 - 2.0d0*fac*fac +3.0d0*(sqom1 + sqom2))
+       ECL = c1 - c2 + c3
+!c!       write (*,*) "w1 = ", w1
+!c!       write (*,*) "w2 = ", w2
+!c!       write (*,*) "om1 = ", om1
+!c!       write (*,*) "om2 = ", om2
+!c!       write (*,*) "om12 = ", om12
+!c!       write (*,*) "fac = ", fac
+!c!       write (*,*) "c1 = ", c1
+!c!       write (*,*) "c2 = ", c2
+!c!       write (*,*) "Ecl = ", Ecl
+!c!       write (*,*) "c2_1 = ", (w2 / Rhead ** 6.0d0)
+!c!       write (*,*) "c2_2 = ",
+!c!     & (4.0d0 + fac * fac -3.0d0 * (sqom1 + sqom2))
+!c!-------------------------------------------------------------------
+!c! dervative of ECL is GCL...
+!c! dECL/dr
+       c1 = (-3.0d0 * w1 * fac) / (Rhead ** 4.0d0)
+       c2 = (-6.0d0 * w2) / (Rhead ** 7.0d0) &
+         * (4.0d0 + fac * fac - 3.0d0 * (sqom1 + sqom2))
+       c3=  (-6.0d0 * w3) / (Rhead ** 7.0d0) &
+         * (2.0d0 - 2.0d0*fac*fac +3.0d0*(sqom1 + sqom2))
+       dGCLdR = c1 - c2 + c3
+!c! dECL/dom1
+       c1 = (-3.0d0 * w1 * om2 ) / (Rhead**3.0d0)
+       c2 = (-6.0d0 * w2) / (Rhead**6.0d0) &
+         * ( om2 * om12 - 3.0d0 * om1 * sqom2 + om1 )
+       c3 =(6.0d0*w3/ Rhead ** 6.0d0)*(om1-2.0d0*(fac)*(-om2))
+       dGCLdOM1 = c1 - c2 + c3 
+!c! dECL/dom2
+       c1 = (-3.0d0 * w1 * om1 ) / (Rhead**3.0d0)
+       c2 = (-6.0d0 * w2) / (Rhead**6.0d0) &
+         * ( om1 * om12 - 3.0d0 * sqom1 * om2 + om2 )
+       c3 =(6.0d0*w3/ Rhead ** 6.0d0)*(om2-2.0d0*(fac)*(-om1))
+       dGCLdOM2 = c1 - c2 + c3
+!c! dECL/dom12
+       c1 = w1 / (Rhead ** 3.0d0)
+       c2 = ( 2.0d0 * w2 * fac ) / Rhead ** 6.0d0
+       c3 = (w3/ Rhead ** 6.0d0)*(-4.0d0*fac)
+       dGCLdOM12 = c1 - c2 + c3
+       DO k= 1, 3
+        erhead(k) = Rhead_distance(k)/Rhead
+       END DO
+       erdxi = scalar( erhead(1), dC_norm(1,i+nres) )
+       erdxj = scalar( erhead(1), dC_norm(1,j+nres) )
+       facd1 = d1i * vbld_inv(i+nres)
+       facd2 = d1j * vbld_inv(j+nres)
+       DO k = 1, 3
+
+        pom = erhead(k)+facd1*(erhead(k)-erdxi*dC_norm(k,i+nres))
+        gvdwx_scbase(k,i) = gvdwx_scbase(k,i) &
+                  - dGCLdR * pom
+        pom = erhead(k)+facd2*(erhead(k)-erdxj*dC_norm(k,j+nres))
+        gvdwx_scbase(k,j) = gvdwx_scbase(k,j) &
+                  + dGCLdR * pom
+
+        gvdwc_scbase(k,i) = gvdwc_scbase(k,i) &
+                  - dGCLdR * erhead(k)
+        gvdwc_scbase(k,j) = gvdwc_scbase(k,j) &
+                  + dGCLdR * erhead(k)
+       END DO
+       endif
+!now charge with dipole eg. ARG-dG
+       if (wqdip_scbase(2,itypi,itypj).gt.0.0d0) then
+      alphapol1 = alphapol_scbase(itypi,itypj)
+       w1        = wqdip_scbase(1,itypi,itypj)
+       w2        = wqdip_scbase(2,itypi,itypj)
+!       w1=0.0d0
+!       w2=0.0d0
+!       pis       = sig0head_scbase(itypi,itypj)
+!       eps_head   = epshead_scbase(itypi,itypj)
+!c!-------------------------------------------------------------------
+!c! R1 - distance between head of ith side chain and tail of jth sidechain
+       R1 = 0.0d0
+       DO k = 1, 3
+!c! Calculate head-to-tail distances tail is center of side-chain
+        R1=R1+(c(k,j+nres)-chead(k,1))**2
+       END DO
+!c! Pitagoras
+       R1 = dsqrt(R1)
+
+!c!      R1     = dsqrt((Rtail**2)+((dtail(1,itypi,itypj)
+!c!     &        +dhead(1,1,itypi,itypj))**2))
+!c!      R2     = dsqrt((Rtail**2)+((dtail(2,itypi,itypj)
+!c!     &        +dhead(2,1,itypi,itypj))**2))
+
+!c!-------------------------------------------------------------------
+!c! ecl
+       sparrow  = w1  *  om1
+       hawk     = w2 *  (1.0d0 - sqom2)
+       Ecl = sparrow / Rhead**2.0d0 &
+           - hawk    / Rhead**4.0d0
+!c!-------------------------------------------------------------------
+!c! derivative of ecl is Gcl
+!c! dF/dr part
+       dGCLdR  = - 2.0d0 * sparrow / Rhead**3.0d0 &
+                + 4.0d0 * hawk    / Rhead**5.0d0
+!c! dF/dom1
+       dGCLdOM1 = (w1) / (Rhead**2.0d0)
+!c! dF/dom2
+       dGCLdOM2 = (2.0d0 * w2 * om2) / (Rhead ** 4.0d0)
+!c--------------------------------------------------------------------
+!c Polarization energy
+!c Epol
+       MomoFac1 = (1.0d0 - chi1 * sqom2)
+       RR1  = R1 * R1 / MomoFac1
+       ee1  = exp(-( RR1 / (4.0d0 * a12sq) ))
+       fgb1 = sqrt( RR1 + a12sq * ee1)
+!       eps_inout_fac=0.0d0
+       epol = 332.0d0 * eps_inout_fac * (( alphapol1 / fgb1 )**4.0d0)
+! derivative of Epol is Gpol...
+       dPOLdFGB1 = -(1328.0d0 * eps_inout_fac * alphapol1 ** 4.0d0) &
+                / (fgb1 ** 5.0d0)
+       dFGBdR1 = ( (R1 / MomoFac1) &
+             * ( 2.0d0 - (0.5d0 * ee1) ) ) &
+             / ( 2.0d0 * fgb1 )
+       dFGBdOM2 = (((R1 * R1 * chi1 * om2) / (MomoFac1 * MomoFac1)) &
+               * (2.0d0 - 0.5d0 * ee1) ) &
+               / (2.0d0 * fgb1)
+       dPOLdR1 = dPOLdFGB1 * dFGBdR1
+!       dPOLdR1 = 0.0d0
+       dPOLdOM1 = 0.0d0
+       dPOLdOM2 = dPOLdFGB1 * dFGBdOM2
+       DO k = 1, 3
+        erhead(k) = Rhead_distance(k)/Rhead
+        erhead_tail(k,1) = ((c(k,j+nres)-chead(k,1))/R1)
+       END DO
+
+       erdxi = scalar( erhead(1), dC_norm(1,i+nres) )
+       erdxj = scalar( erhead(1), dC_norm(1,j+nres) )
+       bat = scalar( erhead_tail(1,1), dC_norm(1,i+nres) )
+!       bat=0.0d0
+       federmaus = scalar(erhead_tail(1,1),dC_norm(1,j+nres))
+       facd1 = d1i * vbld_inv(i+nres)
+       facd2 = d1j * vbld_inv(j+nres)
+!       facd4 = dtail(2,itypi,itypj) * vbld_inv(j+nres)
+
+       DO k = 1, 3
+        hawk = (erhead_tail(k,1) + &
+        facd1 * (erhead_tail(k,1) - bat * dC_norm(k,i+nres)))
+!        facd1=0.0d0
+!        facd2=0.0d0
+        pom = erhead(k)+facd1*(erhead(k)-erdxi*dC_norm(k,i+nres))
+        gvdwx_scbase(k,i) = gvdwx_scbase(k,i)   &
+                   - dGCLdR * pom &
+                   - dPOLdR1 *  (erhead_tail(k,1))
+!     &             - dGLJdR * pom
+
+        pom = erhead(k)+facd2*(erhead(k)-erdxj*dC_norm(k,j+nres))
+        gvdwx_scbase(k,j) = gvdwx_scbase(k,j)    &
+                   + dGCLdR * pom  &
+                   + dPOLdR1 * (erhead_tail(k,1))
+!     &             + dGLJdR * pom
+
+
+        gvdwc_scbase(k,i) = gvdwc_scbase(k,i)  &
+                  - dGCLdR * erhead(k) &
+                  - dPOLdR1 * erhead_tail(k,1)
+!     &             - dGLJdR * erhead(k)
+
+        gvdwc_scbase(k,j) = gvdwc_scbase(k,j)         &
+                  + dGCLdR * erhead(k)  &
+                  + dPOLdR1 * erhead_tail(k,1)
+!     &             + dGLJdR * erhead(k)
+
+       END DO
+       endif
+!       print *,i,j,evdwij,epol,Fcav,ECL
+       escbase=escbase+evdwij+epol+Fcav+ECL
+       call sc_grad_scbase
+         enddo
+      enddo
+
+      return
+      end subroutine eprot_sc_base
+      SUBROUTINE sc_grad_scbase
+      use calc_data
+
+       real (kind=8) :: dcosom1(3),dcosom2(3)
+       eom1  =    &
+              eps2der * eps2rt_om1   &
+            - 2.0D0 * alf1 * eps3der &
+            + sigder * sigsq_om1     &
+            + dCAVdOM1               &
+            + dGCLdOM1               &
+            + dPOLdOM1
+
+       eom2  =  &
+              eps2der * eps2rt_om2   &
+            + 2.0D0 * alf2 * eps3der &
+            + sigder * sigsq_om2     &
+            + dCAVdOM2               &
+            + dGCLdOM2               &
+            + dPOLdOM2
+
+       eom12 =    &
+              evdwij  * eps1_om12     &
+            + eps2der * eps2rt_om12   &
+            - 2.0D0 * alf12 * eps3der &
+            + sigder *sigsq_om12      &
+            + dCAVdOM12               &
+            + dGCLdOM12
+
+!       print *,eom1,eom2,eom12,i,j,"eom1,2,12",erij(1),erij(2),erij(3)
+!       print *,dsci_inv,dscj_inv,dc_norm(2,nres+j),dc_norm(2,nres+i),&
+!               gg(1),gg(2),"rozne"
+       DO k = 1, 3
+        dcosom1(k) = rij * (dc_norm(k,nres+i) - om1 * erij(k))
+        dcosom2(k) = rij * (dc_norm(k,nres+j) - om2 * erij(k))
+        gg(k) = gg(k) + eom1 * dcosom1(k) + eom2 * dcosom2(k)
+        gvdwx_scbase(k,i)= gvdwx_scbase(k,i) - gg(k)   &
+                 + (eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i)) &
+                 + eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
+        gvdwx_scbase(k,j)= gvdwx_scbase(k,j) + gg(k)  &
+                 + (eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j)) &
+                 + eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
+        gvdwc_scbase(k,i)=gvdwc_scbase(k,i)-gg(k)
+        gvdwc_scbase(k,j)=gvdwc_scbase(k,j)+gg(k)
+       END DO
+       RETURN
+      END SUBROUTINE sc_grad_scbase
+
+
+      subroutine epep_sc_base(epepbase)
+      use calc_data
+      logical :: lprn
+!el local variables
+      integer :: iint,itypi,itypi1,itypj,subchap
+      real(kind=8) :: rrij,xi,yi,zi,sig,rij_shift,fac,e1,e2,sigm,epsi
+      real(kind=8) :: evdw,sig0ij
+      real(kind=8) :: xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,&
+                    dist_temp, dist_init,aa,bb,ssgradlipi,ssgradlipj, &
+                    sslipi,sslipj,faclip
+      integer :: ii
+      real(kind=8) :: fracinbuf
+       real (kind=8) :: epepbase
+       real (kind=8),dimension(4):: ener
+       real(kind=8) :: b1,b2,b3,b4,egb,eps_in,eps_inout_fac,eps_out
+       real(kind=8) :: ECL,Elj,Equad,Epol,eheadtail,rhead,dGCLOM2,&
+        sqom1,sqom2,sqom12,c1,c2,c3,pom,Lambf,sparrow,&
+        Chif,ChiLambf,bat,eagle,top,bot,botsq,Fcav,dtop,dFdR,dFdOM1,&
+        dFdOM2,w1,w2,w3,dGCLdR,dFdL,dFdOM12,dbot ,&
+        r1,eps_head,alphapol1,pis,facd2,d2,facd1,d1,erdxj,erdxi,federmaus,&
+        dPOLdR1,dFGBdOM2,dFGBdR1,dPOLdFGB1,RR1,MomoFac1,hawk,d1i,d1j,&
+        sig1,sig2,chis12,chis2,ee1,fgb1,a12sq,chis1
+       real(kind=8),dimension(3,2)::chead,erhead_tail
+       real(kind=8),dimension(3) :: Rhead_distance,ertail,erhead
+       integer troll
+       eps_out=80.0d0
+       epepbase=0.0d0
+!       do i=1,nres_molec(1)-1
+        do i=ibond_start,ibond_end
+        if (itype(i,1).eq.ntyp1_molec(1).or.itype(i+1,1).eq.ntyp1_molec(1)) cycle
+!C        itypi  = itype(i,1)
+        dxi    = dc_norm(1,i)
+        dyi    = dc_norm(2,i)
+        dzi    = dc_norm(3,i)
+!        print *,dxi,(-c(1,i)+c(1,i+1))*vbld_inv(i+1)
+        dsci_inv = vbld_inv(i+1)/2.0
+        xi=(c(1,i)+c(1,i+1))/2.0
+        yi=(c(2,i)+c(2,i+1))/2.0
+        zi=(c(3,i)+c(3,i+1))/2.0
+        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 j=nres_molec(1)+1,nres_molec(2)+nres_molec(1)
+           itypj= itype(j,2)
+           if (itype(j,2).eq.ntyp1_molec(2))cycle
+           xj=c(1,j+nres)
+           yj=c(2,j+nres)
+           zj=c(3,j+nres)
+           xj=dmod(xj,boxxsize)
+           if (xj.lt.0) xj=xj+boxxsize
+           yj=dmod(yj,boxysize)
+           if (yj.lt.0) yj=yj+boxysize
+           zj=dmod(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
+
+          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 )
+!          d1i = dhead_scbasei(itypi) !this is shift of dipole/charge
+!          d1j = dhead_scbasej(itypi) !this is shift of dipole/charge
+
+! Gay-berne var's
+          sig0ij = sigma_pepbase(itypj )
+          chi1   = chi_pepbase(itypj,1 )
+          chi2   = chi_pepbase(itypj,2 )
+!          chi1=0.0d0
+!          chi2=0.0d0
+          chi12  = chi1 * chi2
+          chip1  = chipp_pepbase(itypj,1 )
+          chip2  = chipp_pepbase(itypj,2 )
+!          chip1=0.0d0
+!          chip2=0.0d0
+          chip12 = chip1 * chip2
+          chis1 = chis_pepbase(itypj,1)
+          chis2 = chis_pepbase(itypj,2)
+          chis12 = chis1 * chis2
+          sig1 = sigmap1_pepbase(itypj)
+          sig2 = sigmap2_pepbase(itypj)
+!       write (*,*) "sig1 = ", sig1
+!       write (*,*) "sig2 = ", sig2
+       DO k = 1,3
+! location of polar head is computed by taking hydrophobic centre
+! and moving by a d1 * dc_norm vector
+! see unres publications for very informative images
+        chead(k,1) = (c(k,i)+c(k,i+1))/2.0
+! + d1i * dc_norm(k, i+nres)
+        chead(k,2) = c(k, j+nres)
+! + d1j * dc_norm(k, j+nres)
+! distance 
+!        Rsc_distance(k) = dabs(c(k, i+nres) - c(k, j+nres))
+!        Rsc(k) = Rsc_distance(k) * Rsc_distance(k)
+        Rhead_distance(k) = chead(k,2) - chead(k,1)
+!        print *,gvdwc_pepbase(k,i)
+
+       END DO
+       Rhead = dsqrt( &
+          (Rhead_distance(1)*Rhead_distance(1)) &
+        + (Rhead_distance(2)*Rhead_distance(2)) &
+        + (Rhead_distance(3)*Rhead_distance(3)))
+
+! alpha factors from Fcav/Gcav
+          b1 = alphasur_pepbase(1,itypj)
+!          b1=0.0d0
+          b2 = alphasur_pepbase(2,itypj)
+          b3 = alphasur_pepbase(3,itypj)
+          b4 = alphasur_pepbase(4,itypj)
+          alf1   = 0.0d0
+          alf2   = 0.0d0
+          alf12  = 0.0d0
+          rrij = 1.0D0 / ( xj*xj + yj*yj + zj*zj)
+!          print *,i,j,rrij
+          rij  = dsqrt(rrij)
+!----------------------------
+       evdwij = 0.0d0
+       ECL = 0.0d0
+       Elj = 0.0d0
+       Equad = 0.0d0
+       Epol = 0.0d0
+       Fcav=0.0d0
+       eheadtail = 0.0d0
+       dGCLdOM1 = 0.0d0
+       dGCLdOM2 = 0.0d0
+       dGCLdOM12 = 0.0d0
+       dPOLdOM1 = 0.0d0
+       dPOLdOM2 = 0.0d0
+          Fcav = 0.0d0
+          dFdR = 0.0d0
+          dCAVdOM1  = 0.0d0
+          dCAVdOM2  = 0.0d0
+          dCAVdOM12 = 0.0d0
+          dscj_inv = vbld_inv(j+nres)
+          CALL sc_angular
+! this should be in elgrad_init but om's are calculated by sc_angular
+! which in turn is used by older potentials
+! om = omega, sqom = om^2
+          sqom1  = om1 * om1
+          sqom2  = om2 * om2
+          sqom12 = om12 * om12
+
+! now we calculate EGB - Gey-Berne
+! It will be summed up in evdwij and saved in evdw
+          sigsq     = 1.0D0  / sigsq
+          sig       = sig0ij * dsqrt(sigsq)
+          rij_shift = 1.0/rij - sig + sig0ij
+          IF (rij_shift.le.0.0D0) THEN
+           evdw = 1.0D20
+           RETURN
+          END IF
+          sigder = -sig * sigsq
+          rij_shift = 1.0D0 / rij_shift
+          fac       = rij_shift**expon
+          c1        = fac  * fac * aa_pepbase(itypj)
+!          c1        = 0.0d0
+          c2        = fac  * bb_pepbase(itypj)
+!          c2        = 0.0d0
+          evdwij    = eps1 * eps2rt * eps3rt * ( c1 + c2 )
+          eps2der   = eps3rt * evdwij
+          eps3der   = eps2rt * evdwij
+!          evdwij    = 4.0d0 * eps2rt * eps3rt * evdwij
+          evdwij    = eps2rt * eps3rt * evdwij
+          c1     = c1 * eps1 * eps2rt**2 * eps3rt**2
+          fac    = -expon * (c1 + evdwij) * rij_shift
+          sigder = fac * sigder
+!          fac    = rij * fac
+! Calculate distance derivative
+          gg(1) =  fac
+          gg(2) =  fac
+          gg(3) =  fac
+          fac = chis1 * sqom1 + chis2 * sqom2 &
+          - 2.0d0 * chis12 * om1 * om2 * om12
+! we will use pom later in Gcav, so dont mess with it!
+          pom = 1.0d0 - chis1 * chis2 * sqom12
+          Lambf = (1.0d0 - (fac / pom))
+          Lambf = dsqrt(Lambf)
+          sparrow = 1.0d0 / dsqrt(sig1**2.0d0 + sig2**2.0d0)
+!       write (*,*) "sparrow = ", sparrow
+          Chif = 1.0d0/rij * sparrow
+          ChiLambf = Chif * Lambf
+          eagle = dsqrt(ChiLambf)
+          bat = ChiLambf ** 11.0d0
+          top = b1 * ( eagle + b2 * ChiLambf - b3 )
+          bot = 1.0d0 + b4 * (ChiLambf ** 12.0d0)
+          botsq = bot * bot
+          Fcav = top / bot
+!          print *,i,j,Fcav
+          dtop = b1 * ((Lambf / (2.0d0 * eagle)) + (b2 * Lambf))
+          dbot = 12.0d0 * b4 * bat * Lambf
+          dFdR = ((dtop * bot - top * dbot) / botsq) * sparrow
+!       dFdR = 0.0d0
+!      write (*,*) "dFcav/dR = ", dFdR
+          dtop = b1 * ((Chif / (2.0d0 * eagle)) + (b2 * Chif))
+          dbot = 12.0d0 * b4 * bat * Chif
+          eagle = Lambf * pom
+          dFdOM1  = -(chis1 * om1 - chis12 * om2 * om12) / (eagle)
+          dFdOM2  = -(chis2 * om2 - chis12 * om1 * om12) / (eagle)
+          dFdOM12 = chis12 * (chis1 * om1 * om12 - om2) &
+              * (chis2 * om2 * om12 - om1) / (eagle * pom)
+
+          dFdL = ((dtop * bot - top * dbot) / botsq)
+!       dFdL = 0.0d0
+          dCAVdOM1  = dFdL * ( dFdOM1 )
+          dCAVdOM2  = dFdL * ( dFdOM2 )
+          dCAVdOM12 = dFdL * ( dFdOM12 )
+
+          ertail(1) = xj*rij
+          ertail(2) = yj*rij
+          ertail(3) = zj*rij
+       DO k = 1, 3
+!      write (*,*) "Gvdwc(",k,",",i,")=", gvdwc(k,i)
+!      write (*,*) "Gvdwc(",k,",",j,")=", gvdwc(k,j)
+        pom = ertail(k)
+!-facd1*(ertail(k)-erdxi*dC_norm(k,i+nres))
+        gvdwc_pepbase(k,i) = gvdwc_pepbase(k,i) &
+                  - (( dFdR + gg(k) ) * pom)/2.0
+!        print *,gvdwc_pepbase(k,i),i,(( dFdR + gg(k) ) * pom)/2.0
+!                 +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i)) &
+!                 +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
+!     &             - ( dFdR * pom )
+        pom = ertail(k)
+!-facd2*(ertail(k)-erdxj*dC_norm(k,j+nres))
+        gvdwx_pepbase(k,j) = gvdwx_pepbase(k,j) &
+                  + (( dFdR + gg(k) ) * pom)
+!                 +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j)) &
+!                 +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
+!c!     &             + ( dFdR * pom )
+
+        gvdwc_pepbase(k,i+1) = gvdwc_pepbase(k,i+1) &
+                  - (( dFdR + gg(k) ) * ertail(k))/2.0
+!        print *,gvdwc_pepbase(k,i+1),i+1,(( dFdR + gg(k) ) * pom)/2.0
+
+!c!     &             - ( dFdR * ertail(k))
+
+        gvdwc_pepbase(k,j) = gvdwc_pepbase(k,j) &
+                  + (( dFdR + gg(k) ) * ertail(k))
+!c!     &             + ( dFdR * ertail(k))
+
+        gg(k) = 0.0d0
+!c!      write (*,*) "Gvdwc(",k,",",i,")=", gvdwc(k,i)
+!c!      write (*,*) "Gvdwc(",k,",",j,")=", gvdwc(k,j)
+      END DO
+
+
+       w1 = wdipdip_pepbase(1,itypj)
+       w2 = -wdipdip_pepbase(3,itypj)/2.0
+       w3 = wdipdip_pepbase(2,itypj)
+!       w1=0.0d0
+!       w2=0.0d0
+!c!-------------------------------------------------------------------
+!c! ECL
+!       w3=0.0d0
+       fac = (om12 - 3.0d0 * om1 * om2)
+       c1 = (w1 / (Rhead**3.0d0)) * fac
+       c2 = (w2 / Rhead ** 6.0d0)  &
+         * (4.0d0 + fac * fac -3.0d0 * (sqom1 + sqom2))
+       c3= (w3/ Rhead ** 6.0d0)  &
+         * (2.0d0 - 2.0d0*fac*fac +3.0d0*(sqom1 + sqom2))
+
+       ECL = c1 - c2 + c3 
+
+       c1 = (-3.0d0 * w1 * fac) / (Rhead ** 4.0d0)
+       c2 = (-6.0d0 * w2) / (Rhead ** 7.0d0) &
+         * (4.0d0 + fac * fac - 3.0d0 * (sqom1 + sqom2))
+       c3=  (-6.0d0 * w3) / (Rhead ** 7.0d0) &
+         * (2.0d0 - 2.0d0*fac*fac +3.0d0*(sqom1 + sqom2))
+
+       dGCLdR = c1 - c2 + c3
+!c! dECL/dom1
+       c1 = (-3.0d0 * w1 * om2 ) / (Rhead**3.0d0)
+       c2 = (-6.0d0 * w2) / (Rhead**6.0d0) &
+         * ( om2 * om12 - 3.0d0 * om1 * sqom2 + om1 )
+       c3 =(6.0d0*w3/ Rhead ** 6.0d0)*(om1-2.0d0*(fac)*(-om2))
+       dGCLdOM1 = c1 - c2 + c3 
+!c! dECL/dom2
+       c1 = (-3.0d0 * w1 * om1 ) / (Rhead**3.0d0)
+       c2 = (-6.0d0 * w2) / (Rhead**6.0d0) &
+         * ( om1 * om12 - 3.0d0 * sqom1 * om2 + om2 )
+       c3 =(6.0d0*w3/ Rhead ** 6.0d0)*(om2-2.0d0*(fac)*(-om1))
+
+       dGCLdOM2 = c1 - c2 + c3 
+!c! dECL/dom12
+       c1 = w1 / (Rhead ** 3.0d0)
+       c2 = ( 2.0d0 * w2 * fac ) / Rhead ** 6.0d0
+       c3 = (w3/ Rhead ** 6.0d0)*(-4.0d0*fac)
+       dGCLdOM12 = c1 - c2 + c3
+       DO k= 1, 3
+        erhead(k) = Rhead_distance(k)/Rhead
+       END DO
+       erdxi = scalar( erhead(1), dC_norm(1,i+nres) )
+       erdxj = scalar( erhead(1), dC_norm(1,j+nres) )
+!       facd1 = d1 * vbld_inv(i+nres)
+!       facd2 = d2 * vbld_inv(j+nres)
+       DO k = 1, 3
+
+!        pom = erhead(k)
+!+facd1*(erhead(k)-erdxi*dC_norm(k,i+nres))
+!        gvdwx_pepbase(k,i) = gvdwx_scbase(k,i) &
+!                  - dGCLdR * pom
+        pom = erhead(k)
+!+facd2*(erhead(k)-erdxj*dC_norm(k,j+nres))
+        gvdwx_pepbase(k,j) = gvdwx_pepbase(k,j) &
+                  + dGCLdR * pom
+
+        gvdwc_pepbase(k,i) = gvdwc_pepbase(k,i) &
+                  - dGCLdR * erhead(k)/2.0d0
+!        print *,gvdwc_pepbase(k,i+1),i+1,- dGCLdR * erhead(k)/2.0d0
+        gvdwc_pepbase(k,i+1) = gvdwc_pepbase(k,i+1) &
+                  - dGCLdR * erhead(k)/2.0d0
+!        print *,gvdwc_pepbase(k,i+1),i+1,- dGCLdR * erhead(k)/2.0d0
+        gvdwc_pepbase(k,j) = gvdwc_pepbase(k,j) &
+                  + dGCLdR * erhead(k)
+       END DO
+!       print *,i,j,evdwij,Fcav,ECL,"vdw,cav,ecl"
+       epepbase=epepbase+evdwij+Fcav+ECL
+       call sc_grad_pepbase
+       enddo
+       enddo
+      END SUBROUTINE epep_sc_base
+      SUBROUTINE sc_grad_pepbase
+      use calc_data
+
+       real (kind=8) :: dcosom1(3),dcosom2(3)
+       eom1  =    &
+              eps2der * eps2rt_om1   &
+            - 2.0D0 * alf1 * eps3der &
+            + sigder * sigsq_om1     &
+            + dCAVdOM1               &
+            + dGCLdOM1               &
+            + dPOLdOM1
+
+       eom2  =  &
+              eps2der * eps2rt_om2   &
+            + 2.0D0 * alf2 * eps3der &
+            + sigder * sigsq_om2     &
+            + dCAVdOM2               &
+            + dGCLdOM2               &
+            + dPOLdOM2
+
+       eom12 =    &
+              evdwij  * eps1_om12     &
+            + eps2der * eps2rt_om12   &
+            - 2.0D0 * alf12 * eps3der &
+            + sigder *sigsq_om12      &
+            + dCAVdOM12               &
+            + dGCLdOM12
+!        om12=0.0
+!        eom12=0.0
+!       print *,eom1,eom2,eom12,om12,i,j,"eom1,2,12",erij(1),erij(2),erij(3)
+!        if (i.eq.30) print *,gvdwc_pepbase(k,i),- gg(k),&
+!                 (-eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,i)))&
+!                 *dsci_inv*2.0
+!       print *,dsci_inv,dscj_inv,dc_norm(2,nres+j),dc_norm(2,nres+i),&
+!               gg(1),gg(2),"rozne"
+       DO k = 1, 3
+        dcosom1(k) = rij * (dc_norm(k,i) - om1 * erij(k))
+        dcosom2(k) = rij * (dc_norm(k,nres+j) - om2 * erij(k))
+        gg(k) = gg(k) + eom1 * dcosom1(k) + eom2 * dcosom2(k)
+        gvdwc_pepbase(k,i)= gvdwc_pepbase(k,i) +0.5*(- gg(k))   &
+                 + (-eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,i)))&
+                 *dsci_inv*2.0 &
+                 - (eom1*(erij(k)-om1*dc_norm(k,i)))*dsci_inv*2.0
+        gvdwc_pepbase(k,i+1)= gvdwc_pepbase(k,i+1) +0.5*(- gg(k))   &
+                 - (-eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,i))) &
+                 *dsci_inv*2.0 &
+                 + (eom1*(erij(k)-om1*dc_norm(k,i)))*dsci_inv*2.0
+!         print *,eom12,eom2,om12,om2
+!eom12*(-dc_norm(k,i)/2.0-om12*dc_norm(k,nres+j)),&
+!                (eom2*(erij(k)-om2*dc_norm(k,nres+j)))
+        gvdwx_pepbase(k,j)= gvdwx_pepbase(k,j) + gg(k)  &
+                 + (eom12*(dc_norm(k,i)-om12*dc_norm(k,nres+j))&
+                 + eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
+        gvdwc_pepbase(k,j)=gvdwc_pepbase(k,j)+gg(k)
+       END DO
+       RETURN
+      END SUBROUTINE sc_grad_pepbase
+      subroutine eprot_sc_phosphate(escpho)
+      use calc_data
+!      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.NAMES'
+!      include 'COMMON.INTERACT'
+!      include 'COMMON.IOUNITS'
+!      include 'COMMON.CALC'
+!      include 'COMMON.CONTROL'
+!      include 'COMMON.SBRIDGE'
+      logical :: lprn
+!el local variables
+      integer :: iint,itypi,itypi1,itypj,subchap
+      real(kind=8) :: rrij,xi,yi,zi,sig,rij_shift,fac,e1,e2,sigm,epsi
+      real(kind=8) :: evdw,sig0ij
+      real(kind=8) :: xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,&
+                    dist_temp, dist_init,aa,bb,ssgradlipi,ssgradlipj, &
+                    sslipi,sslipj,faclip,alpha_sco
+      integer :: ii
+      real(kind=8) :: fracinbuf
+       real (kind=8) :: escpho
+       real (kind=8),dimension(4):: ener
+       real(kind=8) :: b1,b2,b3,b4,egb,eps_in,eps_inout_fac,eps_out
+       real(kind=8) :: ECL,Elj,Equad,Epol,eheadtail,rhead,dGCLOM2,&
+        sqom1,sqom2,sqom12,c1,c2,pom,Lambf,sparrow,&
+        Chif,ChiLambf,bat,eagle,top,bot,botsq,Fcav,dtop,dFdR,dFdOM1,&
+        dFdOM2,w1,w2,dGCLdR,dFdL,dFdOM12,dbot ,&
+        r1,eps_head,alphapol1,pis,facd2,d2,facd1,d1,erdxj,erdxi,federmaus,&
+        dPOLdR1,dFGBdOM2,dFGBdR1,dPOLdFGB1,RR1,MomoFac1,hawk,d1i,d1j,&
+        sig1,sig2,chis12,chis2,ee1,fgb1,a12sq,chis1,Rhead_sq,Qij,dFGBdOM1
+       real(kind=8),dimension(3,2)::chead,erhead_tail
+       real(kind=8),dimension(3) :: Rhead_distance,ertail,erhead
+       integer troll
+       eps_out=80.0d0
+       escpho=0.0d0
+!       do i=1,nres_molec(1)
+        do i=ibond_start,ibond_end
+        if (itype(i,1).eq.ntyp1_molec(1)) cycle
+        itypi  = itype(i,1)
+        dxi    = dc_norm(1,nres+i)
+        dyi    = dc_norm(2,nres+i)
+        dzi    = dc_norm(3,nres+i)
+        dsci_inv = vbld_inv(i+nres)
+        xi=c(1,nres+i)
+        yi=c(2,nres+i)
+        zi=c(3,nres+i)
+        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 j=nres_molec(1)+1,nres_molec(2)+nres_molec(1)-1
+           itypj= itype(j,2)
+           if ((itype(j,2).eq.ntyp1_molec(2)).or.&
+            (itype(j+1,2).eq.ntyp1_molec(2))) cycle
+           xj=(c(1,j)+c(1,j+1))/2.0
+           yj=(c(2,j)+c(2,j+1))/2.0
+           zj=(c(3,j)+c(3,j+1))/2.0
+           xj=dmod(xj,boxxsize)
+           if (xj.lt.0) xj=xj+boxxsize
+           yj=dmod(yj,boxysize)
+           if (yj.lt.0) yj=yj+boxysize
+           zj=dmod(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
+          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,j )
+          dyj = dc_norm( 2,j )
+          dzj = dc_norm( 3,j )
+          dscj_inv = vbld_inv(j+1)
+
+! Gay-berne var's
+          sig0ij = sigma_scpho(itypi )
+          chi1   = chi_scpho(itypi,1 )
+          chi2   = chi_scpho(itypi,2 )
+!          chi1=0.0d0
+!          chi2=0.0d0
+          chi12  = chi1 * chi2
+          chip1  = chipp_scpho(itypi,1 )
+          chip2  = chipp_scpho(itypi,2 )
+!          chip1=0.0d0
+!          chip2=0.0d0
+          chip12 = chip1 * chip2
+          chis1 = chis_scpho(itypi,1)
+          chis2 = chis_scpho(itypi,2)
+          chis12 = chis1 * chis2
+          sig1 = sigmap1_scpho(itypi)
+          sig2 = sigmap2_scpho(itypi)
+!       write (*,*) "sig1 = ", sig1
+!       write (*,*) "sig1 = ", sig1
+!       write (*,*) "sig2 = ", sig2
+! alpha factors from Fcav/Gcav
+          alf1   = 0.0d0
+          alf2   = 0.0d0
+          alf12  = 0.0d0
+          a12sq = rborn_scphoi(itypi) * rborn_scphoj(itypi)
+
+          b1 = alphasur_scpho(1,itypi)
+!          b1=0.0d0
+          b2 = alphasur_scpho(2,itypi)
+          b3 = alphasur_scpho(3,itypi)
+          b4 = alphasur_scpho(4,itypi)
+! used to determine whether we want to do quadrupole calculations
+! used by Fgb
+       eps_in = epsintab_scpho(itypi)
+       if (eps_in.eq.0.0) eps_in=1.0
+       eps_inout_fac = ( (1.0d0/eps_in) - (1.0d0/eps_out))
+!       write (*,*) "eps_inout_fac = ", eps_inout_fac
+!-------------------------------------------------------------------
+! tail location and distance calculations
+          d1i = dhead_scphoi(itypi) !this is shift of dipole/charge
+          d1j = 0.0
+       DO k = 1,3
+! location of polar head is computed by taking hydrophobic centre
+! and moving by a d1 * dc_norm vector
+! see unres publications for very informative images
+        chead(k,1) = c(k, i+nres) + d1i * dc_norm(k, i+nres)
+        chead(k,2) = (c(k, j) + c(k, j+1))/2.0
+! distance 
+!        Rsc_distance(k) = dabs(c(k, i+nres) - c(k, j+nres))
+!        Rsc(k) = Rsc_distance(k) * Rsc_distance(k)
+        Rhead_distance(k) = chead(k,2) - chead(k,1)
+       END DO
+! pitagoras (root of sum of squares)
+       Rhead = dsqrt( &
+          (Rhead_distance(1)*Rhead_distance(1)) &
+        + (Rhead_distance(2)*Rhead_distance(2)) &
+        + (Rhead_distance(3)*Rhead_distance(3)))
+       Rhead_sq=Rhead**2.0
+!-------------------------------------------------------------------
+! zero everything that should be zero'ed
+       evdwij = 0.0d0
+       ECL = 0.0d0
+       Elj = 0.0d0
+       Equad = 0.0d0
+       Epol = 0.0d0
+       Fcav=0.0d0
+       eheadtail = 0.0d0
+       dGCLdR=0.0d0
+       dGCLdOM1 = 0.0d0
+       dGCLdOM2 = 0.0d0
+       dGCLdOM12 = 0.0d0
+       dPOLdOM1 = 0.0d0
+       dPOLdOM2 = 0.0d0
+          Fcav = 0.0d0
+          dFdR = 0.0d0
+          dCAVdOM1  = 0.0d0
+          dCAVdOM2  = 0.0d0
+          dCAVdOM12 = 0.0d0
+          dscj_inv = vbld_inv(j+1)/2.0
+!dhead_scbasej(itypi,itypj)
+!          print *,i,j,dscj_inv,dsci_inv
+! rij holds 1/(distance of Calpha atoms)
+          rrij = 1.0D0 / ( xj*xj + yj*yj + zj*zj)
+          rij  = dsqrt(rrij)
+!----------------------------
+          CALL sc_angular
+! this should be in elgrad_init but om's are calculated by sc_angular
+! which in turn is used by older potentials
+! om = omega, sqom = om^2
+          sqom1  = om1 * om1
+          sqom2  = om2 * om2
+          sqom12 = om12 * om12
+
+! now we calculate EGB - Gey-Berne
+! It will be summed up in evdwij and saved in evdw
+          sigsq     = 1.0D0  / sigsq
+          sig       = sig0ij * dsqrt(sigsq)
+!          rij_shift = 1.0D0  / rij - sig + sig0ij
+          rij_shift = 1.0/rij - sig + sig0ij
+          IF (rij_shift.le.0.0D0) THEN
+           evdw = 1.0D20
+           RETURN
+          END IF
+          sigder = -sig * sigsq
+          rij_shift = 1.0D0 / rij_shift
+          fac       = rij_shift**expon
+          c1        = fac  * fac * aa_scpho(itypi)
+!          c1        = 0.0d0
+          c2        = fac  * bb_scpho(itypi)
+!          c2        = 0.0d0
+          evdwij    = eps1 * eps2rt * eps3rt * ( c1 + c2 )
+          eps2der   = eps3rt * evdwij
+          eps3der   = eps2rt * evdwij
+!          evdwij    = 4.0d0 * eps2rt * eps3rt * evdwij
+          evdwij    = eps2rt * eps3rt * evdwij
+          c1     = c1 * eps1 * eps2rt**2 * eps3rt**2
+          fac    = -expon * (c1 + evdwij) * rij_shift
+          sigder = fac * sigder
+!          fac    = rij * fac
+! Calculate distance derivative
+          gg(1) =  fac
+          gg(2) =  fac
+          gg(3) =  fac
+          fac = chis1 * sqom1 + chis2 * sqom2 &
+          - 2.0d0 * chis12 * om1 * om2 * om12
+! we will use pom later in Gcav, so dont mess with it!
+          pom = 1.0d0 - chis1 * chis2 * sqom12
+          Lambf = (1.0d0 - (fac / pom))
+          Lambf = dsqrt(Lambf)
+          sparrow = 1.0d0 / dsqrt(sig1**2.0d0 + sig2**2.0d0)
+!       write (*,*) "sparrow = ", sparrow
+          Chif = 1.0d0/rij * sparrow
+          ChiLambf = Chif * Lambf
+          eagle = dsqrt(ChiLambf)
+          bat = ChiLambf ** 11.0d0
+          top = b1 * ( eagle + b2 * ChiLambf - b3 )
+          bot = 1.0d0 + b4 * (ChiLambf ** 12.0d0)
+          botsq = bot * bot
+          Fcav = top / bot
+          dtop = b1 * ((Lambf / (2.0d0 * eagle)) + (b2 * Lambf))
+          dbot = 12.0d0 * b4 * bat * Lambf
+          dFdR = ((dtop * bot - top * dbot) / botsq) * sparrow
+!       dFdR = 0.0d0
+!      write (*,*) "dFcav/dR = ", dFdR
+          dtop = b1 * ((Chif / (2.0d0 * eagle)) + (b2 * Chif))
+          dbot = 12.0d0 * b4 * bat * Chif
+          eagle = Lambf * pom
+          dFdOM1  = -(chis1 * om1 - chis12 * om2 * om12) / (eagle)
+          dFdOM2  = -(chis2 * om2 - chis12 * om1 * om12) / (eagle)
+          dFdOM12 = chis12 * (chis1 * om1 * om12 - om2) &
+              * (chis2 * om2 * om12 - om1) / (eagle * pom)
+
+          dFdL = ((dtop * bot - top * dbot) / botsq)
+!       dFdL = 0.0d0
+          dCAVdOM1  = dFdL * ( dFdOM1 )
+          dCAVdOM2  = dFdL * ( dFdOM2 )
+          dCAVdOM12 = dFdL * ( dFdOM12 )
+
+          ertail(1) = xj*rij
+          ertail(2) = yj*rij
+          ertail(3) = zj*rij
+       DO k = 1, 3
+!      write (*,*) "Gvdwc(",k,",",i,")=", gvdwc(k,i)
+!      write (*,*) "Gvdwc(",k,",",j,")=", gvdwc(k,j)
+!         if (i.eq.3) print *,'decl0',gvdwx_scpho(k,i),i
+
+        pom = ertail(k)
+!        print *,pom,gg(k),dFdR
+!-facd1*(ertail(k)-erdxi*dC_norm(k,i+nres))
+        gvdwx_scpho(k,i) = gvdwx_scpho(k,i) &
+                  - (( dFdR + gg(k) ) * pom)
+!                 +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i)) &
+!                 +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
+!     &             - ( dFdR * pom )
+!        pom = ertail(k)
+!-facd2*(ertail(k)-erdxj*dC_norm(k,j+nres))
+!        gvdwx_scpho(k,j) = gvdwx_scpho(k,j) &
+!                  + (( dFdR + gg(k) ) * pom)
+!                 +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j)) &
+!                 +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
+!c!     &             + ( dFdR * pom )
+
+        gvdwc_scpho(k,i) = gvdwc_scpho(k,i) &
+                  - (( dFdR + gg(k) ) * ertail(k))
+!c!     &             - ( dFdR * ertail(k))
+
+        gvdwc_scpho(k,j) = gvdwc_scpho(k,j) &
+                  + (( dFdR + gg(k) ) * ertail(k))/2.0
+
+        gvdwc_scpho(k,j+1) = gvdwc_scpho(k,j+1) &
+                  + (( dFdR + gg(k) ) * ertail(k))/2.0
+
+!c!     &             + ( dFdR * ertail(k))
+
+        gg(k) = 0.0d0
+        ENDDO
+!c!      write (*,*) "Gvdwc(",k,",",i,")=", gvdwc(k,i)
+!c!      write (*,*) "Gvdwc(",k,",",j,")=", gvdwc(k,j)
+!      alphapol1 = alphapol_scpho(itypi)
+       if (wqq_scpho(itypi).ne.0.0) then
+       Qij=wqq_scpho(itypi)/eps_in
+       alpha_sco=1.d0/alphi_scpho(itypi)
+!       Qij=0.0
+       Ecl = (332.0d0 * Qij*dexp(-Rhead*alpha_sco)) / Rhead
+!c! derivative of Ecl is Gcl...
+       dGCLdR = (-332.0d0 * Qij*dexp(-Rhead*alpha_sco)*  &
+                (Rhead*alpha_sco+1) ) / Rhead_sq
+       if (energy_dec) write(iout,*) "ECL",ECL,Rhead,1.0/rij
+       else if (wqdip_scpho(2,itypi).gt.0.0d0) then
+       w1        = wqdip_scpho(1,itypi)
+       w2        = wqdip_scpho(2,itypi)
+!       w1=0.0d0
+!       w2=0.0d0
+!       pis       = sig0head_scbase(itypi,itypj)
+!       eps_head   = epshead_scbase(itypi,itypj)
+!c!-------------------------------------------------------------------
+
+!c!      R1     = dsqrt((Rtail**2)+((dtail(1,itypi,itypj)
+!c!     &        +dhead(1,1,itypi,itypj))**2))
+!c!      R2     = dsqrt((Rtail**2)+((dtail(2,itypi,itypj)
+!c!     &        +dhead(2,1,itypi,itypj))**2))
+
+!c!-------------------------------------------------------------------
+!c! ecl
+       sparrow  = w1  *  om1
+       hawk     = w2 *  (1.0d0 - sqom2)
+       Ecl = sparrow / Rhead**2.0d0 &
+           - hawk    / Rhead**4.0d0
+!c!-------------------------------------------------------------------
+       if (energy_dec) write(iout,*) "ECLdipdip",ECL,Rhead,&
+           1.0/rij,sparrow
+
+!c! derivative of ecl is Gcl
+!c! dF/dr part
+       dGCLdR  = - 2.0d0 * sparrow / Rhead**3.0d0 &
+                + 4.0d0 * hawk    / Rhead**5.0d0
+!c! dF/dom1
+       dGCLdOM1 = (w1) / (Rhead**2.0d0)
+!c! dF/dom2
+       dGCLdOM2 = (2.0d0 * w2 * om2) / (Rhead ** 4.0d0)
+       endif
+      
+!c--------------------------------------------------------------------
+!c Polarization energy
+!c Epol
+       R1 = 0.0d0
+       DO k = 1, 3
+!c! Calculate head-to-tail distances tail is center of side-chain
+        R1=R1+((c(k,j)+c(k,j+1))/2.0-chead(k,1))**2
+       END DO
+!c! Pitagoras
+       R1 = dsqrt(R1)
+
+      alphapol1 = alphapol_scpho(itypi)
+!      alphapol1=0.0
+       MomoFac1 = (1.0d0 - chi2 * sqom1)
+       RR1  = R1 * R1 / MomoFac1
+       ee1  = exp(-( RR1 / (4.0d0 * a12sq) ))
+!       print *,"ee1",ee1,a12sq,alphapol1,eps_inout_fac
+       fgb1 = sqrt( RR1 + a12sq * ee1)
+!       eps_inout_fac=0.0d0
+       epol = 332.0d0 * eps_inout_fac * (( alphapol1 / fgb1 )**4.0d0)
+! derivative of Epol is Gpol...
+       dPOLdFGB1 = -(1328.0d0 * eps_inout_fac * alphapol1 ** 4.0d0) &
+                / (fgb1 ** 5.0d0)
+       dFGBdR1 = ( (R1 / MomoFac1) &
+             * ( 2.0d0 - (0.5d0 * ee1) ) ) &
+             / ( 2.0d0 * fgb1 )
+       dFGBdOM2 = (((R1 * R1 * chi1 * om2) / (MomoFac1 * MomoFac1)) &
+               * (2.0d0 - 0.5d0 * ee1) ) &
+               / (2.0d0 * fgb1)
+       dPOLdR1 = dPOLdFGB1 * dFGBdR1
+!       dPOLdR1 = 0.0d0
+!       dPOLdOM1 = 0.0d0
+       dFGBdOM1 = (((R1 * R1 * chi2 * om1) / (MomoFac1 * MomoFac1)) &
+               * (2.0d0 - 0.5d0 * ee1) ) &
+               / (2.0d0 * fgb1)
+
+       dPOLdOM1 = dPOLdFGB1 * dFGBdOM1
+       dPOLdOM2 = 0.0
+       DO k = 1, 3
+        erhead(k) = Rhead_distance(k)/Rhead
+        erhead_tail(k,1) = (((c(k,j)+c(k,j+1))/2.0-chead(k,1))/R1)
+       END DO
+
+       erdxi = scalar( erhead(1), dC_norm(1,i+nres) )
+       erdxj = scalar( erhead(1), dC_norm(1,j) )
+       bat = scalar( erhead_tail(1,1), dC_norm(1,i+nres) )
+!       bat=0.0d0
+       federmaus = scalar(erhead_tail(1,1),dC_norm(1,j))
+       facd1 = d1i * vbld_inv(i+nres)
+       facd2 = d1j * vbld_inv(j)
+!       facd4 = dtail(2,itypi,itypj) * vbld_inv(j+nres)
+
+       DO k = 1, 3
+        hawk = (erhead_tail(k,1) + &
+        facd1 * (erhead_tail(k,1) - bat * dC_norm(k,i+nres)))
+!        facd1=0.0d0
+!        facd2=0.0d0
+!         if (i.eq.3) print *,'decl1',dGCLdR,dPOLdR1,gvdwc_scpho(k,i),i,&
+!                pom,(erhead_tail(k,1))
+
+!        print *,'decl',dGCLdR,dPOLdR1,gvdwc_scpho(k,i)
+        pom = erhead(k)+facd1*(erhead(k)-erdxi*dC_norm(k,i+nres))
+        gvdwx_scpho(k,i) = gvdwx_scpho(k,i)   &
+                   - dGCLdR * pom &
+                   - dPOLdR1 *  (erhead_tail(k,1))
+!     &             - dGLJdR * pom
+
+        pom = erhead(k)+facd2*(erhead(k)-erdxj*dC_norm(k,j))
+!        gvdwx_scpho(k,j) = gvdwx_scpho(k,j)    &
+!                   + dGCLdR * pom  &
+!                   + dPOLdR1 * (erhead_tail(k,1))
+!     &             + dGLJdR * pom
+
+
+        gvdwc_scpho(k,i) = gvdwc_scpho(k,i)  &
+                  - dGCLdR * erhead(k) &
+                  - dPOLdR1 * erhead_tail(k,1)
+!     &             - dGLJdR * erhead(k)
+
+        gvdwc_scpho(k,j) = gvdwc_scpho(k,j)         &
+                  + (dGCLdR * erhead(k)  &
+                  + dPOLdR1 * erhead_tail(k,1))/2.0
+        gvdwc_scpho(k,j+1) = gvdwc_scpho(k,j+1)         &
+                  + (dGCLdR * erhead(k)  &
+                  + dPOLdR1 * erhead_tail(k,1))/2.0
+
+!     &             + dGLJdR * erhead(k)
+!        if (i.eq.3) print *,'decl2',dGCLdR,dPOLdR1,gvdwc_scpho(k,i),i
+
+       END DO
+!       if (i.eq.3) print *,i,j,evdwij,epol,Fcav,ECL
+       if (energy_dec) write (iout,'(a22,2i5,4f8.3,f16.3)'), &
+        "escpho:evdw,pol,cav,CL",i,j,evdwij,epol,Fcav,ECL,escpho
+       escpho=escpho+evdwij+epol+Fcav+ECL
+       call sc_grad_scpho
+         enddo
+
+      enddo
+
+      return
+      end subroutine eprot_sc_phosphate
+      SUBROUTINE sc_grad_scpho
+      use calc_data
+
+       real (kind=8) :: dcosom1(3),dcosom2(3)
+       eom1  =    &
+              eps2der * eps2rt_om1   &
+            - 2.0D0 * alf1 * eps3der &
+            + sigder * sigsq_om1     &
+            + dCAVdOM1               &
+            + dGCLdOM1               &
+            + dPOLdOM1
+
+       eom2  =  &
+              eps2der * eps2rt_om2   &
+            + 2.0D0 * alf2 * eps3der &
+            + sigder * sigsq_om2     &
+            + dCAVdOM2               &
+            + dGCLdOM2               &
+            + dPOLdOM2
+
+       eom12 =    &
+              evdwij  * eps1_om12     &
+            + eps2der * eps2rt_om12   &
+            - 2.0D0 * alf12 * eps3der &
+            + sigder *sigsq_om12      &
+            + dCAVdOM12               &
+            + dGCLdOM12
+!        om12=0.0
+!        eom12=0.0
+!       print *,eom1,eom2,eom12,om12,i,j,"eom1,2,12",erij(1),erij(2),erij(3)
+!        if (i.eq.30) print *,gvdwc_scpho(k,i),- gg(k),&
+!                 (-eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,i)))&
+!                 *dsci_inv*2.0
+!       print *,dsci_inv,dscj_inv,dc_norm(2,nres+j),dc_norm(2,nres+i),&
+!               gg(1),gg(2),"rozne"
+       DO k = 1, 3
+        dcosom1(k) = rij * (dc_norm(k,nres+i) - om1 * erij(k))
+        dcosom2(k) = rij * (dc_norm(k,j) - om2 * erij(k))
+        gg(k) = gg(k) + eom1 * dcosom1(k) + eom2 * dcosom2(k)
+        gvdwc_scpho(k,j)= gvdwc_scpho(k,j) +0.5*( gg(k))   &
+                 + (-eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,j)))&
+                 *dscj_inv*2.0 &
+                 - (eom2*(erij(k)-om2*dc_norm(k,j)))*dscj_inv*2.0
+        gvdwc_scpho(k,j+1)= gvdwc_scpho(k,j+1) +0.5*( gg(k))   &
+                 - (-eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,j))) &
+                 *dscj_inv*2.0 &
+                 + (eom2*(erij(k)-om2*dc_norm(k,j)))*dscj_inv*2.0
+        gvdwx_scpho(k,i)= gvdwx_scpho(k,i) - gg(k)   &
+                 + (eom12*(dc_norm(k,j)-om12*dc_norm(k,nres+i)) &
+                 + eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
+
+!         print *,eom12,eom2,om12,om2
+!eom12*(-dc_norm(k,i)/2.0-om12*dc_norm(k,nres+j)),&
+!                (eom2*(erij(k)-om2*dc_norm(k,nres+j)))
+!        gvdwx_scpho(k,j)= gvdwx_scpho(k,j) + gg(k)  &
+!                 + (eom12*(dc_norm(k,i)-om12*dc_norm(k,nres+j))&
+!                 + eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
+        gvdwc_scpho(k,i)=gvdwc_scpho(k,i)-gg(k)
+       END DO
+       RETURN
+      END SUBROUTINE sc_grad_scpho
+      subroutine eprot_pep_phosphate(epeppho)
+      use calc_data
+!      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.NAMES'
+!      include 'COMMON.INTERACT'
+!      include 'COMMON.IOUNITS'
+!      include 'COMMON.CALC'
+!      include 'COMMON.CONTROL'
+!      include 'COMMON.SBRIDGE'
+      logical :: lprn
+!el local variables
+      integer :: iint,itypi,itypi1,itypj,subchap
+      real(kind=8) :: rrij,xi,yi,zi,sig,rij_shift,fac,e1,e2,sigm,epsi
+      real(kind=8) :: evdw,sig0ij
+      real(kind=8) :: xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,&
+                    dist_temp, dist_init,aa,bb,ssgradlipi,ssgradlipj, &
+                    sslipi,sslipj,faclip
+      integer :: ii
+      real(kind=8) :: fracinbuf
+       real (kind=8) :: epeppho
+       real (kind=8),dimension(4):: ener
+       real(kind=8) :: b1,b2,b3,b4,egb,eps_in,eps_inout_fac,eps_out
+       real(kind=8) :: ECL,Elj,Equad,Epol,eheadtail,rhead,dGCLOM2,&
+        sqom1,sqom2,sqom12,c1,c2,pom,Lambf,sparrow,&
+        Chif,ChiLambf,bat,eagle,top,bot,botsq,Fcav,dtop,dFdR,dFdOM1,&
+        dFdOM2,w1,w2,dGCLdR,dFdL,dFdOM12,dbot ,&
+        r1,eps_head,alphapol1,pis,facd2,d2,facd1,d1,erdxj,erdxi,federmaus,&
+        dPOLdR1,dFGBdOM2,dFGBdR1,dPOLdFGB1,RR1,MomoFac1,hawk,d1i,d1j,&
+        sig1,sig2,chis12,chis2,ee1,fgb1,a12sq,chis1,Rhead_sq,Qij,dFGBdOM1
+       real(kind=8),dimension(3,2)::chead,erhead_tail
+       real(kind=8),dimension(3) :: Rhead_distance,ertail,erhead
+       integer troll
+       real (kind=8) :: dcosom1(3),dcosom2(3)
+       epeppho=0.0d0
+!       do i=1,nres_molec(1)
+        do i=ibond_start,ibond_end
+        if (itype(i,1).eq.ntyp1_molec(1)) cycle
+        itypi  = itype(i,1)
+        dsci_inv = vbld_inv(i+1)/2.0
+        dxi    = dc_norm(1,i)
+        dyi    = dc_norm(2,i)
+        dzi    = dc_norm(3,i)
+        xi=(c(1,i)+c(1,i+1))/2.0
+        yi=(c(2,i)+c(2,i+1))/2.0
+        zi=(c(3,i)+c(3,i+1))/2.0
+        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 j=nres_molec(1)+1,nres_molec(2)+nres_molec(1)-1
+           itypj= itype(j,2)
+           if ((itype(j,2).eq.ntyp1_molec(2)).or.&
+            (itype(j+1,2).eq.ntyp1_molec(2))) cycle
+           xj=(c(1,j)+c(1,j+1))/2.0
+           yj=(c(2,j)+c(2,j+1))/2.0
+           zj=(c(3,j)+c(3,j+1))/2.0
+           xj=dmod(xj,boxxsize)
+           if (xj.lt.0) xj=xj+boxxsize
+           yj=dmod(yj,boxysize)
+           if (yj.lt.0) yj=yj+boxysize
+           zj=dmod(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
+          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)
+          rij  = dsqrt(rrij)
+          dxj = dc_norm( 1,j )
+          dyj = dc_norm( 2,j )
+          dzj = dc_norm( 3,j )
+          dscj_inv = vbld_inv(j+1)/2.0
+! Gay-berne var's
+          sig0ij = sigma_peppho
+          chi1=0.0d0
+          chi2=0.0d0
+          chi12  = chi1 * chi2
+          chip1=0.0d0
+          chip2=0.0d0
+          chip12 = chip1 * chip2
+          chis1 = 0.0d0
+          chis2 = 0.0d0
+          chis12 = chis1 * chis2
+          sig1 = sigmap1_peppho
+          sig2 = sigmap2_peppho
+!       write (*,*) "sig1 = ", sig1
+!       write (*,*) "sig1 = ", sig1
+!       write (*,*) "sig2 = ", sig2
+! alpha factors from Fcav/Gcav
+          alf1   = 0.0d0
+          alf2   = 0.0d0
+          alf12  = 0.0d0
+          b1 = alphasur_peppho(1)
+!          b1=0.0d0
+          b2 = alphasur_peppho(2)
+          b3 = alphasur_peppho(3)
+          b4 = alphasur_peppho(4)
+          CALL sc_angular
+       sqom1=om1*om1
+       evdwij = 0.0d0
+       ECL = 0.0d0
+       Elj = 0.0d0
+       Equad = 0.0d0
+       Epol = 0.0d0
+       Fcav=0.0d0
+       eheadtail = 0.0d0
+       dGCLdR=0.0d0
+       dGCLdOM1 = 0.0d0
+       dGCLdOM2 = 0.0d0
+       dGCLdOM12 = 0.0d0
+       dPOLdOM1 = 0.0d0
+       dPOLdOM2 = 0.0d0
+          Fcav = 0.0d0
+          dFdR = 0.0d0
+          dCAVdOM1  = 0.0d0
+          dCAVdOM2  = 0.0d0
+          dCAVdOM12 = 0.0d0
+          rij_shift = rij 
+          fac       = rij_shift**expon
+          c1        = fac  * fac * aa_peppho
+!          c1        = 0.0d0
+          c2        = fac  * bb_peppho
+!          c2        = 0.0d0
+          evdwij    =  c1 + c2 
+! Now cavity....................
+       eagle = dsqrt(1.0/rij_shift)
+       top = b1 * ( eagle + b2 * 1.0/rij_shift - b3 )
+          bot = 1.0d0 + b4 * (1.0/rij_shift ** 12.0d0)
+          botsq = bot * bot
+          Fcav = top / bot
+          dtop = b1 * ((1.0/ (2.0d0 * eagle)) + (b2))
+          dbot = 12.0d0 * b4 * (1.0/rij_shift) ** 11.0d0
+          dFdR = ((dtop * bot - top * dbot) / botsq)
+       w1        = wqdip_peppho(1)
+       w2        = wqdip_peppho(2)
+!       w1=0.0d0
+!       w2=0.0d0
+!       pis       = sig0head_scbase(itypi,itypj)
+!       eps_head   = epshead_scbase(itypi,itypj)
+!c!-------------------------------------------------------------------
+
+!c!      R1     = dsqrt((Rtail**2)+((dtail(1,itypi,itypj)
+!c!     &        +dhead(1,1,itypi,itypj))**2))
+!c!      R2     = dsqrt((Rtail**2)+((dtail(2,itypi,itypj)
+!c!     &        +dhead(2,1,itypi,itypj))**2))
+
+!c!-------------------------------------------------------------------
+!c! ecl
+       sparrow  = w1  *  om1
+       hawk     = w2 *  (1.0d0 - sqom1)
+       Ecl = sparrow * rij_shift**2.0d0 &
+           - hawk    * rij_shift**4.0d0
+!c!-------------------------------------------------------------------
+!c! derivative of ecl is Gcl
+!c! dF/dr part
+!       rij_shift=5.0
+       dGCLdR  = - 2.0d0 * sparrow * rij_shift**3.0d0 &
+                + 4.0d0 * hawk    * rij_shift**5.0d0
+!c! dF/dom1
+       dGCLdOM1 = (w1) * (rij_shift**2.0d0)
+!c! dF/dom2
+       dGCLdOM2 = (2.0d0 * w2 * om1) * (rij_shift ** 4.0d0)
+       eom1  =    dGCLdOM1+dGCLdOM2 
+       eom2  =    0.0               
+       
+          fac    = -expon * (c1 + evdwij) * rij_shift+dFdR+dGCLdR 
+!          fac=0.0
+          gg(1) =  fac*xj*rij
+          gg(2) =  fac*yj*rij
+          gg(3) =  fac*zj*rij
+         do k=1,3
+         gvdwc_peppho(k,j) = gvdwc_peppho(k,j) +gg(k)/2.0
+         gvdwc_peppho(k,j+1) = gvdwc_peppho(k,j+1) +gg(k)/2.0
+         gvdwc_peppho(k,i) = gvdwc_peppho(k,i) -gg(k)/2.0
+         gvdwc_peppho(k,i+1) = gvdwc_peppho(k,i+1) -gg(k)/2.0
+         gg(k)=0.0
+         enddo
+
+      DO k = 1, 3
+        dcosom1(k) = rij* (dc_norm(k,i) - om1 * erij(k))
+        dcosom2(k) = rij* (dc_norm(k,j) - om2 * erij(k))
+        gg(k) = gg(k) + eom1 * dcosom1(k)! + eom2 * dcosom2(k)
+        gvdwc_peppho(k,j)= gvdwc_peppho(k,j)        +0.5*( gg(k))   !&
+!                 - (eom2*(erij(k)-om2*dc_norm(k,j)))*dscj_inv*2.0
+        gvdwc_peppho(k,j+1)= gvdwc_peppho(k,j+1)    +0.5*( gg(k))   !&
+!                 + (eom2*(erij(k)-om2*dc_norm(k,j)))*dscj_inv*2.0
+        gvdwc_peppho(k,i)= gvdwc_peppho(k,i)     -0.5*( gg(k))   &
+                 - (eom1*(erij(k)-om1*dc_norm(k,i)))*dsci_inv*2.0
+        gvdwc_peppho(k,i+1)= gvdwc_peppho(k,i+1) - 0.5*( gg(k))  &
+                 + (eom1*(erij(k)-om1*dc_norm(k,i)))*dsci_inv*2.0
+        enddo
+       epeppho=epeppho+evdwij+Fcav+ECL
+!          print *,i,j,evdwij,Fcav,ECL,rij_shift
+       enddo
+       enddo
+      end subroutine eprot_pep_phosphate
       end module energy
       end module energy