1! { dg-do run }
2! { dg-additional-options "-cpp" }
3
4! { dg-additional-options "-fopt-info-note-omp" }
5! { dg-additional-options "--param=openacc-privatization=noisy" }
6! { dg-additional-options "-foffload=-fopt-info-note-omp" }
7! { dg-additional-options "-foffload=--param=openacc-privatization=noisy" }
8! for testing/documenting aspects of that functionality.
9
10! It's only with Tcl 8.5 (released in 2007) that "the variable 'varName'
11! passed to 'incr' may be unset, and in that case, it will be set to [...]",
12! so to maintain compatibility with earlier Tcl releases, we manually
13! initialize counter variables:
14! { dg-line l_dummy[variable c_compute 0] }
15! { dg-message "dummy" "" { target iN-VAl-Id } l_dummy } to avoid
16! "WARNING: dg-line var l_dummy defined, but not used".  */
17
18program main
19  use openacc
20  implicit none
21
22  integer, parameter :: N = 8
23  integer, parameter :: one = 1
24  integer, parameter :: zero = 0
25  integer i, nn
26  real, allocatable :: a(:), b(:)
27  real exp, exp2
28
29  i = 0
30
31  allocate (a(N))
32  allocate (b(N))
33
34  a(:) = 4.0
35
36  !$acc parallel copyin (a(1:N)) copyout (b(1:N)) if (1 == 1) ! { dg-line l_compute[incr c_compute] }
37  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
38     do i = 1, N
39        ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
40        !TODO Unhandled 'CONST_DECL' instances for constant argument in 'acc_on_device' call.
41        if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
42          b(i) = a(i) + 1
43        else
44          b(i) = a(i)
45        end if
46     end do
47  !$acc end parallel
48
49#if ACC_MEM_SHARED
50  exp = 5.0
51#else
52  exp = 4.0
53#endif
54
55  do i = 1, N
56    if (b(i) .ne. exp) STOP 1
57  end do
58
59  a(:) = 16.0
60
61  !$acc parallel if (0 == 1) ! { dg-line l_compute[incr c_compute] }
62  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
63     do i = 1, N
64        ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
65       if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
66         b(i) = a(i) + 1
67       else
68         b(i) = a(i)
69       end if
70     end do
71  !$acc end parallel
72
73  do i = 1, N
74    if (b(i) .ne. 17.0) STOP 2
75  end do
76
77  a(:) = 8.0
78
79  !$acc parallel copyin (a(1:N)) copyout (b(1:N)) if (one == 1) ! { dg-line l_compute[incr c_compute] }
80  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
81    do i = 1, N
82       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
83      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
84        b(i) = a(i) + 1
85      else
86        b(i) = a(i)
87      end if
88    end do
89  !$acc end parallel
90
91#if ACC_MEM_SHARED
92  exp = 9.0
93#else
94  exp = 8.0
95#endif
96
97  do i = 1, N
98    if (b(i) .ne. exp) STOP 3
99  end do
100
101  a(:) = 22.0
102
103  !$acc parallel if (zero == 1) ! { dg-line l_compute[incr c_compute] }
104  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
105    do i = 1, N
106       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
107      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
108        b(i) = a(i) + 1
109      else
110        b(i) = a(i)
111      end if
112    end do
113  !$acc end parallel
114
115  do i = 1, N
116    if (b(i) .ne. 23.0) STOP 4
117  end do
118
119  a(:) = 16.0
120
121  !$acc parallel copyin (a(1:N)) copyout (b(1:N)) if (.TRUE.) ! { dg-line l_compute[incr c_compute] }
122  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
123    do i = 1, N
124       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
125      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
126        b(i) = a(i) + 1
127      else
128        b(i) = a(i)
129      end if
130    end do
131  !$acc end parallel
132
133#if ACC_MEM_SHARED
134  exp = 17.0;
135#else
136  exp = 16.0;
137#endif
138
139  do i = 1, N
140    if (b(i) .ne. exp) STOP 5
141  end do
142
143  a(:) = 76.0
144
145  !$acc parallel if (.FALSE.) ! { dg-line l_compute[incr c_compute] }
146  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
147    do i = 1, N
148       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
149      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
150        b(i) = a(i) + 1
151      else
152        b(i) = a(i)
153      end if
154    end do
155  !$acc end parallel
156
157  do i = 1, N
158    if (b(i) .ne. 77.0) STOP 6
159  end do
160
161  a(:) = 22.0
162
163  nn = 1
164
165  !$acc parallel copyin (a(1:N)) copyout (b(1:N)) if (nn == 1) ! { dg-line l_compute[incr c_compute] }
166  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
167    do i = 1, N
168       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
169      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
170        b(i) = a(i) + 1
171      else
172        b(i) = a(i)
173      end if
174    end do
175  !$acc end parallel
176
177#if ACC_MEM_SHARED
178  exp = 23.0;
179#else
180  exp = 22.0;
181#endif
182
183  do i = 1, N
184    if (b(i) .ne. exp) STOP 7
185  end do
186
187  a(:) = 18.0
188
189  nn = 0
190
191  !$acc parallel if (nn == 1) ! { dg-line l_compute[incr c_compute] }
192  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
193    do i = 1, N
194       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
195      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
196        b(i) = a(i) + 1
197      else
198        b(i) = a(i)
199      end if
200    end do
201  !$acc end parallel
202
203  do i = 1, N
204    if (b(i) .ne. 19.0) STOP 8
205  end do
206
207  a(:) = 49.0
208
209  nn = 1
210
211  !$acc parallel copyin (a(1:N)) copyout (b(1:N)) if ((nn + nn) > 0) ! { dg-line l_compute[incr c_compute] }
212  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
213    do i = 1, N
214       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
215      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
216        b(i) = a(i) + 1
217      else
218        b(i) = a(i)
219      end if
220    end do
221  !$acc end parallel
222
223#if ACC_MEM_SHARED
224  exp = 50.0
225#else
226  exp = 49.0
227#endif
228
229  do i = 1, N
230    if (b(i) .ne. exp) STOP 9
231  end do
232
233  a(:) = 38.0
234
235  nn = 0;
236
237  !$acc parallel copyin (a(1:N)) copyout (b(1:N)) if ((nn + nn) > 0) ! { dg-line l_compute[incr c_compute] }
238  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
239    do i = 1, N
240       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
241      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
242        b(i) = a(i) + 1
243      else
244        b(i) = a(i)
245      end if
246    end do
247  !$acc end parallel
248
249  do i = 1, N
250    if (b(i) .ne. 39.0) STOP 10
251  end do
252
253  a(:) = 91.0
254
255  !$acc parallel copyin (a(1:N)) copyout (b(1:N)) if (-2 > 0) ! { dg-line l_compute[incr c_compute] }
256  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
257    do i = 1, N
258       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
259      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
260        b(i) = a(i) + 1
261      else
262        b(i) = a(i)
263      end if
264    end do
265  !$acc end parallel
266
267  do i = 1, N
268    if (b(i) .ne. 92.0) STOP 11
269  end do
270
271  a(:) = 43.0
272
273  !$acc parallel copyin (a(1:N)) copyout (b(1:N)) if (one == 1) ! { dg-line l_compute[incr c_compute] }
274  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
275    do i = 1, N
276       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
277      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
278        b(i) = a(i) + 1
279      else
280        b(i) = a(i)
281      end if
282    end do
283  !$acc end parallel
284
285#if ACC_MEM_SHARED
286  exp = 44.0
287#else
288  exp = 43.0
289#endif
290
291  do i = 1, N
292    if (b(i) .ne. exp) STOP 12
293  end do
294
295  a(:) = 87.0
296
297  !$acc parallel if (one == 0) ! { dg-line l_compute[incr c_compute] }
298  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
299    do i = 1, N
300       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
301      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
302        b(i) = a(i) + 1
303      else
304        b(i) = a(i)
305      end if
306    end do
307  !$acc end parallel
308
309  do i = 1, N
310    if (b(i) .ne. 88.0) STOP 13
311  end do
312
313  a(:) = 3.0
314  b(:) = 9.0
315
316#if ACC_MEM_SHARED
317  exp = 0.0
318  exp2 = 0.0
319#else
320  call acc_copyin (a, sizeof (a))
321  call acc_copyin (b, sizeof (b))
322  exp = 3.0;
323  exp2 = 9.0;
324#endif
325
326  !$acc update device (a(1:N), b(1:N)) if (1 == 1)
327
328  a(:) = 0.0
329  b(:) = 0.0
330
331  !$acc update host (a(1:N), b(1:N)) if (1 == 1)
332
333  do i = 1, N
334    if (a(i) .ne. exp) STOP 14
335    if (b(i) .ne. exp2) STOP 15
336  end do
337
338  a(:) = 6.0
339  b(:) = 12.0
340
341  !$acc update device (a(1:N), b(1:N)) if (0 == 1)
342
343  a(:) = 0.0
344  b(:) = 0.0
345
346  !$acc update host (a(1:N), b(1:N)) if (1 == 1)
347
348  do i = 1, N
349    if (a(i) .ne. exp) STOP 16
350    if (b(i) .ne. exp2) STOP 17
351  end do
352
353  a(:) = 26.0
354  b(:) = 21.0
355
356  !$acc update device (a(1:N), b(1:N)) if (1 == 1)
357
358  a(:) = 0.0
359  b(:) = 0.0
360
361  !$acc update host (a(1:N), b(1:N)) if (0 == 1)
362
363  do i = 1, N
364    if (a(i) .ne. 0.0) STOP 18
365    if (b(i) .ne. 0.0) STOP 19
366  end do
367
368#if !ACC_MEM_SHARED
369  call acc_copyout (a, sizeof (a))
370  call acc_copyout (b, sizeof (b))
371#endif
372
373  a(:) = 4.0
374  b(:) = 0.0
375
376  !$acc data copyin (a(1:N)) copyout (b(1:N)) if (1 == 1)
377  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
378  ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
379
380    !$acc parallel present (a(1:N)) ! { dg-line l_compute[incr c_compute] }
381    ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
382       do i = 1, N
383           b(i) = a(i)
384       end do
385    !$acc end parallel
386  !$acc end data
387
388  do i = 1, N
389    if (b(i) .ne. 4.0) STOP 20
390  end do
391
392  a(:) = 8.0
393  b(:) = 1.0
394
395  !$acc data copyin (a(1:N)) copyout (b(1:N)) if (0 == 1)
396  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target { ! openacc_host_selected } } .-1 }
397  ! { dg-note {variable 'parm\.[0-9]+' declared in block is candidate for adjusting OpenACC privatization level} "" { target { ! openacc_host_selected } } .-2 }
398
399#if !ACC_MEM_SHARED
400  if (acc_is_present (a) .eqv. .TRUE.) STOP 21
401  if (acc_is_present (b) .eqv. .TRUE.) STOP 22
402#endif
403
404  !$acc end data
405
406  a(:) = 18.0
407  b(:) = 21.0
408
409  !$acc data copyin (a(1:N)) if (1 == 1)
410  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
411  ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
412  ! { dg-note {variable 'parm\.[0-9]+' declared in block is candidate for adjusting OpenACC privatization level} "" { target { ! openacc_host_selected } } .-3 }
413
414#if !ACC_MEM_SHARED
415    if (acc_is_present (a) .eqv. .FALSE.) STOP 23
416#endif
417
418    !$acc data copyout (b(1:N)) if (0 == 1)
419    ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
420    ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
421    ! { dg-note {variable 'parm\.[0-9]+' declared in block is candidate for adjusting OpenACC privatization level} "" { target { ! openacc_host_selected } } .-3 }
422#if !ACC_MEM_SHARED
423      if (acc_is_present (b) .eqv. .TRUE.) STOP 24
424#endif
425        !$acc data copyout (b(1:N)) if (1 == 1)
426        ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
427        ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
428
429        !$acc parallel present (a(1:N)) present (b(1:N)) ! { dg-line l_compute[incr c_compute] }
430        ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
431          do i = 1, N
432            b(i) = a(i)
433          end do
434      !$acc end parallel
435
436    !$acc end data
437
438#if !ACC_MEM_SHARED
439    if (acc_is_present (b) .eqv. .TRUE.) STOP 25
440#endif
441    !$acc end data
442  !$acc end data
443
444  do i = 1, N
445   if (b(1) .ne. 18.0) STOP 26
446  end do
447
448  !$acc enter data copyin (b(1:N)) if (0 == 1)
449
450#if !ACC_MEM_SHARED
451  if (acc_is_present (b) .eqv. .TRUE.) STOP 27
452#endif
453
454  !$acc exit data delete (b(1:N)) if (0 == 1)
455
456  !$acc enter data copyin (b(1:N)) if (1 == 1)
457
458#if !ACC_MEM_SHARED
459    if (acc_is_present (b) .eqv. .FALSE.) STOP 28
460#endif
461
462  !$acc exit data delete (b(1:N)) if (1 == 1)
463
464#if !ACC_MEM_SHARED
465  if (acc_is_present (b) .eqv. .TRUE.) STOP 29
466#endif
467
468  !$acc enter data copyin (b(1:N)) if (zero == 1)
469
470#if !ACC_MEM_SHARED
471    if (acc_is_present (b) .eqv. .TRUE.) STOP 30
472#endif
473
474  !$acc exit data delete (b(1:N)) if (zero == 1)
475
476  !$acc enter data copyin (b(1:N)) if (one == 1)
477
478#if !ACC_MEM_SHARED
479    if (acc_is_present (b) .eqv. .FALSE.) STOP 31
480#endif
481
482  !$acc exit data delete (b(1:N)) if (one == 1)
483
484#if !ACC_MEM_SHARED
485  if (acc_is_present (b) .eqv. .TRUE.) STOP 32
486#endif
487
488  !$acc enter data copyin (b(1:N)) if (one == 0)
489
490#if !ACC_MEM_SHARED
491    if (acc_is_present (b) .eqv. .TRUE.) STOP 33
492#endif
493
494  !$acc exit data delete (b(1:N)) if (one == 0)
495
496  !$acc enter data copyin (b(1:N)) if (one == 1)
497
498#if !ACC_MEM_SHARED
499    if (acc_is_present (b) .eqv. .FALSE.) STOP 34
500#endif
501
502  !$acc exit data delete (b(1:N)) if (one == 1)
503
504#if !ACC_MEM_SHARED
505  if (acc_is_present (b) .eqv. .TRUE.) STOP 35
506#endif
507
508  a(:) = 4.0
509
510  !$acc kernels copyin (a(1:N)) copyout (b(1:N)) if (1 == 1) ! { dg-line l_compute[incr c_compute] }
511  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
512     do i = 1, N
513        ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
514        if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
515          b(i) = a(i) + 1
516        else
517          b(i) = a(i)
518        end if
519     end do
520  !$acc end kernels
521
522#if ACC_MEM_SHARED
523  exp = 5.0
524#else
525  exp = 4.0
526#endif
527
528  do i = 1, N
529    if (b(i) .ne. exp) STOP 36
530  end do
531
532  a(:) = 16.0
533
534  !$acc kernels if (0 == 1) ! { dg-line l_compute[incr c_compute] }
535  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
536     do i = 1, N
537        ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
538       if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
539         b(i) = a(i) + 1
540       else
541         b(i) = a(i)
542       end if
543     end do
544  !$acc end kernels
545
546  do i = 1, N
547    if (b(i) .ne. 17.0) STOP 37
548  end do
549
550  a(:) = 8.0
551
552  !$acc kernels copyin (a(1:N)) copyout (b(1:N)) if (one == 1) ! { dg-line l_compute[incr c_compute] }
553  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
554    do i = 1, N
555       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
556      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
557        b(i) = a(i) + 1
558      else
559        b(i) = a(i)
560      end if
561    end do
562  !$acc end kernels
563
564#if ACC_MEM_SHARED
565  exp = 9.0
566#else
567  exp = 8.0
568#endif
569
570  do i = 1, N
571    if (b(i) .ne. exp) STOP 38
572  end do
573
574  a(:) = 22.0
575
576  !$acc kernels if (zero == 1) ! { dg-line l_compute[incr c_compute] }
577  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
578    do i = 1, N
579       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
580      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
581        b(i) = a(i) + 1
582      else
583        b(i) = a(i)
584      end if
585    end do
586  !$acc end kernels
587
588  do i = 1, N
589    if (b(i) .ne. 23.0) STOP 39
590  end do
591
592  a(:) = 16.0
593
594  !$acc kernels copyin (a(1:N)) copyout (b(1:N)) if (.TRUE.) ! { dg-line l_compute[incr c_compute] }
595  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
596    do i = 1, N
597       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
598      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
599        b(i) = a(i) + 1
600      else
601        b(i) = a(i)
602      end if
603    end do
604  !$acc end kernels
605
606#if ACC_MEM_SHARED
607  exp = 17.0;
608#else
609  exp = 16.0;
610#endif
611
612  do i = 1, N
613    if (b(i) .ne. exp) STOP 40
614  end do
615
616  a(:) = 76.0
617
618  !$acc kernels if (.FALSE.) ! { dg-line l_compute[incr c_compute] }
619  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
620    do i = 1, N
621       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
622      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
623        b(i) = a(i) + 1
624      else
625        b(i) = a(i)
626      end if
627    end do
628  !$acc end kernels
629
630  do i = 1, N
631    if (b(i) .ne. 77.0) STOP 41
632  end do
633
634  a(:) = 22.0
635
636  nn = 1
637
638  !$acc kernels copyin (a(1:N)) copyout (b(1:N)) if (nn == 1) ! { dg-line l_compute[incr c_compute] }
639  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
640    do i = 1, N
641       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
642      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
643        b(i) = a(i) + 1
644      else
645        b(i) = a(i)
646      end if
647    end do
648  !$acc end kernels
649
650#if ACC_MEM_SHARED
651  exp = 23.0;
652#else
653  exp = 22.0;
654#endif
655
656  do i = 1, N
657    if (b(i) .ne. exp) STOP 42
658  end do
659
660  a(:) = 18.0
661
662  nn = 0
663
664  !$acc kernels if (nn == 1) ! { dg-line l_compute[incr c_compute] }
665  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
666    do i = 1, N
667       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
668      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
669        b(i) = a(i) + 1
670      else
671        b(i) = a(i)
672      end if
673    end do
674  !$acc end kernels
675
676  do i = 1, N
677    if (b(i) .ne. 19.0) STOP 43
678  end do
679
680  a(:) = 49.0
681
682  nn = 1
683
684  !$acc kernels copyin (a(1:N)) copyout (b(1:N)) if ((nn + nn) > 0) ! { dg-line l_compute[incr c_compute] }
685  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
686    do i = 1, N
687       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
688      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
689        b(i) = a(i) + 1
690      else
691        b(i) = a(i)
692      end if
693    end do
694  !$acc end kernels
695
696#if ACC_MEM_SHARED
697  exp = 50.0
698#else
699  exp = 49.0
700#endif
701
702  do i = 1, N
703    if (b(i) .ne. exp) STOP 44
704  end do
705
706  a(:) = 38.0
707
708  nn = 0;
709
710  !$acc kernels copyin (a(1:N)) copyout (b(1:N)) if ((nn + nn) > 0) ! { dg-line l_compute[incr c_compute] }
711  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
712    do i = 1, N
713       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
714      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
715        b(i) = a(i) + 1
716      else
717        b(i) = a(i)
718      end if
719    end do
720  !$acc end kernels
721
722  do i = 1, N
723    if (b(i) .ne. 39.0) STOP 45
724  end do
725
726  a(:) = 91.0
727
728  !$acc kernels copyin (a(1:N)) copyout (b(1:N)) if (-2 > 0) ! { dg-line l_compute[incr c_compute] }
729  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
730    do i = 1, N
731       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
732      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
733        b(i) = a(i) + 1
734      else
735        b(i) = a(i)
736      end if
737    end do
738  !$acc end kernels
739
740  do i = 1, N
741    if (b(i) .ne. 92.0) STOP 46
742  end do
743
744  a(:) = 43.0
745
746  !$acc kernels copyin (a(1:N)) copyout (b(1:N)) if (one == 1) ! { dg-line l_compute[incr c_compute] }
747  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
748    do i = 1, N
749       ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
750      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
751        b(i) = a(i) + 1
752      else
753        b(i) = a(i)
754      end if
755    end do
756  !$acc end kernels
757
758#if ACC_MEM_SHARED
759  exp = 44.0
760#else
761  exp = 43.0
762#endif
763
764  do i = 1, N
765    if (b(i) .ne. exp) STOP 47
766  end do
767
768  a(:) = 87.0
769
770  !$acc kernels if (one == 0) ! { dg-line l_compute[incr c_compute] }
771  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
772    do i = 1, N
773      ! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } l_compute$c_compute }
774      if (acc_on_device (acc_device_host) .eqv. .TRUE.) then
775        b(i) = a(i) + 1
776      else
777        b(i) = a(i)
778      end if
779    end do
780  !$acc end kernels
781
782  do i = 1, N
783    if (b(i) .ne. 88.0) STOP 48
784  end do
785
786  a(:) = 3.0
787  b(:) = 9.0
788
789#if ACC_MEM_SHARED
790  exp = 0.0
791  exp2 = 0.0
792#else
793  call acc_copyin (a, sizeof (a))
794  call acc_copyin (b, sizeof (b))
795  exp = 3.0;
796  exp2 = 9.0;
797#endif
798
799  !$acc update device (a(1:N), b(1:N)) if (1 == 1)
800
801  a(:) = 0.0
802  b(:) = 0.0
803
804  !$acc update host (a(1:N), b(1:N)) if (1 == 1)
805
806  do i = 1, N
807    if (a(i) .ne. exp) STOP 49
808    if (b(i) .ne. exp2) STOP 50
809  end do
810
811  a(:) = 6.0
812  b(:) = 12.0
813
814  !$acc update device (a(1:N), b(1:N)) if (0 == 1)
815
816  a(:) = 0.0
817  b(:) = 0.0
818
819  !$acc update host (a(1:N), b(1:N)) if (1 == 1)
820
821  do i = 1, N
822    if (a(i) .ne. exp) STOP 51
823    if (b(i) .ne. exp2) STOP 52
824  end do
825
826  a(:) = 26.0
827  b(:) = 21.0
828
829  !$acc update device (a(1:N), b(1:N)) if (1 == 1)
830
831  a(:) = 0.0
832  b(:) = 0.0
833
834  !$acc update host (a(1:N), b(1:N)) if (0 == 1)
835
836  do i = 1, N
837    if (a(i) .ne. 0.0) STOP 53
838    if (b(i) .ne. 0.0) STOP 54
839  end do
840
841#if !ACC_MEM_SHARED
842  call acc_copyout (a, sizeof (a))
843  call acc_copyout (b, sizeof (b))
844#endif
845
846  a(:) = 4.0
847  b(:) = 0.0
848
849  !$acc data copyin (a(1:N)) copyout (b(1:N)) if (1 == 1)
850  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
851  ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
852
853    !$acc kernels present (a(1:N)) ! { dg-line l_compute[incr c_compute] }
854    ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
855       do i = 1, N
856           b(i) = a(i)
857       end do
858    !$acc end kernels
859  !$acc end data
860
861  do i = 1, N
862    if (b(i) .ne. 4.0) STOP 55
863  end do
864
865  a(:) = 8.0
866  b(:) = 1.0
867
868  !$acc data copyin (a(1:N)) copyout (b(1:N)) if (0 == 1)
869  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target { ! openacc_host_selected } } .-1 }
870  ! { dg-note {variable 'parm\.[0-9]+' declared in block is candidate for adjusting OpenACC privatization level} "" { target { ! openacc_host_selected } } .-2 }
871
872#if !ACC_MEM_SHARED
873  if (acc_is_present (a) .eqv. .TRUE.) STOP 56
874  if (acc_is_present (b) .eqv. .TRUE.) STOP 57
875#endif
876
877  !$acc end data
878
879  a(:) = 18.0
880  b(:) = 21.0
881
882  !$acc data copyin (a(1:N)) if (1 == 1)
883  ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
884  ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
885  ! { dg-note {variable 'parm\.[0-9]+' declared in block is candidate for adjusting OpenACC privatization level} "" { target { ! openacc_host_selected } } .-3 }
886
887#if !ACC_MEM_SHARED
888    if (acc_is_present (a) .eqv. .FALSE.) STOP 58
889#endif
890
891    !$acc data copyout (b(1:N)) if (0 == 1)
892    ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
893    ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
894    ! { dg-note {variable 'parm\.[0-9]+' declared in block is candidate for adjusting OpenACC privatization level} "" { target { ! openacc_host_selected } } .-3 }
895#if !ACC_MEM_SHARED
896      if (acc_is_present (b) .eqv. .TRUE.) STOP 59
897#endif
898        !$acc data copyout (b(1:N)) if (1 == 1)
899        ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
900        ! { dg-note {variable 'parm\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
901
902        !$acc kernels present (a(1:N)) present (b(1:N)) ! { dg-line l_compute[incr c_compute] }
903        ! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_compute$c_compute }
904          do i = 1, N
905            b(i) = a(i)
906          end do
907      !$acc end kernels
908
909    !$acc end data
910
911#if !ACC_MEM_SHARED
912    if (acc_is_present (b) .eqv. .TRUE.) STOP 60
913#endif
914    !$acc end data
915  !$acc end data
916
917  do i = 1, N
918   if (b(1) .ne. 18.0) STOP 61
919  end do
920
921  !$acc enter data copyin (b(1:N)) if (0 == 1)
922
923#if !ACC_MEM_SHARED
924  if (acc_is_present (b) .eqv. .TRUE.) STOP 62
925#endif
926
927  !$acc exit data delete (b(1:N)) if (0 == 1)
928
929  !$acc enter data copyin (b(1:N)) if (1 == 1)
930
931#if !ACC_MEM_SHARED
932    if (acc_is_present (b) .eqv. .FALSE.) STOP 63
933#endif
934
935  !$acc exit data delete (b(1:N)) if (1 == 1)
936
937#if !ACC_MEM_SHARED
938  if (acc_is_present (b) .eqv. .TRUE.) STOP 64
939#endif
940
941  !$acc enter data copyin (b(1:N)) if (zero == 1)
942
943#if !ACC_MEM_SHARED
944    if (acc_is_present (b) .eqv. .TRUE.) STOP 65
945#endif
946
947  !$acc exit data delete (b(1:N)) if (zero == 1)
948
949  !$acc enter data copyin (b(1:N)) if (one == 1)
950
951#if !ACC_MEM_SHARED
952    if (acc_is_present (b) .eqv. .FALSE.) STOP 66
953#endif
954
955  !$acc exit data delete (b(1:N)) if (one == 1)
956
957#if !ACC_MEM_SHARED
958  if (acc_is_present (b) .eqv. .TRUE.) STOP 67
959#endif
960
961  !$acc enter data copyin (b(1:N)) if (one == 0)
962
963#if !ACC_MEM_SHARED
964    if (acc_is_present (b) .eqv. .TRUE.) STOP 68
965#endif
966
967  !$acc exit data delete (b(1:N)) if (one == 0)
968
969  !$acc enter data copyin (b(1:N)) if (one == 1)
970
971#if !ACC_MEM_SHARED
972    if (acc_is_present (b) .eqv. .FALSE.) STOP 69
973#endif
974
975  !$acc exit data delete (b(1:N)) if (one == 1)
976
977#if !ACC_MEM_SHARED
978  if (acc_is_present (b) .eqv. .TRUE.) STOP 70
979#endif
980
981end program main
982