GFortran implicit deallocation?

Hi everyone,

doesn’t GFortran implicitly deallocate local allocatables at the exit of a procedure’s scope ?

I’m getting RT errors of trying to allocate an already allocated variable, but the problem is that the variable is a local variable. The error goes away if I explicitly deallocate it manually at the end. But that would require to do it for a lot of variables…

From GFortran documentation, I understand that one could use -fno-automatic to get the save implicit attribute, which I don’t use clearly.

Thanks everyone.

I’ve had this same problem in the past with gfortran. In my case, it was associated with (my) code errors in other parts of the program that I eventually tracked down, with some luck and with difficulty. Watch out for things like dangling pointers that are referenced.

I had an issue a couple of years ago with gfortran not deallocating deferred length strings (aka allocatable strings) on program exit. I don’t use gfortran that much so I don’t know if it was fixed. Valgrind spotted it but it took me a while to figure out that is was a compiler problem and not something I did. Explicitly DEALLOCATEing the strings appeared to solve the problem.

With gfortran-10 (a bit old), this code seems to work as expected (no runtime error):

module test_m
    implicit none
contains
subroutine test( n )
    integer, intent(in) :: n
    integer, allocatable :: arr(:)

    allocate( arr( 2 ), source= n )
    print *, arr
    !! No explicit deallocation here.
end
end module

program main
    use test_m
    call test( n= 100 )
    call test( n= 200 )
end

Result (gfortran-10):
100 100
200 200

My experience up to now is that gfortran deallocates local allocatable arrays automatically when exiting a subroutine (if I use Linux or Mac). Is this not the case on different compiler versions or environments (e.g. Windows)? Or, is the problematic case related to allocatable derived types?

My Linux Ubuntu system using gfortran 13.1.0 gave @septc’s output with @septc’s program.

I tested your code in the same environment, and it gives the desired behaviour.

However, having (in a given procedure):

      real(bsa_real_t), allocatable, target  :: D_S_uvw_w2(:, :)
[...]
      if (allocated(D_S_uvw_w2)) deallocate(D_S_uvw_w2)

at the second iteration I get

Fortran runtime error: Attempting to allocate already allocated variable 'd_s_uvw_w2'

Smells like memory corruption.
I think I managed to track it down to LAPACK and BLAS routines (used and acting on such arrays), which is not working properly.

Thanks @RonShepard . May I ask what kind of errors were they ? Just to know where I might want to look as well in case I don’t get it to work otherwise.

Thanks for the feedback @rwmsu .

I tried running Valgrind, and this is what I get after the runtime error occurs:
I do see that the very first “still reachable block” report is at the stack frame where the program crashes:

==3741335== 1 bytes in 1 blocks are still reachable in loss record 1 of 82
==3741335==    at 0x4C3BE4B: calloc (vg_replace_malloc.c:1328)
==3741335==    by 0x524ED06: _gfortrani_xcalloc (memory.c:78)
==3741335==    by 0x52502D6: recursion_check (error.c:316)
==3741335==    by 0x525080B: _gfortran_runtime_error_at (error.c:462)
==3741335==    by 0x44F791: [...]__f_name__ (functionsImpl.F90:530)  !<--- HERE
==3741335==    by 0x472F2F: __bsalib_mrectzone_MOD_compute_rz_ (_shared_poly2d.fi:253)
==3741335==    by 0x45DA47: __bsalib.bsalib_mesherimpl_MOD_premesh (BsaMesherImpl.F90:411)
==3741335==    by 0x464F7B: __bsalib_MOD_mainmesher_ (BsaMesherImpl.F90:84)
==3741335==    by 0x423248: __bsalib_MOD_bsa_run (BsaLibImpl.F90:387)
==3741335==    by 0x404246: MAIN__ (bsa.F90:144)
==3741335==    by 0x41577C: main (bsa.F90:98)

But, at the end it says:

==3691876== LEAK SUMMARY:
==3691876==    definitely lost: 0 bytes in 0 blocks
==3691876==    indirectly lost: 0 bytes in 0 blocks
==3691876==      possibly lost: 0 bytes in 0 blocks
==3691876==    still reachable: 738,532 bytes in 98 blocks
==3691876==         suppressed: 0 bytes in 0 blocks
==3691876==
==3691876== ERROR SUMMARY: 0 errors from 0 contexts (suppressed: 0 from 0)

It does not seem to have detected any memory corruption, does it?

I guess memory corruption can happen if some other routine (e.g. in the [...] part in your code) does something that leads to buffer overflow (for example). To test this, I’ve tried a modified code that sets a value to another local array (work(:)) with an incorrect size.

module test_m
    implicit none

    !! Results depends on the setting...
    integer, parameter :: lw = 2      !! results in "hmm"
    !! integer, parameter :: lw = 5

contains
subroutine test( n )
    integer, intent(in) :: n

    real :: work( lw )   !! local work array
    integer, allocatable :: arr(:)   !! local allocatable array

    call legacy( work, lw + 1 )   !! pass an incorrect size

    if (allocated(arr)) stop "hmm..."

    allocate( arr( 2 ), source= n )
    print *, arr
    !! No explicit deallocation here.
end
end module

!! F77-like routine with implicit interface and typing.
subroutine legacy( work, nsize )
    real work( nsize )
    val = 1.11   !! results in "hmm"
    !! val = 0.0   !! "works" apparently (because zero is written)

    do i = 1, nsize
        work( i ) = val   !! buffer overflow can occur
    enddo
end

program main
    use test_m
    call test( n= 100 )
    call test( n= 200 )
end

Result:
$ gfortran-10 test.f90 && ./a.out
STOP hmm...
$ gfortran-10 -O2 test.f90 && ./a.out
         100         100
         200         200

My current understanding (which may be wrong!) is that writing too many values to work(:) leads to buffer overflow, which breaks the metadata (array descriptor) of arr(:) and artificially changes the pointer value inside arr(:) (so resulting in allocated(arr) == true). In the following picture (taken from Wikipedia), A and B correspond to work(lw) and the metadata of arr(:), respectively.

But the error may or may not happen depending on various conditions (optimization levels, the length of work arrays, values assigned, etc), so I guess the overall behavior becomes very weird… (FYI, the above code gives no memory leak with valgrind because no allocation is done before the “hmm” line.)

1 Like

In my case, I had some other allocatable arrays that were used as actual arguments to an intent(out) dummy argument. This causes the original memory to be deallocated, but there were then dangling pointers to some of that memory. Those dangling pointers still worked afterwards, so I did not catch the memory error immediately. The compiler eventually reused some of that memory, and it was only then that the error appeared, long after my own coding mistake. One of the symptoms was that a local allocatable array appeared to not be deallocated upon subroutine exit. This symptom was far removed from the actual code error, and I admit that it was just by luck, following other odd behavior, that I eventually identified the intent(out) error.

1 Like