triss; AFM; Lorentz restrains included -debug might be on
[unres4.git] / source / unres / data / energy_data.f90
index 873f053..71015c7 100644 (file)
@@ -64,7 +64,7 @@
       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
 #ifdef CLUSTER
       real(kind=8) :: scalscp
 #endif
 !-----------------------------------------------------------------------------
 ! 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
 ! 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)
       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)
       integer,dimension(:),allocatable :: nbondterm    !(ntyp)
 !-----------------------------------------------------------------------------
        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,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,&
       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/
 !      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)
 !-----------------------------------------------------------------------------
 ! 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
 !      common/fourier/  z wham
       real(kind=8),dimension(:,:),allocatable :: b !(13,0:maxtor)
 !-----------------------------------------------------------------------------
-!-----------------------------------------------------------------------------
+! 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