Program does not return from`deallocate` statement

Hi to everyone,

wish you all a good 2023!

I’m having a problem in the execution of a program, which at some point hangs at the level of a deallocate statement.

It’s surely related to some bad memory mangement, though I’m using
/heap-arrays /check:all /debug:all /Od and no RT error is thrown.

I tried using the VS’s built-in heap allocation tracker, but without useful outcome.

If you’d have any suggestion on how to face this issue, I’d more than happy to hear them.

Cheers,
Michele

EDIT:
I had forgot to mention that, the issue shows only after a given dimension (fom which some big bunch of allocations depend) is greater than say x=17, where the actual threshold value x does not seem to be meaningful (just random).

EDIT 2:
Also, I am afraid that the problem might be “bigger than it seems”.
What I mean by that, is because this issue happens only when the logic of the program passes through some procedures which use (externally, statically linked) LAPACK procedures. I already had some very strange behavious, at the very lines of calling those routines (some memory overlapping, which was ending up in unintentional memory overriding). This should have been fixed already. Or, this is what I think…
So, I am afraid that this issue might somewhat be related to what I was having before.

NOTE: this failing routine is called within a loop. The failing does not happen at the very first loop iteration, but after some. In the middle, no other allocation/deallocation happen if not for the variables in question.

1 Like

Welcome to the forum. DEALLOCATE cannot be used on an array that is not ALLOCATEd. I don’t know if this is the problem, but it is the first thing I would look for, based on experience.

What happens if you write

if (allocated(x)) deallocate(x)

instead of

deallocate(x)

@Beliavsky,

thanks for your answer. I’m surely not an expert as you are, but I know a bit of Fortran :stuck_out_tongue:

And what you suggest is exactly what I do. I could actually also remove those lines because allocation happens within a procedure, but I added them to see which one was failing. Of course, before program did not return from that procedure (same issue).

PS: in that case, I guess the RT would have complained about that, trying to reference an allocatable not being allocated.

How do you know the program hangs in the deallocate statement? Running in the debugger?

Issues with deallocate often result from a memory overflow somewhere in the code, and it can be tricky to debug… A strategy can be trying deallocating the array earlier and earlier until it “works” (i.e. until the deallocate does what it is supposed to do): this way you can locate where in the code something bad happens.

@PierU, yes, I run the VS debugger. Also tried the built-in heap allocation tracer, but I didn’t see any useful info coming out of it. Surely, been the very first time I am using it, maybe it’s that I don’t know how to use it.

For your suggestion to deallocate them before, I don’t think I can, since the whole procedure logic depends on these allocatables, which are then deallocated at the end.

I am afraid, as you say, that spotting it will be much harder than I might think. See the EDIT 2 for some addition info. I am thinking, if it might help, to directly link (as a Project dependency) my project to LAPACK (i.e. including sources, not just linking to it), so that I can enter with the debugger in it, and see what happens there…

This is for debugging: obviously once deallocated before it should be, the rest of the code won’t work. But at least you can know where the problem is:

  • move before: it still hangs
  • move even before: it still hangs
  • move again before: it doesn’t hang… Then you know that the problem is likely between this location and the previous one.

Edit: the real problem is if the allocation/deallocation is inside a loop and the problem is not at the first iteration. The solution is to determine at which iteration it hangs, and deallocate only at this iteration.

1 Like

Oh, I see. I’ll try it out and let you know what it gives. Thanks!

Ok, I have an update. What you suggest cannot be done directly, since the loop resides in a ModuleA procedure, while the hanging (called) procedure is in ModuleB (it is actually a type-bound procedure). This would require some logic modification (including sharing the outer-loop index variable, i.e. module variable for example, as well as for the inner-allocated (local) ones, in order to allocate them only once before the loop starts).

But, I notice it hangs always (for what I experienced) at the 4th iteration. And it does even placing the deallocations right after the allocatiion statements.

So? I’m in big trouble, am I? :smiley:

Still, I wonder how such issue can happen. What might be the causes? Shouldn’t a process know all the memory it holds? How can an allocation “give back” memory which is already in u se? I does not make much sense…

This is bad…

Just thinking:

  • the allocatable object may be corrupted even before allocating it and for some reason the corruption only shows up at the deallocation
  • or compiler bug?

Without a Minimal Working Example (which can be difficult/impossible to provide) it’s difficult to help

Welcome,
Can you add STAT= and ERRMSG= clauses to the potentially offending allocate and deallocate statements?
The STAT= clause should prevent the program stopping, and the character variable assigned to ERRMSG may or may not contain an explanation.
Good luck

@NormanKirkby , thanks for your answer.

Where exactly do you mean? At the allocate or deallocate statements? I already had the STAT= at the allocate, and allocation happens successfully, meaning that stat= returns 0. I’ll try at the deallocate, adding ERRMSG=, though I am afraid it will not give any help once it will have hang…

Just asking: could an allocation happen on a corrupted object?. Shouldn’t the allocate statement hang in place of the deallocate, or maybe throw an error since all the runtime checks are enabled? I mean, there should be a way to “prevent”, or at least catch these errors.

I’d love to provide one, but it’s almost impossible, since it also involves some external dependencies…
If you’d be interested, I could show you the real example :slight_smile:

This is what I would expect too, but who knows… This may depend on what is corrupted precisely.

