Skip to content

Commit

Permalink
Fix memory leak in reduced dg scheme when running in parallel + some …
Browse files Browse the repository at this point in the history
…cosmetic changes.
  • Loading branch information
Juha Ruokolainen committed Dec 13, 2024
1 parent 82a3231 commit e97ae12
Show file tree
Hide file tree
Showing 3 changed files with 31 additions and 16 deletions.
20 changes: 19 additions & 1 deletion fem/src/ElementUtils.F90
Original file line number Diff line number Diff line change
Expand Up @@ -177,6 +177,7 @@ END SUBROUTINE SolveTrilinos4
IF(ASSOCIATED(Matrix % ParallelInfo)) THEN
IF(ASSOCIATED(Matrix % ParallelInfo % GlobalDOFs)) DEALLOCATE(Matrix % ParallelInfo % GlobalDOFs)
IF(ASSOCIATED(Matrix % ParallelInfo % GInterface)) DEALLOCATE(Matrix % ParallelInfo % GInterface)
IF(ASSOCIATED(Matrix % ParallelInfo % Gorder)) DEALLOCATE(Matrix % ParallelInfo % GOrder)

IF(ASSOCIATED(Matrix % ParallelInfo % NeighbourList)) THEN
DO i=1,SIZE(Matrix % ParallelInfo % NeighbourList)
Expand All @@ -185,10 +186,27 @@ END SUBROUTINE SolveTrilinos4
END DO
DEALLOCATE(Matrix % ParallelInfo % NeighbourList)
END IF
IF(ASSOCIATED(Matrix % ParallelInfo % Gorder)) DEALLOCATE(Matrix % ParallelInfo % GOrder)

IF(ASSOCIATED(Matrix % ParallelInfo % FaceNeighbourList)) THEN
DO i=1,SIZE(Matrix % ParallelInfo % FaceNeighbourList)
IF (ASSOCIATED(Matrix % ParallelInfo % FaceNeighbourList(i) % Neighbours)) &
DEALLOCATE(Matrix % ParallelInfo % FaceNeighbourList(i) % Neighbours)
END DO
DEALLOCATE(Matrix % ParallelInfo % FaceNeighbourList)
END IF
IF(ASSOCIATED(Matrix % ParallelInfo % FaceInterface)) DEALLOCATE(Matrix % ParallelInfo % FaceInterface)

IF(ASSOCIATED(Matrix % ParallelInfo % EdgeNeighbourList)) THEN
DO i=1,SIZE(Matrix % ParallelInfo % EdgeNeighbourList)
IF (ASSOCIATED(Matrix % ParallelInfo % EdgeNeighbourList(i) % Neighbours)) &
DEALLOCATE(Matrix % ParallelInfo % EdgeNeighbourList(i) % Neighbours)
END DO
DEALLOCATE(Matrix % ParallelInfo % EdgeNeighbourList)
END IF
IF(ASSOCIATED(Matrix % ParallelInfo % EdgeInterface)) DEALLOCATE(Matrix % ParallelInfo % EdgeInterface)
DEALLOCATE(Matrix % ParallelInfo)
END IF


p=>Matrix % ParMatrix
IF(ASSOCIATED(p)) THEN
Expand Down
16 changes: 6 additions & 10 deletions fem/src/ParallelUtils.F90
Original file line number Diff line number Diff line change
Expand Up @@ -166,9 +166,10 @@ SUBROUTINE ParallelInitMatrix( Solver, Matrix, inPerm )
END IF
END DO

ALLOCATE( Matrix % ParallelInfo )

IF ( .NOT. Matrix % DGMatrix ) THEN
n = Matrix % NumberOfRows
ALLOCATE( Matrix % ParallelInfo )
ALLOCATE( Matrix % ParallelInfo % NeighbourList(n) )
CALL AllocateVector( Matrix % ParallelInfo % GInterface, n)
CALL AllocateVector( Matrix % ParallelInfo % GlobalDOFs, n)
Expand Down Expand Up @@ -511,10 +512,7 @@ SUBROUTINE ParallelInitMatrix( Solver, Matrix, inPerm )
ELSE

MeshPI => Solver % Mesh % ParallelInfo

ALLOCATE( Matrix % ParallelInfo )
MatrixPI => Matrix % ParallelInfo

