6.5. Fortran Allocatable Array Mapping#

The following examples illustrate the use of Fortran allocatable arrays in target regions.

In the first example, allocatable variables (a and b) are first allocated on the host, and then mapped onto a device in the Target 1 and 2 sections, respectively. For a the map is implicit and for b an explicit map is used. Both are mapped with the default tofrom map type. The user-level behavior is similar to non-allocatable arrays. However, the mapping operations include creation of the allocatable variable, creation of the allocated storage, setting the allocation status to allocated, and making sure the allocatable variable references the storage.

In Target 3 and 4 sections, allocatable variables are mapped in two different ways before they are allocated on the host and subsequently used on the device. In one case, a target data construct creates an enclosing region for the allocatable variable to persist, and in the other case a declare target directive maps the allocation variable for all device executions. In both cases the new array storage is mapped tofrom with the always modifier. An explicit map is used here with an always modifier to ensure that the allocatable variable status is updated on the device.

Note: OpenMP 5.1 specifies that an always map modifier guarantees the allocation status update for an existing allocatable variable on the device. In OpenMP 6.0, this restriction may be relaxed to also guarantee updates without the always modifier.

In Target 3 and 4 sections, the behavior of an allocatable variable is very much like a Fortran pointer, in which a pointer can be mapped to a device with an associated or disassociated status, and associated storage can be mapped and attached as needed. For allocatable variables, the update of the allocation status to allocated (allowing reference to allocated storage) on the device, is similar to pointer attachment.

!!%compiler: gfortran
!!%cflags: -fopenmp

! @@name:       target_fort_allocatable_map.1
! @@type:       F-free
! @@compilable: yes
! @@linkable:   yes
! @@expect:     success
! @@version:    omp_5.1
program main
  implicit none
  integer :: i

  integer, save, allocatable :: d(:)
  !$omp    declare target(d)

  integer, allocatable :: a(:)
  integer, allocatable :: b(:)
  integer, allocatable :: c(:)

  allocate(a(4))
  !$omp target                      ! Target 1
    a(:) = 4
  !$omp end target
  print *, a ! prints 4*4

  allocate(b(4))
  !$omp target map(b)               ! Target 2 
    b(:) = 4
  !$omp end target
  print *, b ! prints 4*4

  !$omp target data map(c)
  
    allocate(c(4), source=[1,2,3,4])
    !$omp target map(always,tofrom:c) ! Target 3 
       c(:) = 4
    !$omp end target 
    print *, c ! prints 4*4

    deallocate(c)
  
  !$omp end target data

  allocate(d(4), source=[1,2,3,4])
  !$omp target map(always,tofrom:d) ! Target 4
     d(:) = d(:) + [ ( i,i=size(d),1,-1) ]
  !$omp end target
  print *, d ! prints 4*5

  deallocate(a, b, d)

end program

Once an allocatable variable has been allocated on the host, its allocation status may not be changed in a target region, either explicitly or implicitly. The following example illustrates typical operations on allocatable variables that violate this restriction. Note, an assignment that reshapes or reassigns (causing a deallocation and allocation) in a target region is not conforming. Also, an initial intrinsic assignment of an allocatable variable requires deallocation before the target region ends.

!!%compiler: gfortran
!!%cflags: -fopenmp

! @@name:       target_fort_allocatable_map.2
! @@type:       F-free
! @@compilable: yes
! @@linkable:   yes
! @@expect:     unspecified
! @@version:    omp_5.1
program main
  implicit none

  integer, allocatable :: a(:,:), b(:), c(:)
  integer              :: x(10,2)

  allocate(a(2,10))

  !$omp target
     a = x             ! Reshape (or resize) NOT ALLOWED (implicit change)

     deallocate(a)     ! Allocation status change of "a" NOT ALLOWED.

     allocate(b(20))   ! Allocation of  b *

     c = 10            ! Intrinsic assignment allocates c *

     ! * Since an explicit deallocation for b and c does not occur before 
     ! the end of the target region, the PROGRAM BEHAVIOR IS UNSPECIFIED.
  !$omp end target

end program

The next example illustrates a corner case of this restriction (allocatable status change in a target region). Two allocatable arrays are passed to a subroutine within a target region. The dummy-variable arrays are declared allocatable. Also, the ain variable has the intent(in) attribute, and bout has the intent(out) attribute. For the dummy argument with the attributes allocatable and intent(out), the compiler will deallocate the associated actual argument when the subroutine is invoked. (However, the allocation on procedure entry can be avoided by specifying the intent as intent(inout), making the intended use conforming.)

!!%compiler: gfortran
!!%cflags: -fopenmp

! @@name:       target_fort_allocatable_map.3
! @@type:       F-free
! @@compilable: yes
! @@linkable:   no
! @@expect:     fail
! @@version:    omp_5.1
module corfu
contains
  subroutine foo(ain,bout)
    implicit none
    integer, allocatable, intent( in) :: ain(:)
    integer, allocatable, intent(out) :: bout(:) !"out" causes de/realloc
    !$omp declare target
    bout = ain
  end subroutine
end module

program  main
  use corfu
  implicit none

  integer, allocatable :: a(:)
  integer, allocatable :: b(:)
  allocate(a(10),b(10))
  a(:)=10
  b(:)=10

  !$omp target

  call foo(a,b) !ERROR: b deallocation/reallocation not allowed
                !  in target region

  !$omp end target

end program