Fix gcc.c-torture/execute/ieee/cdivchkf.c on hpux
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / privatized-ref-1.f95
blobb027d14e7f52f007190b95376f7f633cd8d62f29
1 ! { dg-do run }
3 ! { dg-additional-options "-fopt-info-note-omp" }
4 ! { dg-additional-options "-foffload=-fopt-info-note-omp" }
6 ! { dg-additional-options "--param=openacc-privatization=noisy" }
7 ! { dg-additional-options "-foffload=--param=openacc-privatization=noisy" }
9 ! { dg-additional-options "-Wuninitialized" }
11 !TODO
12 ! { dg-xfail-run-if TODO { openacc_radeon_accel_selected && { ! __OPTIMIZE__ } } }
14 ! It's only with Tcl 8.5 (released in 2007) that "the variable 'varName'
15 ! passed to 'incr' may be unset, and in that case, it will be set to [...]",
16 ! so to maintain compatibility with earlier Tcl releases, we manually
17 ! initialize counter variables:
18 ! { dg-line l_dummy[variable c_loop 0] }
19 ! { dg-message "dummy" "" { target iN-VAl-Id } l_dummy } to avoid
20 ! "WARNING: dg-line var l_dummy defined, but not used". */
22 program main
23 implicit none
24 integer :: myint
25 integer :: i
26 real :: res(65536), tmp
28 res(:) = 0.0
30 myint = 3
31 call gangs(myint, res)
33 do i=1,65536
34 tmp = i * 97
35 if (res(i) .ne. tmp) stop 1
36 end do
38 res(:) = 0.0
40 myint = 5
41 call workers(myint, res)
43 do i=1,65536
44 tmp = i * 99
45 if (res(i) .ne. tmp) stop 2
46 end do
48 res(:) = 0.0
50 myint = 7
51 call vectors(myint, res)
53 do i=1,65536
54 tmp = i * 101
55 if (res(i) .ne. tmp) stop 3
56 end do
58 res(:) = 0.0
60 myint = 9
61 call gangs_workers_vectors(myint, res)
63 do i=1,65536
64 tmp = i * 103
65 if (res(i) .ne. tmp) stop 4
66 end do
68 contains
70 subroutine gangs(t1, res)
71 implicit none
72 integer :: t1
73 integer :: i, j
74 real, intent(out) :: res(:)
76 !$acc parallel copyout(res) num_gangs(64)
78 !$acc loop collapse(2) gang private(t1) ! { dg-line l_loop[incr c_loop] }
79 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
80 ! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
81 ! { dg-note {variable 't1' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
82 do i=0,255
83 do j=1,256
84 t1 = (i * 256 + j) * 97
85 res(i * 256 + j) = t1
86 end do
87 end do
89 !$acc end parallel
90 end subroutine gangs
92 subroutine workers(t1, res)
93 implicit none
94 integer :: t1
95 integer :: i, j
96 real, intent(out) :: res(:)
98 !$acc parallel copyout(res) num_gangs(64) num_workers(64)
99 ! { dg-warning "using .num_workers \\(32\\)., ignoring 64" "" { target openacc_nvidia_accel_selected } .-1 }
101 !$acc loop gang ! { dg-line l_loop[incr c_loop] }
102 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
103 do i=0,255
104 !$acc loop worker private(t1) ! { dg-line l_loop[incr c_loop] }
105 ! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
106 ! { dg-note {variable 't1' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
107 do j=1,256
108 t1 = (i * 256 + j) * 99
109 res(i * 256 + j) = t1
110 end do
111 end do
113 !$acc end parallel
114 end subroutine workers
116 subroutine vectors(t1, res)
117 implicit none
118 integer :: t1
119 integer :: i, j
120 real, intent(out) :: res(:)
122 !$acc parallel copyout(res) num_gangs(64) num_workers(64)
123 ! { dg-warning "using .num_workers \\(32\\)., ignoring 64" "" { target openacc_nvidia_accel_selected } .-1 }
125 !$acc loop gang worker ! { dg-line l_loop[incr c_loop] }
126 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
127 do i=0,255
128 !$acc loop vector private(t1) ! { dg-line l_loop[incr c_loop] }
129 ! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
130 ! { dg-note {variable 't1' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
131 do j=1,256
132 t1 = (i * 256 + j) * 101
133 res(i * 256 + j) = t1
134 end do
135 end do
137 !$acc end parallel
138 end subroutine vectors
140 subroutine gangs_workers_vectors(t1, res)
141 implicit none
142 integer :: t1
143 integer :: i, j
144 real, intent(out) :: res(:)
146 !$acc parallel copyout(res) num_gangs(64) num_workers(64)
147 ! { dg-warning "using .num_workers \\(32\\)., ignoring 64" "" { target openacc_nvidia_accel_selected } .-1 }
149 !$acc loop collapse(2) gang worker vector private(t1) ! { dg-line l_loop[incr c_loop] }
150 ! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
151 ! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
152 ! { dg-note {variable 't1' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
153 do i=0,255
154 do j=1,256
155 t1 = (i * 256 + j) * 103
156 res(i * 256 + j) = t1
157 end do
158 end do
160 !$acc end parallel
161 end subroutine gangs_workers_vectors
163 end program main