Best practice: Deallocating allocatable arrays explicitly vs implicitly

Allocatable errorsarrays are deallocated automatically once they are out of scope, i.e. at the end of the procedure they are declared. Should one still use explicit deallocation?

(If you want to deallocate early then you have to do it explicitly of course.)

1 Like

I’d say let the compiler handle this for you. Why spend time writing something something that the compiler will do regardless?

In older/legacy code you’ll sometimes find that allocable-s are manually deallocated at the end of the scope. This is usually a sign that the code has been written with the assumption that all variables are save-d which means that allocatable-s are not deallocated at the end of the scope. With the Intel compiler you achieve this with the -save flag. This is (of course) considered bad practice these days, but certain legacy code might depend on it to function properly.

1 Like

Explicit DEALLOCATE, when appropriate, does improve the documentation for those who may follow, which may be yourself !

2 Likes

Do you have any example code to explain where you find explicit deallocation more readable/understandable?

I can see this being an argument if one is working on a project where -save is the norm and there’s very few source files without it. I think such projects should strive to modernize instead of using such old concepts though. Apart from that I struggle to think of situations where an otherwise automatic deallocation would be appropriate to write out explicitly.

Personally, I expect my “readers” (myself included) to have a basic understanding of the Fortran standard and I consider the lifetime of an allocatable variable to be part of those basics.

1 Like

If there is a group of lines of code with an ALLOCATE at the beginning and DEALLOCATE at the end, the code can be wrapped in a loop in the future. If there is no deallocate, you get a run-time error for allocating a variable that is already allocated. So future-proofing is a benefit of deallocate where it is not necessary. An advantage of using allocation on assignment instead of allocate is that no deallocate is needed even in a loop. OTOH, you may want allocations to stand out and not look like ordinary assignment.

If the allocate is in a Fortran BLOCK, no deallocate is necessary, even if the block is in a loop, as demonstrated below:

program main
integer, parameter :: n(3) = [4,2,6]
integer :: i
do i=1,size(n)
   block
      real, allocatable :: x(:)
      integer :: size_x
      size_x = n(i)
      allocate (x(size_x))
      call random_number(x)
      print*,x(size(x))
   end block
end do
end program main
1 Like

If there were such a group at all that could be consumed “in a loop in the future”, it will be far better if it were in a subprogram of its own in which case the explicit DEALLOCATE again won’t be necessary.

2 Likes

No, especially not for local objects in subprograms and such.

You will find it useful to consider the following:

  1. Avoid static data as much as possible. An example in the case of Fortran will be those with explicit or implied SAVE attribute. Then with this rule, you don’t need to bother with DEALLOCATE generally.
  2. But if you must use static data, then implement the means for clean-up e.g., procedures that do DEALLOCATE or otherwise free-up resources, etc. when the objects are to be destroyed.
1 Like

I would only remind you that you do not get the choice of implicit deallocation in procedures when compiling with gfortran using heap arrays (gfortran -fmax-stack-var-size=10 main.f90 -o). To me, this seems to be a bug in gfortran. Intel ifort compiler has no issues with it.

    call testAutoDealloc
    call testAutoDealloc
contains
    subroutine testAutoDealloc
        real, allocatable :: temp(:)
        allocate(temp(200))
        !deallocate(temp)
    end
end
1 Like

I can be wrong, if your allocatable array has save property, then you may have to explicitly deallocate it at the end of your subroutine.

1 Like

That is indeed correct :+1: Also note that variables will be save when e.g compiled with -save on Intel Fortran even if the source code does not specify it.

1 Like

Thanks @plevold !
By the way, if I remember correctly, -save in Intel Fortran is basically equivalent with -fno-automatic in gfortran. Yeah, some old code does require -save flag as you mentioned before.

The -fmax-stack-var-size option should not even touch any allocated array. The manual says that clearly:

-fmax-stack-var-size=n
[…]
This option currently only affects local arrays declared with constant bounds,

After all, how could an allocated array land in the program’s (heap) static memory?

Edit: my fault, I meant static memory, not heap. Thanks, @Sideboard

I thought that is exactly where allocated arrays are located, in contrast to non-allocated ones that live on the stack.

1 Like

You’re right, my fault. The non-allocated objects, however, go either on stack (automatic) or to the static memory (non-automatic, e.g. save-d)

If you allocate pointer, then perhaps you may need to deallocate it before may changes to the pointer, otherwise the previously allocated memory will be wasted. For example

integer, target :: a=1, b=2
integer, pointer :: p
allocate(p) ! configure a memory address for p.
p=1 ! set the content of p as 1
write (6,*) p ! show 1
deallocate(p) ! release the memory. 
p => a ! after releasing the memory of p, then p point to a. If do not deallocate(p) in advance, then the memory previously allocated to p will be wasted.