X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2Fdata%2Fenergy_data.f90;h=844aa85eb0450948daf413fdc65115a8689c05af;hb=e1aeda758c35ccdf5a5b88e825b6ca391c2dc1ae;hp=11382e28e05f02562918360ef74ecb24724c5cfa;hpb=299e2c41124d3fa8adba7244716515a2cc160ed1;p=unres4.git diff --git a/source/unres/data/energy_data.f90 b/source/unres/data/energy_data.f90 index 11382e2..844aa85 100644 --- a/source/unres/data/energy_data.f90 +++ b/source/unres/data/energy_data.f90 @@ -64,7 +64,9 @@ 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 + 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 #ifdef CLUSTER real(kind=8) :: scalscp #endif @@ -88,20 +90,27 @@ !----------------------------------------------------------------------------- ! common.interact ! common /interact/ - real(kind=8),dimension(:,:),allocatable :: aa,bb,augm !(ntyp,ntyp) + 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) :: 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 integer :: expon,expon2, nnt,nct,itypro integer,dimension(:,:),allocatable :: istart,iend !(maxres,maxint_gr) - integer,dimension(:),allocatable :: nint_gr,itype,itel,& + integer,dimension(:),allocatable :: nint_gr,itel,& ielstart,ielend,ielstart_vdw,ielend_vdw,nscp_gr !(maxres) + 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 ! 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,sigmaii,& + 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) @@ -109,9 +118,15 @@ real(kind=8),dimension(:,:),allocatable :: r0d,eps_scp,rscp !(ntyp,2) r0d !!! nie używane ! 12/5/03 modified 09/18/03 Bond stretching parameters. ! common /stretch/ - real(kind=8) :: vbldp0,akp,distchainmax + 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 @@ -126,6 +141,20 @@ 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/ @@ -149,7 +178,11 @@ 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 + 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 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,& @@ -165,18 +198,7 @@ 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/ - real(kind=8),dimension(50) :: qfrag - real(kind=8),dimension(100) :: qpair - real(kind=8),dimension(:,:),allocatable :: qinfrag,wfrag !(50,maxprocs/20) - real(kind=8),dimension(:,:),allocatable :: qinpair,wpair !(100,maxprocs/20) - real(kind=8) :: eq_time,Uconst - integer :: iset,nset - integer,dimension(:),allocatable :: mset !(maxprocs/20) - integer,dimension(:,:,:),allocatable :: ifrag !(2,50,maxprocs/20) - integer,dimension(:,:,:),allocatable :: ipair !(2,100,maxprocs/20) - integer :: nfrag,npair - logical :: usampl +! common /qmeas/ in module geometry !----------------------------------------------------------------------------- ! common.sbridge ! common /sbridge/ @@ -184,7 +206,7 @@ integer :: ns,nss,nfree integer,dimension(:),allocatable :: iss !(maxss) ! common /links/ - real(kind=8),dimension(:),allocatable :: dhpb,forcon,dhpb1 !(maxdim) !el dhpb1 !!! nie używane + 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/ @@ -192,7 +214,7 @@ ! common /links_split/ integer :: link_start,link_end ! common /dyn_ssbond/ - real(kind=8) :: Ht + real(kind=8) :: Ht,atriss,btriss,ctriss,dtriss integer,dimension(:),allocatable :: idssb,jdssb !(maxdim) logical :: dyn_ss logical,dimension(:),allocatable :: dyn_ss_mask !(maxres) @@ -217,12 +239,15 @@ !----------------------------------------------------------------------------- ! common.torcnstr ! common /torcnstr/ - integer :: ndih_constr,ndih_nconstr - integer,dimension(:),allocatable :: idih_constr,idih_nconstr !(maxdih_constr) - integer :: idihconstr_start,idihconstr_end + 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 !(maxdih_constr) + 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 :: for_thet_constr !(maxdih_constr) + !----------------------------------------------------------------------------- ! common.torsion ! Torsional constants of the rotation about virtual-bond dihedral angles @@ -238,6 +263,15 @@ integer,dimension(:),allocatable :: itortyp !(-ntyp1:ntyp1) integer,dimension(:,:,:),allocatable :: nterm,nlor !(-maxtor:maxtor,-maxtor:maxtor,2) integer :: ntortyp,nterm_old +!------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 @@ -257,22 +291,23 @@ ! common/fourier/ z wham real(kind=8),dimension(:,:),allocatable :: b !(13,0:maxtor) !----------------------------------------------------------------------------- -! common.var -! Store the geometric variables in the following COMMON block. -! common /var/ in module geometry_data -! Store the angles and variables corresponding to old conformations (for use -! in MCM). -! common /oldgeo/ -!el real(kind=8),dimension(:,:),allocatable :: varsave !(maxvar,maxsave) -! real(kind=8),dimension(:),allocatable :: esave !(maxsave) -! integer,dimension(:),allocatable :: Origin !(maxsave) -! integer :: nstore -! freeze some variables -! common /restr/ - real(kind=8),dimension(:),allocatable :: varall !(maxvar) - integer,dimension(:),allocatable :: mask_theta,& - mask_phi,mask_side !(maxres) - logical :: mask_r -!----------------------------------------------------------------------------- -!----------------------------------------------------------------------------- +! 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 + + + + end module energy_data