cleaning water
[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=57 !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 ! Maximum number of valence and torsional in rigorous approach
22       integer,parameter :: maxtor_kcc=6
23       integer,parameter :: maxval_kcc=6
24       integer,parameter :: maxang_kcc=36
25
26 !-----------------------------------------------------------------------------
27 ! commom.contacts
28 !      common /contacts/
29       integer :: ncont,ncont_ref
30       integer,dimension(:,:),allocatable :: icont,icont_ref !(2,maxcont)
31 !#ifdef WHAM_RUN
32 !      integer,dimension(:),allocatable :: nsccont_frag_ref !(mmaxfrag) !wham
33 !      integer,dimension(:,:,:),allocatable :: isccont_frag_ref !(2,maxcont,mmaxfrag) !wham
34 !#endif
35 ! 12/13/2008 (again Poland-Jaruzel war anniversary)
36 !   RE: Parallelization of 4th and higher order loc-el correlations
37 !      common /contdistrib/
38       integer,dimension(:),allocatable :: iat_sent !(maxres)
39 ! iat_sent - zainicjowane w initialize_p.F;
40       integer,dimension(:,:,:),allocatable :: iint_sent,iint_sent_local !(4,maxres,maxres)
41       integer,dimension(:,:),allocatable :: iturn3_sent,iturn4_sent,&
42        iturn3_sent_local,iturn4_sent_local      !(4,maxres),
43       integer,dimension(:),allocatable :: itask_cont_from,itask_cont_to !(0:max_fg_procs-1),
44       integer :: nat_sent,ntask_cont_from,ntask_cont_to
45 !-----------------------------------------------------------------------------
46 ! commom.deriv;
47 !      common /derivat/ 
48       real(kind=8),dimension(:,:),allocatable :: dcdv,dxdv !(6,maxdim)
49       real(kind=8),dimension(:,:),allocatable :: dxds !(6,maxres)
50       real(kind=8),dimension(:,:,:),allocatable :: gradx,gradc !(3,maxres,2)
51       real(kind=8),dimension(:,:),allocatable :: gvdwx !(3,maxres)
52       real(kind=8),dimension(:,:),allocatable :: gloc,gloc_x !(maxvar,2)   ,gloc_x  !!! nie używane
53       real(kind=8),dimension(:,:,:),allocatable :: dtheta       !(3,2,maxres)
54       real(kind=8),dimension(:,:,:),allocatable :: dphi,dalpha,domega !(3,3,maxres)
55       integer :: nfl,icg
56
57 !      common /derivat/   wham
58       logical :: calc_grad
59 !      common /mpgrad/
60       integer :: igrad_start,igrad_end
61       integer,dimension(:),allocatable :: jgrad_start,jgrad_end !(maxres)
62 !-----------------------------------------------------------------------------
63 ! The following COMMON block selects the type of the force field used in
64 ! calculations and defines weights of various energy terms.
65 ! 12/1/95 wcorr added
66 !-----------------------------------------------------------------------------
67 ! common.ffield
68 !      common /ffield/
69       integer :: n_ene_comp
70       integer :: rescale_mode
71       real(kind=8) :: wsc,wscp,welec,wbond,wstrain,wtor,wtor_d,wang,&
72        wscloc,wcorr,wcorr4,wcorr5,wcorr6,wsccor,wel_loc,wturn3,wturn4,&
73        wturn6,wvdwpp,wliptran,wshield,lipscale,wtube, &
74        wbond_nucl,wang_nucl,wcorr_nucl,wcorr3_nucl,welpp,wtor_nucl,&
75        wtor_d_nucl,welsb,wsbloc,wvdwsb,welpsb,wvdwpp_nucl,wvdwpsb,wcatprot,&
76        wcatcat,wscbase,wpepbase,wscpho,wpeppho,wdihc,wcatnucl,wcat_tran,wcat_ang
77 #ifdef CLUSTER
78       real(kind=8) :: scalscp
79 #endif
80       real(kind=8),dimension(:),allocatable :: weights !(n_ene)
81       real(kind=8) :: temp0,scal14,cutoff_corr,delt_corr,r0_corr
82       integer :: ipot,ipot_nucl
83 !      common /potentials/
84       character(len=3),dimension(5) :: potname = &
85         (/'LJ ','LJK','BP ','GB ','GBV'/)
86 !-----------------------------------------------------------------------------
87 ! wlong,welec,wtor,wang,wscloc are the weight of the energy terms 
88 ! corresponding to side-chain, electrostatic, torsional, valence-angle,
89 ! and local side-chain terms.
90 !
91 ! IPOT determines which SC...SC interaction potential will be used:
92 ! 1 - LJ:  2n-n Lennard-Jones
93 ! 2 - LJK: 2n-n Kihara type (shifted Lennard-Jones) 
94 ! 3 - BP;  Berne-Pechukas (angular dependence)
95 ! 4 - GB;  Gay-Berne (angular dependence)
96 ! 5 - GBV; Gay-Berne-Vorobjev; angularly-dependent Kihara potential
97 !-----------------------------------------------------------------------------
98 ! common.interact
99 !      common /interact/
100       real(kind=8),dimension(:,:),allocatable :: aa_aq,bb_aq,augm,aa_lip,bb_lip !(ntyp,ntyp)
101       real(kind=8),dimension(:),allocatable :: sc_aa_tube_par,sc_bb_tube_par,&
102        acavtub,bcavtub,ccavtub,dcavtub,tubetranene
103       real(kind=8),dimension(:,:),allocatable :: aa_nucl,bb_nucl
104       real(kind=8) :: acavtubpep,bcavtubpep,ccavtubpep,dcavtubpep, &
105       tubetranenepep,pep_aa_tube,pep_bb_tube,tubeR0
106       real(kind=8),dimension(3) :: tubecenter
107       real(kind=8),dimension(:,:),allocatable :: aad,bad !(ntyp,2)
108       real(kind=8),dimension(2,2) :: app,bpp,ael6,ael3
109       real(kind=8),dimension(:),allocatable :: aad_nucl,bad_nucl !(ntyp,2)
110       real(kind=8),dimension(2,2) :: app_nucl,bpp_nucl
111       real(kind=8),dimension(:,:),allocatable :: ael6_nucl,&
112         ael3_nucl,ael32_nucl,ael63_nucl
113       integer :: expon,expon2, nnt,nct,itypro
114       integer,dimension(5) :: nnt_molec,nct_molec
115       integer,dimension(:,:),allocatable :: istart,iend !(maxres,maxint_gr)
116       integer,dimension(:),allocatable :: nint_gr,itel,&
117        ielstart,ielend,ielstart_vdw,ielend_vdw,nscp_gr !(maxres)
118       integer,dimension(:,:),allocatable :: istart_nucl,iend_nucl !(maxres,maxint_gr)
119       integer,dimension(:),allocatable :: nint_gr_nucl,itel_nucl,&
120        ielstart_nucl,ielend_nucl,ielstart_vdw_nucl,ielend_vdw_nucl,nscp_gr_nucl !(maxres)
121       integer,dimension(:,:),allocatable :: iscpstart_nucl,iscpend_nucl !(maxres,maxint_gr)
122
123       integer,dimension(:),allocatable :: istype,molnum
124       integer,dimension(:,:),allocatable :: itype ! now itype has more molecule types
125       integer,dimension(:,:),allocatable :: iscpstart,iscpend !(maxres,maxint_gr)
126       integer :: iatsc_s,iatsc_e,iatel_s,iatel_e,iatel_s_vdw,&
127        iatel_e_vdw,iatscp_s,iatscp_e,ispp,iscp
128       integer :: iatsc_s_nucl,iatsc_e_nucl,iatel_s_nucl,iatel_e_nucl,&
129        iatel_s_vdw_nucl,iatel_e_vdw_nucl,iatscp_s_nucl,iatscp_e_nucl,&
130        ispp_nucl,iscp_nucl
131       
132 ! 12/1/95 Array EPS included in the COMMON block.
133 !      common /body/
134       real(kind=8),dimension(:,:),allocatable :: sigma !(0:ntyp1,0:ntyp1)
135       real(kind=8),dimension(:,:),allocatable :: eps,epslip,sigmaii,&
136        rs0,chi,r0,r0e   !(ntyp,ntyp) r0e !!! nie używane
137       real(kind=8),dimension(:),allocatable :: chip,alp,sigma0,&
138        sigii,rr0        !(ntyp)
139       real(kind=8),dimension(2,2) :: rpp,epp,elpp6,elpp3
140       real(kind=8),dimension(:,:),allocatable :: sigma_nucl !(0:ntyp1,0:ntyp1)
141       real(kind=8),dimension(:,:),allocatable :: eps_nucl,sigmaii_nucl,&
142        chi_nucl,r0_nucl, chip_nucl   !(ntyp,ntyp) r0e !!! nie używane
143       real(kind=8),dimension(:),allocatable :: alp_nucl,sigma0_nucl,&
144        sigii_nucl,rr0_nucl        !(ntyp)
145       real(kind=8),dimension(2,2) :: rpp_nucl,epp_nucl
146       real(kind=8),dimension(:,:),allocatable ::elpp6_nucl,&
147        elpp3_nucl,elpp32_nucl,elpp63_nucl
148       real(kind=8):: r0pp,epspp,AEES,BEES
149
150       real(kind=8),dimension(:,:),allocatable :: r0d,eps_scp,rscp !(ntyp,2)  r0d  !!! nie używane
151       real(kind=8),dimension(:),allocatable :: eps_scp_nucl,rscp_nucl!(ntyp,2)  r0d  !!! nie używane
152
153 ! 12/5/03 modified 09/18/03 Bond stretching parameters.
154 !      common /stretch/
155       real(kind=8) :: vbldp0,akp,distchainmax,vbldpDUM
156       real(kind=8),dimension(:,:),allocatable :: vbldsc0,aksc,abond0 !(maxbondterm,ntyp)
157       real(kind=8) :: vbldp0_nucl,akp_nucl
158       real(kind=8),dimension(:,:),allocatable :: vbldsc0_nucl,&
159        aksc_nucl,abond0_nucl !(maxbondterm,ntyp)
160
161       integer,dimension(:),allocatable :: nbondterm     !(ntyp)
162       integer,dimension(:),allocatable :: nbondterm_nucl     !(ntyp)
163
164
165
166       integer,dimension(:,:),allocatable :: nterm_scend     !(ntyp)
167       real(kind=8),dimension(:,:,:),allocatable:: arotam_end
168 !-----------------------------------------------------------------------------
169 ! common.local
170 ! Parameters of ab initio-derived potential of virtual-bond-angle bending
171 !      common /theta_abinitio/
172       integer :: nthetyp,ntheterm,ntheterm2,ntheterm3,nsingle,&
173        ndouble,nntheterm
174       integer,dimension(:),allocatable :: ithetyp !(-ntyp1:ntyp1)
175       integer,dimension(:,:),allocatable :: nstate !(-ntyp1:ntyp1)
176       real(kind=8),dimension(:,:,:,:),allocatable :: aa0thet
177 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
178       real(kind=8),dimension(:,:,:,:,:),allocatable :: aathet
179       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: bbthet,&
180        ccthet,ddthet,eethet
181 !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
182       real(kind=8),dimension(:,:,:,:,:,:,:),allocatable :: ffthet,ggthet
183
184 !-----------nucleic acid parameters--------------------------
185       integer :: nthetyp_nucl,ntheterm_nucl,ntheterm2_nucl,&
186       ntheterm3_nucl,nsingle_nucl,&
187        ndouble_nucl,nntheterm_nucl
188       integer,dimension(:),allocatable :: ithetyp_nucl !(-ntyp1:ntyp1)
189       real(kind=8),dimension(:,:,:),allocatable :: aa0thet_nucl
190 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
191       real(kind=8),dimension(:,:,:,:),allocatable :: aathet_nucl
192       real(kind=8),dimension(:,:,:,:,:),allocatable :: bbthet_nucl,&
193        ccthet_nucl,ddthet_nucl,eethet_nucl
194 !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
195       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: ffthet_nucl,ggthet_nucl
196
197 !(maxdouble,maxdouble,maxtheterm3,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
198 ! Parameters of the virtual-bond-angle probability distribution
199 !      common /thetas/ 
200       real(kind=8),dimension(:),allocatable :: a0thet,theta0,&
201        sig0,sigc0       !(-ntyp:ntyp)
202       real(kind=8),dimension(:,:,:,:),allocatable :: athet,bthet !(2,-ntyp:ntyp,-1:1,-1:1)
203       real(kind=8),dimension(:,:),allocatable :: polthet        !(0:3,-ntyp:ntyp)
204       real(kind=8),dimension(:,:),allocatable :: gthet  !(3,-ntyp:ntyp)
205 ! Parameters of the side-chain probability distribution
206 !      common /sclocal/
207       real(kind=8),dimension(:),allocatable :: dsc,dsc_inv,dsc0 !(ntyp1)
208       real(kind=8),dimension(:,:),allocatable :: bsc !(maxlob,ntyp)
209       real(kind=8),dimension(:,:,:),allocatable :: censc !(3,maxlob,-ntyp:ntyp)
210       real(kind=8),dimension(:,:,:,:),allocatable :: gaussc !(3,3,maxlob,-ntyp:ntyp)
211       integer,dimension(:),allocatable :: nlob !(ntyp1)
212 ! Virtual-bond lenghts
213 !      common /peptbond/
214       real(kind=8) :: vbl,vblinv,vblinv2,vbl_cis,vbl0
215 !      common /indices/
216       integer :: loc_start,loc_end,ithet_start,ithet_end,iphi_start,&
217        iphi_end,iphid_start,iphid_end,ibond_start,ibond_end,&
218        ibondp_start,ibondp_end,ivec_start,ivec_end,iset_start,iset_end,&
219        iturn3_start,iturn3_end,iturn4_start,iturn4_end,iint_start,&
220        iint_end,iphi1_start,iphi1_end,itau_start,itau_end,&
221        ilip_start,ilip_end,itube_start,itube_end
222       integer :: ibond_nucl_start,ibond_nucl_end,iphi_nucl_start,&
223        iphi_nucl_end,iphid_nucl_start,iphid_nucl_end,& 
224        ibondp_nucl_start,ibondp_nucl_end,ithet_nucl_start,ithet_nucl_end,&
225         loc_start_nucl,loc_end_nucl
226       integer :: icatb_start,icatb_end
227       integer,dimension(:),allocatable :: ibond_displ,ibond_count,&
228        ithet_displ,ithet_count,iphi_displ,iphi_count,iphi1_displ,&
229        iphi1_count,ivec_displ,ivec_count,iset_displ,iset_count,&
230        iint_count,iint_displ    !(0:max_fg_procs-1)
231 !-----------------------------------------------------------------------------
232 ! common.MD
233 !      common /mdgrad/
234       real(kind=8),dimension(:,:),allocatable :: gcart,gxcart !(3,0:MAXRES)
235       real(kind=8),dimension(:,:),allocatable :: gradcag,gradxag !(3,MAXRES)  !!! nie używane
236 !      common /back_constr/
237       integer :: nfrag_back
238       real(kind=8) :: uconst_back
239       real(kind=8),dimension(:),allocatable :: utheta,ugamma,uscdiff !(maxfrag_back)
240       real(kind=8),dimension(:,:,:),allocatable :: wfrag_back !(3,maxfrag_back,maxprocs/20)
241       integer,dimension(:,:,:),allocatable :: ifrag_back !(3,maxfrag_back,maxprocs/20)
242 !      common /qmeas/ in module geometry
243 !-----------------------------------------------------------------------------
244 ! common.sbridge
245 !      common /sbridge/
246       real(kind=8) :: ss_depth,ebr,d0cm,akcm,akth,akct,v1ss,v2ss,v3ss
247       integer :: ns,nss,nfree
248       integer,dimension(:),allocatable :: iss   !(maxss)
249 !      common /links/
250       real(kind=8),dimension(:),allocatable :: dhpb,forcon,dhpb1,fordepth !(maxdim) !el dhpb1 !!! nie używane
251       integer :: nhpb
252       integer,dimension(:),allocatable :: ihpb,jhpb,ibecarb !(maxdim) !el ibecarb !!! nie używane
253 !      common /restraints/
254       real(kind=8) :: weidis
255 !      common /links_split/
256       integer :: link_start,link_end
257 !      common /dyn_ssbond/
258       real(kind=8) :: Ht,atriss,btriss,ctriss,dtriss
259       integer,dimension(:),allocatable :: idssb,jdssb !(maxdim)
260       logical :: dyn_ss
261       logical,dimension(:),allocatable :: dyn_ss_mask !(maxres)
262 !-----------------------------------------------------------------------------
263 ! common.sccor
264 ! Parameters of the SCCOR term
265 !      common/sccor/
266       real(kind=8),dimension(:,:,:,:),allocatable :: v1sccor,v2sccor !(maxterm_sccor,3,-ntyp:ntyp,-ntyp:ntyp)
267       real(kind=8),dimension(:,:,:),allocatable :: v0sccor !(maxterm_sccor,-ntyp:ntyp,-ntyp:ntyp)
268       integer :: nsccortyp
269       integer,dimension(:),allocatable :: isccortyp !(-ntyp:ntyp)
270       integer,dimension(:,:),allocatable :: nterm_sccor,nlor_sccor !(-ntyp:ntyp,-ntyp:ntyp)
271       real(kind=8),dimension(:,:,:),allocatable :: vlor1sccor,&
272        vlor2sccor,vlor3sccor    !(maxterm_sccor,20,20)
273       real(kind=8),dimension(:,:,:),allocatable :: gloc_sc !(3,0:maxres2,10)
274       real(kind=8),dimension(:,:,:,:),allocatable :: dtauangle !(3,3,3,maxres2)
275 !-----------------------------------------------------------------------------
276 ! common.scrot
277 ! Parameters of the SC rotamers (local) term
278 !      common/scrot/
279       real(kind=8),dimension(:,:),allocatable :: sc_parmin !(maxsccoef,ntyp)
280       real(kind=8),dimension(:,:),allocatable :: sc_parmin_nucl !(maxsccoef,ntyp)
281
282 !-----------------------------------------------------------------------------
283 ! common.torcnstr
284 !      common /torcnstr/
285       integer :: ndih_constr,ndih_nconstr,ntheta_constr
286       integer,dimension(:),allocatable :: idih_constr,idih_nconstr,itheta_constr !(maxdih_constr)
287       integer :: idihconstr_start,idihconstr_end, &
288        ithetaconstr_start,ithetaconstr_end
289 !      real(kind=8) :: ftors
290       real(kind=8),dimension(:),allocatable :: drange,theta_constr0,theta_drange !(maxdih_constr)
291       real(kind=8),dimension(:),allocatable :: phi0,ftors !(maxdih_constr)
292       real(kind=8),dimension(:),allocatable :: for_thet_constr !(maxdih_constr)
293
294 !-----------------------------------------------------------------------------
295 ! common.torsion
296 ! Torsional constants of the rotation about virtual-bond dihedral angles
297 !      common/torsion/
298       real(kind=8),dimension(:,:,:),allocatable :: v0 !(-maxtor:maxtor,-maxtor:maxtor,2)
299 #ifdef CRYST_TOR
300       real(kind=8),dimension(:,:,:),allocatable :: v1,v2 !(maxterm,-maxtor:maxtor,-maxtor:maxtor)
301 #else
302       real(kind=8),dimension(:,:,:,:),allocatable :: v1,v2 !(maxterm,-maxtor:maxtor,-maxtor:maxtor,2)
303 #endif
304       real(kind=8),dimension(:,:,:),allocatable :: vlor1 !(maxlor,-maxtor:maxtor,-maxtor:maxtor)
305       real(kind=8),dimension(:,:,:),allocatable :: vlor2,vlor3 !(maxlor,maxtor,maxtor)
306       integer,dimension(:),allocatable :: itortyp !(-ntyp1:ntyp1)
307       integer,dimension(:,:,:),allocatable :: nterm,nlor !(-maxtor:maxtor,-maxtor:maxtor,2)
308 ! ---- for rigorous approach
309       integer :: ntortyp,nterm_old
310 !      integer nloctyp
311       integer,dimension(:,:),allocatable :: nterm_kcc_Tb,nterm_kcc
312       integer,dimension(:),allocatable :: iloctyp,itype2loc
313       real(kind=8),dimension(:,:,:,:,:),allocatable :: v1_kcc,v2_kcc
314       real(kind=8),dimension(:,:),allocatable :: v1bend_chyb
315       integer,dimension(:),allocatable :: nbend_kcc_Tb
316 !------torsion nucleic
317       real(kind=8),dimension(:,:),allocatable :: v0_nucl !(-maxtor:maxtor,-maxtor:maxtor,2)
318       real(kind=8),dimension(:,:,:),allocatable :: v1_nucl,v2_nucl !(maxterm,-maxtor:maxtor,-maxtor:maxtor)
319       real(kind=8),dimension(:,:,:),allocatable :: vlor1_nucl !(maxlor,-maxtor:maxtor,-maxtor:maxtor)
320       real(kind=8),dimension(:,:,:),allocatable :: vlor2_nucl,vlor3_nucl !(maxlor,maxtor,maxtor)
321       integer,dimension(:),allocatable :: itortyp_nucl !(-ntyp1:ntyp1)
322       integer,dimension(:,:),allocatable :: nterm_nucl,nlor_nucl !(-maxtor:maxtor,-maxtor:maxtor,2)
323       integer :: ntortyp_nucl,nterm_old_nucl
324
325 ! 6/23/01 - constants for double torsionals
326 !      common /torsiond/ 
327       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: v1c,v1s 
328         !(2,maxtermd_1,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
329       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: v2c,v2s
330         !(maxtermd_2,maxtermd_2,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
331       integer,dimension(:,:,:,:),allocatable :: ntermd_1,ntermd_2
332         !(-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
333 ! 9/18/99 - added Fourier coeffficients of the expansion of local energy 
334 !           surfacecommon
335 !      common/fourier/
336       real(kind=8),dimension(:,:),allocatable :: b1,b2,&
337        b1tilde,b2tilde,gtb1,gtb2!(2,-maxtor:maxtor),
338       real(kind=8),dimension(:,:,:),allocatable :: cc,dd,ee,&
339        ctilde,dtilde,bnew1,bnew2,ccnew,ddnew,bnew1tor,&
340        bnew2tor,ccnewtor,ddnewtor,ccold,ddold,eeold,&
341        gtCC,gtDD,gtEE,gtEUg
342       real(kind=8),dimension(:,:,:,:),allocatable :: eenew,eenewtor
343       real(kind=8),dimension(:,:),allocatable :: e0new,e0newtor
344       integer :: nloctyp
345 !      common/fourier/  z wham
346       real(kind=8),dimension(:,:),allocatable :: b !(13,0:maxtor)
347 !---------------MOMO---------------------------------------------------
348         integer,dimension(:),allocatable :: icharge
349         real(kind=8),dimension(:,:),allocatable :: alphapol,epshead,&
350            sig0head,sigiso1,sigiso2,rborn,sigmap1,sigmap2,chis,wquad,chipp,&
351            epsintab,debaykap
352         real(kind=8),dimension(:,:,:),allocatable :: alphasur,alphiso,&
353            wqdip,wstate,dtail
354          real(kind=8),dimension(:,:,:,:),allocatable :: dhead
355 !-----------------------------------------------------------------------------
356 ! 24 Apr 2017 
357 ! Varibles for cutoff on electorstatic
358       real(kind=8) sss_ele_cut,sss_ele_grad
359       integer xshift,yshift,zshift
360 !2 Jul 2017 lipidc parameters -----------------------------------------------------
361       real(kind=8),dimension(:), allocatable :: liptranene
362       real(kind=8) :: pepliptran
363
364 ! 4 Jul 2017 parameters for shieliding 
365       real(kind=8),dimension(:), allocatable :: long_r_sidechain, &
366         short_r_sidechain
367       real(kind=8) :: VSolvSphere,VSolvSphere_div,buff_shield
368 ! AFM
369        real(kind=8) :: distafminit,forceAFMconst,velAFMconst,&
370        velnanoconst,distnanoinit,forcenanoconst,inanomove,vecsim,vectrue
371       real(kind=8),dimension(1000) :: inanotab
372       integer :: afmend,afmbeg,nbegafmmat,nendafmmat
373       integer, dimension(1000) :: afmendcentr,afmbegcentr
374       real(kind=8),dimension(:,:), allocatable :: catprm
375       real(kind=8),dimension(:,:,:), allocatable :: catnuclprm
376
377
378          real(kind=8),dimension(:,:), allocatable ::  eps_scbase, &
379         sigma_scbase,                         &
380         sigmap1_scbase,sigmap2_scbase,        &
381         dhead_scbasei, dhead_scbasej, epshead_scbase,&
382         sig0head_scbase,  rborn_scbasei,rborn_scbasej,alphapol_scbase,epsintab_scbase,&
383         aa_scbase,bb_scbase
384          real(kind=8),dimension(:,:,:), allocatable :: alphasur_scbase, &
385         wdipdip_scbase,wqdip_scbase,chi_scbase,chipp_scbase,chis_scbase
386
387         real(kind=8),dimension(:), allocatable ::  eps_pepbase, &
388         sigma_pepbase,                         &
389         sigmap1_pepbase,sigmap2_pepbase,&
390         aa_pepbase,bb_pepbase
391
392          real(kind=8),dimension(:,:), allocatable :: alphasur_pepbase, &
393         wdipdip_pepbase,chi_pepbase,chipp_pepbase,chis_pepbase
394
395         real(kind=8),dimension(:), allocatable ::  eps_scpho, &
396         sigma_scpho,                         &
397         sigmap1_scpho,sigmap2_scpho,&
398         aa_scpho,bb_scpho,wqq_scpho,epsintab_scpho,alphapol_scpho,&
399         rborn_scphoi,rborn_scphoj,dhead_scphoi,alphi_scpho
400
401          real(kind=8),dimension(:,:), allocatable :: alphasur_scpho, &
402         chi_scpho,chipp_scpho,chis_scpho,              &
403         wqdip_scpho
404          real(kind=8) ,dimension(4) :: alphasur_peppho
405          real(kind=8) ,dimension(2) :: wqdip_peppho
406          real(kind=8) :: eps_peppho,sigma_peppho,sigmap1_peppho,sigmap2_peppho, &
407          aa_peppho,bb_peppho
408 !------------- for psi prec constraints
409          real(kind=8),dimension(:,:), allocatable :: vpsipred,sdihed
410
411 !23 Jul 2019 ions parameters by Agnieszka Lipska (Ca, K, Na, Mg, Cl)--------------------
412 !        real(kind=8),dimension(:,:),allocatable :: alphapolcat,&
413 !           epsheadcat,sig0headcat,sigiso1cat,sigiso2cat,sigmap1cat,&
414 !           sigmap2cat,wquadcat,chicat,chiscat,chippcat,&
415 !           epsintabcat,debaykapcat
416         integer,dimension(:),allocatable :: ichargecat
417 !        integer oldion
418
419         real(kind=8),dimension(:,:),allocatable :: alphapolcat, alphapolcat2, &
420            epsheadcat,sig0headcat,sigiso1cat,sigiso2cat,rborn1cat,rborn2cat,&
421            sigmap1cat,sigmap2cat,chis1cat,chis2cat,wquadcat,chipp1cat,chipp2cat,&
422            epsintabcat,debaykapcat,chi1cat,chi2cat,sigmacat, nstatecat, epscat,&
423            aa_aq_cat,bb_aq_cat
424
425         real(kind=8),dimension(:,:,:),allocatable :: alphasurcat,&
426            alphisocat,wqdipcat,dtailcat,wstatecat
427          real(kind=8),dimension(:,:,:,:),allocatable :: dheadcat
428           integer,dimension(60000) :: contlistscpi_f,contlistscpj_f
429 !         integer :: ifirstrun,ilist_scp_first
430 !        real(kind=8),dimension(:,:),allocatable :: alphapol,epshead,&
431 !           sig0head,sigiso1,sigiso2,rborn,sigmap1,sigmap2,chis,wquad,chipp,&
432 !           epsintab,debaykap
433
434
435 !end of ions parameters by Agnieszka Lipska (Ca, K, Na, Mg, Cl)-----------------------
436 !
437
438 ! Parameters for transistion ions
439        real(kind=8),dimension(:,:,:),allocatable:: agamacattran,&
440        athetacattran
441        real(kind=8),dimension(:,:),allocatable::acatshiftdsc,&
442        bcatshiftdsc,demorsecat,alphamorsecat,x0catleft,x0catright,&
443        x0cattrans,aomicattr
444        real(kind=8),dimension(:),allocatable::ntrantyp
445
446 ! FRAGMENT FOR INTERACTION LIST
447         integer,dimension(:),allocatable :: newcontlistppi,newcontlistppj,&
448         newcontlisti,newcontlistj,  newcontlistscpi,newcontlistscpj,&
449         newcontlistcatscnormi,newcontlistcatscnormj,&
450         newcontlistcatpnormi,newcontlistcatpnormj,&
451         newcontlistcatsctrani,newcontlistcatsctranj,&
452         newcontlistcatptrani,newcontlistcatptranj,&
453         newcontlistcatscangi,newcontlistcatscangj,&
454         newcontlistcatscangfi,newcontlistcatscangfj,&
455         newcontlistcatscangfk,&
456         newcontlistcatscangti,newcontlistcatscangtj,&
457         newcontlistcatscangtk,newcontlistcatscangtl,&
458         newcontlistcatcatnormi,newcontlistcatcatnormj
459
460
461
462
463         integer :: g_listpp_start,g_listpp_end,g_listscp_start,g_listscp_end,&
464         g_listscsc_start,g_listscsc_end, &
465         g_listcatsctran_start,g_listcatsctran_end,&
466         g_listcatscnorm_start,g_listcatscnorm_end,&
467         g_listcatptran_start,g_listcatptran_end,&
468         g_listcatpnorm_start,g_listcatpnorm_end,&
469         g_ilist_catscnorm,g_ilist_catsctran,g_ilist_catpnorm,&
470         g_ilist_catptran,g_ilist_catscang,g_ilist_catscangf,g_ilist_catscangt,&
471         g_listcatscang_start,g_listcatscang_end,&
472         g_listcatscangf_start,g_listcatscangf_end,&
473         g_listcatscangt_start,g_listcatscangt_end,&
474         g_listcatcatnorm_start,g_listcatcatnorm_end,g_ilist_catcatnorm
475
476
477 ! MARTINI FORCE FIELD
478         integer :: ilipbond_start,ilipbond_end,ilipang_start,ilipang_end, &
479         maxelecliplist,ilip_elec_start,ilipelec_end,maxljliplist,iliplj_start,iliplj_end,&
480         ilipbond_start_tub,ilipbond_end_tub
481         integer,dimension(:),allocatable :: mlipljlisti,mlipljlistj,&
482         mlipeleclisti,mlipeleclistj
483         real(kind=8),dimension(:,:,:),allocatable :: lip_angle_force,lip_angle_angle
484         real(kind=8),dimension(:,:),allocatable :: lip_bond,lip_eps,lip_sig
485         integer,dimension(:),allocatable :: ichargelipid     
486         real(kind=8) :: kjtokcal,krad,k_coulomb_lip,kbondlip 
487 !homology
488       integer ::  inprint,npermut,&
489        tubelog,constr_homology,homol_nset
490       logical :: mremd_dec,out_cart,&
491        out_int,gmatout,&
492        with_dihed_constr,read2sigma,start_from_model,read_homol_frag,&
493        out_template_coord,out_template_restr,loc_qlike,adaptive
494       real(kind=8) :: aincr,waga_dist,waga_angle,waga_theta,&
495        waga_d,dist2_cut
496       real(kind=8),dimension(:),allocatable :: waga_homology
497       real(kind=8),dimension(:,:),allocatable :: odl,&
498        sigma_odl,dih,sigma_dih, sigma_odlir, xxtpl,&
499        yytpl,zztpl,thetatpl,sigma_theta,sigma_d
500       integer,dimension(:),allocatable :: ires_homo,jres_homo
501       integer,dimension(:,:),allocatable :: idomain,tabpermchain,iequiv,&
502                   chain_border,chain_border1
503       integer :: lim_odl,lim_dih,link_start_homo,&
504        link_end_homo,idihconstr_start_homo,idihconstr_end_homo
505       logical,dimension(:,:),allocatable :: l_homo
506       integer ::nchain,iprzes,&
507         npermchain,&
508         nchain_group,&
509         nmodel_start,nran_start
510 !      real(kind=8),dimension(:,:),allocatable :: c,dc,dc_old,xloc,xrot,&
511 !                 dc_norm,dc_norm2,cref,crefjlee
512 !      real(kind=8),dimension(:),allocatable :: d_c_work
513       real(kind=8),dimension(:,:,:),allocatable :: chomo
514 !      real(kind=8) :: totTafm
515       character(len=256),dimension(:),allocatable:: pdbfiles_chomo
516       integer,dimension(:),allocatable :: chain_length,ireschain,&
517        nequiv,mapchain, nres_chomo
518       real(kind=8) :: enecut,sscut,sss,sssgrad
519 ! waterwater
520        real(kind=8),dimension(:),allocatable :: awaterenta,bwaterenta,&
521            cwaterenta,dwaterenta,awaterentro,bwaterentro,cwaterentro,&
522            dwaterentro
523 !       buflipbot, bufliptop,bordlipbot,bordliptop,lipbufthick,lipthick
524 !-------------------------------------------------------------------------
525         real(kind=8),dimension(3,70000) :: ea
526 #ifdef LBFGS 
527       character*9 statusbf
528       integer niter,nfun,ncalls
529 #endif
530 !      real(kind=8) :: buftubebot, buftubetop,bordtubebot,bordtubetop,tubebufthick
531       end module energy_data