Skip to content

Commit

Permalink
Fix post merge and the changing of ParEnv to a pointer to the ParMatr…
Browse files Browse the repository at this point in the history
…ix. We need to create (at least?) one parmatrix during interpolation. It needs to be created on matrix present on bulk in all parts. Not sure this is the best solution...
  • Loading branch information
iwheel committed Dec 19, 2024
1 parent 9bace4f commit 602da8a
Showing 1 changed file with 24 additions and 2 deletions.
26 changes: 24 additions & 2 deletions elmerice/Solvers/CalvingGeometry.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3491,14 +3491,15 @@ SUBROUTINE SwitchMesh(Model, Solver, OldMesh, NewMesh)
TYPE(Matrix_t), POINTER :: WorkMatrix=>NULL()
LOGICAL :: Found, Global, GlobalBubbles, Debug, DoPrevValues, &
NoMatrix, DoOptimizeBandwidth, PrimaryVar, HasValuesInPartition, &
PrimarySolver
PrimarySolver,CreatedParMatrix
LOGICAL, POINTER :: UnfoundNodes(:)=>NULL(), BulkUnfoundNodes(:)=>NULL()
INTEGER :: i,j,k,DOFs, nrows,n, dummyint
INTEGER :: i,j,k,DOFs, nrows,n, dummyint, ierr
INTEGER, POINTER :: WorkPerm(:)=>NULL(), SolversToIgnore(:)=>NULL(), &
SurfaceMaskPerm(:)=>NULL(), BottomMaskPerm(:)=>NULL()
REAL(KIND=dp), POINTER :: WorkReal(:)=>NULL(), WorkReal2(:)=>NULL(), PArray(:,:) => NULL()
REAL(KIND=dp) :: FrontOrientation(3), RotationMatrix(3,3), UnRotationMatrix(3,3), &
globaleps, localeps
LOGICAL, ALLOCATABLE :: PartActive(:)
CHARACTER(LEN=MAX_NAME_LEN) :: SolverName, WorkName

INTERFACE
Expand Down Expand Up @@ -3557,6 +3558,10 @@ END SUBROUTINE InterpolateMeshToMesh
!----------------------------------------------

Var => OldMesh % Variables

ALLOCATE(PartActive(ParEnv % PEs))
CreatedParMatrix = .FALSE.

DO WHILE( ASSOCIATED(Var) )

DoPrevValues = ASSOCIATED(Var % PrevValues)
Expand Down Expand Up @@ -3635,6 +3640,9 @@ END SUBROUTINE InterpolateMeshToMesh
END IF
END IF

IF(.NOT. CreatedParMatrix) &
CALL MPI_AllGather(.NOT. NoMatrix, 1, MPI_LOGICAL, PartActive, 1, MPI_LOGICAL, ELMER_COMM_WORLD, ierr)

IF ( ASSOCIATED(Var % EigenValues) ) THEN
n = SIZE(Var % EigenValues)

Expand Down Expand Up @@ -3678,6 +3686,20 @@ END SUBROUTINE InterpolateMeshToMesh
IF(ASSOCIATED(WorkSolver % Matrix)) CALL FreeMatrix(WorkSolver % Matrix)
WorkSolver % Matrix => WorkMatrix

! bit of a hack
! since ParEnv become a pointer to ParMatrix we need to ensure one ParMatrix is formed
! it needs to be from a solver present on all parts hence the all gather further up.
! it seems we only need to this once per timestep/interpolation as ParEnv will have some thing
! to point to. If we don't do this ParEnv % PEs, % MyPE etc. all become nans mucking eveything up!
IF ( ASSOCIATED(WorkSolver % Matrix) .and. ALL(PartActive) .and. .NOT. CreatedParMatrix) THEN
IF (.NOT. ASSOCIATED(WorkSolver % Matrix % ParMatrix) ) THEN
WorkSolver % Mesh => NewMesh

CALL ParallelInitMatrix( WorkSolver, WorkSolver % Matrix, WorkPerm)
CreatedParMatrix = .TRUE.
END IF
END IF

NULLIFY(WorkMatrix)

!NOTE: We don't switch Solver % Variable here, because
Expand Down

0 comments on commit 602da8a

Please sign in to comment.