Skip to content

Commit

Permalink
[skip ci] Add some code to locate whether we crash in gcr allocation.
Browse files Browse the repository at this point in the history
  • Loading branch information
raback committed Oct 29, 2024
1 parent 616cdb1 commit faa2394
Showing 1 changed file with 15 additions and 9 deletions.
24 changes: 15 additions & 9 deletions fem/src/IterativeMethods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1205,6 +1205,9 @@ SUBROUTINE itermethod_gcr( xvec, rhsvec, &

REAL(KIND=dp), POINTER :: x(:),b(:)

CALL Info('Itermetod_gcr','Starting GCR iteration',Level=25)


ndim = HUTI_NDIM
Rounds = HUTI_MAXIT
MinIter = HUTI_MINIT
Expand Down Expand Up @@ -1944,6 +1947,8 @@ SUBROUTINE itermethod_z_gcr( xvec, rhsvec, &
INTEGER :: Rounds, OutputInterval
REAL(KIND=dp) :: MinTol, MaxTol, Residual
LOGICAL :: Converged, Diverged, UseStopCFun

CALL Info('Itermetod_z_gcr','Starting GCR iteration',Level=25)

ndim = HUTI_NDIM
Rounds = HUTI_MAXIT
Expand Down Expand Up @@ -1989,27 +1994,28 @@ SUBROUTINE GCR_Z( n, A, x, b, Rounds, MinTolerance, MaxTolerance, Residual, &
LOGICAL :: Converged, Diverged
REAL(KIND=dp) :: MinTolerance, MaxTolerance, Residual
INTEGER :: n, OutputInterval, m
!------------------------------------------------------------------------------
REAL(KIND=dp) :: bnorm,rnorm
COMPLEX(KIND=dp), ALLOCATABLE :: R(:)

COMPLEX(KIND=dp), ALLOCATABLE :: S(:,:), V(:,:), T1(:), T2(:)

!------------------------------------------------------------------------------
INTEGER :: i,j,k,allocstat
COMPLEX(KIND=dp) :: beta
COMPLEX(KIND=dp) :: beta, czero
REAL(KIND=dp) :: alpha, trueresnorm, normerr
COMPLEX(KIND=dp) :: trueres(n)
COMPLEX(KIND=dp), ALLOCATABLE :: trueres(:)
!------------------------------------------------------------------------------

ALLOCATE( R(n), T1(n), T2(n) )
IF ( m > 1 ) THEN
ALLOCATE( R(n), T1(n), T2(n), trueres(n), STAT=allocstat )
IF( allocstat /= 0) &
CALL Fatal('GCR_Z','Failed to allocate memory of size: '//I2S(n))
IF ( m > 1 ) THEN
ALLOCATE( S(n,m-1), V(n,m-1), STAT=allocstat )
IF ( allocstat /= 0 ) THEN
CALL Fatal('GCR_Z','Failed to allocate memory of size: '&
//I2S(n)//' x '//I2S(m-1))
END IF
V(1:n,1:m-1) = CMPLX( 0.0d0, 0.0d0, kind=dp)
S(1:n,1:m-1) = CMPLX( 0.0d0, 0.0d0, kind=dp)
czero = CMPLX( 0.0_dp, 0.0_dp )
V(1:n,1:m-1) = czero
S(1:n,1:m-1) = czero
END IF

CALL matvecsubr( x, r, ipar )
Expand Down

0 comments on commit faa2394

Please sign in to comment.