The rule you are referring to for C++ sounds like this one:
If the reduction identifier is an implicitly declared reduction identifier or otherwise not an id-expression then it is implicitly converted to one by prepending the keyword operator (for example, + becomes operator+). This conversion is valid for the +, *, /, && and || operators.
One hiccup in Fortran is there is no guarantee the operator(+)
is available to begin with. For example a user could forget to import it:
program foo
use Typedef, only: inttype
integer, parameter :: nsize = 50
type(inttype) :: intsum, intarray(nsize)
intsum = inttype(0)
!$omp parallel do reduction(+:intsum) !! + not available
do i=1,nsize
intsum = intsum + intarray(i) !! + not available
end do
!$omp end parallel do
end program
The OpenMP 5.0 standard addresses this as follows:
If the reduction-identifier is the same as the name of a user-defined operator or an extended operator, or the same as a generic name that is one of the allowed intrinsic procedures, and if the operator or procedure name appears in an accessibility statement in the same module, the accessibility of the corresponding declare reduction directive is determined by the accessibility attribute of the statement.
The overhead we are talking about is at most five lines for the set of operators (+
, *
, /
, .and.
, .or.
) where C++ will lookup the corresponding operatorX
if it is defined. In Fortran you will need to add a line as @lkedward has shown, preferably close to the interface itself:
interface operator(+)
module procedure add
end interface
!$omp declare reduction(+:cmplx:omp_out=omp_out+omp_in)
For anyone else curious about this, here is another example:
module cmplx_type
implicit none
private
public :: cmplx, operator(+)
type :: cmplx
real :: re = 0, im = 0
end type
interface operator(+)
module procedure add
end interface
!$omp declare reduction(+:cmplx:omp_out=omp_out+omp_in)
contains
pure function add(a,b) result(c)
type(cmplx), intent(in) :: a, b
type(cmplx) :: c
c = cmplx(a%re + b%re, a%im + b%im)
end function
end module
program cmplx_demo
use cmplx_type
implicit none
type(cmplx) :: a(5), asum
integer, parameter :: sp = kind(0.0)
complex(sp) :: b(5), bsum
integer :: i
call random_number(a%re)
call random_number(a%im)
asum = cmplx(0.,0.)
!$omp parallel do reduction(+: asum)
do i = 1, size(a)
asum = asum + a(i)
end do
b%re = a%re
b%im = a%im
bsum = 0
!$omp parallel do reduction(+: bsum)
do i = 1, size(b)
bsum = bsum + b(i)
end do
print *, asum
print *, bsum
end program
I’ve tested it with both gfortran
(10 and higer) and ifort
(2021.4 and higher). For ifx
(version 2022.2.0) it didn’t work and I’ve reported an error.