#if 0
n = 0
DO i=1,Mesh % NumberOfBulkElements
Expand All @@ -536,9 +534,8 @@ SUBROUTINE ParallelInitMatrix( Solver, Matrix, inPerm )
IF( DGReduced ) THEN
BLOCK
INTEGER, POINTER :: DgMap(:), DgMaster(:), DgSlave(:)
LOGICAL :: GotDgMap, GotMaster, GotSlave
INTEGER :: group0, group
LOGICAL, ALLOCATABLE :: Tagged(:)
LOGICAL :: GotDgMap, GotMaster, GotSlave

DgMap => ListGetIntegerArray( Solver % Values,'DG Reduced Basis Mapping',GotDgMap )
DgMaster => ListGetIntegerArray( Solver % Values,'DG Reduced Basis Master Bodies',GotMaster )
Expand Down Expand Up @@ -633,10 +630,11 @@ SUBROUTINE ParallelInitMatrix( Solver, Matrix, inPerm )

MeshN => MeshPI % NeighbourList(L)
MtrxN => MatrixPI % NeighbourList(K)

MatrixPI % GInterface(k) = .TRUE.

IF( ASSOCIATED(MtrxN % Neighbours) ) DEALLOCATE(MtrxN % Neighbours)
CALL AllocateVector( MtrxN % Neighbours, SIZE(MeshN % Neighbours) )

MtrxN % Neighbours = MeshN % Neighbours
IF(.NOT.DGReduced) THEN ! ?
DO m=1,SIZE(MeshN % Neighbours)
Expand Down Expand Up @@ -695,9 +693,7 @@ SUBROUTINE ParallelInitMatrix( Solver, Matrix, inPerm )
END IF
END BLOCK


Matrix % ParMatrix => &
ParInitMatrix( Matrix, Matrix % ParallelInfo )
Matrix % ParMatrix => ParInitMatrix( Matrix, Matrix % ParallelInfo )

!if(parenv%mype==0) print*,'MATRIX INIT TIME: ', realtime()-tt
#endif
Expand Down
11 changes: 6 additions & 5 deletions fem/src/SolverUtils.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15011,7 +15011,6 @@ END SUBROUTINE BlockSolveExt
END IF
END IF


CONTAINS


Expand Down Expand Up @@ -18945,10 +18944,13 @@ RECURSIVE SUBROUTINE SolveWithLinearRestriction( StiffMatrix, ForceVector, &
TYPE(ValueList_t), POINTER :: Params
CHARACTER(*), PARAMETER :: Caller = 'SolveWithLinearRestriction'

TYPE(ParEnv_t), POINTER :: ParEnvSave

SAVE MultiplierValues, SolverPointer

!------------------------------------------------------------------------------
CALL Info( Caller, ' ', Level=12 )
ParEnvSave => ParEnv

SolverPointer => Solver
Params => Solver % Values
Expand Down Expand Up @@ -19003,7 +19005,7 @@ RECURSIVE SUBROUTINE SolveWithLinearRestriction( StiffMatrix, ForceVector, &
ELSE
DEALLOCATE(CollectionMatrix % RHS)
CollectionMatrix % Values = 0.0_dp

IF(NeedMassDampValues) THEN
IF(ASSOCIATED(CollectionMatrix % MassValues)) CollectionMatrix % MassValues = 0.0_dp
IF(ASSOCIATED(CollectionMatrix % DampValues)) CollectionMatrix % DampValues = 0.0_dp
Expand Down Expand Up @@ -19320,7 +19322,6 @@ RECURSIVE SUBROUTINE SolveWithLinearRestriction( StiffMatrix, ForceVector, &
END IF
END IF


IF(CollectionMatrix % FORMAT==MATRIX_LIST) THEN
CALL Info(Caller,'Reverting CollectionMatrix back to CRS matrix',Level=10)
CALL List_toCRSMatrix(CollectionMatrix)
Expand Down Expand Up @@ -19567,13 +19568,13 @@ RECURSIVE SUBROUTINE SolveWithLinearRestriction( StiffMatrix, ForceVector, &
CALL ComputeChange(Solver,.FALSE.,StiffMatrix % NumberOfRows,Matrix=StiffMatrix,Rhs=ForceVector)
END IF

StiffMatrix % CollectionMatrix => CollectionMatrix
DEALLOCATE(CollectionSolution)
CollectionMatrix % ConstraintMatrix => NULL()
StiffMatrix % CollectionMatrix => CollectionMatrix

ParEnv => ParEnvSave

CALL Info( Caller, 'All done', Level=10 )

CONTAINS


Expand Down

0 comments on commit e97ae12

Please sign in to comment.