unres_package_Oct_2016 from emilial
[unres4.git] / source / unres / MCM_MD.f90
index fe6fbb9..afb31bb 100644 (file)
 
       implicit none
 !-----------------------------------------------------------------------------
+! Max. number of move types in MCM
+!      integer,parameter :: maxmovetype=4
+!-----------------------------------------------------------------------------
 ! Max. number of conformations in Master's cache array
       integer,parameter :: max_cache=10
 !-----------------------------------------------------------------------------
+! Max. number of stored confs. in MC/MCM simulation
+!      integer,parameter :: maxsave=20
+!-----------------------------------------------------------------------------
 ! Number of threads in deformation
       integer,parameter :: max_thread=4, max_thread2=2*max_thread    
 !-----------------------------------------------------------------------------
 ! commom.cache
 !      common /cache/
       integer :: ncache
+!      integer,dimension(max_cache) :: CachSrc nie używane
+!      integer,dimension(max_cache) :: isent,iused
+!      logical :: cache_update
+!      real(kind=8),dimension(max_cache) :: ecache
+!      real(kind=8),dimension(:,:),allocatable :: xcache !(maxvar,max_cache)
 !-----------------------------------------------------------------------------
 ! common.mce
 !      common /mce/
 !      integer :: nacc_tot
       integer,dimension(:),allocatable :: nacc_part !(0:MaxProcs) !el nie uzywane???
 !      common /windows/
+!      integer :: nwindow
+!      integer,dimension(:),allocatable :: winstart,winend,winlen !(maxres)
 !      common /moveID/
+!      character(len=16),dimension(-1:MaxMoveType+1) :: MovTypID !(-1:MaxMoveType+1)
 !------------------------------------------------------------------------------
 !... koniecl - the number of bonds to be considered "end bonds" subjected to
 !...          end moves;
       use control, only:tcpu,ovrtim
       use regularize_, only:fitsq
       use compare
+!      use control
 ! Does Boltzmann and entropic sampling without energy minimization
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
       use compare, only:contact,contact_fract
       use minimm, only:minimize
       use regularize_, only:fitsq
+!      use contact_, only:contact
+!      use minim
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
       include 'mpif.h'
 
       use MPI_data
       use minimm, only:minimize
+!      use minim
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
       include 'mpif.h'