Skip to content

An API for working with allocatable arrays #598

Open
@ivan-pi

Description

@ivan-pi

Motivation

While working with data that varies at runtime like reading data from a file, or algorithms that don't have fixed bounds on the number of items they create (Poisson disk sampling comes to mind) one needs a suitable data structure. One option is to use a linked list (#68, #463); a second (and arguably more Fortranic) method is to use allocatable arrays with a pattern like follows:

integer, allocatable :: items(:)

do

   ! ... perform action resulting in value ...
   items(npoints) = value
   npoints = npoints + 1

   ! ... check loop exit condition
   if (exit) exit

   if (npoints > size(items)) then
     ! ... resize items ...
     items = [items, new_chunk]
   end if

end do
if (npoints < size(items)) then
  items = [items(1:npoints)]
end if

The resize operation can either be performed in fixed chunks (preferably with some form of alignment), increasing by a fraction of the old size, or doubling the size.

The approach above with re-allocation upon assignment is neat, however I don't think it generalizes well to arbitrary rank data.
Say we are reading an RGB image stack, we might use an array like integer, allocatable :: stack(:,:,:,:) where the first two subscripts are the x and y coordinates of the image, the third index is the RGB color, and the last index counts separate images. Here it would be useful to have a set of subroutines that help perform the two operations of:

  • growing an array, and
  • shrinking an array

An example of growing a 1D array could like this

  subroutine increase(items,cursize)
    integer, intent(inout), allocatable :: items(:)
    integer, allocatable :: temp(:)

    associate(oldsize => size(ivals))
      allocate(tmp(2*oldsize),source=0)
      tmp(1:oldsize) = items
    end associate

    call move_alloc(tmp,items)
  end subroutine

Prior Art

A nice example of this was provided recently in a Discourse thread.

Additional Information

If the API is successful, creators of derived types could be encouraged to provide the grow and shrink operations in conformance with the stdlib interface which would offer a (fypp) template. This is for the "array of structures" pattern.

For the opposite "structure of arrays" the resize methods must be performed for each allocatable component, using a purpose subroutine or type-bound method.

Activity

added
ideaProposition of an idea and opening an issue to discuss it
topic: container(Abstract) data structures and containers
on Dec 13, 2021
awvwgk

awvwgk commented on Dec 13, 2021

@awvwgk
Member

I'm usually using a routine of this style to reallocate arrays:

!> Reallocate list of integers
pure subroutine resize_int(var, n)

  !> Instance of the array to be resized
  integer, allocatable, intent(inout) :: var(:)

  !> Dimension of the final array size
  integer, intent(in), optional :: n

  integer, allocatable :: tmp(:)
  integer :: this_size, new_size

  if (allocated(var)) then
    this_size = size(var, 1)
    call move_alloc(var, tmp)
  else
    this_size = initial_size
  end if

  if (present(n)) then
    new_size = n
  else
    new_size = this_size + this_size/2 + 1
  end if

  allocate(var(new_size))

  if (allocated(tmp)) then
    this_size = min(size(tmp, 1), size(var, 1))
    var(:this_size) = tmp(:this_size)
    deallocate(tmp)
  end if

end subroutine resize_int

Note that growing an array of size(var) == 0 must work. Also reallocating to a smaller size might be useful.

If there is interest I can propose a 1D version of resize.

beddalumia

beddalumia commented on Sep 6, 2022

@beddalumia

As I noted in #68, here I also report that move_alloc should perform better than items = [items, new_chunk] syntax, as thoroughly discussed in a discourse thread. The move_alloc approach would arguably be more flexible in higher rank domain too, but I think is worth pointing out that a main reason to prefer it over the alternative (admittedly syntactically more elegant) lies in performance.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment

Metadata

Metadata

Assignees

No one assigned

    Labels

    ideaProposition of an idea and opening an issue to discuss ittopic: container(Abstract) data structures and containers

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions

      An API for working with allocatable arrays · Issue #598 · fortran-lang/stdlib