xref: /llvm-project/flang/test/Semantics/OpenMP/workshare02.f90 (revision 252645528eefee9319f99172c2470aea0dcc31cf)
1! RUN: %python %S/../test_errors.py %s %flang -fopenmp
2! OpenMP Version 4.5
3! 2.7.4 workshare Construct
4! The !omp workshare construct must not contain any user defined
5! function calls unless the function is ELEMENTAL.
6
7module my_mod
8  contains
9  integer function my_func()
10    my_func = 10
11  end function my_func
12
13  impure integer function impure_my_func()
14    impure_my_func = 20
15  end function impure_my_func
16
17  impure elemental integer function impure_ele_my_func()
18    impure_ele_my_func = 20
19  end function impure_ele_my_func
20end module my_mod
21
22subroutine workshare(aa, bb, cc, dd, ee, ff, n)
23  use my_mod
24  integer n, i, j
25  real aa(n), bb(n), cc(n), dd(n), ee(n), ff(n)
26
27  !$omp workshare
28  !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
29  aa = my_func()
30  cc = dd
31  ee = ff
32
33  !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
34  where (aa .ne. my_func()) aa = bb * cc
35  !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
36  where (dd .lt. 5) dd = aa * my_func()
37
38  !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
39  where (aa .ge. my_func())
40    !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
41    cc = aa + my_func()
42  !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
43  elsewhere (aa .le. my_func())
44    !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
45    cc = dd + my_func()
46  elsewhere
47    !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
48    cc = ee + my_func()
49  end where
50
51  !WARNING: Impure procedure 'my_func' should not be referenced in a FORALL header
52  !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
53  forall (j = 1:my_func()) aa(j) = aa(j) + bb(j)
54
55  forall (j = 1:10)
56    aa(j) = aa(j) + bb(j)
57
58    !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
59    where (cc .le. j) cc = cc + my_func()
60  end forall
61
62  !$omp atomic update
63  !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
64  j = j + my_func()
65
66  !$omp atomic capture
67  i = j
68  !ERROR: User defined non-ELEMENTAL function 'my_func' is not allowed in a WORKSHARE construct
69  j = j - my_func()
70  !$omp end atomic
71
72  !ERROR: User defined IMPURE, non-ELEMENTAL function 'impure_my_func' is not allowed in a WORKSHARE construct
73  cc = impure_my_func()
74  !ERROR: User defined IMPURE function 'impure_ele_my_func' is not allowed in a WORKSHARE construct
75  aa(1) = impure_ele_my_func()
76
77  !$omp end workshare
78
79  !$omp workshare
80    j = j + 1
81  !ERROR: At most one NOWAIT clause can appear on the END WORKSHARE directive
82  !$omp end workshare nowait nowait
83
84end subroutine workshare
85