corrections of max... ranges of arrays
authorEmilia Lubecka <emilia.lubecka@ug.edu.pl>
Thu, 20 Apr 2017 13:28:48 +0000 (15:28 +0200)
committerEmilia Lubecka <emilia.lubecka@ug.edu.pl>
Thu, 20 Apr 2017 13:28:48 +0000 (15:28 +0200)
13 files changed:
source/unres/MD.f90
source/unres/cinfo.f90
source/unres/data/MD_data.f90
source/unres/data/control_data.f90
source/unres/data/energy_data.f90
source/unres/data/geometry_data.f90
source/unres/energy.f90
source/unres/io_config.f90
source/unres/unres.f90
source/wham/cinfo.f90
source/wham/enecalc.f90
source/wham/io_database.f90
source/wham/io_wham.f90

index c378ece..36124aa 100644 (file)
 !el      integer maxamino,maxnuc,maxbnd
 !el      integer maxang,maxtors,maxpi
 !el      integer maxpib,maxpit
-      integer :: maxatm        !=2*nres        !maxres2 maxres2=2*maxres
-      integer,parameter :: maxval=8
-      integer,parameter :: maxgrp=1000
-      integer,parameter :: maxtyp=3000
-      integer,parameter :: maxclass=500
-      integer,parameter :: maxkey=10000
-      integer,parameter :: maxrot=1000
-      integer,parameter :: maxopt=1000
-      integer,parameter :: maxhess=1000000
-      integer :: maxlight      !=8*maxatm
-      integer,parameter :: maxvib=1000
-      integer,parameter :: maxgeo=1000
-      integer,parameter :: maxcell=10000
-      integer,parameter :: maxring=10000
-      integer,parameter :: maxfix=10000
-      integer,parameter :: maxbio=10000
-      integer,parameter :: maxamino=31
-      integer,parameter :: maxnuc=12
-      integer :: maxbnd                !=2*maxatm
-      integer :: maxang                !=3*maxatm
-      integer :: maxtors       !=4*maxatm
-      integer,parameter :: maxpi=100
-      integer,parameter :: maxpib=2*maxpi
-      integer,parameter :: maxpit=4*maxpi
+!      integer :: maxatm       !=2*nres        !maxres2 maxres2=2*maxres
+!      integer,parameter :: maxval=8
+!      integer,parameter :: maxgrp=1000
+!      integer,parameter :: maxtyp=3000
+!      integer,parameter :: maxclass=500
+!      integer,parameter :: maxkey=10000
+!      integer,parameter :: maxrot=1000
+!      integer,parameter :: maxopt=1000
+!      integer,parameter :: maxhess=1000000
+!      integer :: maxlight     !=8*maxatm
+!      integer,parameter :: maxvib=1000
+!      integer,parameter :: maxgeo=1000
+!      integer,parameter :: maxcell=10000
+!      integer,parameter :: maxring=10000
+!      integer,parameter :: maxfix=10000
+!      integer,parameter :: maxbio=10000
+!      integer,parameter :: maxamino=31
+!      integer,parameter :: maxnuc=12
+!      integer :: maxbnd               !=2*maxatm
+!      integer :: maxang               !=3*maxatm
+!      integer :: maxtors      !=4*maxatm
+!      integer,parameter :: maxpi=100
+!      integer,parameter :: maxpib=2*maxpi
+!      integer,parameter :: maxpit=4*maxpi
 !-----------------------------------------------------------------------------
 ! Maximum number of seed
-      integer,parameter :: max_seed=1
+!      integer,parameter :: max_seed=1
 !-----------------------------------------------------------------------------
       real(kind=8),dimension(:),allocatable :: stochforcvec !(MAXRES6) maxres6=6*maxres
 !      common /stochcalc/ stochforcvec
       logical :: omit(maxarc)
 !
 !      include 'sizes.i'
-      maxatm = 2*nres  !maxres2 maxres2=2*maxres
-      maxlight = 8*maxatm
-      maxbnd = 2*maxatm
-      maxang = 3*maxatm
-      maxtors = 4*maxatm
+!      maxatm = 2*nres !maxres2 maxres2=2*maxres
+!      maxlight = 8*maxatm
+!      maxbnd = 2*maxatm
+!      maxang = 3*maxatm
+!      maxtors = 4*maxatm
 !
 !     zero out the surface area for the sphere of interest
 !
