correction for gfortran
[unres4.git] / source / unres / data / MD_data.f90
index 9ec0a10..3273cfc 100644 (file)
 ! common.MD
 !      common /mdgrad/ in module.energy
 !      common /back_constr/ in module.energy
-!      common /qmeas/ in module.energy
+!      common /qmeas/ others in module.geometry
+      real(kind=8) :: eq_time
+      integer :: iset,nset
+      integer,dimension(:),allocatable :: mset !(maxprocs/20)
+      logical :: usampl
 !      common /mdpar/
       real(kind=8) :: v_ini,d_time,d_time0,scal_fric,&
        t_bath,tau_bath,dvmax,damax
@@ -45,7 +49,7 @@
        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) :: totT,totE,potE,EK,amax,edriftmax,kinetic_T,totTafm
       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)
       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)
+      real(kind=8),dimension(5) :: 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) :: rwat,etawat
+      real(kind=8), dimension(5) :: pstok,gamp,stdfp
       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 :: gamsc !(ntyp1)
+      real(kind=8),dimension(:,:),allocatable :: stdfsc !(ntyp)
 
-      real(kind=8),dimension(:),allocatable :: restok !(ntyp+1)
+      real(kind=8),dimension(:,:),allocatable :: restok !(ntyp+1)
       logical :: surfarea
       integer :: reset_fricmat
 !      common /mdpmpi/
 !      COMMON /BANII/ D
       real(kind=8),DIMENSION(:),allocatable :: D_ban !(MAXRES6) maxres6=6*maxres
 !-----------------------------------------------------------------------------
+      logical preminim ! pre-minimizaation flag
       end module MD_data