X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2Fdata%2Fenergy_data.f90;h=a26a0aa352549df91465e9894a7ee179ed502d9a;hb=4baa9e481f53d4c89b076f3aece756fc47282649;hp=44e3d3052ec05a42eadcd40b27d6065407c7f27e;hpb=04d0eb23476c67cc0cadc32bf09aa91c03e2dc15;p=unres4.git diff --git a/source/unres/data/energy_data.f90 b/source/unres/data/energy_data.f90 index 44e3d30..a26a0aa 100644 --- a/source/unres/data/energy_data.f90 +++ b/source/unres/data/energy_data.f90 @@ -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 @@ -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,wscpho,wpeppho #ifdef CLUSTER real(kind=8) :: scalscp #endif @@ -104,6 +105,7 @@ 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) @@ -208,7 +210,8 @@ 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,& @@ -262,6 +265,8 @@ ! 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/ @@ -269,9 +274,9 @@ 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) !----------------------------------------------------------------------------- @@ -332,8 +337,36 @@ ! 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 + 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