Skip gnat.dg/prot7.adb on hppa.
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / lib-14.f90
blob90c2868e643fc656bebde37f6d2677c1c79c0e75
1 ! Exercise the data movement runtime library functions on non-shared memory
2 ! targets.
4 ! { dg-do run }
5 ! { dg-skip-if "" { *-*-* } { "*" } { "-DACC_MEM_SHARED=0" } }
7 program main
8 use openacc
9 implicit none
11 integer, parameter :: N = 256
12 integer, allocatable :: h(:)
13 integer :: i
15 allocate (h(N))
17 do i = 1, N
18 h(i) = i
19 end do
21 call acc_present_or_copyin (h)
23 if (acc_is_present (h) .neqv. .TRUE.) stop 1
25 call acc_copyout (h)
27 if (acc_is_present (h) .neqv. .FALSE.) stop 1
29 do i = 1, N
30 if (h(i) /= i) stop 1
31 end do
33 do i = 1, N
34 h(i) = i + i
35 end do
37 call acc_pcopyin (h, sizeof (h))
39 if (acc_is_present (h) .neqv. .TRUE.) stop 1
41 call acc_copyout (h)
43 if (acc_is_present (h) .neqv. .FALSE.) stop 1
45 do i = 1, N
46 if (h(i) /= i + i) stop 1
47 end do
49 call acc_create (h)
51 if (acc_is_present (h) .neqv. .TRUE.) stop 1
53 !$acc parallel loop
54 do i = 1, N
55 h(i) = i
56 end do
57 !$end acc parallel
59 call acc_copyout (h)
61 if (acc_is_present (h) .neqv. .FALSE.) stop 1
63 do i = 1, N
64 if (h(i) /= i) stop 1
65 end do
67 call acc_present_or_create (h, sizeof (h))
69 if (acc_is_present (h) .neqv. .TRUE.) stop 1
71 call acc_delete (h)
73 if (acc_is_present (h) .neqv. .FALSE.) stop 1
75 call acc_pcreate (h)
77 if (acc_is_present (h) .neqv. .TRUE.) stop 1
79 call acc_delete (h)
81 if (acc_is_present (h) .neqv. .FALSE.) stop 1
83 end program