Allocatable vs adjustable

Hello,

I need to declare an array of a subroutine so that its dimensions matches those of a dummy argument array.

I see basically two options.
The former is employing an adjustable array (mysub1), the latter is employing allotable array (mysub2).

module test
implicit none

contains

subroutine mysub1(array)
  implicit none
  integer, intent(in) :: array(:)
  integer :: work(size(array))
  integer :: i, nelem
  
  nelem = size(array)
  do i=1, nelem
    work(i) = array(i) + 1
  end do
  
  write(*,*) work

end subroutine mysub1

subroutine mysub2(array)
  integer, intent(in) :: array(:)
  integer, allocatable :: work(:)
  integer :: i, nelem

  nelem = size(array)
  allocate(work(nelem))
  
  do i=1, nelem
    work(i) = array(i) + 2
  end do
  
  write(*,*) work
  
end subroutine mysub2

end module test

program main
  use test
  implicit none

  integer :: data(5)
  
  data = [1,2,3,4,5]
  
  call mysub1(data)
  call mysub2(data)

end program main

What are the advantages and disadvantages of both?
I would say that the compiler should basically act in the same way in both.

2 Likes

Welcome to the forum!

Yes, the two solutions are very similar, but you need to understand the memory requirements:

  • With the automatic or adjustable array the memory comes from the stack and that may be a limted resource. If you run out of stack space, the program will crash without any means to recover.
  • With the explicit allocation you get memory from the heap and you can check whether that was successful.
  • There may be a slight difference in performance, but I doubt it is noticeable.
5 Likes

MYSUB1 declares ARRAY to be assumed-shape, MYSUB2 declares ARRAY to be deferred-shape, because it is marked ALLOCATABLE.

Do you have a need for ARRAY to change its shape during execution of the subroutine? If yes, you must choose the latter, and only ever pass ALLOCATABLEs to the subroutine.

If no, you can choose the former.

In either case, you must call the subroutines with an explicit interface (as you do here, by making them module procedures).

It is your responsibility to check the allocation status of an ALLOCATABLE dummy in the subroutine (with the ALLOCATED intrinsic), because it could have been argument associated (“called”) with an unallocated array.

2 Likes

Thank you for your reply.

Why do I need to pass allocatables to the subroutine?
In mysub2, I marked work to be allocatable because I later call allocate based on the dimension of array.
In any case, work is just a local variable.

Instead, array is the dummy argument declared as assumed-shape, which potentially may be just a stack vector (as in the example) or a heap vector, depeding of the declaration in the actual argument.

Let’s suppose that the main reads this way. Do both the approaches remain valid? I guess so.

program main
  use test
  implicit none

  integer, allocatable :: data(:)
  
  allocate(data(5))
  data = [1,2,3,4,5]
  
  call mysub1(data)
  call mysub2(data)

end program main
1 Like

Staying with the dummy ARRAY, a deferred-shape ALLOCATABLE is always contiguous giving it the advantage of cache-efficiency. But any sub-arrays (slices) will not be ALLOCATABLE, as they cannot be guaranteed contiguous anymore. If you don’t plan on using slices, and you don’t plan on making these routines callable from outside Fortran, then ALLOCATABLE could be the way to go.

The local WORK can be automatic or ALLOCATABLE. Automatic has the edge on performance (because it could be marked out on the stack very quickly) but there is no graceful failure. If there is not enough space, the program will probably crash horribly at some unspecified later time, leaving you scratching your head. An ALLOCATABLE will take more time to allocate/deallocate, but ALLOCATE statement takes a STAT specifier that you can use to check that allocation has succeeded and produce some output if it hasn’t. Some people keep a small local fixed-shape array and an ALLOCATABLE, and switch to “firing-up” the ALLOCATABLE only when the size of the fixed-shape array is insufficient.

If I understand correctly your answer, it may be possible to define array as contiguous, so that the compiler may potentially pass by copyin instead of by reference.

Could you please let me see in an example the use of allocatable for array?
If I have an explicit-size vector as actual argument, I guess that the dummy argument may not be allocatable. Or am I missing something?

15.5.2.7 Allocatable dummy variables
1 The requirements in this subclause apply to actual arguments that correspond to allocatable dummy data objects.
2 The actual argument shall be allocatable. It is permissible for the actual argument to have an allocation status of unallocated.

Also, NOTE 2 of 9.5.3.1, Array elements and array sections, Syntax

