1 ! Test OpenACC 'declare create' with allocatable arrays.
5 !TODO-OpenACC-declare-allocate
6 ! Missing support for OpenACC "Changes from Version 2.0 to 2.5":
7 ! "The 'declare create' directive with a Fortran 'allocatable' has new behavior".
8 ! Thus, after 'allocate'/before 'deallocate', call 'acc_create'/'acc_delete'
11 !TODO { dg-additional-options -fno-inline } for stable results regarding OpenACC 'routine'.
13 ! { dg-additional-options -fopt-info-all-omp }
14 ! { dg-additional-options -foffload=-fopt-info-all-omp }
16 ! { dg-additional-options --param=openacc-privatization=noisy }
17 ! { dg-additional-options -foffload=--param=openacc-privatization=noisy }
18 ! Prune a few: uninteresting, and potentially varying depending on GCC configuration (data types):
19 ! { dg-prune-output {note: variable '[Di]\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} }
21 ! { dg-additional-options -Wopenacc-parallelism }
23 ! It's only with Tcl 8.5 (released in 2007) that "the variable 'varName'
24 ! passed to 'incr' may be unset, and in that case, it will be set to [...]",
25 ! so to maintain compatibility with earlier Tcl releases, we manually
26 ! initialize counter variables:
27 ! { dg-line l_dummy[variable c 0] }
28 ! { dg-message dummy {} { target iN-VAl-Id } l_dummy } to avoid
29 ! "WARNING: dg-line var l_dummy defined, but not used".
34 integer, parameter :: n
= 100
35 real*8, allocatable
:: b(:)
36 !$acc declare create (b)
54 real*8 function fun1 (ix
)
59 real*8 function fun2 (ix
)
65 if (allocated (b
)) error
stop
67 ! Test local usage of an allocated declared array.
72 if (.not
.allocated (b
)) error
stop
73 if (.not
.acc_is_present (b
)) error
stop
77 !$acc parallel loop ! { dg-line l[incr c] }
78 ! { dg-note {variable 'i' in 'private' clause is candidate for adjusting OpenACC privatization level} {} { target *-*-* } l$c }
79 ! { dg-note {variable 'i' ought to be adjusted for OpenACC privatization level: 'vector'} {} { target *-*-* } l$c }
80 ! { dg-note {variable 'i' adjusted for OpenACC privatization level: 'vector'} {} { target { ! openacc_host_selected } } l$c }
81 ! { dg-note {variable 'i\.[0-9]+' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} {} { target *-*-* } l$c }
82 ! { dg-optimized {assigned OpenACC gang vector loop parallelism} {} { target *-*-* } l$c }
87 if (.not
.acc_is_present (b
)) error
stop
92 if (b(i
) /= i
*a
) error
stop
98 ! Test the usage of an allocated declared array inside an acc
104 if (.not
.allocated (b
)) error
stop
105 if (.not
.acc_is_present (b
)) error
stop
108 call sub1
! { dg-line l[incr c] }
109 ! { dg-optimized {assigned OpenACC gang worker vector loop parallelism} {} { target *-*-* } l$c }
112 if (.not
.acc_is_present (b
)) error
stop
117 if (b(i
) /= i
*2) error
stop
123 ! Test the usage of an allocated declared array inside a host
128 if (.not
.acc_is_present (b
)) error
stop
133 if (b(i
) /= 1.0) error
stop
139 if (allocated (b
)) error
stop
141 ! Test the usage of an allocated declared array inside an acc
147 if (.not
.allocated (b
)) error
stop
148 if (.not
.acc_is_present (b
)) error
stop
150 !$acc parallel loop ! { dg-line l[incr c] }
151 ! { dg-note {variable 'i' in 'private' clause is candidate for adjusting OpenACC privatization level} {} { target *-*-* } l$c }
152 ! { dg-note {variable 'i' ought to be adjusted for OpenACC privatization level: 'vector'} {} { target *-*-* } l$c }
153 ! { dg-note {variable 'i' adjusted for OpenACC privatization level: 'vector'} {} { target { ! openacc_host_selected } } l$c }
154 ! { dg-note {variable 'i\.[0-9]+' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} {} { target *-*-* } l$c }
155 ! { dg-optimized {assigned OpenACC gang vector loop parallelism} {} { target *-*-* } l$c }
160 !$acc parallel loop ! { dg-line l[incr c] }
161 ! { dg-note {variable 'i' in 'private' clause is candidate for adjusting OpenACC privatization level} {} { target *-*-* } l$c }
162 ! { dg-note {variable 'i' ought to be adjusted for OpenACC privatization level: 'vector'} {} { target *-*-* } l$c }
163 ! { dg-note {variable 'i' adjusted for OpenACC privatization level: 'vector'} {} { target { ! openacc_host_selected } } l$c }
164 ! { dg-note {variable 'i\.[0-9]+' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} {} { target *-*-* } l$c }
165 ! { dg-optimized {assigned OpenACC gang vector loop parallelism} {} { target *-*-* } l$c }
167 b(i
) = fun1 (i
) ! { dg-line l[incr c] }
168 ! { dg-optimized {assigned OpenACC seq loop parallelism} {} { target *-*-* } l$c }
171 if (.not
.acc_is_present (b
)) error
stop
176 if (b(i
) /= i
) error
stop
182 ! Test the usage of an allocated declared array inside a host
188 if (.not
.allocated (b
)) error
stop
189 if (.not
.acc_is_present (b
)) error
stop
191 !$acc parallel loop ! { dg-line l[incr c] }
192 ! { dg-note {variable 'i' in 'private' clause is candidate for adjusting OpenACC privatization level} {} { target *-*-* } l$c }
193 ! { dg-note {variable 'i' ought to be adjusted for OpenACC privatization level: 'vector'} {} { target *-*-* } l$c }
194 ! { dg-note {variable 'i' adjusted for OpenACC privatization level: 'vector'} {} { target { ! openacc_host_selected } } l$c }
195 ! { dg-note {variable 'i\.[0-9]+' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} {} { target *-*-* } l$c }
196 ! { dg-optimized {assigned OpenACC gang vector loop parallelism} {} { target *-*-* } l$c }
207 if (.not
.acc_is_present (b
)) error
stop
210 if (b(i
) /= i
*i
) error
stop
215 end program test
! { dg-line l[incr c] }
216 ! { dg-bogus {note: variable 'overflow\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} {TODO n/a} { xfail *-*-* } l$c }
217 ! { dg-bogus {note: variable 'not_prev_allocated\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} {TODO n/a} { xfail *-*-* } l$c }
218 ! { dg-bogus {note: variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: artificial} {TODO n/a} { xfail *-*-* } l$c }
220 ! Set each element in array 'b' at index i to i*2.
222 subroutine sub1
! { dg-line subroutine_sub1 }
227 ! { dg-bogus {[Ww]arning: region is worker partitioned but does not contain worker partitioned code} {TODO default 'gang' 'vector'} { xfail *-*-* } subroutine_sub1 }
229 !$acc loop ! { dg-line l[incr c] }
230 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} {} { target *-*-* } l$c }
231 ! { dg-optimized {assigned OpenACC gang vector loop parallelism} {} { target *-*-* } l$c }
237 ! Allocate array 'b', and set it to all 1.0.
248 if (.not
.allocated (b
)) error
stop
249 if (.not
.acc_is_present (b
)) error
stop
251 !$acc parallel loop ! { dg-line l[incr c] }
252 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} {} { target *-*-* } l$c }
253 ! { dg-optimized {assigned OpenACC gang vector loop parallelism} {} { target *-*-* } l$c }
261 real*8 function fun1 (i
)
270 ! Return b(i) * i * i;
272 real*8 function fun2 (i
)