index 21be40d..6e9b6c8 100644 (file)
@@ -1,12 +1,12 @@
 ! DO NOT EDIT THIS FILE - IT HAS BEEN GENERATED BY COMPINFO.C
-! 0 40376 81
+! 0 40376 83
       subroutine cinfo
 !      include 'COMMON.IOUNITS'
       use io_units
       write(iout,*)'++++ Compile info ++++'
-      write(iout,*)'Version 0.40376 build 81'
-      write(iout,*)'compiled Wed Apr 19 12:39:43 2017'
-      write(iout,*)'compiled by adam@piasek4'
+      write(iout,*)'Version 0.40376 build 83'
+      write(iout,*)'compiled Thu Apr 20 14:26:12 2017'
+      write(iout,*)'compiled by emilial@piasek4'
       write(iout,*)'OS name:    Linux '
       write(iout,*)'OS release: 3.2.0-124-generic '
       write(iout,*)'OS version:',&
index 9ec0a10..73246ba 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
index 6ec06d0..7f0dc87 100644 (file)
@@ -2,7 +2,7 @@
 !-----------------------------------------------------------------------------
 ! Max. number of types of dihedral angles & multiplicity of torsional barriers
 ! and the number of terms in double torsionals
-      integer,parameter :: maxtor=4,maxterm=10,maxlor=3
+      integer,parameter :: maxlor=3,maxterm=10 !maxtor=4
       integer,parameter :: maxtermd_1=8,maxtermd_2=8
 !-----------------------------------------------------------------------------
 ! Max. number of groups of interactions that a given SC is involved in
 !-----------------------------------------------------------------------------
 ! Max. number of residue types and parameters in expressions for 
 ! virtual-bond angle bending potentials
-      integer,parameter :: maxthetyp=3,maxthetyp1=maxthetyp+1
-      integer,parameter :: maxtheterm=20
-      integer,parameter :: maxtheterm2=6,maxtheterm3=4
-      integer,parameter :: maxsingle=6,maxdouble=4
-      integer,parameter :: mmaxtheterm=maxtheterm
+!      integer,parameter :: maxthetyp=3,maxthetyp1=maxthetyp+1
+!      integer,parameter :: maxtheterm=20
+!      integer,parameter :: maxtheterm2=6,maxtheterm3=4
+!      integer,parameter :: maxsingle=6,maxdouble=4
+!      integer,parameter :: mmaxtheterm=maxtheterm
 !-----------------------------------------------------------------------------
 ! Max number of torsional terms in SCCOR
       integer,parameter :: maxterm_sccor=7000
@@ -23,7 +23,7 @@
 !      integer,parameter :: maxlob=4 in geometry
 !-----------------------------------------------------------------------------
 ! Max. number of S-S bridges
-      integer,parameter :: maxss=20
+!      integer,parameter :: maxss=20
 !-----------------------------------------------------------------------------
 !-----------------------------------------------------------------------------
 ! commom.control
index 11382e2..873f053 100644 (file)
       real(kind=8),dimension(:),allocatable :: utheta,ugamma,uscdiff !(maxfrag_back)
       real(kind=8),dimension(:,:,:),allocatable :: wfrag_back !(3,maxfrag_back,maxprocs/20)
       integer,dimension(:,:,:),allocatable :: ifrag_back !(3,maxfrag_back,maxprocs/20)
-!      common /qmeas/
-      real(kind=8),dimension(50) :: qfrag
-      real(kind=8),dimension(100) :: qpair
-      real(kind=8),dimension(:,:),allocatable :: qinfrag,wfrag !(50,maxprocs/20)
-      real(kind=8),dimension(:,:),allocatable :: qinpair,wpair !(100,maxprocs/20)
-      real(kind=8) :: eq_time,Uconst
-      integer :: iset,nset
-      integer,dimension(:),allocatable :: mset !(maxprocs/20)
-      integer,dimension(:,:,:),allocatable :: ifrag !(2,50,maxprocs/20)
-      integer,dimension(:,:,:),allocatable :: ipair !(2,100,maxprocs/20)
-      integer :: nfrag,npair
-      logical :: usampl
+!      common /qmeas/ in module geometry
 !-----------------------------------------------------------------------------
 ! common.sbridge
 !      common /sbridge/
 !      common/fourier/  z wham
       real(kind=8),dimension(:,:),allocatable :: b !(13,0:maxtor)
 !-----------------------------------------------------------------------------
