This PR aims to fix a mapping error when trying to map nullary elements of a record type (primary example is allocatables/pointer types in Fortran at the moment). This should be legal to map, just not write to without pointing to anything within the target region. A common Fortran OpenMP idiom/example where this is useful can be found in the added Fortran offload example. The runtime error arises when we try to map the pointer member utilising a prescribed constant size that we receive from the lowered type, resulting in mapping of data that will be non-existent when there is no allocated data. The fix in this case is to emit a runtime check to see if the data has been allocated, if it hasn't been we select a size of 0, if it has we emit the usual type size.
25 lines
560 B
Fortran
25 lines
560 B
Fortran
! Offloading test with a target region mapping a null-ary (no target or
|
|
! allocated data) to device, and then setting the target on device before
|
|
! printing the changed target on host.
|
|
! REQUIRES: flang, amdgpu
|
|
|
|
! RUN: %libomptarget-compile-fortran-run-and-check-generic
|
|
program main
|
|
implicit none
|
|
integer, pointer :: Set
|
|
integer, target, allocatable :: Set_Target
|
|
|
|
allocate(Set_Target)
|
|
|
|
Set_Target = 30
|
|
|
|
!$omp target map(Set)
|
|
Set => Set_Target
|
|
Set = 45
|
|
!$omp end target
|
|
|
|
print *, Set_Target
|
|
end program main
|
|
|
|
! CHECK: 45
|