Files
clang-p2996/flang/test/Semantics/OpenMP/declare-reduction-operator.f90
Tom Eccles ce603a0f16 [flang][openmp]Add UserReductionDetails and use in DECLARE REDUCTION (#140066)
This adds another puzzle piece for the support of OpenMP DECLARE
REDUCTION functionality.

This adds support for operators with derived types, as well as declaring
multiple different types with the same name or operator.

A new detail class for UserReductionDetials is introduced to hold the
list of types supported for a given reduction declaration.

Tests for parsing and symbol generation added.

Declare reduction is still not supported to lowering, it will generate a
"Not yet implemented" fatal error.

Fixes #141306
Fixes #97241
Fixes #92832
Fixes #66453

---------

Co-authored-by: Mats Petersson <mats.petersson@arm.com>
2025-06-09 11:17:03 +01:00

37 lines
1.2 KiB
Fortran

! RUN: %flang_fc1 -fdebug-dump-symbols -fopenmp -fopenmp-version=50 %s | FileCheck %s
module m1
interface operator(.fluffy.)
!CHECK: .fluffy., PUBLIC (Function): Generic DefinedOp procs: my_mul
procedure my_mul
end interface
type t1
integer :: val = 1
end type
!$omp declare reduction(.fluffy.:t1:omp_out=omp_out.fluffy.omp_in)
!CHECK: op.fluffy., PUBLIC: UserReductionDetails TYPE(t1)
!CHECK: t1, PUBLIC: DerivedType components: val
!CHECK: OtherConstruct scope: size=16 alignment=4 sourceRange=0 bytes
!CHECK: omp_in size=4 offset=0: ObjectEntity type: TYPE(t1)
!CHECK: omp_orig size=4 offset=4: ObjectEntity type: TYPE(t1)
!CHECK: omp_out size=4 offset=8: ObjectEntity type: TYPE(t1)
!CHECK: omp_priv size=4 offset=12: ObjectEntity type: TYPE(t1)
contains
function my_mul(x, y)
type (t1), intent (in) :: x, y
type (t1) :: my_mul
my_mul%val = x%val * y%val
end function my_mul
subroutine subr(a, r)
implicit none
type(t1), intent(in), dimension(10) :: a
type(t1), intent(out) :: r
integer :: i
!$omp parallel do reduction(.fluffy.:r)
do i=1,10
r = r .fluffy. a(i)
end do
end subroutine subr
end module m1