By the way, I would try removing the runtime checks, just to see what happens.

As I was fearing, even placing STAT= and ERRMSG= to the deallocate statements, it did not prevent the program from hanging…

Nothing changes, hangs as usual…

Do you actually need to deallocate manually? If not does the program run fine if you remove the deallocate statement?

A local allocatable variable will be deallocated automatically at the end of the scope so no explicit deallocation is needed here:

subroutine sub()
    integer, allocatable :: arr(:)
    arr = [1, 2, 3] ! Fortran 2003(?) reallocation semantics allocates the array at this line
    print *, arr
end subroutine ! The array will be deallocated here as the variable goes out of scope

If you reuse the variable at a later stage then you definitely need the deallocation and my suggestion won’t work. Example:

integer, allocatable :: arr(:)
allocate(arr(2))
arr(1) = 1
arr(2) = 2
print *, arr
deallocate(arr)
allocate(arr(3)
arr(1) = 3
arr(2) = 2
arr(3) = 1
print *, arr

There are (at least) two situations where you should deallocate in order to avoid memory leaks:

  1. When using pointers:
subroutine sub()
    integer, pointer :: arr(:)
    allocate(arr(3))
end subroutine ! The variable goes out of scope here, but data will NOT be deallocated since it's a pointer!
  1. When using save:
subroutine sub()
    integer, allocatable, save :: arr(:)
    allocate(arr(3))
end subroutine ! The variable goes out of scope here, but data will NOT be deallocated since it's a saved!

Note that legacy code might depend on being compiled with the ifort -save which implicitly makes all variables saved even if the keyword save doesn’t appear.

That is a feature, not a bug. The memory does not “leak”, the array is still there the next time it comes into scope. Its values and all of its attributes (lower and upper bounds, etc.) are all still there, and any external pointers to that array remain valid, even if the array itself is not in scope.

[edit:]
Just to clarify this a little more the 1. When using pointers: case is a memory leak. Upon return, the pointer is eliminated (its memory on the stack is returned and reused), but the anonymous memory that it pointed to is not deallocated, so even upon subsequent calls to that subroutine, it is no longer possible to access that memory.

Fair point. It’s not a memory leak per se because you can still reach the memory by invoking that procedure again. It is however an exception from the statement I made in the second paragraph about automatic deallocation and does require special care to avoid issues from e.g. calling allocate again on that variable.

As has been mentioned, this hints that the hang at the deallocation is a symptom, and that you have corrupted something previously. Do you have a previous version where the problem does not occur? If so, look carefully at the points where you changed the code and look for incorrect calls to procedures and array bound errors. Not everything is detected with array bound checks on. Any procedures with arguments passed to something dimensioned with an asterisk or any calls to something with no explicit interface are the most suspect. Trying with another compiler can often be useful. Add /warn:all and /gen-interfaces on your build(s) if you have a lot of procedures without interfaces and not defined in modules (check the documentation, I do not have it handy; but the sytnax is something like that). These types of bugs can be particularly difficult to debug because the actual corruption probably occurred long before the problem occurs, typically. If you are allocating a number of entities in the procedure and then deallocating them, if possible deallocate them in the opposite order you allocated them and see if that affects when the hang occurs.

1 Like

@mEm
You have not provided any code example of the declaration, allocation and deallocation of the array causing the problem.

  1. document allocate
    I would suggest you expand your code (if not already done) to:

! at allocate
IF ( .not. allocated (array) ) then
allocate ( array(n,m), stat=stat )
if ( stat==0 ) then
write ( ,) ‘array sucessfully allocated at cycle’, loop_id
else
write ( ,) ‘array failed to allocate at cycle’, loop_id
end if
ELSE
write ( ,) ‘array already allocated at cycle’, loop_id
END IF

! at deallocate
IF ( allocated (array) ) then
deallocate ( array, stat=stat ) ! note using stat= should not hang
if ( stat==0 ) then
write ( ,) ‘array sucessfully deallocated at cycle’, loop_id
else
write ( ,) ‘array failed to deallocate at cycle’, loop_id
end if
ELSE
write ( ,) ‘array was NOT allocated at cycle’, loop_id
END IF

  1. track memory usage looks correct.
    Using “/check:all” can inhibit the release of memory for debugging, so the allocate/deallocate might not function correctly.

I would try to track free memory while the program is running ( eg Task Manager in Win x64 can show free memory changes) Perhaps put a pause at the deallocate so you can monitor the memory for each pass (you stated pass = 4 is a problem?)
GlobalMemoryStatusEx is helpful for this in Win x64. There probably are equivalent routines for other OS.

      interface
        function GlobalMemoryStatusEx(mdata) bind(C, name="GlobalMemoryStatusEx")
          use ISO_C_BINDING
          !GCC$ ATTRIBUTES STDCALL :: GLOBALMEMORYSTATUSEX
          logical(C_BOOL) GLOBALMEMORYSTATUSEX
          integer(C_LONG) mdata(16)
        end function GlobalMemoryStatusEx
      end interface
  1. Stack corruption
    The other problem could be an incorrect call to LAPACK, which is corrupting the stack and this becoming evident on return from a previous call before the deallocate.
    Check the argument lists or utilise INTERFACE checking.

Just some ideas that might help.

1 Like