[clangd] Re-land "support outgoing calls in call hierarchy" (#117673)
[llvm-project.git] / flang / test / Semantics / OpenMP / copyprivate04.f90
blob291cf1103fb2794456be43da57e0245dd7db2e89
1 ! RUN: %python %S/../test_errors.py %s %flang_fc1 -fopenmp
2 ! OpenMP Version 5.2
3 ! 5.1.1 - Variables Referenced in a Construct
4 ! Copyprivate must accept variables that are predetermined as private.
6 module m1
7 integer :: m
8 end module
10 program omp_copyprivate
11 use m1
12 implicit none
13 integer :: i
14 integer, save :: j
15 integer :: k
16 common /c/ k
17 real, parameter :: pi = 3.14
18 integer :: a1(10)
20 ! Local variables are private.
21 !$omp single
22 i = 123
23 !$omp end single copyprivate(i)
24 !$omp single
25 !$omp end single copyprivate(a1)
27 ! Variables with the SAVE attribute are not private.
28 !$omp single
29 !ERROR: COPYPRIVATE variable 'j' is not PRIVATE or THREADPRIVATE in outer context
30 !$omp end single copyprivate(j)
32 ! Common block variables are not private.
33 !$omp single
34 !ERROR: COPYPRIVATE variable 'k' is not PRIVATE or THREADPRIVATE in outer context
35 !$omp end single copyprivate(/c/)
36 !$omp single
37 !ERROR: COPYPRIVATE variable 'k' is not PRIVATE or THREADPRIVATE in outer context
38 !$omp end single copyprivate(k)
40 ! Module variables are not private.
41 !$omp single
42 !ERROR: COPYPRIVATE variable 'm' is not PRIVATE or THREADPRIVATE in outer context
43 !$omp end single copyprivate(m)
45 ! Parallel can make a variable shared.
46 !$omp parallel
47 !$omp single
48 i = 456
49 !ERROR: COPYPRIVATE variable 'i' is not PRIVATE or THREADPRIVATE in outer context
50 !$omp end single copyprivate(i)
51 call sub(j, a1)
52 !$omp end parallel
54 !$omp parallel shared(i)
55 !$omp single
56 i = 456
57 !ERROR: COPYPRIVATE variable 'i' is not PRIVATE or THREADPRIVATE in outer context
58 !$omp end single copyprivate(i)
59 !$omp end parallel
61 !FIXME: an error should be emitted in this case.
62 ! copyprivate(i) should be considered as a reference to i and a new
63 ! symbol should be created in `parallel` scope, for this case to be
64 ! handled properly.
65 !$omp parallel
66 !$omp single
67 !$omp end single copyprivate(i)
68 !$omp end parallel
70 ! Named constants are shared.
71 !$omp single
72 !ERROR: COPYPRIVATE variable 'pi' is not PRIVATE or THREADPRIVATE in outer context
73 !$omp end single copyprivate(pi)
75 !$omp parallel do
76 do i = 1, 10
77 !$omp parallel
78 !$omp single
79 j = i
80 !ERROR: COPYPRIVATE variable 'i' is not PRIVATE or THREADPRIVATE in outer context
81 !$omp end single copyprivate(i)
82 !$omp end parallel
83 end do
84 !$omp end parallel do
86 contains
87 subroutine sub(s1, a)
88 integer :: s1
89 integer :: a(:)
91 ! Dummy argument.
92 !$omp single
93 !$omp end single copyprivate(s1)
95 ! Assumed shape arrays are shared.
96 !$omp single
97 !ERROR: COPYPRIVATE variable 'a' is not PRIVATE or THREADPRIVATE in outer context
98 !$omp end single copyprivate(a)
99 end subroutine
101 integer function fun(f1)
102 integer :: f1
104 ! Dummy argument.
105 !$omp single
106 !$omp end single copyprivate(f1)
108 ! Function result is private.
109 !$omp single
110 !$omp end single copyprivate(fun)
111 end function
112 end program