Unless otherwise specified, an array element or array section does not have an attribute of the whole array. In particular, an array element or an array section does not have the POINTER or ALLOCATABLE attribute.

Array sections is how you would pass a slice of an array as an argument to a subroutine.

One of us is reading this wrong! The input array is not allocatable in either subroutine, it’s just the local variable work that is in the second subroutine. There’s no issues with passing allocatable or static-sized arrays to either one.

2 Likes

Yes, but you cannot mix CONTIGUOUS and ALLOCATABLE. CONTIGUOUS is for when you don’t go with the ALLOCATABLE route. It could be that further down the stack of calls, you decide that you can’t/won’t pass the whole ALLOCATABLE array around and you must use slices. Anything downwind of that will have to use non-ALLOCATABLE dummy arguments. And then you can use CONTIGUOUS attribute with assumed-shape, pointer, or assumed-rank arrays (but not deferred-shape arrays).

Assumed-shape allows the compiler to decide when to do copy-in/copy-out to try to get some cache-efficiency. You specify CONTIGUOUS when you want to force some behaviour on that from the compiler. A CONTIGUOUS dummy would force the compiler to do copy-in/copy-out when the actual argument is not contiguous, and the compiler cannot always tell at compile-time, so it might over do it. There is no attribute with the opposite effect, telling the compiler to never do copy-in/copy-out and always let the callee deal with strides (we have vector-subscript to handle, ARRAY(INT_ARRAY) is a possible actual argument, and no strides will save you from copy-in/copy-out here). But some compilers have command-line switches to affect how enthusiastic they are about copy-in/copy-out.

You are right, I was reading it wrong. But I haven’t said anything wrong about ALLOCATABLE dummy, I believe.

1 Like

Differences not mentioned are that the allocatable array can have the SAVE attribute, and that you can deallocate the work array. There are a few special cases where adding an optional parameter lets you selectively keep the previous allocatable work array. This is useful when a large number of calls are made with a very large array or when (partial sorting is one case) the work array may be worked on incrementally. Admittedly rare cases, but an adjustable array cannot be saved. The example also indirectly raises the question of whether using the DO loop or array syntax or initializing via the ALLOCATE is “best” or not.

allocate(work,storage=array+2,stat=stat,errmsg=errmsg)

would replace the loop for example.

1 Like

We should make FAQs.

Yes. I have lamented before there is no well-defined progression from Discourse discussions to FAQs or Wiki-like group-editable documents or ultimately manuals. Short papers on fortran-lang, several Fortran FAQs, the on-line Modern Fortran manual, the Fortran wiki are all available but not a natural progression from a Discourse discussion. I think the Fortran wiki is the most accessible once one makes an initial entry. Downloading the entire site as markdown for examples is easy. And then you can compose something and paste it back in as a new entry. Anyone can edit any entry. If Discourse had some way to easily “upvote” discussions into a wiki-like document that could be group-edited I think it would be a valuable feature. There are a good number of Discourse discussions that deserve to be organized into some form of reference that is more categorized than Discourse.

1 Like

I tried something out of curiosity:

  • Me to chatgpt:

Could you summarize the discussion in the following Fortran Discourse thread Allocatable vs adjustable and extract the key take aways in a FAQ style?

  • ChatGPT after 2-3 seconds of reading the thread:

FAQ: Allocatable vs Adjustable Arrays in Fortran

Q1: What are the main differences between allocatable and adjustable arrays?

  • Adjustable arrays use stack memory, which is limited and can cause program crashes without recovery if exceeded. Performance is generally better as memory is allocated quickly.
  • Allocatable arrays use heap memory, offering more flexibility. Allocation success can be checked with the STAT specifier, allowing for better error handling.

Q2: When should I use allocatable arrays?

Use allocatable arrays if:

  • The array shape may change during execution.
  • Error checking for allocation failure is necessary.

Q3: Can slices of allocatable arrays be passed as arguments?

No, array slices cannot retain the allocatable attribute as they may not be contiguous. Instead, use assumed-shape or contiguous attributes.

Q4: Are allocatable arrays cache-efficient?

Yes, allocatable arrays are always contiguous, optimizing cache usage. However, this advantage diminishes if sub-arrays are used.

Q5: Can allocatable arrays have the SAVE attribute?

Yes, allocatable arrays can be saved across subroutine calls, enabling use cases like incremental work on large arrays.

For more details, refer to the discussion thread.


:exploding_head:

