c++/coroutines: correct passing *this to promise type [PR104981]
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / declare-target-4.f90
blob55534d8fe9987eb4cf8abf99cbd36aaa79fdaa87
1 ! { dg-do compile }
2 ! { dg-additional-options "-fdump-tree-original" }
4 subroutine f1
5 !$omp declare target device_type (any) ! { dg-warning "OMP DECLARE TARGET directive at .1. with only DEVICE_TYPE or INDIRECT clauses is ignored" }
6 end subroutine
8 subroutine f2
9 !$omp declare target to (f2) device_type (any)
10 end subroutine
12 subroutine f3
13 !$omp declare target device_type (any) to (f3)
14 end subroutine
16 subroutine f4
17 !$omp declare target device_type (host) to (f4)
18 end subroutine
20 subroutine f5
21 !$omp declare target device_type (nohost) to (f5)
22 end subroutine
24 subroutine f6
25 !$omp declare target enter (f6) device_type (any)
26 end subroutine
28 module mymod
29 ! device_type is ignored for variables in OpenMP 5.0
30 ! but TR8 and later apply those rules to variables as well
31 implicit none
32 integer :: a, b(4), c, d
33 integer :: e, f, g
34 integer :: m, n, o, p, q, r, s, t, u, v, w, x
35 common /block1/ m, n
36 common /block2/ o, p
37 common /block3/ q, r
38 common /block4/ s, t
39 common /block5/ u, v
40 common /block6/ w, x
42 !$omp declare target to(a) device_type(nohost)
43 !$omp declare target to(b) device_type(host)
44 !$omp declare target to(c) device_type(any)
45 ! Fails in ME with "Error: wrong number of arguments specified for 'omp declare target link' attribute"
46 ! !$omp declare target link(e) device_type(nohost)
47 ! !$omp declare target link(f) device_type(host)
48 ! !$omp declare target link(g) device_type(any)
50 !$omp declare target to(/block1/) device_type(nohost)
51 !$omp declare target to(/block2/) device_type(host)
52 !$omp declare target to(/block3/) device_type(any)
53 !$omp declare target link(/block4/) device_type(nohost)
54 !$omp declare target link(/block5/) device_type(host)
55 !$omp declare target link(/block6/) device_type(any)
56 contains
57 subroutine s1
58 !$omp declare target to (s1) device_type (any)
59 end
60 subroutine s2
61 !$omp declare target to (s2) device_type (nohost)
62 end
63 subroutine s3
64 !$omp declare target to (s3) device_type (host)
65 end
66 end module
68 module m2
69 use mymod
70 implicit none
71 public
72 private :: s1, s2, s3, a, b, c, d, e, f, g
73 public :: m, n, o, p, q, r, s, t, u, v, w, x
74 end module m2
76 ! { dg-final { scan-tree-dump-times "omp declare target" 8 "original" } }
77 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(" 8 "original" } }
78 ! { dg-final { scan-tree-dump-not "__attribute__\\(\\(omp declare target \[^\n\r\]*\[\n\r\]void f1" "original" } }
79 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(any\\)\\)\\)\\)\[\n\r]__attribute__\[^\n\r]+\[\n\r]void f2" 1 "original" } }
80 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(any\\)\\)\\)\\)\[\n\r]__attribute__\[^\n\r]+\[\n\r\]void f3" 1 "original" } }
81 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(host\\)\\)\\)\\)\[\n\r]__attribute__\[^\n\r]+\[\n\r\]void f4" 1 "original" } }
82 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(nohost\\)\\)\\)\\)\[\n\r]__attribute__\[^\n\r]+\[\n\r\]void f5" 1 "original" } }
83 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(any\\)\\)\\)\\)\[\n\r]__attribute__\[^\n\r]+\[\n\r]void f6" 1 "original" } }
84 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(any\\)\\)\\)\\)\[\n\r]__attribute__\[^\n\r]+\[\n\r\]void s1" 1 "original" } }
85 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(nohost\\)\\)\\)\\)\[\n\r]__attribute__\[^\n\r]+\[\n\r\]void s2" 1 "original" } }
86 ! { dg-final { scan-tree-dump-times "__attribute__\\(\\(omp declare target \\(device_type\\(host\\)\\)\\)\\)\[\n\r]__attribute__\[^\n\r]+\[\n\r\]void s3" 1 "original" } }