Reductions such as min are intrinsic procedures. This distinguishes them from user defined reductions. Previously, the intrinsic attribute was not set when visiting reduction clauses causing them to be missed. wsloop-reduction-min.f90 (the other min reduction test) worked because it contained "min" used as an intrinsic inside of the body of the reduction. This allowed ResolveNamesVisitor::HandleProcedureName to set the correct attribute on that Symbol.
23 lines
757 B
Fortran
23 lines
757 B
Fortran
! RUN: %flang_fc1 -fopenmp -fdebug-dump-symbols -o - %s 2>&1 | FileCheck %s
|
|
! Check intrinsic reduction symbols (in this case "max" are marked as INTRINSIC
|
|
|
|
! CHECK: MainProgram scope: omp_reduction
|
|
program omp_reduction
|
|
! CHECK: i size=4 offset=0: ObjectEntity type: INTEGER(4)
|
|
integer i
|
|
! CHECK: k size=4 offset=4: ObjectEntity type: INTEGER(4) init:10_4
|
|
integer :: k = 10
|
|
! CHECK: m size=4 offset=8: ObjectEntity type: INTEGER(4) init:12_4
|
|
integer :: m = 12
|
|
|
|
! CHECK: OtherConstruct scope
|
|
! CHECK: i (OmpPrivate, OmpPreDetermined): HostAssoc
|
|
! CHECK: k (OmpReduction): HostAssoc
|
|
! CHECK: max, INTRINSIC: ProcEntity
|
|
!$omp parallel do reduction(max:k)
|
|
do i=1,10
|
|
k = i
|
|
end do
|
|
!$omp end parallel do
|
|
end program omp_reduction
|