Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28703 Discussions

What to do when DEALLOCATE doesn't do its job?

FortranFan
Honored Contributor III
2,574 Views

Other than a plain, old bug, can anyone think of situations where DEALLOCATE statement will not deallocate the provided object, but yet it won’t return an error code and an error message?

We’ve a major problem with one of the use cases for an important code library where DEALLOCATE statement runs into such a problem.  The pseudo code is as follows:

    ...
    INTEGER :: Istat
    CHARACTER(LEN=80) :: ErrAlloc
    ...
    IF (ALLOCATED(Foo)) THEN
       DEALLOCATE(Foo, STAT=Istat, ERRMSG=ErrAlloc)  ! <= returns Istat of 0
       IF (Istat /= 0) THEN
          ... ! error handling
          RETURN
       END IF
    END IF
    ALLOCATE(Foo, STAT=Istat, ERRMSG=ErrAlloc) ! <-- failure, Istat=151; Foo already allocated.
    IF (Istat /= 0) THEN
       ... ! error handling
       RETURN
    END IF
    ...

where Foo is an instance of an extensible derived type containing allocatable components as well as type-bound procedures.

The issue is the ALLOCATE statement fails with an error code of 151 and returns an error message, “an allocatable array is already allocated.” because the DEALLOCATE in the code block just prior to this hasn't done its its job but hasn't returned an error.   Note the IF (ALLOCATED(..)) check does indeed return true.  

Isn't DEALLOCATE statement always supposed to return a non-zero error code if it is unable to deallocate the object for any reason?

The application structure is as follows: a Fortran main program calls DLL A which calls DLL B.  The main program has a “TYPE(Foo_t), ALLOCATABLE :: Foo” kind of declaration.  Foo is an argument specified with “TYPE (Foo_t), INTENT(INOUT) :: ” in some of the procedures in DLLs A and B which, under certain circumstances, will need to deallocate and reallocate Foo.  The code is built with /standard-semantics compiler option.

Any thoughts on what to check before I start thinking of this as a bug?

0 Kudos
22 Replies
Andrew_Smith
Valued Contributor I
2,273 Views

"Foo is an argument specified with “TYPE (Foo_t), INTENT(INOUT) :: ” in some of the procedures in DLLs A and B which, under certain circumstances, will need to deallocate and reallocate Foo"

It is not possible to deallocate something that was not declared allocatable or pointer. It should have given a compile error so yes its a bug.

0 Kudos
Steven_L_Intel1
Employee
2,273 Views

Without seeing a complete test case, it's hard to speculate, but we did have a bug where an INTENT(OUT) allocatable variable of derived type with an allocatable component didn't deallocate the component. This is fixed in the upcoming 15.0. But your problem seems different - I'll look forward to the complete test case.

0 Kudos
FortranFan
Honored Contributor III
2,273 Views

Andrew Smith wrote:

"Foo is an argument specified with “TYPE (Foo_t), INTENT(INOUT) :: ” in some of the procedures in DLLs A and B which, under certain circumstances, will need to deallocate and reallocate Foo"

It is not possible to deallocate something that was not declared allocatable or pointer. It should have given a compile error so yes its a bug.

Andrew,

Thanks, I think your conclusion that this is a bug does appear to be correct.  However some clarification may still be in order based on your comment, "It is not possible to deallocate something that was not declared allocatable or pointer."  Please note:

  • Foo is indeed declared as ALLOCATABLE type in the main program, as explained in the sentence previous to the one you quoted from my original post,
  • Foo is passed as an argument to procedures in DLLs A and B with an "INTENT(INOUT)" attribute, not INTENT(OUT) or INTENT(IN),
  • Within the DLL procedures, IF (ALLOCATED(Foo)) check works as expected,
  • The problem is with the DEALLOCATE(Foo, STAT=Istat, ERRMSG=ErrAlloc) statement within IF (ALLOCATED(Foo)) THEN.. block.  Foo doesn't get deallocated, yet Istat remains zero, and ErrAlloc is blank.
  • So a subsequent ALLOCATE(Foo, STAT=Istat, ERRMSG=ErrAlloc) statement fails with an Istat of 151 and ErrAlloc message of "an allocatable array is already allocated".  The program then shuts down due to this non-zero Istat value, albeit gracefully because the code does indeed have appropriate error handling scheme!

 

 

0 Kudos
FortranFan
Honored Contributor III
2,273 Views

Steve Lionel (Intel) wrote:

