[LLVM] Fix Maintainers.md formatting (NFC)
[llvm-project.git] / flang / test / Examples / omp-declarative-directive.f90
blob632ebcec17885b690e61dc339c439940c787970b
1 ! REQUIRES: plugins, examples, shell
3 ! RUN: %flang_fc1 -load %llvmshlibdir/flangOmpReport.so -plugin flang-omp-report -fopenmp %s -o - | FileCheck %s
5 ! Check OpenMP declarative directives
7 ! 2.8.2 declare-simd
9 subroutine declare_simd_1(a, b)
10 real(8), intent(inout) :: a, b
11 !$omp declare simd(declare_simd_1) aligned(a)
12 a = 3.14 + b
13 end subroutine declare_simd_1
15 ! 2.10.6 declare-target
16 ! 2.15.2 threadprivate
18 module m2
19 contains
20 subroutine foo
21 !$omp declare target
22 integer, parameter :: N=10000, M=1024
23 integer :: i
24 real :: Q(N, N), R(N,M), S(M,M)
25 end subroutine foo
26 end module m2
28 end
30 ! CHECK:---
31 ! CHECK-NEXT:- file: '{{[^"]*}}omp-declarative-directive.f90'
32 ! CHECK-NEXT: line: 11
33 ! CHECK-NEXT: construct: declare simd
34 ! CHECK-NEXT: clauses:
35 ! CHECK-NEXT: - clause: aligned
36 ! CHECK-NEXT: details: a
37 ! CHECK-NEXT:- file: '{{[^"]*}}omp-declarative-directive.f90'
38 ! CHECK-NEXT: line: 21
39 ! CHECK-NEXT: construct: declare target
40 ! CHECK-NEXT: clauses: []
41 ! CHECK-NEXT:...