-! common.var
-! Store the geometric variables in the following COMMON block.
-!      common /var/ in module geometry_data
-! Store the angles and variables corresponding to old conformations (for use
-! in MCM).
-!      common /oldgeo/
-!el      real(kind=8),dimension(:,:),allocatable :: varsave !(maxvar,maxsave)
-!      real(kind=8),dimension(:),allocatable :: esave !(maxsave)
-!      integer,dimension(:),allocatable :: Origin !(maxsave)
-!      integer :: nstore
-! freeze some variables
-!      common /restr/
-      real(kind=8),dimension(:),allocatable :: varall !(maxvar)
-      integer,dimension(:),allocatable :: mask_theta,&
-       mask_phi,mask_side !(maxres)
-      logical :: mask_r
-!-----------------------------------------------------------------------------
 !-----------------------------------------------------------------------------
       end module energy_data
index e6e73d2..5efd1be 100644 (file)
       integer,dimension(:,:),allocatable :: ialph !(maxres,2)
       integer,dimension(:),allocatable :: ivar !(4*maxres2)
       integer :: ntheta,nphi,nside,nvar
+! Store the angles and variables corresponding to old conformations (for use
+! in MCM).
+!      common /oldgeo/
+!el      real(kind=8),dimension(:,:),allocatable :: varsave !(maxvar,maxsave)
+!      real(kind=8),dimension(:),allocatable :: esave !(maxsave)
+!      integer,dimension(:),allocatable :: Origin !(maxsave)
+!      integer :: nstore
+! freeze some variables
+!      common /restr/
+      real(kind=8),dimension(:),allocatable :: varall !(maxvar)
+      integer,dimension(:),allocatable :: mask_theta,&
+       mask_phi,mask_side !(maxres)
+      logical :: mask_r
+!-----------------------------------------------------------------------------
+! common.MD
+!      common /qmeas/
+      real(kind=8),dimension(50) :: qfrag
+      real(kind=8),dimension(100) :: qpair
+      real(kind=8),dimension(:,:),allocatable :: qinfrag,wfrag !(50,maxprocs/20)
+      real(kind=8),dimension(:,:),allocatable :: qinpair,wpair !(100,maxprocs/20)
+      real(kind=8) :: Uconst
+      integer,dimension(:,:,:),allocatable :: ifrag !(2,50,maxprocs/20)
+      integer,dimension(:,:,:),allocatable :: ipair !(2,100,maxprocs/20)
+      integer :: nfrag,npair
 !-----------------------------------------------------------------------------
       integer,dimension(:),allocatable :: itype_pdb !(maxres) initialize in molread
 !-----------------------------------------------------------------------------
index da1a2f4..40153e4 100644 (file)
       subroutine etotal(energia)
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
-      use MD_data, only: totT
+      use MD_data
 #ifndef ISNAN
       external proc_proc
 #ifdef WINPGI
@@ -13324,7 +13324,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
-      use MD_data, only: totT
+      use MD_data, only: totT,usampl,eq_time
 #ifndef ISNAN
       external proc_proc
 #ifdef WINPGI
@@ -14004,7 +14004,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
       use energy_data
-      use MD_data, only: totT
+      use MD_data, only: totT,usampl,eq_time
 #ifdef MPI
       include 'mpif.h'
 #endif
@@ -16174,7 +16174,7 @@ write(iout,*) 'Calling CHECK_ECARTIN else.'
 !-----------------------------------------------------------------------------
       subroutine alloc_ener_arrays
 !EL Allocation of arrays used by module energy
-
+      use MD_data, only: mset
 !el local variables
       integer :: i,j
       
index 19daec7..018dbee 100644 (file)
 
       use geometry_data
       use energy_data
-      use control_data, only:maxtor,maxterm
+      use control_data, only:maxterm !,maxtor
       use MD_data
       use MPI_data
 !el      use map_data
 
 !----------------------------------------------------
       allocate(ithetyp(-ntyp1:ntyp1)) !(-ntyp1:ntyp1)
