[LLVM] Fix Maintainers.md formatting (NFC)
[llvm-project.git] / flang / test / Lower / OpenACC / acc-loop-and-cpu-dir.f90
blob51c6c367d653e09a7683c83574fa533246a9568e
1 ! Test that $dir loop directives (known or unknown) are not clashing
2 ! with $acc lowering.
4 ! RUN: %flang_fc1 -fopenacc -emit-hlfir %s -o - | FileCheck %s
6 subroutine test_before_acc_loop(a, b, c)
7 real, dimension(10) :: a,b,c
8 !dir$ myloop_directive_1
9 !dir$ myloop_directive_2
10 !$acc loop
11 do i=1,N
12 a(i) = b(i) + c(i)
13 enddo
14 end subroutine
15 ! CHECK-LABEL: test_before_acc_loop
16 ! CHECK: acc.loop
18 subroutine test_after_acc_loop(a, b, c)
19 real, dimension(10) :: a,b,c
20 !$acc loop
21 !dir$ myloop_directive_1
22 !dir$ myloop_directive_2
23 do i=1,N
24 a(i) = b(i) + c(i)
25 enddo
26 end subroutine
27 ! CHECK-LABEL: test_after_acc_loop
28 ! CHECK: acc.loop
30 subroutine test_before_acc_combined(a, b, c)
31 real, dimension(10) :: a,b,c
32 !dir$ myloop_directive_1
33 !dir$ myloop_directive_2
34 !$acc parallel loop
35 do i=1,N
36 a(i) = b(i) + c(i)
37 enddo
38 end subroutine
39 ! CHECK-LABEL: test_before_acc_combined
40 ! CHECK: acc.parallel combined(loop)
42 subroutine test_after_acc_combined(a, b, c)
43 real, dimension(10) :: a,b,c
44 !$acc parallel loop
45 !dir$ myloop_directive_1
46 !dir$ myloop_directive_2
47 do i=1,N
48 a(i) = b(i) + c(i)
49 enddo
50 end subroutine
51 ! CHECK-LABEL: test_after_acc_combined
52 ! CHECK: acc.parallel combined(loop)
55 subroutine test_vector_always_after_acc(a, b, c)
56 real, dimension(10) :: a,b,c
57 !$acc loop
58 !dir$ vector always
59 do i=1,N
60 a(i) = b(i) + c(i)
61 enddo
62 end subroutine
63 ! CHECK-LABEL: test_vector_always_after_acc
64 ! CHECK: acc.loop
66 subroutine test_vector_always_before_acc(a, b, c)
67 real, dimension(10) :: a,b,c
68 !dir$ vector always
69 !$acc loop
70 do i=1,N
71 a(i) = b(i) + c(i)
72 enddo
73 end subroutine
74 ! CHECK-LABEL: test_vector_always_before_acc
75 ! CHECK: acc.loop