workink EVDW i EES for PP,SB,PSB- warning energies differ as corrections made for...
[unres4.git] / source / unres / data / energy_data.f90
index 844aa85..44e3d30 100644 (file)
@@ -72,7 +72,7 @@
 #endif
       real(kind=8),dimension(:),allocatable :: weights !(n_ene)
       real(kind=8) :: temp0,scal14,cutoff_corr,delt_corr,r0_corr
-      integer :: ipot
+      integer :: ipot,ipot_nucl
 !      common /potentials/
       character(len=3),dimension(5) :: potname = &
         (/'LJ ','LJK','BP ','GB ','GBV'/)
       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),dimension(:,:),allocatable :: aa_nucl,bb_nucl
       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
+      real(kind=8),dimension(:),allocatable :: aad_nucl,bad_nucl !(ntyp,2)
+      real(kind=8),dimension(2,2) :: app_nucl,bpp_nucl
+      real(kind=8),dimension(:,:),allocatable :: ael6_nucl,&
+        ael3_nucl,ael32_nucl,ael63_nucl
       integer :: expon,expon2, nnt,nct,itypro
       integer,dimension(:,:),allocatable :: istart,iend !(maxres,maxint_gr)
       integer,dimension(:),allocatable :: nint_gr,itel,&
        ielstart,ielend,ielstart_vdw,ielend_vdw,nscp_gr !(maxres)
+      integer,dimension(:,:),allocatable :: istart_nucl,iend_nucl !(maxres,maxint_gr)
+      integer,dimension(:),allocatable :: nint_gr_nucl,itel_nucl,&
+       ielstart_nucl,ielend_nucl,ielstart_vdw_nucl,ielend_vdw_nucl,nscp_gr_nucl !(maxres)
+      integer,dimension(:,:),allocatable :: iscpstart_nucl,iscpend_nucl !(maxres,maxint_gr)
+
       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
+      integer :: iatsc_s_nucl,iatsc_e_nucl,iatel_s_nucl,iatel_e_nucl,&
+       iatel_s_vdw_nucl,iatel_e_vdw_nucl,iatscp_s_nucl,iatscp_e_nucl,&
+       ispp_nucl,iscp_nucl
+
 ! 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 :: chip,alp,sigma0,&
        sigii,rr0       !(ntyp)
       real(kind=8),dimension(2,2) :: rpp,epp,elpp6,elpp3
+      real(kind=8),dimension(:,:),allocatable :: sigma_nucl !(0:ntyp1,0:ntyp1)
+      real(kind=8),dimension(:,:),allocatable :: eps_nucl,sigmaii_nucl,&
+       chi_nucl,r0_nucl, chip_nucl   !(ntyp,ntyp) r0e !!! nie używane
+      real(kind=8),dimension(:),allocatable :: alp_nucl,sigma0_nucl,&
+       sigii_nucl,rr0_nucl        !(ntyp)
+      real(kind=8),dimension(2,2) :: rpp_nucl,epp_nucl
+      real(kind=8),dimension(:,:),allocatable ::elpp6_nucl,&
+       elpp3_nucl,elpp32_nucl,elpp63_nucl
+      real(kind=8):: r0pp,epspp,AEES,BEES
+
       real(kind=8),dimension(:,:),allocatable :: r0d,eps_scp,rscp !(ntyp,2)  r0d  !!! nie używane
+      real(kind=8),dimension(:),allocatable :: eps_scp_nucl,rscp_nucl!(ntyp,2)  r0d  !!! nie używane
+
 ! 12/5/03 modified 09/18/03 Bond stretching parameters.
 !      common /stretch/
       real(kind=8) :: vbldp0,akp,distchainmax,vbldpDUM