1 ! REQUIRES: openmp_runtime
3 !RUN: %flang_fc1 -emit-hlfir %openmp_flags %s -o - | FileCheck %s
5 !===============================================================================
6 ! Parallel sections construct
7 !===============================================================================
9 !CHECK: func @_QPomp_parallel_sections
10 subroutine omp_parallel_sections(x
, y
)
11 integer, intent(inout
) :: x
, y
12 !CHECK: omp.parallel {
13 !CHECK: omp.sections {
14 !$omp parallel sections
21 !CHECK: omp.terminator
28 !CHECK: omp.terminator
29 !CHECK: omp.terminator
30 !CHECK: omp.terminator
31 !$omp end parallel sections
32 end subroutine omp_parallel_sections
34 !===============================================================================
35 ! Parallel sections construct with allocate clause
36 !===============================================================================
38 !CHECK: func @_QPomp_parallel_sections
39 subroutine omp_parallel_sections_allocate(x
, y
)
41 integer, intent(inout
) :: x
, y
43 !CHECK: %[[allocator_1:.*]] = arith.constant 4 : i64
44 !CHECK: omp.sections allocate(%[[allocator_1]] : i64 -> %{{.*}} : !fir.ref<i32>) {
45 !$omp parallel sections allocate(omp_high_bw_mem_alloc: x) private(x, y)
49 !CHECK: omp.terminator
53 !CHECK: omp.terminator
54 !CHECK: omp.terminator
55 !CHECK: omp.terminator
56 !$omp end parallel sections
57 end subroutine omp_parallel_sections_allocate