Skip to content

Commit

Permalink
Merge branch 'fix.mpi.off.hdg' into 'master.dev'
Browse files Browse the repository at this point in the history
Fixed MPI=OFF compilation for HDG and removed warnings.

See merge request piclas/piclas!779
  • Loading branch information
pnizenkov committed Feb 20, 2023
2 parents b14d943 + b2c5287 commit 5632b3c
Showing 1 changed file with 9 additions and 4 deletions.
13 changes: 9 additions & 4 deletions src/io_hdf5/hdf5_output_state.f90
Original file line number Diff line number Diff line change
Expand Up @@ -82,11 +82,11 @@ SUBROUTINE WriteStateToHDF5(MeshFileName,OutputTime,PreviousTime)
#endif /*PP_nVar*/
USE MOD_Mesh_Vars ,ONLY: nSides
USE MOD_Utils ,ONLY: QuickSortTwoArrays
USE MOD_Mesh_Vars ,ONLY: lastInnerSide
USE MOD_Mappings ,ONLY: CGNS_SideToVol2
USE MOD_Utils ,ONLY: Qsort1DoubleInt1PInt
USE MOD_Mesh_Tools ,ONLY: LambdaSideToMaster
#if USE_MPI
USE MOD_Mesh_Vars ,ONLY: lastInnerSide
USE MOD_MPI_Vars ,ONLY: OffsetMPISides_rec,nNbProcs,nMPISides_rec,nbProc
USE MOD_Mesh_Tools ,ONLY: GetMasteriLocSides
#endif /*USE_MPI*/
Expand Down Expand Up @@ -159,10 +159,12 @@ SUBROUTINE WriteStateToHDF5(MeshFileName,OutputTime,PreviousTime)
INTEGER :: iSide
INTEGER :: iGlobSide
INTEGER,ALLOCATABLE :: SortedUniqueSides(:),GlobalUniqueSideID_tmp(:)
#if USE_MPI
LOGICAL,ALLOCATABLE :: OutputSide(:)
INTEGER :: SideID_start, SideID_end,iNbProc,SendID
#endif /*USE_MPI*/
REAL,ALLOCATABLE :: SortedLambda(:,:,:) ! lambda, ((PP_N+1)^2,nSides)
INTEGER :: SortedOffset,SortedStart,SortedEnd
INTEGER :: SideID_start, SideID_end,iNbProc,SendID
#ifdef PARTICLES
INTEGER :: i,j,k,iElem
#endif /*PARTICLES*/
Expand Down Expand Up @@ -357,12 +359,14 @@ SUBROUTINE WriteStateToHDF5(MeshFileName,OutputTime,PreviousTime)
! Set side ID in processor local list
iSide = SortedUniqueSides(iGlobSide)

#if USE_MPI
! Skip sides that are not processed by the current proc
IF(nProcessors.GT.1)THEN
! Check if a side belongs to me (all BC and inner sides automatically included); at MPI interfaces the smaller rank wins and
! must output the data, because for these sides it is ambiguous
IF(.NOT.OutputSide(iSide)) CYCLE
END IF ! nProcessors.GT.1
#endif /*USE_MPI*/

CALL LambdaSideToMaster(iSide,SortedLambda(:,:,iGlobSide))

Expand All @@ -376,7 +380,9 @@ SUBROUTINE WriteStateToHDF5(MeshFileName,OutputTime,PreviousTime)
! Get offset and min/max index in sorted list
SortedStart = 1
SortedEnd = nSides
SortedOffset = 0 ! initialize

#if USE_MPI
IF(nProcessors.GT.1)THEN
SortedOffset=HUGE(1)
DO iSide = 1, nSides
Expand All @@ -390,9 +396,8 @@ SUBROUTINE WriteStateToHDF5(MeshFileName,OutputTime,PreviousTime)
END DO
SortedOffset = SortedOffset-1
DEALLOCATE(OutputSide)
ELSE
SortedOffset = 0
END IF ! nProcessors.GT.1
#endif /*USE_MPI*/

ASSOCIATE( nOutputSides => INT(SortedEnd-SortedStart+1,IK) ,&
SortedOffset => INT(SortedOffset,IK) ,&
Expand Down

0 comments on commit 5632b3c

Please sign in to comment.