bolt/deps/llvm-18.1.8/flang/test/Lower/OpenMP/FIR/flush.f90
2025-02-14 19:21:04 +01:00

45 lines
1.6 KiB
Fortran

! This test checks lowering of OpenMP Flush Directive.
!RUN: %flang_fc1 -emit-fir -flang-deprecated-no-hlfir -fopenmp %s -o - | FileCheck %s --check-prefixes="FIRDialect,OMPDialect"
!RUN: %flang_fc1 -emit-fir -flang-deprecated-no-hlfir -fopenmp %s -o - | fir-opt --cfg-conversion | fir-opt --fir-to-llvm-ir | FileCheck %s --check-prefixes="LLVMIRDialect,OMPDialect"
subroutine flush_standalone(a, b, c)
integer, intent(inout) :: a, b, c
!$omp flush(a,b,c)
!$omp flush
!OMPDialect: omp.flush(%{{.*}}, %{{.*}}, %{{.*}} :
!FIRDialect: !fir.ref<i32>, !fir.ref<i32>, !fir.ref<i32>)
!LLVMIRDialect: !llvm.ptr, !llvm.ptr, !llvm.ptr)
!OMPDialect: omp.flush
end subroutine flush_standalone
subroutine flush_parallel(a, b, c)
integer, intent(inout) :: a, b, c
!$omp parallel
!OMPDialect: omp.parallel {
!OMPDialect: omp.flush(%{{.*}}, %{{.*}}, %{{.*}} :
!FIRDialect: !fir.ref<i32>, !fir.ref<i32>, !fir.ref<i32>)
!LLVMIRDialect: !llvm.ptr, !llvm.ptr, !llvm.ptr)
!OMPDialect: omp.flush
!$omp flush(a,b,c)
!$omp flush
!FIRDialect: %{{.*}} = fir.load %{{.*}} : !fir.ref<i32>
!FIRDialect: %{{.*}} = fir.load %{{.*}} : !fir.ref<i32>
!FIRDialect: %{{.*}} = arith.addi %{{.*}}, %{{.*}} : i32
!FIRDialect: fir.store %{{.*}} to %{{.*}} : !fir.ref<i32>
!LLVMIRDialect: %{{.*}} = llvm.load %{{.*}} : !llvm.ptr -> i32
!LLVMIRDialect: %{{.*}} = llvm.load %{{.*}} : !llvm.ptr -> i32
!LLVMIRDialect: %{{.*}} = llvm.add %{{.*}}, %{{.*}} : i32
!LLVMIRDialect: llvm.store %{{.*}}, %{{.*}} : i32, !llvm.ptr
c = a + b
!OMPDialect: omp.terminator
!$omp END parallel
end subroutine flush_parallel