unres_package_Oct_2016 from emilial
[unres4.git] / source / unres / MD_data.f90
diff --git a/source/unres/MD_data.f90 b/source/unres/MD_data.f90
deleted file mode 100644 (file)
index 1332327..0000000
+++ /dev/null
@@ -1,100 +0,0 @@
-      module MD_data
-!-----------------------------------------------------------------------------
-#ifndef LANG0
-! commom.langevin
-!      common /langforc/
-      real(kind=8),dimension(:,:),allocatable :: friction,stochforc !(3,0:MAXRES2)
-      real(kind=8),dimension(:),allocatable :: fric_work,stoch_work,&
-       fricgam !(MAXRES6)
-      real(kind=8),dimension(:,:),allocatable :: fricmat,fricvec,&
-       pfric_mat,vfric_mat,afric_mat,prand_mat,vrand_mat1,&
-       vrand_mat2 !(MAXRES2,MAXRES2)
-      real(kind=8),dimension(:,:,:),allocatable :: pfric0_mat,&
-       afric0_mat,vfric0_mat,prand0_mat,vrand0_mat1,vrand0_mat2 !(MAXRES2,MAXRES2,0:maxflag_stoch)
-      logical,dimension(:),allocatable :: flag_stoch !(0:maxflag_stoch)
-!      common /langmat/
-      real(kind=8),dimension(:,:),allocatable :: mt1,mt2,mt3 !(maxres2,maxres2)
-!-----------------------------------------------------------------------------
-#else
-! commom.langevin.lang0
-!      common /langforc/
-      real(kind=8),dimension(:,:),allocatable :: friction,stochforc !(3,0:MAXRES2)
-      real(kind=8),dimension(:,:),allocatable :: fricmat,fricvec !(MAXRES2,MAXRES2)
-      real(kind=8),dimension(:),allocatable :: fric_work,stoch_work,&
-       fricgam !(MAXRES6)
-      logical,dimension(:),allocatable :: flag_stoch !(0:maxflag_stoch)
-      real(kind=8) :: vrand_mat1,vrand_mat2,prand_mat,vfric_mat,afric_mat,&
-       pfric_mat,pfric0_mat,afric0_mat,vfric0_mat,prand0_mat,vrand0_mat1,&
-       vrand0_mat2
-!      common /langmat/
-      integer :: mt1,mt2,mt3
-#endif
-!-----------------------------------------------------------------------------
-! commom.hairpin in CSA module
-!-----------------------------------------------------------------------------
-! common.mce in MCM_MD module
-!-----------------------------------------------------------------------------
-! common.MD
-!      common /mdgrad/ in module.energy
-!      common /back_constr/ in module.energy
-!      common /qmeas/ in module.energy
-!      common /mdpar/
-      real(kind=8) :: v_ini,d_time,d_time0,scal_fric,&
-       t_bath,tau_bath,dvmax,damax
-      integer :: n_timestep,ntime_split,ntime_split0,maxtime_split,&
-       ntwx,ntwe
-      logical :: mdpdb,large,print_compon,tbf,rest
-!      common /MDcalc/
-      real(kind=8) :: totT,totE,potE,EK,amax,edriftmax,kinetic_T
-      real(kind=8),dimension(:),allocatable :: potEcomp !(0:n_ene+4)
-!      common /lagrange/
-      real(kind=8),dimension(:,:),allocatable :: d_t,d_a,d_t_old !(3,0:MAXRES2)
-      real(kind=8),dimension(:),allocatable :: d_a_work !(6*MAXRES)
-      real(kind=8),dimension(:,:),allocatable :: Gmat,Ginv,A,&
-       Gsqrp,Gsqrm,Gvec !(maxres2,maxres2)
-      real(kind=8),dimension(:),allocatable :: Geigen !(maxres2)
-      real(kind=8),dimension(:),allocatable ::vtot !(maxres2)
-      logical :: reset_moment,reset_vel,rattle,RESPA
-      integer :: dimen,dimen1,dimen3
-      integer :: lang,count_reset_moment,count_reset_vel
-!      common /inertia/
-      real(kind=8) :: IP,mp
-      real(kind=8),dimension(:),allocatable :: ISC,msc !(ntyp+1)
-!      common /langevin/
-      real(kind=8) :: rwat,etawat,stdfp,pstok,gamp!,Rb
-      real(kind=8) :: cPoise=2.9361d0, Rb=0.001986d0
-      real(kind=8),dimension(:),allocatable :: gamsc !(ntyp1)
-      real(kind=8),dimension(:),allocatable :: stdfsc !(ntyp)
-
-      real(kind=8),dimension(:),allocatable :: restok !(ntyp+1)
-      logical :: surfarea
-      integer :: reset_fricmat
-!      common /mdpmpi/
-      integer :: igmult_start,igmult_end,my_ng_count,myginv_ng_count
-      integer,dimension(:),allocatable :: ng_start,ng_counts,&
-       nginv_counts !(0:MaxProcs-1)
-      integer,dimension(:),allocatable :: nginv_start !(0:MaxProcs)
-!-----------------------------------------------------------------------------
-! common.muca
-!      common /double_muca/
-      real(kind=8) :: elow,ehigh,factor,hbin,factor_min
-      real(kind=8),dimension(:),allocatable :: emuca,nemuca,&
-       nemuca2,hist !(4*maxres)
-!      common /integer_muca/
-      integer :: nmuca,imtime,muca_smooth
-!      common /mucarem/
-      real(kind=8),dimension(:),allocatable :: elowi,ehighi !(maxprocs)
-!-----------------------------------------------------------------------------
-! Maximum number of timesteps for which stochastic MD matrices can be stored
-      integer,parameter :: maxflag_stoch=0
-!-----------------------------------------------------------------------------
-!      common /przechowalnia/ subroutines: setup_MD_matrices
-      real(kind=8),dimension(:,:),allocatable :: Gcopy !(maxres2,maxres2), maxres2=2*maxres
-!-----------------------------------------------------------------------------
-!      common /przechowalnia/ subroutines: setup_fricmat,setup_MD_matrices
-      real(kind=8),dimension(:),allocatable :: Ghalf
-!-----------------------------------------------------------------------------
-!      COMMON /BANII/ D
-      real(kind=8),DIMENSION(:),allocatable :: D_ban !(MAXRES6) maxres6=6*maxres
-!-----------------------------------------------------------------------------
-      end module MD_data