PR c++/86342 - -Wdeprecated-copy and system headers.
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / data-4.f90
bloba444395d7c160924ca64ef2a83b3f6c11822ea83
1 ! { dg-do run }
3 program asyncwait
4 real, allocatable :: a(:), b(:), c(:), d(:), e(:)
5 integer i, N
7 N = 64
9 allocate (a(N))
10 allocate (b(N))
11 allocate (c(N))
12 allocate (d(N))
13 allocate (e(N))
15 a(:) = 3.0
16 b(:) = 0.0
18 !$acc enter data copyin (a(1:N)) copyin (b(1:N)) copyin (N) async
20 !$acc parallel async wait
21 !$acc loop
22 do i = 1, N
23 b(i) = a(i)
24 end do
25 !$acc end parallel
27 !$acc update host (a(1:N), b(1:N)) async wait
28 !$acc wait
30 do i = 1, N
31 if (a(i) .ne. 3.0) STOP 1
32 if (b(i) .ne. 3.0) STOP 2
33 end do
35 a(:) = 2.0
36 b(:) = 0.0
38 !$acc update device (a(1:N), b(1:N)) async (1)
40 !$acc parallel async (1) wait (1)
41 !$acc loop
42 do i = 1, N
43 b(i) = a(i)
44 end do
45 !$acc end parallel
47 !$acc update self (a(1:N), b(1:N)) async (1) wait (1)
48 !$acc wait (1)
50 do i = 1, N
51 if (a(i) .ne. 2.0) STOP 3
52 if (b(i) .ne. 2.0) STOP 4
53 end do
55 a(:) = 3.0
56 b(:) = 0.0
57 c(:) = 0.0
58 d(:) = 0.0
60 !$acc enter data copyin (c(1:N), d(1:N)) async (1)
61 !$acc update device (a(1:N), b(1:N)) async (1)
63 !$acc parallel async (1)
64 do i = 1, N
65 b(i) = (a(i) * a(i) * a(i)) / a(i)
66 end do
67 !$acc end parallel
69 !$acc parallel async (1)
70 do i = 1, N
71 c(i) = (a(i) * 4) / a(i)
72 end do
73 !$acc end parallel
75 !$acc parallel async (1)
76 do i = 1, N
77 d(i) = ((a(i) * a(i) + a(i)) / a(i)) - a(i)
78 end do
79 !$acc end parallel
81 !$acc update host (a(1:N), b(1:N), c(1:N), d(1:N)) async (1) wait (1)
83 !$acc wait (1)
85 do i = 1, N
86 if (a(i) .ne. 3.0) STOP 5
87 if (b(i) .ne. 9.0) STOP 6
88 if (c(i) .ne. 4.0) STOP 7
89 if (d(i) .ne. 1.0) STOP 8
90 end do
92 a(:) = 2.0
93 b(:) = 0.0
94 c(:) = 0.0
95 d(:) = 0.0
96 e(:) = 0.0
98 !$acc enter data copyin (e(1:N)) async (1)
99 !$acc update device (a(1:N), b(1:N), c(1:N), d(1:N)) async (1)
101 !$acc parallel async (1)
102 do i = 1, N
103 b(i) = (a(i) * a(i) * a(i)) / a(i)
104 end do
105 !$acc end parallel
107 !$acc parallel async (1)
108 do i = 1, N
109 c(i) = (a(i) * 4) / a(i)
110 end do
111 !$acc end parallel
113 !$acc parallel async (1)
114 do i = 1, N
115 d(i) = ((a(i) * a(i) + a(i)) / a(i)) - a(i)
116 end do
117 !$acc end parallel
119 !$acc parallel wait (1) async (1)
120 do i = 1, N
121 e(i) = a(i) + b(i) + c(i) + d(i)
122 end do
123 !$acc end parallel
125 !$acc update host (a(1:N), b(1:N), c(1:N), d(1:N), e(1:N)) async (1) wait (1)
126 !$acc wait (1)
127 !$acc exit data delete (N, a(1:N), b(1:N), c(1:N), d(1:N), e(1:N))
129 do i = 1, N
130 if (a(i) .ne. 2.0) STOP 9
131 if (b(i) .ne. 4.0) STOP 10
132 if (c(i) .ne. 4.0) STOP 11
133 if (d(i) .ne. 1.0) STOP 12
134 if (e(i) .ne. 11.0) STOP 13
135 end do
136 end program asyncwait