Fivediag debugg
[unres4.git] / source / unres / MD.f90
index 1ddffac..196d5a0 100644 (file)
       real(kind=8),dimension(:,:),allocatable :: ginvfric !(2*nres,2*nres) !maxres2=2*maxres
 !-----------------------------------------------------------------------------
 !      common /przechowalnia/ subroutine: setup_fricmat
-!el      real(kind=8),dimension(:,:),allocatable :: fcopy !(2*nres,2*nres)
+      real(kind=8),dimension(:,:),allocatable :: fcopy !(2*nres,2*nres)
 !-----------------------------------------------------------------------------
 !
 !
       integer :: rstcount      !ilen,
 !el      external ilen
 !el      real(kind=8),dimension(6*nres) :: stochforcvec         !(MAXRES6) maxres6=6*maxres
-      real(kind=8),dimension(6*nres,2*nres) :: Bmat,GBmat,Tmat !(MAXRES6,MAXRES2) (maxres2=2*maxres,maxres6=6*maxres)
-      real(kind=8),dimension(2*nres,2*nres) :: Cmat_,Cinv      !(maxres2,maxres2) maxres2=2*maxres
-      real(kind=8),dimension(6*nres,6*nres) :: Pmat    !(maxres6,maxres6) maxres6=6*maxres
+!      real(kind=8),dimension(6*nres,2*nres) :: Bmat,GBmat,Tmat        !(MAXRES6,MAXRES2) (maxres2=2*maxres,maxres6=6*maxres)
+!      real(kind=8),dimension(2*nres,2*nres) :: Cmat_,Cinv     !(maxres2,maxres2) maxres2=2*maxres
+!      real(kind=8),dimension(6*nres,6*nres) :: Pmat   !(maxres6,maxres6) maxres6=6*maxres
+      real(kind=8),dimension(:,:),allocatable :: Bmat,GBmat,Tmat       !(MAXRES6,MAXRES2) (maxres2=2*maxres,maxres6=6*maxres)
+      real(kind=8),dimension(:,:),allocatable :: Cmat_,Cinv    !(maxres2,maxres2) maxres2=2*maxres
+      real(kind=8),dimension(:,:),allocatable :: Pmat  !(maxres6,maxres6) maxres6=6*maxres
       real(kind=8),dimension(6*nres) :: Td     !(maxres6) maxres6=6*maxres
       real(kind=8),dimension(2*nres) :: ppvec  !(maxres2) maxres2=2*maxres
 !el      common /stochcalc/ stochforcvec
       logical :: osob
       nres2=2*nres
       nres6=6*nres
+      allocate(Bmat(6*nres,2*nres),GBmat(6*nres,2*nres),Tmat(6*nres,2*nres))
+      allocate(Cmat_(2*nres,2*nres),Cinv(2*nres,2*nres))
+      allocate(Pmat(6*nres,6*nres))
 
       if (.not.allocated(stochforcvec)) allocate(stochforcvec(nres6))  !(MAXRES6) maxres6=6*maxres
 
 #else
       tt0 = tcpu()
 #endif
-       print *,"just befor setup matix"
+       print *,"just befor setup matix",nres
 ! Determine the inverse of the inertia matrix.
       call setup_MD_matrices
 ! Initialize MD
         stop
 #endif
       else if (lang.eq.1 .or. lang.eq.4) then
+        print *,"before setup_fricmat"
         call setup_fricmat
+        print *,"after setup_fricmat"
       endif
 #ifdef MPI
       t_langsetup=MPI_Wtime()-tt0
         enddo
          mnum=molnum(i)
          if (itype(i,1).ne.10 .and. itype(i,mnum).ne.ntyp1_molec(mnum)&
-          .and.(mnum.ne.5))
+          .and.(mnum.ne.5)) then
           do k=1,3
             d_t(k,j+nres)=d_t_work(ind)
             ind=ind+1
 !        if (itype(i,1).eq.10) then
          mnum=molnum(i)
          if (itype(i,1).eq.10 .or. itype(i,mnum).eq.ntyp1_molec(mnum)&
-          .or.(mnum.eq.5))
+          .or.(mnum.eq.5)) then
           do j=1,3
             d_t(j,i)=d_t(j,i+1)-d_t(j,i)
           enddo
       logical :: lprn = .false.
       real(kind=8) :: dtdi !el ,gamvec(2*nres)
 !el      real(kind=8),dimension(2*nres,2*nres) :: ginvfric,fcopy
-      real(kind=8),dimension(2*nres,2*nres) :: fcopy
+!      real(kind=8),allocatable,dimension(:,:) :: fcopy
 !el      real(kind=8),dimension(2*nres*(2*nres+1)/2) :: Ghalf   !(mmaxres2) (mmaxres2=(maxres2*(maxres2+1)/2))
 !el      common /syfek/ gamvec
       real(kind=8) :: work(8*2*nres)
       integer :: iwork(2*nres)
 !el      common /przechowalnia/ ginvfric,Ghalf,fcopy
       integer :: ii,iti,k,l,nzero,nres2,nres6,ierr,mnum
+      nres2=2*nres
+      nres6=6*nres
 #ifdef MPI
+      if(.not.allocated(fricmat)) allocate(fricmat(nres2,nres2))
+       if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2)) !maxres2=2*maxres
       if (fg_rank.ne.king) goto 10
 #endif
-      nres2=2*nres
-      nres6=6*nres
+!      nres2=2*nres
+!      nres6=6*nres
 
       if(.not.allocated(gamvec)) allocate(gamvec(nres2)) !(MAXRES2)
       if(.not.allocated(ginvfric)) allocate(ginvfric(nres2,nres2)) !maxres2=2*maxres
-!el      if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2)) !maxres2=2*maxres
+       if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2)) !maxres2=2*maxres
 !el      allocate(fcopy(nres2,nres2)) !maxres2=2*maxres
       if(.not.allocated(Ghalf)) allocate(Ghalf(nres2*(nres2+1)/2)) !maxres2=2*maxres
 
-!el      if(.not.allocated(fricmat)) allocate(fricmat(nres2,nres2))
+      if(.not.allocated(fricmat)) allocate(fricmat(nres2,nres2))
 !  Zeroing out fricmat
       do i=1,dimen
         do j=1,dimen
       allocate(flag_stoch(0:maxflag_stoch)) !(0:maxflag_stoch)
 #endif
 
-!el      if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2))
+      if(.not.allocated(fcopy)) allocate(fcopy(nres2,nres2))
 !----------------------
 ! commom.hairpin in CSA module
 !----------------------