gcc/libgomp/testsuite/libgomp.fortran/target-var.f90
Tobias Burnus 1c0fdaf79e openmp: ensure variables in offload table are streamed out (PRs 94848 + 95551)
gcc/ChangeLog:

	PR lto/94848
	PR middle-end/95551
	* omp-offload.c (add_decls_addresses_to_decl_constructor,
	omp_finish_file): Skip removed items.
	* lto-cgraph.c (output_offload_tables): Likewise; set force_output
	to this node for variables and functions.

libgomp/ChangeLog:

	PR lto/94848
	PR middle-end/95551
	* testsuite/libgomp.fortran/target-var.f90: New test.
2020-06-08 23:24:57 +02:00

33 lines
780 B
Fortran

! { dg-additional-options "-O3" }
!
! With -O3 the static local variable A.10 generated for
! the array constructor [-2, -4, ..., -20] is optimized
! away - which has to be handled in the offload_vars table.
!
program main
implicit none (type, external)
integer :: j
integer, allocatable :: A(:)
A = [(3*j, j=1, 10)]
call bar (A)
deallocate (A)
contains
subroutine bar (array)
integer :: i
integer :: array(:)
!$omp target map(from:array)
!$acc parallel copyout(array)
array = [(-2*i, i = 1, size(array))]
!$omp do private(array)
!$acc loop gang private(array)
do i = 1, 10
array(i) = 9*i
end do
if (any (array /= [(-2*i, i = 1, 10)])) error stop 2
!$omp end target
!$acc end parallel
end subroutine bar
end