Without seeing a complete test case, it's hard to speculate, but we did have a bug where an INTENT(OUT) allocatable variable of derived type with an allocatable component didn't deallocate the component. This is fixed in the upcoming 15.0. But your problem seems different - I'll look forward to the complete test case.

Steve,

Yes, I agree with you that the complete test case would be necessary to truly diagnose the problem because, after all, DEALLOCATE statement gets used all the time, and only a gazillion times in the various libraries I support, let alone every where else.

But as you can surmise, the situation becomes quite complicated when it comes to packaging the full program and shipping it over (corporate policy, auxiliary software and their licensing, etc.).

So I'm trying to create a small enough reproducer but it is proving nearly impossible (all simple cases work as expected, not a surprise right!?), hence I think this has something to do with memory requirements of the actual use case.

But I anticipated the difficulty in getting to the root of this matter and that's why I initiated this forum topic to see if anyone has any advice on what all I can check.  Anyways, I'll continue with the effort to create a reproducer.

In the mean time, please note:

  • the problem exists with both compiler 13 as well as compiler 2015 Beta (June update) versions,
  • the argument list declaration in my case is INTENT(INOUT), not INTENT(OUT).
0 Kudos
Steven_L_Intel1
Employee
2,273 Views

Please show the declaration of Foo and of its derived type, if any.

0 Kudos
Andrew_Smith
Valued Contributor I
2,273 Views

The dummy argument declaration must have ALLOCATABLE specified:

TYPE (Foo_t), ALLOCATABLE, INTENT(INOUT) :: Foo.

It is illegal to try to dellaocate Foo within the subroutines without this.

0 Kudos
Steven_L_Intel1
Employee
2,273 Views

The compiler would give an error if FOO didn't have ALLOCATABLE or POINTER in the subroutine.

0 Kudos
FortranFan
Honored Contributor III
2,273 Views

Andrew Smith wrote:

The dummy argument declaration must have ALLOCATABLE specified:

TYPE (Foo_t), ALLOCATABLE, INTENT(INOUT) :: Foo.

It is illegal to try to dellaocate Foo within the subroutines without this.

Thanks.  And very sorry for any added confusion, but the actual case is "TYPE(Foo_t), INTENT(INOUT) :: Foo" and it is DEALLOCATE(Foo%Bar, STAT..), not DEALLOCATE(Foo, STAT=..).  Note Bar is an allocatable component of Foo.  By the way, all interfaces and type definitions are explicit since everything is in modules, the modules are indeed available to callers, and everything is accessed via USE statements.

Steve Lionel (Intel) wrote:

Please show the declaration of Foo and of its derived type, if any.

However, I think Andrew's comment in Quote #7 and Steve's request in Quote #6 have given me the clue I was looking for.  And that is, the problem most likely has to do with the BIND(C) attribute in the DLL procedures.  And that this code may most likely be non-conforming with C interoperability aspects of the Fortran standard.

However, none of this may let the compiler off the hook since it gives no errors or warnings, even though all the relevant flags have been turned on (/stand:f08, /warn:.. etc.).  Plus DEALLOCATE behaves oddly during execution which it shouldn't.  But I now think I can resolve this issue and also be able to create a reproducer for Intel team.

So many things to do, such little time!   Thank you much.

As goes the 37th item on " AFI's 100 Years... 100 Movie Quotes", "I'll be back"!

0 Kudos
Steven_L_Intel1
Employee
2,273 Views

Unless you used a syntax extension it's not likely you'd get a compiler error. It could be that you have a mismatch that results in data corruption. 

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,273 Views

FortranFan wrote:

  • Foo is indeed declared as ALLOCATABLE type in the main program, as explained in the sentence previous to the one you quoted from my original post,
  • Foo is passed as an argument to procedures in DLLs A and B with an "INTENT(INOUT)" attribute, not INTENT(OUT) or INTENT(IN),

Therefor on its path from the main program through the call stack into the DLL, the attribute ALLOCATABLE was lost. If your above description is correct, then what it appears you are trying to do is to "cast" the ALLOCATABLE attribute to an argument that was once described without ALLOCATABLE. This isn't in compliance.

Your example doesn't show test of component of type, then deallocate, allocate of that component. It shows the allocated, dealocate, allocate of the object itself.

Note, Fortran may use a reference to the original object, or it may construct a descriptor of the original object (e.g. slice) and pass that.

When the original object reference is passed, and it is allocatable, then it is likely your test and use above will work provided everything was compiled with the same version of Fortran.