There is no such thing as adjustable arrays in the current Fortran standard. The last time this term appeared was in FORTRAN77.

Adjustable arrays use stack memory

They can be implemented in that way, but they don’t have to.

Etc, etc. Please, let’s not waste time on garbage like this.

The point is not the exactness of the information which is of course not correct.
The point is that the tool can be used to kick start organizing the information which needs to be reviewed… like everything

1 Like

If I understand correctly, I may summarized as follows:

  1. mysub1 employs an automatic array for work. The only drawback of this approach is for very large arrays, that may exceed stack size. This would be true for any local variable, anyhow.
  2. mysub2 employs a deferred-shape array for work. It is a safer approach for large vectors, with a slight performance penalty of the manual allocation. Deallocation is automatic when going out of scope, except in case of save attribute.
  3. For both mysub1 and mysub2 it may be useful to define the input dummy array as contiguous.
2 Likes

The right wording is “allocatable array”.

Note that using “save” is generally discouraged, unless you have a very good reason to do so.

1 Like

Today, you made me understand the save attribute in one sentence, so thank you. Perhaps a more serious discussion about the Fortran documentation should be in order (elsewhere), and while I love the general appearance and clearness of the QuickStart, there are so many new tools to exploit it could be worthy to think about it (Sphinx supports notebooks, notebooks could support Fortran…). Since the advent of godbolt.org, I’ve been making myself simple and runnable example to test my understanding of what I was reading on this forum. I used the following to understand the save attribute:

module test
    !!   This module contains...
   use, intrinsic :: iso_fortran_env, only: real32, real64
   implicit none

   integer, parameter :: sp = real32
   integer, parameter :: dp = real64

contains

    subroutine mysub1(array)
        real(real32), intent(in   ) :: array(:)

        ! This routine serves to show that inside a routine, the custom
        ! bounds of your array are not maintained 
        print *, array 
        print *, lbound(array), ubound(array)

    end subroutine

    subroutine mysub2(array)
        real(real32),              intent(in   ) :: array(:)
        real(real32), allocatable                :: array2(:)
        
        ! This routine shows that array2 will be deallocated when
        ! exiting the routine, you can call it multiple times and
        ! no errors will be thrown
        allocate(array2, source=array)
        print *, "    allocating"
        print *, array2

    end subroutine

    subroutine mysub3(array)
        real(real32),                   intent(in   ) :: array(:)
        real(real32), allocatable, save               :: array2(:)
        
        ! This routine shows that array2 will NOT be deallocated when
        ! exiting the routine, thus calling this routine in a loop 
        ! will give you an error
        allocate(array2, source=array)
        print *, "    allocating"
        print *, array2

    end subroutine

    subroutine mysub4(array)
        real(real32),              intent(in   ) :: array(:)
        real(real32), allocatable, save   :: array2(:)

        ! This routine has the save attribute, so repeated allocation would
        ! crash the program. However, if we allocate only if array is not 
        ! allocated, we can use this routine AND the content of the array
        ! is maintained along from one call to the others
        if (.not. allocated(array2) ) then
            allocate(array2, source=array)
            print *, "    allocating"
        else
            print *, "not allocating"
            print *, array2
        end if 

    end subroutine

end module test

program testgrid
   use, intrinsic :: iso_fortran_env, only: real32, real64
   use test
   implicit none
   
   integer      :: i
   real(real32) :: array(-3:3)

   do i = -3, 3
      array(i) = real(i, kind=real32)
   end do

    print *, array 
    print *, lbound(array), ubound(array)
    print *, "--------------------------"
    call mysub1(array)

    do i = 1, 10

       ! Comment/Uncomment to test

       ! allocatable, nosave: all good in the loop
       !call mysub2(array)

       ! allocatable, save:
       ! "Fortran runtime error: Attempting to allocate already allocated variable 'array2'"
       !call mysub3(array)


       ! allocatable, save, with conditional allocation
       ! The array is not deallocated from one call to the other and it will have the same 
       ! content as the previous iterations
       call mysub4(array)

    end do

end program

Perhaps a collaborative document could be the starting point for a documentation, even an open GitHub repo with a bunch of Markdown documents could be a good starting point, people could propose macro topics, modifications, notes and simple examples and then work incrementally with the contents.

1 Like

Submit a PR with documentation to appear at Learn — Fortran Programming Language, you can create a tutorial, or FAQ, or any other format that you think is appropriate. Maybe we can just expand Arrays — Fortran Programming Language.

1 Like