view libgomp/testsuite/libgomp.oacc-fortran/lib-14.f90 @ 143:76e1cf5455ef

add cbc_gc test
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Sun, 23 Dec 2018 19:24:05 +0900
parents 84e7813d76e9
children 1830386684a0
line wrap: on
line source

! Exercise the data movement runtime library functions on non-shared memory
! targets.

! { dg-do run { target openacc_nvidia_accel_selected } }

program main
  use openacc
  implicit none

  integer, parameter :: N = 256
  integer, allocatable :: h(:)
  integer :: i

  allocate (h(N))

  do i = 1, N
    h(i) = i
  end do 

  call acc_present_or_copyin (h)

  if (acc_is_present (h) .neqv. .TRUE.) call abort

  call acc_copyout (h)

  if (acc_is_present (h) .neqv. .FALSE.) call abort

  do i = 1, N
    if (h(i) /= i) call abort
  end do

  do i = 1, N
    h(i) = i + i
  end do 

  call acc_pcopyin (h, sizeof (h))

  if (acc_is_present (h) .neqv. .TRUE.) call abort

  call acc_copyout (h)

  if (acc_is_present (h) .neqv. .FALSE.) call abort

  do i = 1, N
    if (h(i) /= i + i) call abort
  end do

  call acc_create (h)

  if (acc_is_present (h) .neqv. .TRUE.) call abort

  !$acc parallel loop
    do i = 1, N
      h(i) = i
    end do
  !$end acc parallel

  call acc_copyout (h)

  if (acc_is_present (h) .neqv. .FALSE.) call abort

  do i = 1, N
    if (h(i) /= i) call abort
  end do

  call acc_present_or_create (h, sizeof (h))

  if (acc_is_present (h) .neqv. .TRUE.) call abort

  call acc_delete (h)

  if (acc_is_present (h) .neqv. .FALSE.) call abort

  call acc_pcreate (h)

  if (acc_is_present (h) .neqv. .TRUE.) call abort

  call acc_delete (h)

  if (acc_is_present (h) .neqv. .FALSE.) call abort

end program