corrections of max... ranges of arrays
[unres4.git] / source / wham / io_wham.f90
index eaea35f..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
@@ -1929,7 +1910,7 @@ enddo
         return 1
       endif
       call readi(controlcard,"NPARMSET",nparmset,1)
-write(iout,*)"in read_gen data"
+!elwrite(iout,*)"in read_gen data"
       separate_parset = index(controlcard,"SEPARATE_PARSET").gt.0
       call readi(controlcard,"IPARMPRINT",iparmprint,1)
       write (iout,*) "PARMPRINT",iparmprint
@@ -1938,7 +1919,7 @@ write(iout,*)"in read_gen data"
           nparmset, Max_Parm
         return 1
       endif
-write(iout,*)"in read_gen data"
+!elwrite(iout,*)"in read_gen data"
       call readi(controlcard,"MAXIT",maxit,5000)
       call reada(controlcard,"FIMIN",fimin,1.0d-3)
       call readi(controlcard,"ENSEMBLES",ensembles,0)
@@ -1948,7 +1929,7 @@ write(iout,*)"in read_gen data"
       call multreadi(controlcard,"ISAMPL",isampl,nparmset,1)
       write (iout,*) "MaxSlice",MaxSlice
       call readi(controlcard,"NSLICE",nslice,1)
-write(iout,*)"in read_gen data"
+!elwrite(iout,*)"in read_gen data"
       call flush(iout)
       if (nslice.gt.MaxSlice) then
         write (iout,*) "Error: parameter out of range: NSLICE",nslice,&
@@ -2358,7 +2339,7 @@ write(iout,*)"in read_gen data"
 !el      integer ilen
 !el      external ilen
       integer :: i,j,k
-write(iout,*)"jestesmy w read_compar"
+!elwrite(iout,*)"jestesmy w read_compar"
       call card_concat(controlcard,.true.)
       pdbref=(index(controlcard,'PDBREF').gt.0)
       call reada(controlcard,'CUTOFF_UP',rmscut_base_up,4.0d0)
@@ -2562,8 +2543,9 @@ write(iout,*)"jestesmy w read_compar"
         do i=1,nres
           itype_pdb(i)=itype(i)
         enddo
-write(iout,*)"jestesmy przed readpdb"
+
         call readpdb
+
         do i=1,nres
           iaux=itype_pdb(i)
           itype_pdb(i)=itype(i)