xref: /llvm-project/flang/test/Integration/OpenMP/workshare-scalar-array-assign.f90 (revision 5d38e6e42a90f5d469b5ff9e25e5e8865606776a)
1*5d38e6e4SIvan R. Ivanov!===----------------------------------------------------------------------===!
2*5d38e6e4SIvan R. Ivanov! This directory can be used to add Integration tests involving multiple
3*5d38e6e4SIvan R. Ivanov! stages of the compiler (for eg. from Fortran to LLVM IR). It should not
4*5d38e6e4SIvan R. Ivanov! contain executable tests. We should only add tests here sparingly and only
5*5d38e6e4SIvan R. Ivanov! if there is no other way to test. Repeat this message in each test that is
6*5d38e6e4SIvan R. Ivanov! added to this directory and sub-directories.
7*5d38e6e4SIvan R. Ivanov!===----------------------------------------------------------------------===!
8*5d38e6e4SIvan R. Ivanov
9*5d38e6e4SIvan R. Ivanov!RUN: %flang_fc1 -emit-hlfir -fopenmp -O3 %s -o - | FileCheck %s --check-prefix HLFIR
10*5d38e6e4SIvan R. Ivanov!RUN: %flang_fc1 -emit-fir -fopenmp -O3 %s -o - | FileCheck %s --check-prefix FIR
11*5d38e6e4SIvan R. Ivanov
12*5d38e6e4SIvan R. Ivanovsubroutine sb1(a, x)
13*5d38e6e4SIvan R. Ivanov  integer :: a
14*5d38e6e4SIvan R. Ivanov  integer :: x(:)
15*5d38e6e4SIvan R. Ivanov  !$omp parallel workshare
16*5d38e6e4SIvan R. Ivanov  x = a
17*5d38e6e4SIvan R. Ivanov  !$omp end parallel workshare
18*5d38e6e4SIvan R. Ivanovend subroutine
19*5d38e6e4SIvan R. Ivanov
20*5d38e6e4SIvan R. Ivanov! HLFIR:     omp.parallel {
21*5d38e6e4SIvan R. Ivanov! HLFIR:       omp.workshare {
22*5d38e6e4SIvan R. Ivanov! HLFIR:         %[[SCALAR:.*]] = fir.load %1#0 : !fir.ref<i32>
23*5d38e6e4SIvan R. Ivanov! HLFIR:         hlfir.assign %[[SCALAR]] to
24*5d38e6e4SIvan R. Ivanov! HLFIR:         omp.terminator
25*5d38e6e4SIvan R. Ivanov! HLFIR:       }
26*5d38e6e4SIvan R. Ivanov! HLFIR:       omp.terminator
27*5d38e6e4SIvan R. Ivanov! HLFIR:     }
28*5d38e6e4SIvan R. Ivanov
29*5d38e6e4SIvan R. Ivanov! FIR:     omp.parallel {
30*5d38e6e4SIvan R. Ivanov! FIR:       %[[SCALAR_ALLOCA:.*]] = fir.alloca i32
31*5d38e6e4SIvan R. Ivanov! FIR:       omp.single copyprivate(%[[SCALAR_ALLOCA]] -> @_workshare_copy_i32 : !fir.ref<i32>) {
32*5d38e6e4SIvan R. Ivanov! FIR:         %[[SCALAR_LOAD:.*]] = fir.load %{{.*}} : !fir.ref<i32>
33*5d38e6e4SIvan R. Ivanov! FIR:         fir.store %[[SCALAR_LOAD]] to %[[SCALAR_ALLOCA]] : !fir.ref<i32>
34*5d38e6e4SIvan R. Ivanov! FIR:         omp.terminator
35*5d38e6e4SIvan R. Ivanov! FIR:       }
36*5d38e6e4SIvan R. Ivanov! FIR:       %[[SCALAR_RELOAD:.*]] = fir.load %[[SCALAR_ALLOCA]] : !fir.ref<i32>
37*5d38e6e4SIvan R. Ivanov! FIR:       %6:3 = fir.box_dims %3, %c0 : (!fir.box<!fir.array<?xi32>>, index) -> (index, index, index)
38*5d38e6e4SIvan R. Ivanov! FIR:       omp.wsloop nowait {
39*5d38e6e4SIvan R. Ivanov! FIR:         omp.loop_nest (%arg2) : index = (%c1) to (%6#1) inclusive step (%c1) {
40*5d38e6e4SIvan R. Ivanov! FIR:           fir.store %[[SCALAR_RELOAD]]
41*5d38e6e4SIvan R. Ivanov! FIR:           omp.yield
42*5d38e6e4SIvan R. Ivanov! FIR:         }
43*5d38e6e4SIvan R. Ivanov! FIR:       }
44*5d38e6e4SIvan R. Ivanov! FIR:       omp.barrier
45*5d38e6e4SIvan R. Ivanov! FIR:       omp.terminator
46