working base with peptide group
[unres4.git] / source / unres / data / energy_data.f90
index 44e3d30..89d4682 100644 (file)
@@ -66,7 +66,8 @@
        wscloc,wcorr,wcorr4,wcorr5,wcorr6,wsccor,wel_loc,wturn3,wturn4,&
        wturn6,wvdwpp,wliptran,wshield,lipscale,wtube, &
        wbond_nucl,wang_nucl,wcorr_nucl,wcorr3_nucl,welpp,wtor_nucl,&
-       wtor_d_nucl,welsb,wsbloc,wvdwsb,welpsb,wvdwpsb
+       wtor_d_nucl,welsb,wsbloc,wvdwsb,welpsb,wvdwpp_nucl,wvdwpsb,wcatprot,&
+       wcatcat,wscbase,wpepbase
 #ifdef CLUSTER
       real(kind=8) :: scalscp
 #endif
       real(kind=8),dimension(:,:),allocatable :: ael6_nucl,&
         ael3_nucl,ael32_nucl,ael63_nucl
       integer :: expon,expon2, nnt,nct,itypro
+      integer,dimension(5) :: nnt_molec,nct_molec
       integer,dimension(:,:),allocatable :: istart,iend !(maxres,maxint_gr)
       integer,dimension(:),allocatable :: nint_gr,itel,&
        ielstart,ielend,ielstart_vdw,ielend_vdw,nscp_gr !(maxres)
        ilip_start,ilip_end,itube_start,itube_end
       integer :: ibond_nucl_start,ibond_nucl_end,iphi_nucl_start,&
        iphi_nucl_end,iphid_nucl_start,iphid_nucl_end,& 
-       ibondp_nucl_start,ibondp_nucl_end,ithet_nucl_start,ithet_nucl_end
+       ibondp_nucl_start,ibondp_nucl_end,ithet_nucl_start,ithet_nucl_end,&
+        loc_start_nucl,loc_end_nucl
       integer,dimension(:),allocatable :: ibond_displ,ibond_count,&
        ithet_displ,ithet_count,iphi_displ,iphi_count,iphi1_displ,&
        iphi1_count,ivec_displ,ivec_count,iset_displ,iset_count,&
 ! Parameters of the SC rotamers (local) term
 !      common/scrot/
       real(kind=8),dimension(:,:),allocatable :: sc_parmin !(maxsccoef,ntyp)
+      real(kind=8),dimension(:,:),allocatable :: sc_parmin_nucl !(maxsccoef,ntyp)
+
 !-----------------------------------------------------------------------------
 ! common.torcnstr
 !      common /torcnstr/
 ! AFM
        real(kind=8) :: distafminit,forceAFMconst,velAFMconst
       integer :: afmend,afmbeg
+      real(kind=8),dimension(:,:), allocatable :: catprm
 
+         real(kind=8),dimension(:,:), allocatable ::  eps_scbase, &
+        sigma_scbase,                         &
+        sigmap1_scbase,sigmap2_scbase,        &
+        dhead_scbasei, dhead_scbasej, epshead_scbase,&
+        sig0head_scbase,  rborn_scbasei,rborn_scbasej,alphapol_scbase,epsintab_scbase,&
+        aa_scbase,bb_scbase
+         real(kind=8),dimension(:,:,:), allocatable :: alphasur_scbase, &
+        wdipdip_scbase,wqdip_scbase,chi_scbase,chipp_scbase,chis_scbase
 
+        real(kind=8),dimension(:), allocatable ::  eps_pepbase, &
+        sigma_pepbase,                         &
+        sigmap1_pepbase,sigmap2_pepbase,&
+        aa_pepbase,bb_pepbase
 
+         real(kind=8),dimension(:,:), allocatable :: alphasur_pepbase, &
+        wdipdip_pepbase,chi_pepbase,chipp_pepbase,chis_pepbase
 
       end module energy_data