Files
clang-p2996/flang/test/Lower/OpenMP/wsloop-reduction-max-2.f90
Tom Eccles 3deaa77f1a [flang][OpenMP] simplify getReductionName (#85666)
Re-use fir::getTypeAsString instead of creating something new here. This
spells integer names like i32 instead of i_32 so there is a lot of test
churn.
2024-03-20 15:47:00 +00:00

21 lines
427 B
Fortran

! RUN: bbc -emit-hlfir -fopenmp -o - %s 2>&1 | FileCheck %s
! RUN: %flang_fc1 -emit-hlfir -fopenmp -o - %s 2>&1 | FileCheck %s
! CHECK: omp.wsloop reduction(@max_i32
! CHECK: arith.cmpi sgt
! CHECK: arith.select
module m1
intrinsic max
end module m1
program main
use m1, ren=>max
n=0
!$omp parallel do reduction(ren:n)
do i=1,100
n=max(n,i)
end do
if (n/=100) print *,101
print *,'pass'
end program main