Skip gnat.dg/prot7.adb on hppa.
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / privatized-ref-2.f90
blob498ef70b63a4ae977d11c4341f16d2443334c714
1 ! { dg-do run }
3 ! PR65181 "Support for alloca in nvptx"
4 ! { dg-excess-errors "lto1, mkoffload and lto-wrapper fatal errors" { target openacc_nvidia_accel_selected } }
5 ! Aside from restricting this testcase to non-nvptx offloading, and duplicating
6 ! it with 'dg-do link' for nvptx offloading, there doesn't seem to be a way to
7 ! XFAIL the "UNRESOLVED: [...] compilation failed to produce executable", or
8 ! get rid of it, unfortunately.
10 ! { dg-additional-options "-fopt-info-note-omp" }
11 ! { dg-additional-options "--param=openacc-privatization=noisy" }
12 ! { dg-additional-options "-foffload=-fopt-info-note-omp" }
13 ! { dg-additional-options "-foffload=--param=openacc-privatization=noisy" }
14 ! for testing/documenting aspects of that functionality.
15 ! Prune a few: uninteresting, and varying depending on GCC configuration (data types):
16 ! { dg-prune-output {note: variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} }
18 ! { dg-additional-options -Wuninitialized }
20 ! It's only with Tcl 8.5 (released in 2007) that "the variable 'varName'
21 ! passed to 'incr' may be unset, and in that case, it will be set to [...]",
22 ! so to maintain compatibility with earlier Tcl releases, we manually
23 ! initialize counter variables:
24 ! { dg-line l_dummy[variable c_compute 0 c_loop 0] }
25 ! { dg-message "dummy" "" { target iN-VAl-Id } l_dummy } to avoid
26 ! "WARNING: dg-line var l_dummy defined, but not used". */
28 program main
29 implicit none (type, external)
30 integer :: j
31 integer, allocatable :: A(:)
32 ! { dg-note {'a' declared here} {} { target *-*-* } .-1 }
33 character(len=:), allocatable :: my_str
34 character(len=15), allocatable :: my_str15
36 A = [(3*j, j=1, 10)]
37 ! { dg-bogus {'a\.offset' is used uninitialized} {PR77504 etc.} { xfail *-*-* } .-1 }
38 ! { dg-bogus {'a\.dim\[0\]\.lbound' is used uninitialized} {PR77504 etc.} { xfail *-*-* } .-2 }
39 ! { dg-bogus {'a\.dim\[0\]\.ubound' is used uninitialized} {PR77504 etc.} { xfail *-*-* } .-3 }
40 ! { dg-bogus {'a\.dim\[0\]\.lbound' may be used uninitialized} {PR77504 etc.} { xfail { ! __OPTIMIZE__ } } .-4 }
41 ! { dg-bogus {'a\.dim\[0\]\.ubound' may be used uninitialized} {PR77504 etc.} { xfail { ! __OPTIMIZE__ } } .-5 }
42 call foo (A, size(A))
43 call bar (A)
44 my_str = "1234567890"
45 call foo_str(my_str)
46 call bar_str(my_str)
47 my_str15 = "123456789012345"
48 call foobar (my_str15)
49 deallocate (A, my_str, my_str15)
50 contains
51 subroutine foo (array, nn)
52 integer :: i, nn
53 integer :: array(nn)
55 !$acc parallel copyout(array) ! { dg-line l_compute[incr c_compute] }
56 ! { dg-note {variable 'atmp\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
57 ! { dg-note {variable 'shadow_loopvar\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
58 ! { dg-note {variable 'offset\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
59 ! { dg-note {variable 'S\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
60 array = [(-i, i = 1, nn)]
61 !$acc end parallel
62 !$acc parallel copy(array)
63 !$acc loop gang private(array) ! { dg-line l_loop[incr c_loop] }
64 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
65 ! { dg-note {variable 'array' in 'private' clause is candidate for adjusting OpenACC privatization level} "" { target *-*-* } l_loop$c_loop }
66 ! { dg-note {variable 'array' ought to be adjusted for OpenACC privatization level: 'gang'} "" { target *-*-* } l_loop$c_loop }
67 ! { dg-note {variable 'array' adjusted for OpenACC privatization level: 'gang'} "" { target { ! { openacc_host_selected || { openacc_nvidia_accel_selected && __OPTIMIZE__ } } } } l_loop$c_loop }
68 ! { dg-message {sorry, unimplemented: target cannot support alloca} PR65181 { target openacc_nvidia_accel_selected } l_loop$c_loop }
69 do i = 1, 10
70 array(i) = i
71 end do
72 !$acc end parallel
73 !$acc parallel copyin(array) ! { dg-line l_compute[incr c_compute] }
74 ! { dg-note {variable 'test\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
75 ! { dg-note {variable 'atmp\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
76 ! { dg-note {variable 'shadow_loopvar\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
77 ! { dg-note {variable 'offset\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
78 ! { dg-note {variable 'S\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
79 if (any (array /= [(-i, i = 1, nn)])) error stop 1
80 !$acc end parallel
81 end subroutine foo
82 subroutine bar (array)
83 integer :: i
84 integer :: array(:)
86 !$acc parallel copyout(array) ! { dg-line l_compute[incr c_compute] }
87 ! { dg-note {variable 'atmp\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
88 ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
89 ! { dg-note {variable 'shadow_loopvar\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
90 ! { dg-note {variable 'offset\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
91 ! { dg-note {variable 'S\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
92 array = [(-2*i, i = 1, size(array))]
93 !$acc end parallel
94 !$acc parallel copy(array)
95 !$acc loop gang private(array) ! { dg-line l_loop[incr c_loop] }
96 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
97 ! { dg-note {variable 'array\.[0-9]+' in 'private' clause is candidate for adjusting OpenACC privatization level} "" { target *-*-* } l_loop$c_loop }
98 ! { dg-note {variable 'array\.[0-9]+' ought to be adjusted for OpenACC privatization level: 'gang'} "" { target *-*-* } l_loop$c_loop }
99 ! { dg-note {variable 'array\.[0-9]+' adjusted for OpenACC privatization level: 'gang'} "" { target { ! { openacc_host_selected || { openacc_nvidia_accel_selected && __OPTIMIZE__ } } } } l_loop$c_loop }
100 ! { dg-message {sorry, unimplemented: target cannot support alloca} PR65181 { target openacc_nvidia_accel_selected } l_loop$c_loop }
101 do i = 1, 10
102 array(i) = 9*i
103 end do
104 !$acc end parallel
105 !$acc parallel copyin(array) ! { dg-line l_compute[incr c_compute] }
106 ! { dg-note {variable 'test\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
107 ! { dg-note {variable 'A\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: static} "" { target *-*-* } l_compute$c_compute }
108 ! { dg-note {variable 'S\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
109 if (any (array /= [(-2*i, i = 1, 10)])) error stop 2
110 !$acc end parallel
111 end subroutine bar
112 subroutine foo_str(str)
113 integer :: i
114 character(len=*) :: str
116 !$acc parallel copyout(str)
117 str = "abcdefghij"
118 !$acc end parallel
119 !$acc parallel copy(str)
120 !$acc loop gang private(str) ! { dg-line l_loop[incr c_loop] }
121 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
122 ! { dg-note {variable 'str' in 'private' clause is candidate for adjusting OpenACC privatization level} "" { target *-*-* } l_loop$c_loop }
123 ! { dg-note {variable 'str' ought to be adjusted for OpenACC privatization level: 'gang'} "" { target *-*-* } l_loop$c_loop }
124 ! { dg-note {variable 'str' adjusted for OpenACC privatization level: 'gang'} "" { target { ! { openacc_host_selected || { openacc_nvidia_accel_selected && __OPTIMIZE__ } } } } l_loop$c_loop }
125 ! { dg-note {variable 'char\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: artificial} "" { target *-*-* } l_loop$c_loop }
126 ! { dg-message {sorry, unimplemented: target cannot support alloca} PR65181 { target openacc_nvidia_accel_selected } l_loop$c_loop }
127 do i = 1, 10
128 str(i:i) = achar(ichar('A') + i)
129 end do
130 !$acc end parallel
131 !$acc parallel copyin(str)
132 if (str /= "abcdefghij") error stop 3
133 !$acc end parallel
135 subroutine bar_str(str)
136 integer :: i
137 character(len=:), allocatable :: str
139 ! ***************************************
140 ! FIXME: Fails due to PR middle-end/95499
141 ! ***************************************
142 !!$acc parallel copyout(str)
143 str = "abcdefghij"
144 !!$acc end parallel
145 !!$acc parallel copy(str)
146 !!$acc loop gang private(str)
147 !do i = 1, 10
148 ! str(i:i) = achar(ichar('A') + i)
149 !end do
150 !!$acc end parallel
151 !!$acc parallel copyin(str)
152 if (str /= "abcdefghij") error stop 5
153 !!$acc end parallel
155 subroutine foobar (scalar)
156 integer :: i
157 character(len=15), optional :: scalar
159 !$acc parallel copyout(scalar)
160 scalar = "abcdefghi-12345"
161 !$acc end parallel
162 !$acc parallel copy(scalar)
163 !$acc loop gang private(scalar) ! { dg-line l_loop[incr c_loop] }
164 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
165 ! { dg-note {variable 'scalar' in 'private' clause is candidate for adjusting OpenACC privatization level} "" { target *-*-* } l_loop$c_loop }
166 ! { dg-note {variable 'scalar' ought to be adjusted for OpenACC privatization level: 'gang'} "" { target *-*-* } l_loop$c_loop }
167 ! { dg-note {variable 'scalar' adjusted for OpenACC privatization level: 'gang'} "" { target { ! { openacc_host_selected || { openacc_nvidia_accel_selected && __OPTIMIZE__ } } } } l_loop$c_loop }
168 ! { dg-note {variable 'char\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: artificial} "" { target *-*-* } l_loop$c_loop }
169 do i = 1, 15
170 scalar(i:i) = achar(ichar('A') + i)
171 end do
172 !$acc end parallel
173 !$acc parallel copyin(scalar)
174 if (scalar /= "abcdefghi-12345") error stop 6
175 !$acc end parallel
176 end subroutine foobar
177 subroutine foobar15 (scalar)
178 integer :: i
179 character(len=15), optional, allocatable :: scalar
181 !$acc parallel copyout(scalar)
182 scalar = "abcdefghi-12345"
183 !$acc end parallel
184 !$acc parallel copy(scalar)
185 !$acc loop gang private(scalar)
186 do i = 1, 15
187 scalar(i:i) = achar(ichar('A') + i)
188 end do
189 !$acc end parallel
190 !$acc parallel copyin(scalar)
191 if (scalar /= "abcdefghi-12345") error stop 1
192 !$acc end parallel
193 end subroutine foobar15