Skip to content

Commit

Permalink
Extend "ParalledReduction" also for complex values.
Browse files Browse the repository at this point in the history
  • Loading branch information
raback committed Aug 3, 2023
1 parent b72e8ce commit 3442c3c
Show file tree
Hide file tree
Showing 2 changed files with 65 additions and 3 deletions.
35 changes: 32 additions & 3 deletions fem/src/ParallelUtils.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ MODULE ParallelUtils
IMPLICIT NONE

INTERFACE ParallelReduction
MODULE PROCEDURE ParallelReductionR, ParallelReductionI
MODULE PROCEDURE ParallelReductionR, ParallelReductionI, ParallelReductionZ
END INTERFACE ParallelReduction

CONTAINS
Expand Down Expand Up @@ -1317,7 +1317,7 @@ FUNCTION ParallelReductionI(i,oper_arg) RESULT(isum)
ELSE
oper = 0
END IF

IF (.NOT.ASSOCIATED(ParEnv % Active)) &
CALL ParallelActive(.TRUE.)
CALL SparActiveSUMInt(isum,oper)
Expand All @@ -1327,7 +1327,36 @@ FUNCTION ParallelReductionI(i,oper_arg) RESULT(isum)
END FUNCTION ParallelReductionI
!-------------------------------------------------------------------------------



!------------------------------------------------------------------------------
! Same as previous byt for complex values.
!-------------------------------------------------------------------------------
FUNCTION ParallelReductionZ(z,oper_arg) RESULT(zsum)
!-------------------------------------------------------------------------------
COMPLEX(KIND=dp) :: z, zsum
INTEGER, OPTIONAL :: oper_arg
!-------------------------------------------------------------------------------
INTEGER :: oper
!-------------------------------------------------------------------------------
zsum = z
#ifdef PARALLEL_FOR_REAL
IF ( ParEnv % PEs>1) THEN
oper = 0
IF (PRESENT(oper_arg)) THEN
oper=oper_arg
ELSE
oper = 0
END IF

IF (.NOT.ASSOCIATED(ParEnv % Active)) &
CALL ParallelActive(.TRUE.)
CALL SparActiveSUMComplex(zsum,oper)
END IF
#endif
!-------------------------------------------------------------------------------
END FUNCTION ParallelReductionZ
!-------------------------------------------------------------------------------


!-------------------------------------------------------------------------------
SUBROUTINE ParallelBarrier
Expand Down
33 changes: 33 additions & 0 deletions fem/src/SParIterComm.F90
Original file line number Diff line number Diff line change
Expand Up @@ -4997,6 +4997,39 @@ END SUBROUTINE SParActiveSUMInt
!*********************************************************************


!*********************************************************************
SUBROUTINE SParActiveSUMComplex(tsum, oper)
INTEGER :: oper
COMPLEX(KIND=dp) :: tsum
!*********************************************************************
INTEGER :: ierr, comm, nact
COMPLEX(KIND=dp) :: ssum

comm = ParEnv % ActiveComm
nact = COUNT(ParEnv % Active)

IF( nact <= 0 ) THEN
comm = ELMER_COMM_WORLD
nact = ParEnv % PEs
END IF

ssum = tsum
SELECT CASE(oper)
CASE(0)
CALL MPI_ALLREDUCE( ssum, tsum, 1, MPI_COMPLEX, &
MPI_SUM, comm, ierr )
CASE(1)
CALL MPI_ALLREDUCE( ssum, tsum, 1, MPI_COMPLEX, &
MPI_MIN, comm, ierr )
CASE(2)
CALL MPI_ALLREDUCE( ssum, tsum, 1, MPI_COMPLEX, &
MPI_MAX, comm, ierr )
END SELECT
!*********************************************************************
END SUBROUTINE SParActiveSUMComplex
!*********************************************************************



!*********************************************************************
!*********************************************************************
Expand Down

0 comments on commit 3442c3c

Please sign in to comment.