fc38d5aac4ded656267065df5d4085bbb03212cc
[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=21 !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 !-----------------------------------------------------------------------------
18 ! Max. number of SC contacts
19       integer :: maxcont
20 !-----------------------------------------------------------------------------
21 ! commom.contacts
22 !      common /contacts/
23       integer :: ncont,ncont_ref
24       integer,dimension(:,:),allocatable :: icont,icont_ref !(2,maxcont)
25 !#ifdef WHAM_RUN
26 !      integer,dimension(:),allocatable :: nsccont_frag_ref !(mmaxfrag) !wham
27 !      integer,dimension(:,:,:),allocatable :: isccont_frag_ref !(2,maxcont,mmaxfrag) !wham
28 !#endif
29 ! 12/13/2008 (again Poland-Jaruzel war anniversary)
30 !   RE: Parallelization of 4th and higher order loc-el correlations
31 !      common /contdistrib/
32       integer,dimension(:),allocatable :: iat_sent !(maxres)
33 ! iat_sent - zainicjowane w initialize_p.F;
34       integer,dimension(:,:,:),allocatable :: iint_sent,iint_sent_local !(4,maxres,maxres)
35       integer,dimension(:,:),allocatable :: iturn3_sent,iturn4_sent,&
36        iturn3_sent_local,iturn4_sent_local      !(4,maxres),
37       integer,dimension(:),allocatable :: itask_cont_from,itask_cont_to !(0:max_fg_procs-1),
38       integer :: nat_sent,ntask_cont_from,ntask_cont_to
39 !-----------------------------------------------------------------------------
40 ! commom.deriv;
41 !      common /derivat/ 
42       real(kind=8),dimension(:,:),allocatable :: dcdv,dxdv !(6,maxdim)
43       real(kind=8),dimension(:,:),allocatable :: dxds !(6,maxres)
44       real(kind=8),dimension(:,:,:),allocatable :: gradx,gradc !(3,maxres,2)
45       real(kind=8),dimension(:,:),allocatable :: gvdwx !(3,maxres)
46       real(kind=8),dimension(:,:),allocatable :: gloc,gloc_x !(maxvar,2)   ,gloc_x  !!! nie używane
47       real(kind=8),dimension(:,:,:),allocatable :: dtheta       !(3,2,maxres)
48       real(kind=8),dimension(:,:,:),allocatable :: dphi,dalpha,domega !(3,3,maxres)
49       integer :: nfl,icg
50
51 !      common /derivat/   wham
52       logical :: calc_grad
53 !      common /mpgrad/
54       integer :: igrad_start,igrad_end
55       integer,dimension(:),allocatable :: jgrad_start,jgrad_end !(maxres)
56 !-----------------------------------------------------------------------------
57 ! The following COMMON block selects the type of the force field used in
58 ! calculations and defines weights of various energy terms.
59 ! 12/1/95 wcorr added
60 !-----------------------------------------------------------------------------
61 ! common.ffield
62 !      common /ffield/
63       integer :: n_ene_comp
64       integer :: rescale_mode
65       real(kind=8) :: wsc,wscp,welec,wbond,wstrain,wtor,wtor_d,wang,&
66        wscloc,wcorr,wcorr4,wcorr5,wcorr6,wsccor,wel_loc,wturn3,wturn4,&
67        wturn6,wvdwpp,wliptran,wshield,lipscale,wtube
68 #ifdef CLUSTER
69       real(kind=8) :: scalscp
70 #endif
71       real(kind=8),dimension(:),allocatable :: weights !(n_ene)
72       real(kind=8) :: temp0,scal14,cutoff_corr,delt_corr,r0_corr
73       integer :: ipot
74 !      common /potentials/
75       character(len=3),dimension(5) :: potname = &
76         (/'LJ ','LJK','BP ','GB ','GBV'/)
77 !-----------------------------------------------------------------------------
78 ! wlong,welec,wtor,wang,wscloc are the weight of the energy terms 
79 ! corresponding to side-chain, electrostatic, torsional, valence-angle,
80 ! and local side-chain terms.
81 !
82 ! IPOT determines which SC...SC interaction potential will be used:
83 ! 1 - LJ:  2n-n Lennard-Jones
84 ! 2 - LJK: 2n-n Kihara type (shifted Lennard-Jones) 
85 ! 3 - BP;  Berne-Pechukas (angular dependence)
86 ! 4 - GB;  Gay-Berne (angular dependence)
87 ! 5 - GBV; Gay-Berne-Vorobjev; angularly-dependent Kihara potential
88 !-----------------------------------------------------------------------------
89 ! common.interact
90 !      common /interact/
91       real(kind=8),dimension(:,:),allocatable :: aa_aq,bb_aq,augm,aa_lip,bb_lip !(ntyp,ntyp)
92       real(kind=8),dimension(:),allocatable :: sc_aa_tube_par,sc_bb_tube_par,&
93        acavtub,bcavtub,ccavtub,dcavtub,tubetranene
94       real(kind=8) :: acavtubpep,bcavtubpep,ccavtubpep,dcavtubpep, &
95       tubetranenepep,pep_aa_tube,pep_bb_tube,tubeR0
96       real(kind=8),dimension(3) :: tubecenter
97       real(kind=8),dimension(:,:),allocatable :: aad,bad !(ntyp,2)
98       real(kind=8),dimension(2,2) :: app,bpp,ael6,ael3
99       integer :: expon,expon2, nnt,nct,itypro
100       integer,dimension(:,:),allocatable :: istart,iend !(maxres,maxint_gr)
101       integer,dimension(:),allocatable :: nint_gr,itel,&
102        ielstart,ielend,ielstart_vdw,ielend_vdw,nscp_gr !(maxres)
103       integer,dimension(:,:),allocatable :: itype ! now itype has more molecule types
104       integer,dimension(:,:),allocatable :: iscpstart,iscpend !(maxres,maxint_gr)
105       integer :: iatsc_s,iatsc_e,iatel_s,iatel_e,iatel_s_vdw,&
106        iatel_e_vdw,iatscp_s,iatscp_e,ispp,iscp
107 ! 12/1/95 Array EPS included in the COMMON block.
108 !      common /body/
109       real(kind=8),dimension(:,:),allocatable :: sigma !(0:ntyp1,0:ntyp1)
110       real(kind=8),dimension(:,:),allocatable :: eps,epslip,sigmaii,&
111        rs0,chi,r0,r0e   !(ntyp,ntyp) r0e !!! nie używane
112       real(kind=8),dimension(:),allocatable :: chip,alp,sigma0,&
113        sigii,rr0        !(ntyp)
114       real(kind=8),dimension(2,2) :: rpp,epp,elpp6,elpp3
115       real(kind=8),dimension(:,:),allocatable :: r0d,eps_scp,rscp !(ntyp,2)  r0d  !!! nie używane
116 ! 12/5/03 modified 09/18/03 Bond stretching parameters.
117 !      common /stretch/
118       real(kind=8) :: vbldp0,akp,distchainmax,vbldpDUM
119       real(kind=8),dimension(:,:),allocatable :: vbldsc0,aksc,abond0 !(maxbondterm,ntyp)
120       integer,dimension(:),allocatable :: nbondterm     !(ntyp)
121 !-----------------------------------------------------------------------------
122 ! common.local
123 ! Parameters of ab initio-derived potential of virtual-bond-angle bending
124 !      common /theta_abinitio/
125       integer :: nthetyp,ntheterm,ntheterm2,ntheterm3,nsingle,&
126        ndouble,nntheterm
127       integer,dimension(:),allocatable :: ithetyp !(-ntyp1:ntyp1)
128       real(kind=8),dimension(:,:,:,:),allocatable :: aa0thet
129 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
130       real(kind=8),dimension(:,:,:,:,:),allocatable :: aathet
131       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: bbthet,&
132        ccthet,ddthet,eethet
133 !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
134       real(kind=8),dimension(:,:,:,:,:,:,:),allocatable :: ffthet,ggthet
135 !(maxdouble,maxdouble,maxtheterm3,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
136 ! Parameters of the virtual-bond-angle probability distribution
137 !      common /thetas/ 
138       real(kind=8),dimension(:),allocatable :: a0thet,theta0,&
139        sig0,sigc0       !(-ntyp:ntyp)
140       real(kind=8),dimension(:,:,:,:),allocatable :: athet,bthet !(2,-ntyp:ntyp,-1:1,-1:1)
141       real(kind=8),dimension(:,:),allocatable :: polthet        !(0:3,-ntyp:ntyp)
142       real(kind=8),dimension(:,:),allocatable :: gthet  !(3,-ntyp:ntyp)
143 ! Parameters of the side-chain probability distribution
144 !      common /sclocal/
145       real(kind=8),dimension(:),allocatable :: dsc,dsc_inv,dsc0 !(ntyp1)
146       real(kind=8),dimension(:,:),allocatable :: bsc !(maxlob,ntyp)
147       real(kind=8),dimension(:,:,:),allocatable :: censc !(3,maxlob,-ntyp:ntyp)
148       real(kind=8),dimension(:,:,:,:),allocatable :: gaussc !(3,3,maxlob,-ntyp:ntyp)
149       integer,dimension(:),allocatable :: nlob !(ntyp1)
150 ! Virtual-bond lenghts
151 !      common /peptbond/
152       real(kind=8) :: vbl,vblinv,vblinv2,vbl_cis,vbl0
153 !      common /indices/
154       integer :: loc_start,loc_end,ithet_start,ithet_end,iphi_start,&
155        iphi_end,iphid_start,iphid_end,ibond_start,ibond_end,&
156        ibondp_start,ibondp_end,ivec_start,ivec_end,iset_start,iset_end,&
157        iturn3_start,iturn3_end,iturn4_start,iturn4_end,iint_start,&
158        iint_end,iphi1_start,iphi1_end,itau_start,itau_end,&
159        ilip_start,ilip_end,itube_start,itube_end
160       integer,dimension(:),allocatable :: ibond_displ,ibond_count,&
161        ithet_displ,ithet_count,iphi_displ,iphi_count,iphi1_displ,&
162        iphi1_count,ivec_displ,ivec_count,iset_displ,iset_count,&
163        iint_count,iint_displ    !(0:max_fg_procs-1)
164 !-----------------------------------------------------------------------------
165 ! common.MD
166 !      common /mdgrad/
167       real(kind=8),dimension(:,:),allocatable :: gcart,gxcart !(3,0:MAXRES)
168       real(kind=8),dimension(:,:),allocatable :: gradcag,gradxag !(3,MAXRES)  !!! nie używane
169 !      common /back_constr/
170       integer :: nfrag_back
171       real(kind=8) :: uconst_back
172       real(kind=8),dimension(:),allocatable :: utheta,ugamma,uscdiff !(maxfrag_back)
173       real(kind=8),dimension(:,:,:),allocatable :: wfrag_back !(3,maxfrag_back,maxprocs/20)
174       integer,dimension(:,:,:),allocatable :: ifrag_back !(3,maxfrag_back,maxprocs/20)
175 !      common /qmeas/ in module geometry
176 !-----------------------------------------------------------------------------
177 ! common.sbridge
178 !      common /sbridge/
179       real(kind=8) :: ss_depth,ebr,d0cm,akcm,akth,akct,v1ss,v2ss,v3ss
180       integer :: ns,nss,nfree
181       integer,dimension(:),allocatable :: iss   !(maxss)
182 !      common /links/
183       real(kind=8),dimension(:),allocatable :: dhpb,forcon,dhpb1,fordepth !(maxdim) !el dhpb1 !!! nie używane
184       integer :: nhpb
185       integer,dimension(:),allocatable :: ihpb,jhpb,ibecarb !(maxdim) !el ibecarb !!! nie używane
186 !      common /restraints/
187       real(kind=8) :: weidis
188 !      common /links_split/
189       integer :: link_start,link_end
190 !      common /dyn_ssbond/
191       real(kind=8) :: Ht,atriss,btriss,ctriss,dtriss
192       integer,dimension(:),allocatable :: idssb,jdssb !(maxdim)
193       logical :: dyn_ss
194       logical,dimension(:),allocatable :: dyn_ss_mask !(maxres)
195 !-----------------------------------------------------------------------------
196 ! common.sccor
197 ! Parameters of the SCCOR term
198 !      common/sccor/
199       real(kind=8),dimension(:,:,:,:),allocatable :: v1sccor,v2sccor !(maxterm_sccor,3,-ntyp:ntyp,-ntyp:ntyp)
200       real(kind=8),dimension(:,:,:),allocatable :: v0sccor !(maxterm_sccor,-ntyp:ntyp,-ntyp:ntyp)
201       integer :: nsccortyp
202       integer,dimension(:),allocatable :: isccortyp !(-ntyp:ntyp)
203       integer,dimension(:,:),allocatable :: nterm_sccor,nlor_sccor !(-ntyp:ntyp,-ntyp:ntyp)
204       real(kind=8),dimension(:,:,:),allocatable :: vlor1sccor,&
205        vlor2sccor,vlor3sccor    !(maxterm_sccor,20,20)
206       real(kind=8),dimension(:,:,:),allocatable :: gloc_sc !(3,0:maxres2,10)
207       real(kind=8),dimension(:,:,:,:),allocatable :: dtauangle !(3,3,3,maxres2)
208 !-----------------------------------------------------------------------------
209 ! common.scrot
210 ! Parameters of the SC rotamers (local) term
211 !      common/scrot/
212       real(kind=8),dimension(:,:),allocatable :: sc_parmin !(maxsccoef,ntyp)
213 !-----------------------------------------------------------------------------
214 ! common.torcnstr
215 !      common /torcnstr/
216       integer :: ndih_constr,ndih_nconstr,ntheta_constr
217       integer,dimension(:),allocatable :: idih_constr,idih_nconstr,itheta_constr !(maxdih_constr)
218       integer :: idihconstr_start,idihconstr_end, &
219        ithetaconstr_start,ithetaconstr_end
220       real(kind=8) :: ftors
221       real(kind=8),dimension(:),allocatable :: drange,theta_constr0,theta_drange !(maxdih_constr)
222       real(kind=8),dimension(:),allocatable :: phi0 !(maxdih_constr)
223       real(kind=8),dimension(:),allocatable :: for_thet_constr !(maxdih_constr)
224
225 !-----------------------------------------------------------------------------
226 ! common.torsion
227 ! Torsional constants of the rotation about virtual-bond dihedral angles
228 !      common/torsion/
229       real(kind=8),dimension(:,:,:),allocatable :: v0 !(-maxtor:maxtor,-maxtor:maxtor,2)
230 #ifdef CRYST_TOR
231       real(kind=8),dimension(:,:,:),allocatable :: v1,v2 !(maxterm,-maxtor:maxtor,-maxtor:maxtor)
232 #else
233       real(kind=8),dimension(:,:,:,:),allocatable :: v1,v2 !(maxterm,-maxtor:maxtor,-maxtor:maxtor,2)
234 #endif
235       real(kind=8),dimension(:,:,:),allocatable :: vlor1 !(maxlor,-maxtor:maxtor,-maxtor:maxtor)
236       real(kind=8),dimension(:,:,:),allocatable :: vlor2,vlor3 !(maxlor,maxtor,maxtor)
237       integer,dimension(:),allocatable :: itortyp !(-ntyp1:ntyp1)
238       integer,dimension(:,:,:),allocatable :: nterm,nlor !(-maxtor:maxtor,-maxtor:maxtor,2)
239       integer :: ntortyp,nterm_old
240 ! 6/23/01 - constants for double torsionals
241 !      common /torsiond/ 
242       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: v1c,v1s 
243         !(2,maxtermd_1,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
244       real(kind=8),dimension(:,:,:,:,:,:),allocatable :: v2c,v2s
245         !(maxtermd_2,maxtermd_2,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
246       integer,dimension(:,:,:,:),allocatable :: ntermd_1,ntermd_2
247         !(-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2)
248 ! 9/18/99 - added Fourier coeffficients of the expansion of local energy 
249 !           surfacecommon
250 !      common/fourier/
251       real(kind=8),dimension(:,:),allocatable :: b1,b2,&
252        b1tilde  !(2,-maxtor:maxtor),
253       real(kind=8),dimension(:,:,:),allocatable :: cc,dd,ee,&
254        ctilde,dtilde !(2,2,-maxtor:maxtor)
255       integer :: nloctyp
256 !      common/fourier/  z wham
257       real(kind=8),dimension(:,:),allocatable :: b !(13,0:maxtor)
258 !-----------------------------------------------------------------------------
259 ! 24 Apr 2017 
260 ! Varibles for cutoff on electorstatic
261       real(kind=8) sss_ele_cut,sss_ele_grad
262       integer xshift,yshift,zshift
263 !2 Jul 2017 lipidc parameters -----------------------------------------------------
264       real(kind=8),dimension(:), allocatable :: liptranene
265       real(kind=8) :: pepliptran
266
267 ! 4 Jul 2017 parameters for shieliding 
268       real(kind=8),dimension(:), allocatable :: long_r_sidechain, &
269         short_r_sidechain
270       real(kind=8) :: VSolvSphere,VSolvSphere_div,buff_shield
271 ! AFM
272        real(kind=8) :: distafminit,forceAFMconst,velAFMconst
273       integer :: afmend,afmbeg
274
275
276
277
278       end module energy_data