xref: /llvm-project/flang/test/Semantics/OpenMP/private03.f90 (revision c734d77b9913052012faf91fdc19753f791421d9)
1! RUN: %python %S/../test_errors.py %s %flang -fopenmp
2! OpenMP Version 4.5
3! Variables that appear in expressions for statement function definitions
4! may not appear in private, firstprivate or lastprivate clauses.
5
6subroutine stmt_function(temp)
7
8  integer :: i, p, q, r
9  real :: c, f, s, v, t(10)
10  real, intent(in) :: temp
11
12  c(temp) = p * (temp - q) / r
13  f(temp) = q + (temp * r/p)
14  v(temp) = c(temp) + f(temp)/2 - s
15
16  p = 5
17  q = 32
18  r = 9
19
20  !ERROR: Variable 'p' in statement function expression cannot be in a PRIVATE clause
21  !$omp parallel private(p)
22  s = c(temp)
23  !$omp end parallel
24
25  !ERROR: Variable 's' in statement function expression cannot be in a FIRSTPRIVATE clause
26  !$omp parallel firstprivate(s)
27  s = s + f(temp)
28  !$omp end parallel
29
30  !ERROR: Variable 's' in statement function expression cannot be in a LASTPRIVATE clause
31  !$omp parallel do lastprivate(s, t)
32  do i = 1, 10
33  t(i) = v(temp) + i - s
34  end do
35  !$omp end parallel do
36
37  print *, t
38
39end subroutine stmt_function
40