1! Test of vector-private variables declared on loop directive.
2
3! { dg-do run }
4
5! { dg-additional-options "-fopt-info-note-omp" }
6! { dg-additional-options "--param=openacc-privatization=noisy" }
7! { dg-additional-options "-foffload=-fopt-info-note-omp" }
8! { dg-additional-options "-foffload=--param=openacc-privatization=noisy" }
9! for testing/documenting aspects of that functionality.
10
11program main
12  integer :: x, i, j, k, idx, arr(0:32*32*32)
13
14  do i = 0, 32*32*32-1
15     arr(i) = i
16  end do
17
18  !$acc kernels copy(arr)
19  !$acc loop gang(num:32)
20  ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
21  do i = 0, 31
22     !$acc loop worker(num:8)
23     ! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
24     do j = 0, 31
25        !$acc loop vector(length:32) private(x)
26        ! { dg-note {variable 'k' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
27        ! { dg-note {variable 'x' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
28        do k = 0, 31
29           x = ieor(i, j * 3)
30           arr(i * 1024 + j * 32 + k) = arr(i * 1024 + j * 32 + k) + x * k
31        end do
32        !$acc loop vector(length:32) private(x)
33        ! { dg-note {variable 'k' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
34        ! { dg-note {variable 'x' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
35        do k = 0, 31
36           x = ior(i, j * 5)
37           arr(i * 1024 + j * 32 + k) = arr(i * 1024 + j * 32 + k) + x * k
38        end do
39     end do
40  end do
41  !$acc end kernels
42
43  do i = 0, 32 - 1
44     do j = 0, 32 -1
45        do k = 0, 32 - 1
46           idx = i * 1024 + j * 32 + k
47           if (arr(idx) .ne. idx + ieor(i, j * 3) * k + ior(i, j * 5) * k) then
48              stop 1
49           end if
50        end do
51     end do
52  end do
53end program main
54