module energy_data !----------------------------------------------------------------------------- use names !----------------------------------------------------------------------------- ! Max. number of energy intervals integer,parameter :: max_ene=49 !10 !----------------------------------------------------------------------------- ! Maximum number of terms in SC bond-stretching potential integer,parameter :: maxbondterm=3 !----------------------------------------------------------------------------- ! Max. number of derivatives of virtual-bond and side-chain vectors in theta ! or phi. integer :: maxdim !----------------------------------------------------------------------------- ! Max. number of contacts per residue integer :: maxconts integer,parameter :: maxcontsshi=50 !----------------------------------------------------------------------------- ! Max. number of SC contacts integer :: maxcont ! Maximum number of valence and torsional in rigorous approach integer,parameter :: maxtor_kcc=6 integer,parameter :: maxval_kcc=6 integer,parameter :: maxang_kcc=36 !----------------------------------------------------------------------------- ! commom.contacts ! common /contacts/ integer :: ncont,ncont_ref integer,dimension(:,:),allocatable :: icont,icont_ref !(2,maxcont) !#ifdef WHAM_RUN ! integer,dimension(:),allocatable :: nsccont_frag_ref !(mmaxfrag) !wham ! integer,dimension(:,:,:),allocatable :: isccont_frag_ref !(2,maxcont,mmaxfrag) !wham !#endif ! 12/13/2008 (again Poland-Jaruzel war anniversary) ! RE: Parallelization of 4th and higher order loc-el correlations ! common /contdistrib/ integer,dimension(:),allocatable :: iat_sent !(maxres) ! iat_sent - zainicjowane w initialize_p.F; integer,dimension(:,:,:),allocatable :: iint_sent,iint_sent_local !(4,maxres,maxres) integer,dimension(:,:),allocatable :: iturn3_sent,iturn4_sent,& iturn3_sent_local,iturn4_sent_local !(4,maxres), integer,dimension(:),allocatable :: itask_cont_from,itask_cont_to !(0:max_fg_procs-1), integer :: nat_sent,ntask_cont_from,ntask_cont_to !----------------------------------------------------------------------------- ! commom.deriv; ! common /derivat/ real(kind=8),dimension(:,:),allocatable :: dcdv,dxdv !(6,maxdim) real(kind=8),dimension(:,:),allocatable :: dxds !(6,maxres) real(kind=8),dimension(:,:,:),allocatable :: gradx,gradc !(3,maxres,2) real(kind=8),dimension(:,:),allocatable :: gvdwx !(3,maxres) real(kind=8),dimension(:,:),allocatable :: gloc,gloc_x !(maxvar,2) ,gloc_x !!! nie używane real(kind=8),dimension(:,:,:),allocatable :: dtheta !(3,2,maxres) real(kind=8),dimension(:,:,:),allocatable :: dphi,dalpha,domega !(3,3,maxres) integer :: nfl,icg ! common /derivat/ wham logical :: calc_grad ! common /mpgrad/ integer :: igrad_start,igrad_end integer,dimension(:),allocatable :: jgrad_start,jgrad_end !(maxres) !----------------------------------------------------------------------------- ! The following COMMON block selects the type of the force field used in ! calculations and defines weights of various energy terms. ! 12/1/95 wcorr added !----------------------------------------------------------------------------- ! common.ffield ! common /ffield/ integer :: n_ene_comp integer :: rescale_mode real(kind=8) :: wsc,wscp,welec,wbond,wstrain,wtor,wtor_d,wang,& 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,wvdwpp_nucl,wvdwpsb,wcatprot,& wcatcat,wscbase,wpepbase,wscpho,wpeppho,wdihc #ifdef CLUSTER real(kind=8) :: scalscp #endif real(kind=8),dimension(:),allocatable :: weights !(n_ene) real(kind=8) :: temp0,scal14,cutoff_corr,delt_corr,r0_corr integer :: ipot,ipot_nucl ! common /potentials/ character(len=3),dimension(5) :: potname = & (/'LJ ','LJK','BP ','GB ','GBV'/) !----------------------------------------------------------------------------- ! wlong,welec,wtor,wang,wscloc are the weight of the energy terms ! corresponding to side-chain, electrostatic, torsional, valence-angle, ! and local side-chain terms. ! ! IPOT determines which SC...SC interaction potential will be used: ! 1 - LJ: 2n-n Lennard-Jones ! 2 - LJK: 2n-n Kihara type (shifted Lennard-Jones) ! 3 - BP; Berne-Pechukas (angular dependence) ! 4 - GB; Gay-Berne (angular dependence) ! 5 - GBV; Gay-Berne-Vorobjev; angularly-dependent Kihara potential !----------------------------------------------------------------------------- ! common.interact ! common /interact/ real(kind=8),dimension(:,:),allocatable :: aa_aq,bb_aq,augm,aa_lip,bb_lip !(ntyp,ntyp) real(kind=8),dimension(:),allocatable :: sc_aa_tube_par,sc_bb_tube_par,& acavtub,bcavtub,ccavtub,dcavtub,tubetranene real(kind=8),dimension(:,:),allocatable :: aa_nucl,bb_nucl real(kind=8) :: acavtubpep,bcavtubpep,ccavtubpep,dcavtubpep, & tubetranenepep,pep_aa_tube,pep_bb_tube,tubeR0 real(kind=8),dimension(3) :: tubecenter real(kind=8),dimension(:,:),allocatable :: aad,bad !(ntyp,2) real(kind=8),dimension(2,2) :: app,bpp,ael6,ael3 real(kind=8),dimension(:),allocatable :: aad_nucl,bad_nucl !(ntyp,2) real(kind=8),dimension(2,2) :: app_nucl,bpp_nucl 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) integer,dimension(:,:),allocatable :: istart_nucl,iend_nucl !(maxres,maxint_gr) integer,dimension(:),allocatable :: nint_gr_nucl,itel_nucl,& ielstart_nucl,ielend_nucl,ielstart_vdw_nucl,ielend_vdw_nucl,nscp_gr_nucl !(maxres) integer,dimension(:,:),allocatable :: iscpstart_nucl,iscpend_nucl !(maxres,maxint_gr) integer,dimension(:),allocatable :: istype,molnum integer,dimension(:,:),allocatable :: itype ! now itype has more molecule types integer,dimension(:,:),allocatable :: iscpstart,iscpend !(maxres,maxint_gr) integer :: iatsc_s,iatsc_e,iatel_s,iatel_e,iatel_s_vdw,& iatel_e_vdw,iatscp_s,iatscp_e,ispp,iscp integer :: iatsc_s_nucl,iatsc_e_nucl,iatel_s_nucl,iatel_e_nucl,& iatel_s_vdw_nucl,iatel_e_vdw_nucl,iatscp_s_nucl,iatscp_e_nucl,& ispp_nucl,iscp_nucl ! 12/1/95 Array EPS included in the COMMON block. ! common /body/ real(kind=8),dimension(:,:),allocatable :: sigma !(0:ntyp1,0:ntyp1) real(kind=8),dimension(:,:),allocatable :: eps,epslip,sigmaii,& rs0,chi,r0,r0e !(ntyp,ntyp) r0e !!! nie używane real(kind=8),dimension(:),allocatable :: chip,alp,sigma0,& sigii,rr0 !(ntyp) real(kind=8),dimension(2,2) :: rpp,epp,elpp6,elpp3 real(kind=8),dimension(:,:),allocatable :: sigma_nucl !(0:ntyp1,0:ntyp1) real(kind=8),dimension(:,:),allocatable :: eps_nucl,sigmaii_nucl,& chi_nucl,r0_nucl, chip_nucl !(ntyp,ntyp) r0e !!! nie używane real(kind=8),dimension(:),allocatable :: alp_nucl,sigma0_nucl,& sigii_nucl,rr0_nucl !(ntyp) real(kind=8),dimension(2,2) :: rpp_nucl,epp_nucl real(kind=8),dimension(:,:),allocatable ::elpp6_nucl,& elpp3_nucl,elpp32_nucl,elpp63_nucl real(kind=8):: r0pp,epspp,AEES,BEES real(kind=8),dimension(:,:),allocatable :: r0d,eps_scp,rscp !(ntyp,2) r0d !!! nie używane real(kind=8),dimension(:),allocatable :: eps_scp_nucl,rscp_nucl!(ntyp,2) r0d !!! nie używane ! 12/5/03 modified 09/18/03 Bond stretching parameters. ! common /stretch/ real(kind=8) :: vbldp0,akp,distchainmax,vbldpDUM real(kind=8),dimension(:,:),allocatable :: vbldsc0,aksc,abond0 !(maxbondterm,ntyp) real(kind=8) :: vbldp0_nucl,akp_nucl real(kind=8),dimension(:,:),allocatable :: vbldsc0_nucl,& aksc_nucl,abond0_nucl !(maxbondterm,ntyp) integer,dimension(:),allocatable :: nbondterm !(ntyp) integer,dimension(:),allocatable :: nbondterm_nucl !(ntyp) !----------------------------------------------------------------------------- ! common.local ! Parameters of ab initio-derived potential of virtual-bond-angle bending ! common /theta_abinitio/ 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 real(kind=8),dimension(:,:,:,:,:,:),allocatable :: bbthet,& ccthet,ddthet,eethet !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2) real(kind=8),dimension(:,:,:,:,:,:,:),allocatable :: ffthet,ggthet !-----------nucleic acid parameters-------------------------- integer :: nthetyp_nucl,ntheterm_nucl,ntheterm2_nucl,& ntheterm3_nucl,nsingle_nucl,& ndouble_nucl,nntheterm_nucl integer,dimension(:),allocatable :: ithetyp_nucl !(-ntyp1:ntyp1) real(kind=8),dimension(:,:,:),allocatable :: aa0thet_nucl !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2) real(kind=8),dimension(:,:,:,:),allocatable :: aathet_nucl real(kind=8),dimension(:,:,:,:,:),allocatable :: bbthet_nucl,& ccthet_nucl,ddthet_nucl,eethet_nucl !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2) real(kind=8),dimension(:,:,:,:,:,:),allocatable :: ffthet_nucl,ggthet_nucl !(maxdouble,maxdouble,maxtheterm3,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2) ! Parameters of the virtual-bond-angle probability distribution ! common /thetas/ real(kind=8),dimension(:),allocatable :: a0thet,theta0,& sig0,sigc0 !(-ntyp:ntyp) real(kind=8),dimension(:,:,:,:),allocatable :: athet,bthet !(2,-ntyp:ntyp,-1:1,-1:1) real(kind=8),dimension(:,:),allocatable :: polthet !(0:3,-ntyp:ntyp) real(kind=8),dimension(:,:),allocatable :: gthet !(3,-ntyp:ntyp) ! Parameters of the side-chain probability distribution ! common /sclocal/ real(kind=8),dimension(:),allocatable :: dsc,dsc_inv,dsc0 !(ntyp1) real(kind=8),dimension(:,:),allocatable :: bsc !(maxlob,ntyp) real(kind=8),dimension(:,:,:),allocatable :: censc !(3,maxlob,-ntyp:ntyp) real(kind=8),dimension(:,:,:,:),allocatable :: gaussc !(3,3,maxlob,-ntyp:ntyp) integer,dimension(:),allocatable :: nlob !(ntyp1) ! Virtual-bond lenghts ! common /peptbond/ real(kind=8) :: vbl,vblinv,vblinv2,vbl_cis,vbl0 ! common /indices/ integer :: loc_start,loc_end,ithet_start,ithet_end,iphi_start,& iphi_end,iphid_start,iphid_end,ibond_start,ibond_end,& ibondp_start,ibondp_end,ivec_start,ivec_end,iset_start,iset_end,& iturn3_start,iturn3_end,iturn4_start,iturn4_end,iint_start,& iint_end,iphi1_start,iphi1_end,itau_start,itau_end,& 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,& 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,& iint_count,iint_displ !(0:max_fg_procs-1) !----------------------------------------------------------------------------- ! common.MD ! common /mdgrad/ real(kind=8),dimension(:,:),allocatable :: gcart,gxcart !(3,0:MAXRES) real(kind=8),dimension(:,:),allocatable :: gradcag,gradxag !(3,MAXRES) !!! nie używane ! common /back_constr/ integer :: nfrag_back real(kind=8) :: uconst_back real(kind=8),dimension(:),allocatable :: utheta,ugamma,uscdiff !(maxfrag_back) real(kind=8),dimension(:,:,:),allocatable :: wfrag_back !(3,maxfrag_back,maxprocs/20) integer,dimension(:,:,:),allocatable :: ifrag_back !(3,maxfrag_back,maxprocs/20) ! common /qmeas/ in module geometry !----------------------------------------------------------------------------- ! common.sbridge ! common /sbridge/ real(kind=8) :: ss_depth,ebr,d0cm,akcm,akth,akct,v1ss,v2ss,v3ss integer :: ns,nss,nfree integer,dimension(:),allocatable :: iss !(maxss) ! common /links/ real(kind=8),dimension(:),allocatable :: dhpb,forcon,dhpb1,fordepth !(maxdim) !el dhpb1 !!! nie używane integer :: nhpb integer,dimension(:),allocatable :: ihpb,jhpb,ibecarb !(maxdim) !el ibecarb !!! nie używane ! common /restraints/ real(kind=8) :: weidis ! common /links_split/ integer :: link_start,link_end ! common /dyn_ssbond/ real(kind=8) :: Ht,atriss,btriss,ctriss,dtriss integer,dimension(:),allocatable :: idssb,jdssb !(maxdim) logical :: dyn_ss logical,dimension(:),allocatable :: dyn_ss_mask !(maxres) !----------------------------------------------------------------------------- ! common.sccor ! Parameters of the SCCOR term ! common/sccor/ real(kind=8),dimension(:,:,:,:),allocatable :: v1sccor,v2sccor !(maxterm_sccor,3,-ntyp:ntyp,-ntyp:ntyp) real(kind=8),dimension(:,:,:),allocatable :: v0sccor !(maxterm_sccor,-ntyp:ntyp,-ntyp:ntyp) integer :: nsccortyp integer,dimension(:),allocatable :: isccortyp !(-ntyp:ntyp) integer,dimension(:,:),allocatable :: nterm_sccor,nlor_sccor !(-ntyp:ntyp,-ntyp:ntyp) real(kind=8),dimension(:,:,:),allocatable :: vlor1sccor,& vlor2sccor,vlor3sccor !(maxterm_sccor,20,20) real(kind=8),dimension(:,:,:),allocatable :: gloc_sc !(3,0:maxres2,10) real(kind=8),dimension(:,:,:,:),allocatable :: dtauangle !(3,3,3,maxres2) !----------------------------------------------------------------------------- ! common.scrot ! 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/ integer :: ndih_constr,ndih_nconstr,ntheta_constr 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),dimension(:),allocatable :: drange,theta_constr0,theta_drange !(maxdih_constr) real(kind=8),dimension(:),allocatable :: phi0,ftors !(maxdih_constr) real(kind=8),dimension(:),allocatable :: for_thet_constr !(maxdih_constr) !----------------------------------------------------------------------------- ! common.torsion ! Torsional constants of the rotation about virtual-bond dihedral angles ! common/torsion/ real(kind=8),dimension(:,:,:),allocatable :: v0 !(-maxtor:maxtor,-maxtor:maxtor,2) #ifdef CRYST_TOR real(kind=8),dimension(:,:,:),allocatable :: v1,v2 !(maxterm,-maxtor:maxtor,-maxtor:maxtor) #else real(kind=8),dimension(:,:,:,:),allocatable :: v1,v2 !(maxterm,-maxtor:maxtor,-maxtor:maxtor,2) #endif real(kind=8),dimension(:,:,:),allocatable :: vlor1 !(maxlor,-maxtor:maxtor,-maxtor:maxtor) real(kind=8),dimension(:,:,:),allocatable :: vlor2,vlor3 !(maxlor,maxtor,maxtor) integer,dimension(:),allocatable :: itortyp !(-ntyp1:ntyp1) integer,dimension(:,:,:),allocatable :: nterm,nlor !(-maxtor:maxtor,-maxtor:maxtor,2) ! ---- for rigorous approach integer :: ntortyp,nterm_old ! integer nloctyp integer,dimension(:,:),allocatable :: nterm_kcc_Tb,nterm_kcc integer,dimension(:),allocatable :: iloctyp,itype2loc real(kind=8),dimension(:,:,:,:,:),allocatable :: v1_kcc,v2_kcc real(kind=8),dimension(:,:),allocatable :: v1bend_chyb integer,dimension(:),allocatable :: nbend_kcc_Tb !------torsion nucleic real(kind=8),dimension(:,:),allocatable :: v0_nucl !(-maxtor:maxtor,-maxtor:maxtor,2) real(kind=8),dimension(:,:,:),allocatable :: v1_nucl,v2_nucl !(maxterm,-maxtor:maxtor,-maxtor:maxtor) real(kind=8),dimension(:,:,:),allocatable :: vlor1_nucl !(maxlor,-maxtor:maxtor,-maxtor:maxtor) real(kind=8),dimension(:,:,:),allocatable :: vlor2_nucl,vlor3_nucl !(maxlor,maxtor,maxtor) integer,dimension(:),allocatable :: itortyp_nucl !(-ntyp1:ntyp1) integer,dimension(:,:),allocatable :: nterm_nucl,nlor_nucl !(-maxtor:maxtor,-maxtor:maxtor,2) integer :: ntortyp_nucl,nterm_old_nucl ! 6/23/01 - constants for double torsionals ! common /torsiond/ real(kind=8),dimension(:,:,:,:,:,:),allocatable :: v1c,v1s !(2,maxtermd_1,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2) real(kind=8),dimension(:,:,:,:,:,:),allocatable :: v2c,v2s !(maxtermd_2,maxtermd_2,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2) integer,dimension(:,:,:,:),allocatable :: ntermd_1,ntermd_2 !(-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2) ! 9/18/99 - added Fourier coeffficients of the expansion of local energy ! surfacecommon ! common/fourier/ real(kind=8),dimension(:,:),allocatable :: b1,b2,& b1tilde,b2tilde,gtb1,gtb2!(2,-maxtor:maxtor), real(kind=8),dimension(:,:,:),allocatable :: cc,dd,ee,& ctilde,dtilde,bnew1,bnew2,ccnew,ddnew,bnew1tor,& bnew2tor,ccnewtor,ddnewtor,ccold,ddold,eeold,& gtCC,gtDD,gtEE,gtEUg real(kind=8),dimension(:,:,:,:),allocatable :: eenew,eenewtor real(kind=8),dimension(:,:),allocatable :: e0new,e0newtor 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,debaykap real(kind=8),dimension(:,:,:),allocatable :: alphasur,alphiso,& wqdip,wstate,dtail real(kind=8),dimension(:,:,:,:),allocatable :: dhead !----------------------------------------------------------------------------- ! 24 Apr 2017 ! Varibles for cutoff on electorstatic real(kind=8) sss_ele_cut,sss_ele_grad integer xshift,yshift,zshift !2 Jul 2017 lipidc parameters ----------------------------------------------------- real(kind=8),dimension(:), allocatable :: liptranene real(kind=8) :: pepliptran ! 4 Jul 2017 parameters for shieliding real(kind=8),dimension(:), allocatable :: long_r_sidechain, & short_r_sidechain real(kind=8) :: VSolvSphere,VSolvSphere_div,buff_shield ! 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 !------------- for psi prec constraints real(kind=8),dimension(:,:), allocatable :: vpsipred,sdihed !23 Jul 2019 ions parameters by Agnieszka Lipska (Ca, K, Na, Mg, Cl)-------------------- ! real(kind=8),dimension(:,:),allocatable :: alphapolcat,& ! epsheadcat,sig0headcat,sigiso1cat,sigiso2cat,sigmap1cat,& ! sigmap2cat,wquadcat,chicat,chiscat,chippcat,& ! epsintabcat,debaykapcat integer,dimension(:),allocatable :: ichargecat integer oldion real(kind=8),dimension(:,:),allocatable :: alphapolcat,& epsheadcat,sig0headcat,sigiso1cat,sigiso2cat,rborncat,& sigmap1cat,sigmap2cat,chiscat,wquadcat,chippcat,& epsintabcat,debaykapcat,chicat,sigmacat, nstatecat, epscat real(kind=8),dimension(:,:,:),allocatable :: alphasurcat,& alphisocat,wqdipcat,dtailcat,wstatecat real(kind=8),dimension(:,:,:,:),allocatable :: dheadcat ! real(kind=8),dimension(:,:),allocatable :: alphapol,epshead,& ! sig0head,sigiso1,sigiso2,rborn,sigmap1,sigmap2,chis,wquad,chipp,& ! epsintab,debaykap !end of ions parameters by Agnieszka Lipska (Ca, K, Na, Mg, Cl)----------------------- end module energy_data