adding ebend_nucl to UCGM+some further reading
[unres4.git] / source / unres / data / energy_data.f90
index a0e0f3a..c41fc11 100644 (file)
@@ -64,7 +64,8 @@
       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,wliptran,wshield,lipscale,wtube
+       wturn6,wvdwpp,wliptran,wshield,lipscale,wtube, &
+       wbond_nucl,wang_nucl
 #ifdef CLUSTER
       real(kind=8) :: scalscp
 #endif
       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 :: istype
+      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,&
 !      common /stretch/
       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
        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/ 
        iturn3_start,iturn3_end,iturn4_start,iturn4_end,iint_start,&
        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, &
+       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,&