However, should a new descriptor be created, as in passing a portion of an array (with or without stride), or potentially when when one call level receives a reference of a descriptor, and passes it to a next level without a descriptor (iow pointer to POD), then you attempt redefine the pointer to POD as being a descriptor reference of an allocatable, well then you have a crash in the making.

So what is it? Is you example sketch wrong, your description wrong, or what you are trying to do wrong?

Jim Dempsey

0 Kudos
mecej4
Honored Contributor III
2,273 Views

The FortranoPhone Devil's Advocate could combine #1 and #9 to create

...
INTEGER :: Istat
CHARACTER(LEN=80) :: ErrAlloc
...
IF (ALLOCATED(Foo%BAR)) THEN
   DEALLOCATE(Foo%BAR, STAT=Istat, ERRMSG=ErrAlloc)  ! <= returns Istat of 0
   IF (Istat /= 0) THEN
      ... ! error handling
      RETURN
   END IF
END IF
ALLOCATE(Foo, STAT=Istat, ERRMSG=ErrAlloc) ! <-- failure, Istat=151; Foo already allocated.
IF (Istat /= 0) THEN
   ... ! error handling
   RETURN
END IF
...

in which case, regardless of all the false scents made available by the OP (DLLs, BIND(C), possibly inconsistent interfaces, etc.), the behavior described in #1 would be completely logical. All of this goes to show that we really must have a correct description of the problem or, better yet, a reproducer.

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,273 Views
...
IF (ALLOCATED(Foo%BAR)) THEN
             //Foo%BAR\\
...
ALLOCATE(Foo, STAT=Istat, ERRMSG=ErrAlloc) ! <-- failure, Istat=151; Foo already allocated.
       //Foo\\

Foo%BAR is being tested and conditionally deallocated

Foo being allocated

Foo and Foo%BAR are different entities

You might have intended:

