[LLVM] Fix Maintainers.md formatting (NFC)
[llvm-project.git] / flang / test / Semantics / OpenMP / declarative-directive01.f90
blob8d6762b87adb9538c56448c070ecb8b2c29fa30d
1 ! RUN: %python %S/../test_errors.py %s %flang -fopenmp -fopenmp-version=52
3 ! Check OpenMP declarative directives
5 !TODO: all internal errors
6 ! enable declare-reduction example after name resolution
8 ! 2.4 requires
10 subroutine requires_1(a)
11 real(8), intent(inout) :: a
12 !$omp requires reverse_offload, unified_shared_memory, atomic_default_mem_order(relaxed)
13 a = a + 0.01
14 end subroutine requires_1
16 subroutine requires_2(a)
17 real(8), intent(inout) :: a
18 !$omp requires unified_address
19 a = a + 0.01
20 end subroutine requires_2
22 ! 2.8.2 declare-simd
24 subroutine declare_simd_1(a, b)
25 real(8), intent(inout) :: a, b
26 !$omp declare simd(declare_simd_1) aligned(a)
27 a = 3.14 + b
28 end subroutine declare_simd_1
30 module m1
31 abstract interface
32 subroutine sub(x,y)
33 integer, intent(in)::x
34 integer, intent(in)::y
35 end subroutine sub
36 end interface
37 end module m1
39 subroutine declare_simd_2
40 use m1
41 procedure (sub) sub1
42 !ERROR: NOTINBRANCH and INBRANCH clauses are mutually exclusive and may not appear on the same DECLARE SIMD directive
43 !$omp declare simd(sub1) inbranch notinbranch
44 procedure (sub), pointer::p
45 p=>sub1
46 call p(5,10)
47 end subroutine declare_simd_2
49 subroutine sub1 (x,y)
50 integer, intent(in)::x, y
51 print *, x+y
52 end subroutine sub1
54 ! 2.10.6 declare-target
55 ! 2.15.2 threadprivate
57 module m2
58 contains
59 subroutine foo
60 !$omp declare target
61 !WARNING: The entity with PARAMETER attribute is used in a DECLARE TARGET directive
62 !WARNING: The entity with PARAMETER attribute is used in a DECLARE TARGET directive
63 !$omp declare target (foo, N, M)
64 !WARNING: The usage of TO clause on DECLARE TARGET directive has been deprecated. Use ENTER clause instead.
65 !ERROR: A variable that appears in a DECLARE TARGET directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
66 !ERROR: A variable that appears in a DECLARE TARGET directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
67 !ERROR: A variable that appears in a DECLARE TARGET directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
68 !$omp declare target to(Q, S) link(R)
69 !ERROR: A variable that appears in a DECLARE TARGET directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
70 !ERROR: A variable that appears in a DECLARE TARGET directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
71 !ERROR: A variable that appears in a DECLARE TARGET directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
72 !$omp declare target enter(Q, S) link(R)
73 !WARNING: The usage of TO clause on DECLARE TARGET directive has been deprecated. Use ENTER clause instead.
74 !ERROR: A variable that appears in a DECLARE TARGET directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
75 !ERROR: MAP clause is not allowed on the DECLARE TARGET directive
76 !$omp declare target to(Q) map(from:Q)
77 !ERROR: A variable that appears in a DECLARE TARGET directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
78 !ERROR: MAP clause is not allowed on the DECLARE TARGET directive
79 !$omp declare target enter(Q) map(from:Q)
80 integer, parameter :: N=10000, M=1024
81 integer :: i
82 real :: Q(N, N), R(N,M), S(M,M)
83 !ERROR: A variable that appears in a THREADPRIVATE directive must be declared in the scope of a module or have the SAVE attribute, either explicitly or implicitly
84 !$omp threadprivate(i)
85 end subroutine foo
86 end module m2
88 ! 2.16 declare-reduction
90 ! subroutine declare_red_1()
91 ! use omp_lib
92 ! integer :: my_var
93 ! !$omp declare reduction (my_add_red : integer : omp_out = omp_out + omp_in) initializer (omp_priv=0)
94 ! my_var = 0
95 ! !$omp parallel reduction (my_add_red : my_var) num_threads(4)
96 ! my_var = omp_get_thread_num() + 1
97 ! !$omp end parallel
98 ! print *, "sum of thread numbers is ", my_var
99 ! end subroutine declare_red_1