-      allocate(aa0thet(-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
+      allocate(aa0thet(-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
-      allocate(aathet(ntheterm,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
+      allocate(aathet(ntheterm,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
 !(maxtheterm,-maxthetyp1:maxthetyp1,&
 !        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
-      allocate(bbthet(nsingle,ntheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
-      allocate(ccthet(nsingle,ntheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
-      allocate(ddthet(nsingle,ntheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
-      allocate(eethet(nsingle,ntheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
+      allocate(bbthet(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
+      allocate(ccthet(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
+      allocate(ddthet(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
+      allocate(eethet(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
 !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,&
 !        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
-      allocate(ffthet(ndouble,ndouble,ntheterm3,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
-      allocate(ggthet(ndouble,ndouble,ntheterm3,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
+      allocate(ffthet(ndouble,ndouble,ntheterm3,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
+      allocate(ggthet(ndouble,ndouble,ntheterm3,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
 !(maxdouble,maxdouble,maxtheterm3,-maxthetyp1:maxthetyp1,&
 !        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
 
 !-----------------------------------------------------------------------------
       subroutine openunits
 
-      use energy_data, only: usampl
+      use MD_data, only: usampl
       use csa_data
       use MPI_data
       use control_data, only:out1file
       subroutine readrst
 
       use geometry_data, only: nres,dc
-      use energy_data, only: usampl,iset
       use MD_data
 !      implicit real*8 (a-h,o-z)
 !      include 'DIMENSIONS'
index 8700369..4216238 100644 (file)
       else
 #endif
       if (modecalc.eq.0) then
-!write(iout,*)"!!!!!!!!!!!!!!!!! in unres"
-
         call exec_eeval_or_minim
-!write(iout,*)"!!!!!!!!!!!!!!!!! in unres"
-
       else if (modecalc.eq.1) then
         call exec_regularize
       else if (modecalc.eq.2) then
         call exec_mult_eeval_or_minim
       else if (modecalc.eq.5) then
         call exec_checkgrad
-!write(iout,*) "check grad dwa razy"
-!el        call exec_checkgrad
       else if (ModeCalc.eq.7) then
         call exec_map
       else if (ModeCalc.eq.8) then
         write (iout,'(a)') 'This calculation type is not supported',&
          ModeCalc
       endif
-!elwrite(iout,*)"!!!!!!!!!!!!!!!!!"
 
 #ifdef MPI
       endif
 
        print *,"Processor",myrank," after chainbuild"
        icall=1
-!elwrite(iout,*)"in exec_eeval or minimim"
 
        call etotal_long(energy_long)
        write (iout,*) "Printing long range energy"
        call enerprint(energy_long)
-!elwrite(iout,*)"in exec_eeval or minimim"
 
        call etotal_short(energy_short)
        write (iout,*) "Printing short range energy"
       endif
 
       call etotal(energy_)
-!elwrite(iout,*)"after etotal in exec_eev"
 #ifdef MPI
       time_ene=MPI_Wtime()-time00
 #endif
       etota = energy_(0)
       etot = etota
       call enerprint(energy_)
-!write(iout,*)"after enerprint"
       call hairpin(.true.,nharp,iharp)
-!write(iout,*) "after hairpin"!,hfrag(1,1)
       call secondary2(.true.)
-!write(iout,*) "after secondary2"
       if (minim) then
 !rc overlap test
-!elwrite(iout,*) "after secondary2 minim",minim
         if (overlapsc) then 
           print *, 'Calling OVERLAP_SC'
-!write(iout,*) 'Calling OVERLAP_SC'
           call overlap_sc(fail)
-!write(iout,*) 'after Calling OVERLAP_SC'
         endif 
 
         if (searchsc) then 
         endif 
 
         if (dccart) then
-!write(iout,*) 'CART  calling minim_dc', nvar
           print *, 'Calling MINIM_DC'
 #ifdef MPI
           time1=MPI_WTIME()
           call minim_dc(etot,iretcode,nfun)
 !    call check_ecartint !el
         else 
-!write(iout,*) "indpdb",indpdb
           if (indpdb.ne.0) then 
-!write(iout,*) 'if indpdb', indpdb
             call bond_regular
             call chainbuild
           endif
           call geom_to_var(nvar,varia)
-!write(iout,*) 'po geom to var; calling minimize', nvar
           print *,'Calling MINIMIZE.'
 #ifdef MPI
           time1=MPI_WTIME()
           write (iout,'(a,i20)') '# of energy evaluations:',nfun+1
           write (iout,'(a,f16.3)')'# of energy evaluations/sec:',evals
       else
-!elwrite(iout,*) "after secondary2 minim",minim
         print *,'refstr=',refstr
         if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
-!elwrite(iout,*) "rms_nac"
-!elwrite(iout,*) "before briefout"
         call briefout(0,etot)
-!elwrite(iout,*) "after briefout"
       endif
       if (outpdb) call pdbout(etot,titel(:32),ipdb)
       if (outmol2) call mol2out(etot,titel(:32))
index 46410f1..0c2ecac 100644 (file)
@@ -1,12 +1,12 @@
 ! DO NOT EDIT THIS FILE - IT HAS BEEN GENERATED BY COMPINFO.C
-! 0 0 1263
+! 0 0 1265
       subroutine cinfo
 !      include 'COMMON.IOUNITS'
       use IO_UNITS
       write(iout,*)'++++ Compile info ++++'
-      write(iout,*)'Version 0.0 build 1263'
-      write(iout,*)'compiled Mon Apr 17 12:54:21 2017'
-      write(iout,*)'compiled by adam@piasek4'
+      write(iout,*)'Version 0.0 build 1265'
+      write(iout,*)'compiled Thu Apr 20 14:48:48 2017'
+      write(iout,*)'compiled by emilial@piasek4'
       write(iout,*)'OS name:    Linux '
       write(iout,*)'OS release: 3.2.0-124-generic '
       write(iout,*)'OS version:',&
index fd5f6ca..ecbce9d 100644 (file)
@@ -5,7 +5,7 @@
 !
       use geometry_data, only:nres
       use energy_data
-      use control_data, only:maxthetyp1
+!      use control_data, only:maxthetyp1
       use energy, only:etotal,enerprint,rescale_weights
 #ifdef MPI
       use MPI_data
@@ -704,9 +704,9 @@ write(iout,*)"enecalc_ i ntot",i,ntot
         ithetyp_all(i,iparm)=ithetyp(i)
       enddo
       do iblock=1,2
-      do i=-maxthetyp1,maxthetyp1
-        do j=-maxthetyp1,maxthetyp1
-          do k=-maxthetyp1,maxthetyp1
+      do i=-nthetyp-1,nthetyp+1
+        do j=-nthetyp-1,nthetyp+1
+          do k=-nthetyp-1,nthetyp+1
             aa0thet_all(i,j,k,iblock,iparm)=aa0thet(i,j,k,iblock)
             do l=1,ntheterm
               aathet_all(l,i,j,k,iblock,iparm)=aathet(l,i,j,k,iblock)
@@ -976,9 +976,9 @@ write(iout,*)"end of store_parm"
         ithetyp(i)=ithetyp_all(i,iparm)
       enddo
       do iblock=1,2
-      do i=-maxthetyp1,maxthetyp1
-        do j=-maxthetyp1,maxthetyp1
-          do k=-maxthetyp1,maxthetyp1
+      do i=-nthetyp-1,nthetyp+1
+        do j=-nthetyp-1,nthetyp+1
+          do k=-nthetyp-1,nthetyp+1
             aa0thet(i,j,k,iblock)=aa0thet_all(i,j,k,iblock,iparm)
             do l=1,ntheterm
               aathet(l,i,j,k,iblock)=aathet_all(l,i,j,k,iblock,iparm)
@@ -1608,34 +1608,34 @@ write(iout,*)"end of store_parm"
       allocate(gthet_all(3,-ntyp:ntyp,iparm)) !(3,-ntyp:ntyp,max_parm)
       allocate(theta0_all(-ntyp:ntyp,iparm),&
         sig0_all(-ntyp:ntyp,iparm),sigc0_all(-ntyp:ntyp,nParmSet)) !(-ntyp:ntyp,max_parm)
-      allocate(aa0thet_all(-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,iparm))
+      allocate(aa0thet_all(-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2,iparm))
 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,max_parm)
-      allocate(aathet_all(maxtheterm,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,iparm))
+      allocate(aathet_all(ntheterm,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2,iparm))
 !(maxtheterm,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,max_parm)
-      allocate(bbthet_all(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,iparm))
-      allocate(ccthet_all(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,iparm))
-      allocate(ddthet_all(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,iparm))
-      allocate(eethet_all(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,iparm))
+      allocate(bbthet_all(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2,iparm))
+      allocate(ccthet_all(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2,iparm))
+      allocate(ddthet_all(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2,iparm))
+      allocate(eethet_all(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2,iparm))
 !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,
 !     & -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2,max_parm)
-      allocate(ffthet_all1(maxdouble,maxdouble,maxtheterm3,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,iparm))
-      allocate(ggthet_all1(maxdouble,maxdouble,maxtheterm3,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,iparm))
-      allocate(ffthet_all2(maxdouble,maxdouble,maxtheterm3,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,iparm))
-      allocate(ggthet_all2(maxdouble,maxdouble,maxtheterm3,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,iparm))
+      allocate(ffthet_all1(ndouble,ndouble,ntheterm3,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,iparm))
+      allocate(ggthet_all1(ndouble,ndouble,ntheterm3,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,iparm))
+      allocate(ffthet_all2(ndouble,ndouble,ntheterm3,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,iparm))
+      allocate(ggthet_all2(ndouble,ndouble,ntheterm3,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,iparm))
 !(maxdouble,maxdouble,maxtheterm3,-maxthetyp1:maxthetyp1,&
 !-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,max_parm)
       allocate(dsc_all(ntyp1,iparm),dsc0_all(ntyp1,nParmSet)) !(ntyp1,max_parm)
@@ -1644,33 +1644,33 @@ write(iout,*)"end of store_parm"
       allocate(censc_all(3,maxlob,-ntyp:ntyp,iparm)) !(3,maxlob,-ntyp:ntyp,max_parm)
       allocate(gaussc_all(3,3,maxlob,-ntyp:ntyp,iparm)) !(3,3,maxlob,-ntyp:ntyp,max_parm)
       allocate(sc_parmin_all(65,ntyp,iparm)) !(65,ntyp,max_parm)
-      allocate(v0_all(-maxtor:maxtor,-maxtor:maxtor,2,iparm))
+      allocate(v0_all(-ntortyp:ntortyp,-ntortyp:ntortyp,2,iparm))
 !(-maxtor:maxtor,-maxtor:maxtor,2,max_parm)
-      allocate(v1_all(maxterm,-maxtor:maxtor,-maxtor:maxtor,2,iparm))
-      allocate(v2_all(maxterm,-maxtor:maxtor,-maxtor:maxtor,2,iparm))
+      allocate(v1_all(maxterm,-ntortyp:ntortyp,-ntortyp:ntortyp,2,iparm))
+      allocate(v2_all(maxterm,-ntortyp:ntortyp,-ntortyp:ntortyp,2,iparm))
 !(maxterm,-maxtor:maxtor,-maxtor:maxtor,2,max_parm)
-      allocate(vlor1_all(maxlor,maxtor,maxtor,iparm))
-      allocate(vlor2_all(maxlor,maxtor,maxtor,iparm))
-      allocate(vlor3_all(maxlor,maxtor,maxtor,iparm)) !(maxlor,maxtor,maxtor,max_parm)
-      allocate(v1c_all(2,maxtermd_1,-maxtor:maxtor,-maxtor:maxtor,&
-        -maxtor:maxtor,2,iparm))
-      allocate(v1s_all(2,maxtermd_1,-maxtor:maxtor,-maxtor:maxtor,&
-        -maxtor:maxtor,2,iparm))
+      allocate(vlor1_all(maxlor,ntortyp,ntortyp,iparm))
+      allocate(vlor2_all(maxlor,ntortyp,ntortyp,iparm))
+      allocate(vlor3_all(maxlor,ntortyp,ntortyp,iparm)) !(maxlor,maxtor,maxtor,max_parm)
+      allocate(v1c_all(2,maxtermd_1,-ntortyp:ntortyp,-ntortyp:ntortyp,&
+        -ntortyp:ntortyp,2,iparm))
+      allocate(v1s_all(2,maxtermd_1,-ntortyp:ntortyp,-ntortyp:ntortyp,&
+        -ntortyp:ntortyp,2,iparm))
 !(2,maxtermd_1,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2,max_parm)
-      allocate(v2c_all(maxtermd_2,maxtermd_2,-maxtor:maxtor,&
-        -maxtor:maxtor,-maxtor:maxtor,2,iparm))
+      allocate(v2c_all(maxtermd_2,maxtermd_2,-ntortyp:ntortyp,&
+        -ntortyp:ntortyp,-ntortyp:ntortyp,2,iparm))
 !(maxtermd_2,maxtermd_2,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2,max_parm)
-      allocate(v2s_all(maxtermd_2,maxtermd_2,-maxtor:maxtor,&
-        -maxtor:maxtor,-maxtor:maxtor,2,iparm))
+      allocate(v2s_all(maxtermd_2,maxtermd_2,-ntortyp:ntortyp,&
+        -ntortyp:ntortyp,-ntortyp:ntortyp,2,iparm))
 !(maxtermd_2,maxtermd_2,-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2,max_parm)
-      allocate(b1_all(2,-maxtor:maxtor,iparm))
-      allocate(b2_all(2,-maxtor:maxtor,iparm)) !(2,-maxtor:maxtor,max_parm)
-      allocate(cc_all(2,2,-maxtor:maxtor,iparm))
-      allocate(dd_all(2,2,-maxtor:maxtor,iparm))
-      allocate(ee_all(2,2,-maxtor:maxtor,iparm)) !(2,2,-maxtor:maxtor,max_parm)
-      allocate(ctilde_all(2,2,-maxtor:maxtor,iparm))
-      allocate(dtilde_all(2,2,-maxtor:maxtor,iparm)) !(2,2,-maxtor:maxtor,max_parm)
-      allocate(b1tilde_all(2,-maxtor:maxtor,iparm)) !(2,-maxtor:maxtor,max_parm)
+      allocate(b1_all(2,-nloctyp:nloctyp,iparm))
+      allocate(b2_all(2,-nloctyp:nloctyp,iparm)) !(2,-maxtor:maxtor,max_parm)
+      allocate(cc_all(2,2,-nloctyp:nloctyp,iparm))
+      allocate(dd_all(2,2,-nloctyp:nloctyp,iparm))
+      allocate(ee_all(2,2,-nloctyp:nloctyp,iparm)) !(2,2,-maxtor:maxtor,max_parm)
+      allocate(ctilde_all(2,2,-nloctyp:nloctyp,iparm))
+      allocate(dtilde_all(2,2,-nloctyp:nloctyp,iparm)) !(2,2,-maxtor:maxtor,max_parm)
+      allocate(b1tilde_all(2,-nloctyp:nloctyp,iparm)) !(2,-maxtor:maxtor,max_parm)
       allocate(app_all(2,2,iparm),bpp_all(2,2,nParmSet),&
         ael6_all(2,2,iparm),ael3_all(2,2,nParmSet)) !(2,2,max_parm)
       allocate(aad_all(ntyp,2,iparm),bad_all(ntyp,2,nParmSet)) !(ntyp,2,max_parm)
@@ -1686,13 +1686,13 @@ write(iout,*)"end of store_parm"
       allocate(v2sccor_all(maxterm_sccor,3,-ntyp:ntyp,-ntyp:ntyp,iparm))
 !(maxterm_sccor,3,-ntyp:ntyp,-ntyp:ntyp,max_parm)
       allocate(nlob_all(ntyp1,iparm)) !(ntyp1,max_parm)
-      allocate(nlor_all(-maxtor:maxtor,-maxtor:maxtor,2,iparm))
-      allocate(nterm_all(-maxtor:maxtor,-maxtor:maxtor,2,iparm))
+      allocate(nlor_all(-ntortyp:ntortyp,-ntortyp:ntortyp,2,iparm))
+      allocate(nterm_all(-ntortyp:ntortyp,-ntortyp:ntortyp,2,iparm))
 !(-maxtor:maxtor,-maxtor:maxtor,2,max_parm)
-      allocate(ntermd1_all(-maxtor:maxtor,-maxtor:maxtor,&
-        -maxtor:maxtor,2,iparm))
-      allocate(ntermd2_all(-maxtor:maxtor,-maxtor:maxtor,&
-        -maxtor:maxtor,2,iparm))
+      allocate(ntermd1_all(-ntortyp:ntortyp,-ntortyp:ntortyp,&
+        -ntortyp:ntortyp,2,iparm))
+      allocate(ntermd2_all(-ntortyp:ntortyp,-ntortyp:ntortyp,&
+        -ntortyp:ntortyp,2,iparm))
 !(-maxtor:maxtor,-maxtor:maxtor,-maxtor:maxtor,2,max_parm)
       allocate(nbondterm_all(ntyp,iparm)) !(ntyp,max_parm)
       allocate(ithetyp_all(-ntyp1:ntyp1,iparm)) !(-ntyp1:ntyp1,max_parm)
index 13d4f37..c501d9f 100644 (file)
@@ -4,7 +4,8 @@
       use wham_data
       use io_units
       use io_base, only:ilen
-      use energy_data, only:nnt,nct,nss,ihpb,jhpb,iset
+      use energy_data, only:nnt,nct,nss,ihpb,jhpb
+      use MD_data, only:iset
       use geometry_data, only:nres,c
 #ifdef MPI
       use MPI_data
index 23530b6..399dc1a 100644 (file)
 
       use geometry_data
       use energy_data
-      use control_data, only: maxtor,maxterm,maxlor,maxterm_sccor,&
-          maxtermd_1,maxtermd_2,maxthetyp,maxthetyp1
+      use control_data, only: maxterm,maxlor,maxterm_sccor,& !maxtor
+          maxtermd_1,maxtermd_2 !,maxthetyp,maxthetyp1
       use MD_data
 !el      use MPI_data
 !el      use map_data
@@ -683,27 +683,27 @@ allocate(ww(max_eneW))
 
 !----------------------------------------------------
       allocate(ithetyp(-ntyp1:ntyp1)) !(-ntyp1:ntyp1)
-      allocate(aa0thet(-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
+      allocate(aa0thet(-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
 !(-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
-      allocate(aathet(ntheterm,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
+      allocate(aathet(ntheterm,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
 !(maxtheterm,-maxthetyp1:maxthetyp1,&
 !        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
-      allocate(bbthet(nsingle,ntheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
-      allocate(ccthet(nsingle,ntheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
-      allocate(ddthet(nsingle,ntheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
-      allocate(eethet(nsingle,ntheterm2,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
+      allocate(bbthet(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
+      allocate(ccthet(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
+      allocate(ddthet(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
+      allocate(eethet(nsingle,ntheterm2,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
 !(maxsingle,maxtheterm2,-maxthetyp1:maxthetyp1,&
 !        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2)
-      allocate(ffthet(ndouble,ndouble,ntheterm3,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
-      allocate(ggthet(ndouble,ndouble,ntheterm3,-maxthetyp1:maxthetyp1,&
-        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
+      allocate(ffthet(ndouble,ndouble,ntheterm3,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
+      allocate(ggthet(ndouble,ndouble,ntheterm3,-nthetyp-1:nthetyp+1,&
+        -nthetyp-1:nthetyp+1,-nthetyp-1:nthetyp+1,2))
 !(maxdouble,maxdouble,maxtheterm3,-maxthetyp1:maxthetyp1,&
 !        -maxthetyp1:maxthetyp1,-maxthetyp1:maxthetyp1,2))
 
@@ -713,34 +713,15 @@ allocate(ww(max_eneW))
         ithetyp(i)=-ithetyp(-i)
       enddo
 !      write (iout,*) "tu dochodze"
-      do iblock=1,2
-      do i=-maxthetyp,maxthetyp
-        do j=-maxthetyp,maxthetyp
-          do k=-maxthetyp,maxthetyp
-            aa0thet(i,j,k,iblock)=0.0d0
-            do l=1,ntheterm
-              aathet(l,i,j,k,iblock)=0.0d0
-            enddo
-            do l=1,ntheterm2
-              do m=1,nsingle
-                bbthet(m,l,i,j,k,iblock)=0.0d0
-                ccthet(m,l,i,j,k,iblock)=0.0d0
-                ddthet(m,l,i,j,k,iblock)=0.0d0
-                eethet(m,l,i,j,k,iblock)=0.0d0
-              enddo
-            enddo
-            do l=1,ntheterm3
-              do m=1,ndouble
-                do mm=1,ndouble
-                 ffthet(mm,m,l,i,j,k,iblock)=0.0d0
-                 ggthet(mm,m,l,i,j,k,iblock)=0.0d0
-                enddo
-              enddo
-            enddo
-          enddo
-        enddo
-      enddo
-      enddo
+      aa0thet(:,:,:,:)=0.0d0
+      aathet(:,:,:,:,:)=0.0d0
+      bbthet(:,:,:,:,:,:)=0.0d0
+      ccthet(:,:,:,:,:,:)=0.0d0
+      ddthet(:,:,:,:,:,:)=0.0d0
+      eethet(:,:,:,:,:,:)=0.0d0
+      ffthet(:,:,:,:,:,:,:)=0.0d0
+      ggthet(:,:,:,:,:,:,:)=0.0d0
+
       do iblock=1,2
       do i=0,nthetyp
         do j=-nthetyp,nthetyp