Files
clang-p2996/flang/test/Lower/OpenMP/parallel-sections.f90
Kiran Chandramohan dd32bf9a77 [Flang,MLIR,OpenMP] Fix a few tests that were not converting to LLVM
A few OpenMP tests were retaining the FIR operands even after running
the LLVM conversion pass. To fix these tests the legality checkes for
OpenMP conversion are made stricter to include operands and results.
The Flush, Single and Sections operations are added to conversions or
legality checks. The RegionLessOpConversion is appropriately renamed
to clarify that it works only for operations with Variable operands.
The operands of the flush operation are changed to match those of
Variable Operands.

Fix for an OpenMP issue mentioned in
https://github.com/llvm/llvm-project/issues/55210.

Reviewed By: shraiysh, peixin, awarzynski

Differential Revision: https://reviews.llvm.org/D127092
2022-06-07 09:55:53 +00:00

60 lines
2.2 KiB
Fortran

!RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s --check-prefixes="FIRDialect,OMPDialect"
!RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | fir-opt --cfg-conversion | fir-opt --fir-to-llvm-ir | FileCheck %s --check-prefixes="OMPDialect,LLVMDialect"
!===============================================================================
! Parallel sections construct
!===============================================================================
!FIRDialect: func @_QPomp_parallel_sections
subroutine omp_parallel_sections(x, y)
integer, intent(inout) :: x, y
!OMPDialect: omp.parallel {
!OMPDialect: omp.sections {
!$omp parallel sections
!OMPDialect: omp.section {
!$omp section
!FIRDialect: fir.load
!FIRDialect: arith.addi
!FIRDialect: fir.store
x = x + 12
!OMPDialect: omp.terminator
!OMPDialect: omp.section {
!$omp section
!FIRDialect: fir.load
!FIRDialect: arith.subi
!FIRDialect: fir.store
y = y - 5
!OMPDialect: omp.terminator
!OMPDialect: omp.terminator
!OMPDialect: omp.terminator
!$omp end parallel sections
end subroutine omp_parallel_sections
!===============================================================================
! Parallel sections construct with allocate clause
!===============================================================================
!FIRDialect: func @_QPomp_parallel_sections
subroutine omp_parallel_sections_allocate(x, y)
use omp_lib
integer, intent(inout) :: x, y
!FIRDialect: %[[allocator:.*]] = arith.constant 1 : i32
!LLVMDialect: %[[allocator:.*]] = llvm.mlir.constant(1 : i32) : i32
!OMPDialect: omp.parallel {
!OMPDialect: omp.sections allocate(
!FIRDialect: %[[allocator]] : i32 -> %{{.*}} : !fir.ref<i32>) {
!LLVMDialect: %[[allocator]] : i32 -> %{{.*}} : !llvm.ptr<i32>) {
!$omp parallel sections allocate(omp_high_bw_mem_alloc: x)
!OMPDialect: omp.section {
!$omp section
x = x + 12
!OMPDialect: omp.terminator
!OMPDialect: omp.section {
!$omp section
y = y + 5
!OMPDialect: omp.terminator
!OMPDialect: omp.terminator
!OMPDialect: omp.terminator
!$omp end parallel sections
end subroutine omp_parallel_sections_allocate