MPI shield
[unres4.git] / source / unres / data / energy_data.f90
index 8807974..5f340cf 100644 (file)
@@ -3,7 +3,7 @@
       use names
 !-----------------------------------------------------------------------------
 ! Max. number of energy intervals
-      integer,parameter :: max_ene=21 !10
+      integer,parameter :: max_ene=49 !10
 !-----------------------------------------------------------------------------
 ! Maximum number of terms in SC bond-stretching potential
       integer,parameter :: maxbondterm=3
@@ -14,6 +14,7 @@
 !-----------------------------------------------------------------------------
 ! Max. number of contacts per residue
       integer :: maxconts
+      integer,parameter :: maxcontsshi=50
 !-----------------------------------------------------------------------------
 ! Max. number of SC contacts
       integer :: maxcont
@@ -67,7 +68,7 @@
        wturn6,wvdwpp,wliptran,wshield,lipscale,wtube, &
        wbond_nucl,wang_nucl,wcorr_nucl,wcorr3_nucl,welpp,wtor_nucl,&
        wtor_d_nucl,welsb,wsbloc,wvdwsb,welpsb,wvdwpp_nucl,wvdwpsb,wcatprot,&
-       wcatcat
+       wcatcat,wscbase,wpepbase,wscpho,wpeppho
 #ifdef CLUSTER
       real(kind=8) :: scalscp
 #endif
       integer :: nthetyp,ntheterm,ntheterm2,ntheterm3,nsingle,&
        ndouble,nntheterm
       integer,dimension(:),allocatable :: ithetyp !(-ntyp1:ntyp1)
+      integer,dimension(:,:),allocatable :: nstate !(-ntyp1:ntyp1)
       real(kind=8),dimension(:,:,:,:),allocatable :: aa0thet
 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
       real(kind=8),dimension(:,:,:,:,:),allocatable :: aathet
       integer,dimension(:),allocatable :: idih_constr,idih_nconstr,itheta_constr !(maxdih_constr)
       integer :: idihconstr_start,idihconstr_end, &
        ithetaconstr_start,ithetaconstr_end
-      real(kind=8) :: ftors
+!      real(kind=8) :: ftors
       real(kind=8),dimension(:),allocatable :: drange,theta_constr0,theta_drange !(maxdih_constr)
-      real(kind=8),dimension(:),allocatable :: phi0 !(maxdih_constr)
+      real(kind=8),dimension(:),allocatable :: phi0,ftors !(maxdih_constr)
       real(kind=8),dimension(:),allocatable :: for_thet_constr !(maxdih_constr)
 
 !-----------------------------------------------------------------------------
       integer :: nloctyp
 !      common/fourier/  z wham
       real(kind=8),dimension(:,:),allocatable :: b !(13,0:maxtor)
+!---------------MOMO---------------------------------------------------
+        integer,dimension(:),allocatable :: icharge
+        real(kind=8),dimension(:,:),allocatable :: alphapol,epshead,&
+           sig0head,sigiso1,sigiso2,rborn,sigmap1,sigmap2,chis,wquad,chipp,&
+           epsintab
+        real(kind=8),dimension(:,:,:),allocatable :: alphasur,alphiso,&
+           wqdip,wstate,dtail
+         real(kind=8),dimension(:,:,:,:),allocatable :: dhead
 !-----------------------------------------------------------------------------
 ! 24 Apr 2017 
 ! Varibles for cutoff on electorstatic
       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
+
+        real(kind=8),dimension(:), allocatable ::  eps_scpho, &
+        sigma_scpho,                         &
+        sigmap1_scpho,sigmap2_scpho,&
+        aa_scpho,bb_scpho,wqq_scpho,epsintab_scpho,alphapol_scpho,&
+        rborn_scphoi,rborn_scphoj,dhead_scphoi,alphi_scpho
+
+         real(kind=8),dimension(:,:), allocatable :: alphasur_scpho, &
+        chi_scpho,chipp_scpho,chis_scpho,              &
+        wqdip_scpho
+         real(kind=8) ,dimension(4) :: alphasur_peppho
+         real(kind=8) ,dimension(2) :: wqdip_peppho
+         real(kind=8) :: eps_peppho,sigma_peppho,sigmap1_peppho,sigmap2_peppho, &
+         aa_peppho,bb_peppho
       end module energy_data