...
INTEGER :: Istat
CHARACTER(LEN=80) :: ErrAlloc
...
IF (ALLOCATED(Foo) THEN
  IF (ALLOCATED(Foo%BAR)) THEN
    DEALLOCATE(Foo%BAR, STAT=Istat, ERRMSG=ErrAlloc)  ! <= returns Istat of 0
    IF (Istat /= 0) THEN
      ... ! error handling
      RETURN
    END IF
    DEALLAOCATE(Foo)
END IF
ALLOCATE(Foo, STAT=Istat, ERRMSG=ErrAlloc) ! <-- failure, Istat=151; Foo already allocated.
IF (Istat /= 0) THEN
   ... ! error handling
   RETURN
END IF
...

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor III
2,273 Views

Jim, mecej4, Steve:

Thank you very much for your time and attention to this matter.  And sorry for any confusion thus far.  Shown below is some pseudo-code that better explains the situation.

  • DLL "B" encapsulates a derived type that also includes some allocatable components and certain type-bound procedures. Say this type is called FooClass and one of the allocatable components is Bar of type BarClass.  
       MODULE FooClassMod
       
          USE ..
          USE BarClassMod, ONLY : BarClass
          USE ..
          
          ..
          
          TYPE, PUBLIC :: FooClass
          
             !.. Private by default
             PRIVATE
             
             !.. Private fields
             ..
             TYPE(BarClass), ALLOCATABLE :: m_Bar
             ..
             
          CONTAINS
          
             !.. Private by default
             PRIVATE
             
             !.. Private methods
             ..
             PROCEDURE, PASS(This) :: CalcFooA
             PROCEDURE, PASS(This) :: CalcFooB
             ..
             PROCEDURE, PASS(This) :: InitFooA
             PROCEDURE, PASS(This) :: InitFooB
             ..
             FINAL :: CleanFoo
             
             !.. Public methods
             ..
             GENERIC, PUBLIC :: Init => InitFooA, InitFooB, ..
             GENERIC, PUBLIC :: Calc => CalcFooA, CalcFooB, ..
             ..
            
          END TYPE FooClass
         
       CONTAINS
       
          ..
          
          PURE ELEMENTAL SUBROUTINE InitFooA(This, .., ErrorCode)
    
             !.. Argument list
             CLASS(FooClass), INTENT(INOUT) :: This
             .. !.. Other scalar arguments
             INTEGER(..), INTENT(INOUT) :: ErrorCode
    
             !.. Local variables
             ..
             CHARACTER(LEN=80) :: ErrAlloc
             ..
             
             !..
             ErrorCode = 0
             
             ..
    
             IF (ALLOCATED(This%m_Bar)) THEN
                DEALLOCATE(This%m_Bar, STAT=ErrorCode, ERRMSG=ErrAlloc)      
                IF (ErrorCode /= 0) THEN
                   .. ! do some error handling
                   RETURN
                END IF
             END IF
             ALLOCATE(This%m_Bar, STAT=ErrorCode, ERRMSG=ErrAlloc)      
             IF (ErrorCode /= 0) THEN
                .. ! do some error handling
                RETURN
             END IF
             
             ..
                
             !..
             RETURN
             
          END SUBROUTINE InitFooA
          
          ..
          
          PURE ELEMENTAL SUBROUTINE CalcFooA(This, .., ErrorCode)
    
             !.. Argument list
             CLASS(FooClass), INTENT(INOUT) :: This
             .. !.. Other scalar arguments
             INTEGER(..), INTENT(INOUT) :: ErrorCode
    
             !.. Local variables
             ..
             
             !..
             ErrorCode = 0
             
             .. ! do some calculations involving private fields of FooClass
            
             ..
                
             !..
             RETURN
             
          END SUBROUTINE CalcFooA
          
          ..
          
       END MODULE FooClassMod
    
  • DLL "A" includes amongst other code a calculation module, say c, which has a procedure CalcSim that takes an argument of type FooClass and say it is named Foo: 
       MODULE c
       
          USE ..
          USE FooClassMod, ONLY : FooClass
          USE ..
          
          ..
          
          PUBLIC :: CalcSim
          ..
         
       CONTAINS
       
          ..
          
          SUBROUTINE CalcSim(.., Foo, .., Err)
    
             !.. Argument list
             ..
             TYPE(FooClass), INTENT(INOUT) :: Foo
             .. !
             INTEGER(..), INTENT(INOUT) :: Err
    
             !.. Local variables
             ..
             
             !..
             Err = 0
             
             ..
    
             IF ( ... ) THEN
             
                ..
                CALL Foo%Init(Err)
                IF (Err /= 0) THEN
                   .. ! do some error handling
                   RETURN
                END IF
                ..
                
             END IF
             
             ..
             CALL Foo%Calc(Err)
             IF (Err /= 0) THEN
                .. ! do some error handling
                RETURN
             END IF
             
             ..
                
             !..
             RETURN
             
          END SUBROUTINE CalcSim
          
          ..
          
       END MODULE c
  • A main program, say p, allocates a type FooClass, say it is named FooInst, and amongst other things, it invokes CalcSim procedure with FooInst as one of the arguments: 
       PROGRAM p
       
          USE ..
          USE FooClassMod, ONLY : FooClass
          USE c, ONLY : .., CalcSim, ..
          USE ..
          
          !.. Local variable type declarations
          TYPE(FooClass), ALLOCATABLE :: FooInst
          INTEGER(..) :: Err
          
          ..
          ALLOCATE(FooInst, STAT=Err, ERRMSG=ErrA)
          IF (Err /= 0)
             ..
             PRINT *, " Allocation of FooInst failed. ErrorCode = ", Err
             PRINT *, ErrA
             STOP
          END iF
          
          ..
          
          CALL CalcSim(.., FooInst, .., Err)
          IF (Err /= 0)
             ..
             PRINT *, " CalcSim failed. ErrorCode = ", Err
             ..
             STOP
          END iF
          
          ..
          
          STOP
          
       END PROGRAM p
  • The problem is the call to Init generic of Foo in CalcSim (refer to line# 35 in module c of above pseudo code) fails the second time it is invoked.  The failure mode is associated with the allocation of m_Bar component in InitFooA procedure (refer to lines 63 thru' 74 in module FooClassMod in above pseudo code).  IF (ALLOCATED(This%mBar)) check returns true, DEALLOCATE(This%m_Bar, ..) statement executes and error code comes back as zero, but the subsequent ALLOCATE(This%m_Bar,, ) returns an error value of 151 and a message of "an allocatable array is already allocated."

Note late yesterday, I thought my problems had something to do with a wrapper procedure to CalcSim that had BIND(C) attribute; since then, I've modified the actual code to follow the design pattern shown in the above pseudo code but the problem remains.

mecej4 wrote:

The FortranoPhone Devil's Advocate could combine #1 and #9 to create

...

..   goes to show that we really must have a correct description of the problem or, better yet, a reproducer.

Look, all I am looking for immediately is some pointers on what all I can check - hope the description in this quote proves adequate.  I'm trying very hard to create a reproducer.  I'll post one as soon as I succeed.  Owing to several constraints, I can't provide details of other components in the FooClass nor any details of the BarClass.  But as I reduce the problem, my belief is that other details of FooClass and specific aspects of BarClass may not be that relevant if anyone is only trying to offer me guidance.

0 Kudos
IanH
Honored Contributor III
2,273 Views

This seems familiar to me - I may have had the same sort of problem.  I have vague recollections it was due to a corrupted descriptor for a [polymorphic?  component of a polymorphic? component of a type that was printed out on paper and placed next to a dictionary with the word polymorphic in it?) (scalar?) allocatable component - exposed because the test for "are-you-allocated" and the test for "are-you-already-allocated-when-I'm-about-to-try-and-allocate-you" looked at different parts of the descriptor (one looks at the memory address, the other looks at flags?  Or maybe one was looking in completely the wrong place?  Or maybe I was looking in the wrong place?  Perhaps I'd been looking in the fridge?).  The complete absence of clarity (hence all the question marks) that I have about this problem indicates that it may have been a while back though.

If you feel brave or silly enough, have a look at the disassembly for the ALLOCATED intrinsic in your program, and try and work out what it is actually testing.  Then repeat the same sort of analysis for the error checking associated with the ALLOCATE statement.  That may give you insight for where the underlying problem might be.  Once the memory locations in the descriptor that are meaningful have been identified, things like hardware breakpoints can be used to try and understand where the wheels actually fall off.

</probably_not_adding_much_value>

0 Kudos
Steven_L_Intel1
Employee
2,273 Views

Are the DLLs and your EXE all linked to the DLL run-time libraries? They should be. If you provided a real, buildable and runnable example, analysis would go much easier. I've been burned too many times by pseudocode that didn't match the actual code.

0 Kudos
FortranFan
Honored Contributor III
2,273 Views

Steve Lionel (Intel) wrote:

Are the DLLs and your EXE all linked to the DLL run-time libraries? They should be. ...

Steve,

All the DLLs and the EXE are linked with the same Intel Fortran compiler version plus /libs:static /threads option i.e., Multithreaded option from the drop-down menu in Visual Studio for Fortran Run-time libraries.  I thought it is ok with everything is built with this option.  Comments?

Steve Lionel (Intel) wrote:

... If you provided a real, buildable and runnable example, analysis would go much easier. I've been burned too many times by pseudocode that didn't match the actual code.

I understand and so I am working toward a small, simple reproducer; hopefully I'll succeed.  I notice that if I redesign the code structure a little, the problem shifts to another section where DEALLOCATE of another object fails with "access violation" error.  This suggests the issue I mention in the original post may be one of those oft-repeated phrases "unexpected processor behavior can be experienced" in connection with non-standard/nonconforming code.  So I do accept there is a problem somewhere in the code - the challenge is to diagnose it.

0 Kudos
Steven_L_Intel1
Employee
2,273 Views

No, absolutely it is NOT ok to link these against the static libraries. You can do this when there is a single Fortran DLL and the caller is not Fortran (C++ or VB), but when you have a Fortran EXE calling Fortran DLLs, you must link them all to the DLL libraries. Do that and my guess is that your problem will go away, as otherwise you have three copies of the Fortran libraries that don't know about the others.

0 Kudos
FortranFan
Honored Contributor III
2,273 Views

Steve Lionel (Intel) wrote:

No, absolutely it is NOT ok to link these against the static libraries. You can do this when there is a single Fortran DLL and the caller is not Fortran (C++ or VB), but when you have a Fortran EXE calling Fortran DLLs, you must link them all to the DLL libraries. Do that and my guess is that your problem will go away, as otherwise you have three copies of the Fortran libraries that don't know about the others.

Ok, that is a discussion for another day.

But I just did what you suggested i.e., linked all the projects involved (2 DLLs and a Fortran EXE) with "/libs:dll /threads" option i.e., Multithreaded DLL from the dropdown menu in Visual Studio: unfortunately, the program still fails in the exact same fashion :-(

0 Kudos
Steven_L_Intel1
Employee
2,273 Views

At this point I'll ask that you construct an actual example we can look at.

0 Kudos
Steven_L_Intel1
Employee
2,107 Views

FortranFan sent me a test case and I can reproduce the problem. It has been escalated to development as issue DPD200359690. The test case had DLLs and C code, but neither of those were necessary to see the problem.

0 Kudos
Reply