llvm-project/flang/test/Lower/OpenMP/wsloop-reduction-logical-kinds.f90
Tom Eccles 1b7cbe1f87
[flang][OpenMP] Create unique reduction decls for different logical kinds (#146558)
Some Fujitsu tests showed incorrect results because we were sharing
reduction declarations for different kinds for logical variables.
2025-07-02 10:25:43 +01:00

25 lines
750 B
Fortran

! RUN: %flang_fc1 -emit-hlfir -fopenmp -o - %s | FileCheck %s
! Check that logical reductions of different kinds do not end up using the same
! reduction declaration
! CHECK-LABEL: omp.declare_reduction @or_reduction_l64 : !fir.logical<8> init {
! CHECK-LABEL: omp.declare_reduction @or_reduction_l32 : !fir.logical<4> init {
subroutine test(a4, a8, sz)
integer :: sz
logical(4), dimension(sz) :: a4
logical(8), dimension(sz) :: a8
logical(4) :: res4 = .false.
logical(8) :: res8 = .false.
integer i
! CHECK: omp.wsloop private({{.*}}) reduction(@or_reduction_l32 {{.*}}, @or_reduction_l64 {{.*}}) {
!$omp do reduction(.or.:res4, res8)
do i = 1,sz
res4 = res4 .or. a4(i)
res8 = res8 .or. a8(i)
enddo
end subroutine