MPI shield
[unres4.git] / source / unres / data / energy_data.f90
1       module energy_data
2 !-----------------------------------------------------------------------------
3       use names
4 !-----------------------------------------------------------------------------
5 ! Max. number of energy intervals
6       integer,parameter :: max_ene=49 !10
7 !-----------------------------------------------------------------------------
8 ! Maximum number of terms in SC bond-stretching potential
9       integer,parameter :: maxbondterm=3
10 !-----------------------------------------------------------------------------
11 ! Max. number of derivatives of virtual-bond and side-chain vectors in theta
12 ! or phi.
13       integer :: maxdim
14 !-----------------------------------------------------------------------------
15 ! Max. number of contacts per residue
16       integer :: maxconts
17       integer,parameter :: maxcontsshi=50
18 !-----------------------------------------------------------------------------
19 ! Max. number of SC contacts
20       integer :: maxcont
21 !-----------------------------------------------------------------------------
22 ! commom.contacts
23 !      common /contacts/
24       integer :: ncont,ncont_ref
25       integer,dimension(:,:),allocatable :: icont,icont_ref !(2,maxcont)
26 !#ifdef WHAM_RUN
27 !      integer,dimension(:),allocatable :: nsccont_frag_ref !(mmaxfrag) !wham
28 !      integer,dimension(:,:,:),allocatable :: isccont_frag_ref !(2,maxcont,mmaxfrag) !wham
29 !#endif
30 ! 12/13/2008 (again Poland-Jaruzel war anniversary)
31 !   RE: Parallelization of 4th and higher order loc-el correlations
32 !      common /contdistrib/
33       integer,dimension(:),allocatable :: iat_sent !(maxres)
34 ! iat_sent - zainicjowane w initialize_p.F;
35       integer,dimension(:,:,:),allocatable :: iint_sent,iint_sent_local !(4,maxres,maxres)
36       integer,dimension(:,:),allocatable :: iturn3_sent,iturn4_sent,&
37        iturn3_sent_local,iturn4_sent_local      !(4,maxres),
38       integer,dimension(:),allocatable :: itask_cont_from,itask_cont_to !(0:max_fg_procs-1),
39       integer :: nat_sent,ntask_cont_from,ntask_cont_to
40 !-----------------------------------------------------------------------------
41 ! commom.deriv;
42 !      common /derivat/ 
43       real(kind=8),dimension(:,:),allocatable :: dcdv,dxdv !(6,maxdim)
44       real(kind=8),dimension(:,:),allocatable :: dxds !(6,maxres)
45       real(kind=8),dimension(:,:,:),allocatable :: gradx,gradc !(3,maxres,2)
46       real(kind=8),dimension(:,:),allocatable :: gvdwx !(3,maxres)
47       real(kind=8),dimension(:,:),allocatable :: gloc,gloc_x !(maxvar,2)   ,gloc_x  !!! nie używane
48       real(kind=8),dimension(:,:,:),allocatable :: dtheta       !(3,2,maxres)
49       real(kind=8),dimension(:,:,:),allocatable :: dphi,dalpha,domega !(3,3,maxres)
50       integer :: nfl,icg
51
52 !      common /derivat/   wham
53       logical :: calc_grad
54 !      common /mpgrad/
55       integer :: igrad_start,igrad_end
56       integer,dimension(:),allocatable :: jgrad_start,jgrad_end !(maxres)
57 !-----------------------------------------------------------------------------
58 ! The following COMMON block selects the type of the force field used in
59 ! calculations and defines weights of various energy terms.
60 ! 12/1/95 wcorr added
61 !-----------------------------------------------------------------------------
62 ! common.ffield
63 !      common /ffield/
64       integer :: n_ene_comp
65       integer :: rescale_mode
66       real(kind=8) :: wsc,wscp,welec,wbond,wstrain,wtor,wtor_d,wang,&
67        wscloc,wcorr,wcorr4,wcorr5,wcorr6,wsccor,wel_loc,wturn3,wturn4,&
68        wturn6,wvdwpp,wliptran,wshield,lipscale,wtube, &
69        wbond_nucl,wang_nucl,wcorr_nucl,wcorr3_nucl,welpp,wtor_nucl,&
70        wtor_d_nucl,welsb,wsbloc,wvdwsb,welpsb,wvdwpp_nucl,wvdwpsb,wcatprot,&
71        wcatcat,wscbase,wpepbase,wscpho,wpeppho
72 #ifdef CLUSTER
73       real(kind=8) :: scalscp
74 #endif
75       real(kind=8),dimension(:),allocatable :: weights !(n_ene)
76       real(kind=8) :: temp0,scal14,cutoff_corr,delt_corr,r0_corr
77       integer :: ipot,ipot_nucl
78 !      common /potentials/
79       character(len=3),dimension(5) :: potname = &
80         (/'LJ ','LJK','BP ','GB ','GBV'/)
81 !-----------------------------------------------------------------------------
82 ! wlong,welec,wtor,wang,wscloc are the weight of the energy terms 
83 ! corresponding to side-chain, electrostatic, torsional, valence-angle,
84 ! and local side-chain terms.
85 !
86 ! IPOT determines which SC...SC interaction potential will be used:
87 ! 1 - LJ:  2n-n Lennard-Jones
88 ! 2 - LJK: 2n-n Kihara type (shifted Lennard-Jones) 
89 ! 3 - BP;  Berne-Pechukas (angular dependence)
90 ! 4 - GB;  Gay-Berne (angular dependence)
91 ! 5 - GBV; Gay-Berne-Vorobjev; angularly-dependent Kihara potential
92 !-----------------------------------------------------------------------------
93 ! common.interact
94 !      common /interact/
95       real(kind=8),dimension(:,:),allocatable :: aa_aq,bb_aq,augm,aa_lip,bb_lip !(ntyp,ntyp)
96       real(kind=8),dimension(:),allocatable :: sc_aa_tube_par,sc_bb_tube_par,&
97        acavtub,bcavtub,ccavtub,dcavtub,tubetranene
98       real(kind=8),dimension(:,:),allocatable :: aa_nucl,bb_nucl
99       real(kind=8) :: acavtubpep,bcavtubpep,ccavtubpep,dcavtubpep, &
100       tubetranenepep,pep_aa_tube,pep_bb_tube,tubeR0
101       real(kind=8),dimension(3) :: tubecenter
102       real(kind=8),dimension(:,:),allocatable :: aad,bad !(ntyp,2)
103       real(kind=8),dimension(2,2) :: app,bpp,ael6,ael3
104       real(kind=8),dimension(:),allocatable :: aad_nucl,bad_nucl !(ntyp,2)
105       real(kind=8),dimension(2,2) :: app_nucl,bpp_nucl
106       real(kind=8),dimension(:,:),allocatable :: ael6_nucl,&
107         ael3_nucl,ael32_nucl,ael63_nucl
108       integer :: expon,expon2, nnt,nct,itypro
109       integer,dimension(5) :: nnt_molec,nct_molec
110       integer,dimension(:,:),allocatable :: istart,iend !(maxres,maxint_gr)
111       integer,dimension(:),allocatable :: nint_gr,itel,&
112        ielstart,ielend,ielstart_vdw,ielend_vdw,nscp_gr !(maxres)
113       integer,dimension(:,:),allocatable :: istart_nucl,iend_nucl !(maxres,maxint_gr)
114       integer,dimension(:),allocatable :: nint_gr_nucl,itel_nucl,&
115        ielstart_nucl,ielend_nucl,ielstart_vdw_nucl,ielend_vdw_nucl,nscp_gr_nucl !(maxres)
116       integer,dimension(:,:),allocatable :: iscpstart_nucl,iscpend_nucl !(maxres,maxint_gr)
117
118       integer,dimension(:),allocatable :: istype,molnum
119       integer,dimension(:,:),allocatable :: itype ! now itype has more molecule types
120       integer,dimension(:,:),allocatable :: iscpstart,iscpend !(maxres,maxint_gr)
121       integer :: iatsc_s,iatsc_e,iatel_s,iatel_e,iatel_s_vdw,&
122        iatel_e_vdw,iatscp_s,iatscp_e,ispp,iscp
123       integer :: iatsc_s_nucl,iatsc_e_nucl,iatel_s_nucl,iatel_e_nucl,&
124        iatel_s_vdw_nucl,iatel_e_vdw_nucl,iatscp_s_nucl,iatscp_e_nucl,&
125        ispp_nucl,iscp_nucl
126
127 ! 12/1/95 Array EPS included in the COMMON block.
128 !      common /body/
129       real(kind=8),dimension(:,:),allocatable :: sigma !(0:ntyp1,0:ntyp1)
130       real(kind=8),dimension(:,:),allocatable :: eps,epslip,sigmaii,&
131        rs0,chi,r0,r0e   !(ntyp,ntyp) r0e !!! nie używane
132       real(kind=8),dimension(:),allocatable :: chip,alp,sigma0,&
133        sigii,rr0        !(ntyp)
134       real(kind=8),dimension(2,2) :: rpp,epp,elpp6,elpp3
135       real(kind=8),dimension(:,:),allocatable :: sigma_nucl !(0:ntyp1,0:ntyp1)
136       real(kind=8),dimension(:,:),allocatable :: eps_nucl,sigmaii_nucl,&
137        chi_nucl,r0_nucl, chip_nucl   !(ntyp,ntyp) r0e !!! nie używane
138       real(kind=8),dimension(:),allocatable :: alp_nucl,sigma0_nucl,&
139        sigii_nucl,rr0_nucl        !(ntyp)
140       real(kind=8),dimension(2,2) :: rpp_nucl,epp_nucl
141       real(kind=8),dimension(:,:),allocatable ::elpp6_nucl,&
142        elpp3_nucl,elpp32_nucl,elpp63_nucl
143       real(kind=8):: r0pp,epspp,AEES,BEES
144
145       real(kind=8),dimension(:,:),allocatable :: r0d,eps_scp,rscp !(ntyp,2)  r0d  !!! nie używane
146       real(kind=8),dimension(:),allocatable :: eps_scp_nucl,rscp_nucl!(ntyp,2)  r0d  !!! nie używane
147
148 ! 12/5/03 modified 09/18/03 Bond stretching parameters.
149 !      common /stretch/
150       real(kind=8) :: vbldp0,akp,distchainmax,vbldpDUM
151       real(kind=8),dimension(:,:),allocatable :: vbldsc0,aksc,abond0 !(maxbondterm,ntyp)
152       real(kind=8) :: vbldp0_nucl,akp_nucl
153       real(kind=8),dimension(:,:),allocatable :: vbldsc0_nucl,&
154        aksc_nucl,abond0_nucl !(maxbondterm,ntyp)
155
156       integer,dimension(:),allocatable :: nbondterm     !(ntyp)
157       integer,dimension(:),allocatable :: nbondterm_nucl     !(ntyp)
158
159 !-----------------------------------------------------------------------------
160 ! common.local
161 ! Parameters of ab initio-derived potential of virtual-bond-angle bending
162 !      common /theta_abinitio/
163       integer :: nthetyp,ntheterm,ntheterm2,ntheterm3,nsingle,&
164        ndouble,nntheterm
165       integer,dimension(:),allocatable :: ithetyp !(-ntyp1:ntyp1)
166       integer,dimension(:,:),allocatable :: nstate !(-ntyp1:ntyp1)
167       real(kind=8),dimension(:,:,:,:),allocatable :: aa0thet
168 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
169       real(kind=8),dimension(:,:,:,:,:),allocatable :: aathet
170       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: bbthet,&
171        ccthet,ddthet,eethet
172 !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
173       real(kind=8),dimension(:,:,:,:,:,:,:),allocatable :: ffthet,ggthet
174
175 !-----------nucleic acid parameters--------------------------
176       integer :: nthetyp_nucl,ntheterm_nucl,ntheterm2_nucl,&
177       ntheterm3_nucl,nsingle_nucl,&
178        ndouble_nucl,nntheterm_nucl
179       integer,dimension(:),allocatable :: ithetyp_nucl !(-ntyp1:ntyp1)
180       real(kind=8),dimension(:,:,:),allocatable :: aa0thet_nucl
181 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
182       real(kind=8),dimension(:,:,:,:),allocatable :: aathet_nucl
183       real(kind=8),dimension(:,:,:,:,:),allocatable :: bbthet_nucl,&
184        ccthet_nucl,ddthet_nucl,eethet_nucl
185 !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
186       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: ffthet_nucl,ggthet_nucl
187
188 !(maxdouble,maxdouble,maxtheterm3,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
189 ! Parameters of the virtual-bond-angle probability distribution
190 !      common /thetas/ 
191       real(kind=8),dimension(:),allocatable :: a0thet,theta0,&
192        sig0,sigc0       !(-ntyp:ntyp)
193       real(kind=8),dimension(:,:,:,:),allocatable :: athet,bthet !(2,-ntyp:ntyp,-1:1,-1:1)
194       real(kind=8),dimension(:,:),allocatable :: polthet        !(0:3,-ntyp:ntyp)
195       real(kind=8),dimension(:,:),allocatable :: gthet  !(3,-ntyp:ntyp)
196 ! Parameters of the side-chain probability distribution
197 !      common /sclocal/
198       real(kind=8),dimension(:),allocatable :: dsc,dsc_inv,dsc0 !(ntyp1)
199       real(kind=8),dimension(:,:),allocatable :: bsc !(maxlob,ntyp)
200       real(kind=8),dimension(:,:,:),allocatable :: censc !(3,maxlob,-ntyp:ntyp)
201       real(kind=8),dimension(:,:,:,:),allocatable :: gaussc !(3,3,maxlob,-ntyp:ntyp)
202       integer,dimension(:),allocatable :: nlob !(ntyp1)
203 ! Virtual-bond lenghts
204 !      common /peptbond/
205       real(kind=8) :: vbl,vblinv,vblinv2,vbl_cis,vbl0
206 !      common /indices/
207       integer :: loc_start,loc_end,ithet_start,ithet_end,iphi_start,&
208        iphi_end,iphid_start,iphid_end,ibond_start,ibond_end,&
209        ibondp_start,ibondp_end,ivec_start,ivec_end,iset_start,iset_end,&
210        iturn3_start,iturn3_end,iturn4_start,iturn4_end,iint_start,&
211        iint_end,iphi1_start,iphi1_end,itau_start,itau_end,&
212        ilip_start,ilip_end,itube_start,itube_end
213       integer :: ibond_nucl_start,ibond_nucl_end,iphi_nucl_start,&
214        iphi_nucl_end,iphid_nucl_start,iphid_nucl_end,& 
215        ibondp_nucl_start,ibondp_nucl_end,ithet_nucl_start,ithet_nucl_end,&
216         loc_start_nucl,loc_end_nucl
217       integer,dimension(:),allocatable :: ibond_displ,ibond_count,&
218        ithet_displ,ithet_count,iphi_displ,iphi_count,iphi1_displ,&
219        iphi1_count,ivec_displ,ivec_count,iset_displ,iset_count,&
220        iint_count,iint_displ    !(0:max_fg_procs-1)
221 !-----------------------------------------------------------------------------
222 ! common.MD
223 !      common /mdgrad/
224       real(kind=8),dimension(:,:),allocatable :: gcart,gxcart !(3,0:MAXRES)
225       real(kind=8),dimension(:,:),allocatable :: gradcag,gradxag !(3,MAXRES)  !!! nie używane
226 !      common /back_constr/
227       integer :: nfrag_back
228       real(kind=8) :: uconst_back
229       real(kind=8),dimension(:),allocatable :: utheta,ugamma,uscdiff !(maxfrag_back)
230       real(kind=8),dimension(:,:,:),allocatable :: wfrag_back !(3,maxfrag_back,maxprocs/20)
231       integer,dimension(:,:,:),allocatable :: ifrag_back !(3,maxfrag_back,maxprocs/20)
232 !      common /qmeas/ in module geometry
233 !-----------------------------------------------------------------------------
234 ! common.sbridge
235 !      common /sbridge/
236       real(kind=8) :: ss_depth,ebr,d0cm,akcm,akth,akct,v1ss,v2ss,v3ss
237       integer :: ns,nss,nfree
238       integer,dimension(:),allocatable :: iss   !(maxss)
239 !      common /links/
240       real(kind=8),dimension(:),allocatable :: dhpb,forcon,dhpb1,fordepth !(maxdim) !el dhpb1 !!! nie używane
241       integer :: nhpb
242       integer,dimension(:),allocatable :: ihpb,jhpb,ibecarb !(maxdim) !el ibecarb !!! nie używane
243 !      common /restraints/
244       real(kind=8) :: weidis
245 !      common /links_split/
246       integer :: link_start,link_end
247 !      common /dyn_ssbond/
248       real(kind=8) :: Ht,atriss,btriss,ctriss,dtriss
249       integer,dimension(:),allocatable :: idssb,jdssb !(maxdim)
250       logical :: dyn_ss
251       logical,dimension(:),allocatable :: dyn_ss_mask !(maxres)
252 !-----------------------------------------------------------------------------
253 ! common.sccor
254 ! Parameters of the SCCOR term
255 !      common/sccor/
256       real(kind=8),dimension(:,:,:,:),allocatable :: v1sccor,v2sccor !(maxterm_sccor,3,-ntyp:ntyp,-ntyp:ntyp)
257       real(kind=8),dimension(:,:,:),allocatable :: v0sccor !(maxterm_sccor,-ntyp:ntyp,-ntyp:ntyp)
258       integer :: nsccortyp
259       integer,dimension(:),allocatable :: isccortyp !(-ntyp:ntyp)
260       integer,dimension(:,:),allocatable :: nterm_sccor,nlor_sccor !(-ntyp:ntyp,-ntyp:ntyp)
261       real(kind=8),dimension(:,:,:),allocatable :: vlor1sccor,&
262        vlor2sccor,vlor3sccor    !(maxterm_sccor,20,20)
263       real(kind=8),dimension(:,:,:),allocatable :: gloc_sc !(3,0:maxres2,10)
264       real(kind=8),dimension(:,:,:,:),allocatable :: dtauangle !(3,3,3,maxres2)
265 !-----------------------------------------------------------------------------
266 ! common.scrot
267 ! Parameters of the SC rotamers (local) term
268 !      common/scrot/
269       real(kind=8),dimension(:,:),allocatable :: sc_parmin !(maxsccoef,ntyp)
270       real(kind=8),dimension(:,:),allocatable :: sc_parmin_nucl !(maxsccoef,ntyp)
271
272 !-----------------------------------------------------------------------------
273 ! common.torcnstr
274 !      common /torcnstr/
275       integer :: ndih_constr,ndih_nconstr,ntheta_constr
276       integer,dimension(:),allocatable :: idih_constr,idih_nconstr,itheta_constr !(maxdih_constr)
277       integer :: idihconstr_start,idihconstr_end, &
278        ithetaconstr_start,ithetaconstr_end
279 !      real(kind=8) :: ftors
280       real(kind=8),dimension(:),allocatable :: drange,theta_constr0,theta_drange !(maxdih_constr)
281       real(kind=8),dimension(:),allocatable :: phi0,ftors !(maxdih_constr)
282       real(kind=8),dimension(:),allocatable :: for_thet_constr !(maxdih_constr)
283
284 !-----------------------------------------------------------------------------
285 ! common.torsion
286 ! Torsional constants of the rotation about virtual-bond dihedral angles
287 !      common/torsion/
288       real(kind=8),dimension(:,:,:),allocatable :: v0 !(-maxtor:maxtor,-maxtor:maxtor,2)
289 #ifdef CRYST_TOR
290       real(kind=8),dimension(:,:,:),allocatable :: v1,v2 !(maxterm,-maxtor:maxtor,-maxtor:maxtor)
291 #else
292       real(kind=8),dimension(:,:,:,:),allocatable :: v1,v2 !(maxterm,-maxtor:maxtor,-maxtor:maxtor,2)
293 #endif
294       real(kind=8),dimension(:,:,:),allocatable :: vlor1 !(maxlor,-maxtor:maxtor,-maxtor:maxtor)
295       real(kind=8),dimension(:,:,:),allocatable :: vlor2,vlor3 !(maxlor,maxtor,maxtor)
296       integer,dimension(:),allocatable :: itortyp !(-ntyp1:ntyp1)
297       integer,dimension(:,:,:),allocatable :: nterm,nlor !(-maxtor:maxtor,-maxtor:maxtor,2)
298       integer :: ntortyp,nterm_old
299 !------torsion nucleic
300       real(kind=8),dimension(:,:),allocatable :: v0_nucl !(-maxtor:maxtor,-maxtor:maxtor,2)
301       real(kind=8),dimension(:,:,:),allocatable :: v1_nucl,v2_nucl !(maxterm,-maxtor:maxtor,-maxtor:maxtor)
302       real(kind=8),dimension(:,:,:),allocatable :: vlor1_nucl !(maxlor,-maxtor:maxtor,-maxtor:maxtor)
303       real(kind=8),dimension(:,:,:),allocatable :: vlor2_nucl,vlor3_nucl !(maxlor,maxtor,maxtor)
304       integer,dimension(:),allocatable :: itortyp_nucl !(-ntyp1:ntyp1)
305       integer,dimension(:,:),allocatable :: nterm_nucl,nlor_nucl !(-maxtor:maxtor,-maxtor:maxtor,2)
306       integer :: ntortyp_nucl,nterm_old_nucl
307
308 ! 6/23/01 - constants for double torsionals
309 !      common /torsiond/ 
310       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: v1c,v1s 
311         !(2,maxtermd_1,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
312       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: v2c,v2s
313         !(maxtermd_2,maxtermd_2,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
314       integer,dimension(:,:,:,:),allocatable :: ntermd_1,ntermd_2
315         !(-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
316 ! 9/18/99 - added Fourier coeffficients of the expansion of local energy 
317 !           surfacecommon
318 !      common/fourier/
319       real(kind=8),dimension(:,:),allocatable :: b1,b2,&
320        b1tilde  !(2,-maxtor:maxtor),
321       real(kind=8),dimension(:,:,:),allocatable :: cc,dd,ee,&
322        ctilde,dtilde !(2,2,-maxtor:maxtor)
323       integer :: nloctyp
324 !      common/fourier/  z wham
325       real(kind=8),dimension(:,:),allocatable :: b !(13,0:maxtor)
326 !---------------MOMO---------------------------------------------------
327         integer,dimension(:),allocatable :: icharge
328         real(kind=8),dimension(:,:),allocatable :: alphapol,epshead,&
329            sig0head,sigiso1,sigiso2,rborn,sigmap1,sigmap2,chis,wquad,chipp,&
330            epsintab
331         real(kind=8),dimension(:,:,:),allocatable :: alphasur,alphiso,&
332            wqdip,wstate,dtail
333          real(kind=8),dimension(:,:,:,:),allocatable :: dhead
334 !-----------------------------------------------------------------------------
335 ! 24 Apr 2017 
336 ! Varibles for cutoff on electorstatic
337       real(kind=8) sss_ele_cut,sss_ele_grad
338       integer xshift,yshift,zshift
339 !2 Jul 2017 lipidc parameters -----------------------------------------------------
340       real(kind=8),dimension(:), allocatable :: liptranene
341       real(kind=8) :: pepliptran
342
343 ! 4 Jul 2017 parameters for shieliding 
344       real(kind=8),dimension(:), allocatable :: long_r_sidechain, &
345         short_r_sidechain
346       real(kind=8) :: VSolvSphere,VSolvSphere_div,buff_shield
347 ! AFM
348        real(kind=8) :: distafminit,forceAFMconst,velAFMconst
349       integer :: afmend,afmbeg
350       real(kind=8),dimension(:,:), allocatable :: catprm
351
352          real(kind=8),dimension(:,:), allocatable ::  eps_scbase, &
353         sigma_scbase,                         &
354         sigmap1_scbase,sigmap2_scbase,        &
355         dhead_scbasei, dhead_scbasej, epshead_scbase,&
356         sig0head_scbase,  rborn_scbasei,rborn_scbasej,alphapol_scbase,epsintab_scbase,&
357         aa_scbase,bb_scbase
358          real(kind=8),dimension(:,:,:), allocatable :: alphasur_scbase, &
359         wdipdip_scbase,wqdip_scbase,chi_scbase,chipp_scbase,chis_scbase
360
361         real(kind=8),dimension(:), allocatable ::  eps_pepbase, &
362         sigma_pepbase,                         &
363         sigmap1_pepbase,sigmap2_pepbase,&
364         aa_pepbase,bb_pepbase
365
366          real(kind=8),dimension(:,:), allocatable :: alphasur_pepbase, &
367         wdipdip_pepbase,chi_pepbase,chipp_pepbase,chis_pepbase
368
369         real(kind=8),dimension(:), allocatable ::  eps_scpho, &
370         sigma_scpho,                         &
371         sigmap1_scpho,sigmap2_scpho,&
372         aa_scpho,bb_scpho,wqq_scpho,epsintab_scpho,alphapol_scpho,&
373         rborn_scphoi,rborn_scphoj,dhead_scphoi,alphi_scpho
374
375          real(kind=8),dimension(:,:), allocatable :: alphasur_scpho, &
376         chi_scpho,chipp_scpho,chis_scpho,              &
377         wqdip_scpho
378          real(kind=8) ,dimension(4) :: alphasur_peppho
379          real(kind=8) ,dimension(2) :: wqdip_peppho
380          real(kind=8) :: eps_peppho,sigma_peppho,sigmap1_peppho,sigmap2_peppho, &
381          aa_peppho,bb_peppho
382       end module energy_data