Skip to content

Commit

Permalink
Exit early if no dofs.
Browse files Browse the repository at this point in the history
  • Loading branch information
raback committed Oct 17, 2024
1 parent 74348ff commit 5b9e798
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 8 deletions.
17 changes: 12 additions & 5 deletions fem/src/SolverUtils.F90
Original file line number Diff line number Diff line change
Expand Up @@ -10306,7 +10306,7 @@ FUNCTION ComputeNorm(Solver, nin, values) RESULT (Norm)
INTEGER, POINTER :: Perm(:)

CALL Info('ComputeNorm','Computing norm of solution',Level=10)

IF(PRESENT(values)) THEN
x => values
ELSE
Expand Down Expand Up @@ -10440,8 +10440,10 @@ FUNCTION ComputeNorm(Solver, nin, values) RESULT (Norm)
totn = totn + 1
END DO
END SELECT

totn = ParallelReduction(totn)
IF(totn == 0) GOTO 10

nscale = 1.0_dp * totn

SELECT CASE(NormDim)
Expand All @@ -10456,9 +10458,11 @@ FUNCTION ComputeNorm(Solver, nin, values) RESULT (Norm)
END SELECT

ELSE IF( NormDofs < Dofs ) THEN
Norm = 0.0_dp
totn = ParallelReduction(n)
IF(totn == 0) GOTO 10

nscale = NormDOFs*totn/(1._dp*DOFs)
Norm = 0.0_dp

SELECT CASE(NormDim)
CASE(0)
Expand Down Expand Up @@ -10526,7 +10530,9 @@ FUNCTION ComputeNorm(Solver, nin, values) RESULT (Norm)
END IF

ELSE
val = 0.0_dp
Norm = 0.0_dp
IF(n==0) GOTO 10

SELECT CASE(NormDim)
CASE(0)
Norm = MAXVAL(ABS(x(1:n)))
Expand All @@ -10539,7 +10545,7 @@ FUNCTION ComputeNorm(Solver, nin, values) RESULT (Norm)
END SELECT
END IF

IF( ComponentsAllocated ) THEN
10 IF( ComponentsAllocated ) THEN
DEALLOCATE( NormComponents )
END IF
!------------------------------------------------------------------------------
Expand Down Expand Up @@ -10896,6 +10902,7 @@ SUBROUTINE ComputeChange(Solver,SteadyState,nsize,values,values0,Matrix,RHS)
! The norm should be bounded in order to reach convergence
!--------------------------------------------------------------------------
IF( Norm /= Norm ) THEN
PRINT *,'Norm:',Norm,PrevNorm, n
CALL NumericalError(Caller,'Norm of solution appears to be NaN')
END IF

Expand Down
7 changes: 4 additions & 3 deletions fem/src/Types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -223,7 +223,7 @@ MODULE Types
DiagScaling(:) => NULL(), TValues(:) => NULL(), Values_im(:) => NULL()

REAL(KIND=dp), ALLOCATABLE :: extraVals(:)
REAL(KIND=dp) :: RhsScaling=1.0, AveScaling=1.0
REAL(KIND=dp) :: RhsScaling=1.0_dp, AveScaling=1.0_dp
INTEGER :: ScalingMethod = 0
REAL(KIND=dp), POINTER CONTIG :: MassValues(:)=>NULL(),DampValues(:)=>NULL(), &
BulkValues(:)=>NULL(), BulkMassValues(:)=>NULL(), BulkDampValues(:)=>NULL(), &
Expand Down Expand Up @@ -610,7 +610,8 @@ MODULE Types
INTEGER :: DOFs = 0
INTEGER, POINTER :: Perm(:) => NULL()
LOGICAL :: PeriodicFlipActive = .FALSE.
REAL(KIND=dp) :: Norm=0, PrevNorm=0,NonlinChange=0, SteadyChange=0
REAL(KIND=dp) :: Norm=0.0_dp, PrevNorm=0.0_dp,&
NonlinChange=0.0_dp, SteadyChange=0.0_dp
INTEGER :: NonlinConverged=-1, SteadyConverged=-1, NonlinIter=-1
INTEGER :: LinConverged=-1
COMPLEX(KIND=dp), POINTER :: EigenValues(:) => NULL(), &
Expand All @@ -631,7 +632,7 @@ MODULE Types
!------------------------------------------------------------------------------
TYPE ListMatrixEntry_t
INTEGER :: Index = -1
REAL(KIND=dp) :: val = 0.0
REAL(KIND=dp) :: val = 0.0_dp
TYPE(ListMatrixEntry_t), POINTER :: Next => NULL()
END TYPE ListMatrixEntry_t

Expand Down

0 comments on commit 5b9e798

Please sign in to comment.