xref: /llvm-project/flang/test/Integration/OpenMP/workshare-axpy.f90 (revision 3f0cc068cef26e820b3acbd21b3577817e4bf4ca)
1!===----------------------------------------------------------------------===!
2! This directory can be used to add Integration tests involving multiple
3! stages of the compiler (for eg. from Fortran to LLVM IR). It should not
4! contain executable tests. We should only add tests here sparingly and only
5! if there is no other way to test. Repeat this message in each test that is
6! added to this directory and sub-directories.
7!===----------------------------------------------------------------------===!
8
9!RUN: %flang_fc1 -emit-hlfir -fopenmp -O3 %s -o - | FileCheck %s --check-prefix HLFIR
10!RUN: %flang_fc1 -emit-fir -fopenmp -O3 %s -o - | FileCheck %s --check-prefix FIR
11
12subroutine sb1(a, x, y, z)
13  integer :: a
14  integer :: x(:)
15  integer :: y(:)
16  integer, allocatable :: z(:)
17  !$omp parallel workshare
18  z = a * x + y
19  !$omp end parallel workshare
20end subroutine
21
22! HLFIR:  func.func @_QPsb1
23! HLFIR:    omp.parallel {
24! HLFIR:      omp.workshare {
25! HLFIR:        hlfir.elemental {{.*}} unordered : (!fir.shape<1>) -> !hlfir.expr<?xi32> {
26! HLFIR:        hlfir.elemental {{.*}} unordered : (!fir.shape<1>) -> !hlfir.expr<?xi32> {
27! HLFIR:        hlfir.assign
28! HLFIR:        hlfir.destroy
29! HLFIR:        hlfir.destroy
30! HLFIR-NOT:    omp.barrier
31! HLFIR:        omp.terminator
32! HLFIR:      }
33! HLFIR-NOT:  omp.barrier
34! HLFIR:      omp.terminator
35! HLFIR:    }
36! HLFIR:    return
37! HLFIR:  }
38! HLFIR:}
39
40
41! FIR:  func.func private @_workshare_copy_heap_Uxi32(%{{[a-z0-9]+}}: !fir.ref<!fir.heap<!fir.array<?xi32>>>, %{{[a-z0-9]+}}: !fir.ref<!fir.heap<!fir.array<?xi32>>>
42! FIR:  func.func private @_workshare_copy_i32(%{{[a-z0-9]+}}: !fir.ref<i32>, %{{[a-z0-9]+}}: !fir.ref<i32>
43
44! FIR:  func.func @_QPsb1
45! FIR:    omp.parallel {
46! FIR:      omp.single copyprivate(%{{[a-z0-9]+}} -> @_workshare_copy_i32 : !fir.ref<i32>, %{{[a-z0-9]+}} -> @_workshare_copy_heap_Uxi32 : !fir.ref<!fir.heap<!fir.array<?xi32>>>) {
47! FIR:        fir.allocmem
48! FIR:      omp.wsloop {
49! FIR:        omp.loop_nest
50! FIR:      omp.single nowait {
51! FIR:        fir.call @_FortranAAssign
52! FIR:        fir.freemem
53! FIR:        omp.terminator
54! FIR:      }
55! FIR:      omp.barrier
56! FIR:      omp.terminator
57! FIR:    }
58