- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
[fortran]MODULE mod
TYPE typ
INTEGER :: i = 1
CONTAINS
PROCEDURE :: mul
FINAL :: destruct
END TYPE typ
CONTAINS
FUNCTION mul(a,m) RESULT (b)
CLASS (typ), INTENT (in) :: a
INTEGER, INTENT (in) :: m
CLASS (typ), ALLOCATABLE :: b
ALLOCATE(b, source=a)
b%i = b%i * m
END FUNCTION mul
SUBROUTINE destruct(a)
TYPE (typ), INTENT (inout) :: a
PRINT *, 'destructor called'
END SUBROUTINE destruct
END MODULE mod
PROGRAM test
USE mod
TYPE(typ) :: a, b
b = a
PRINT *
b = mul(a,5)
PRINT *, b%i
END PROGRAM test
[/fortran]
When compiled with ifort (version 12.1.1.256), both assignments in the main program call the final subroutine once (for the left hand side variable). I would expect that the second assignment should call it twice; the extra finalization should be for the allocated function result of 'mul'. Is it a bug in ifort or am I wrong?
Link kopiert
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Your final subroutine gets called twice for b, following this rule:
"When an intrinsic assignment statement is executed, the variable is finalized after the evaluation of expr and before the definition of the variable." [Fortran 2008,4.5.6.3, paragraph 9]
For the function call, two rules apply:
"If an executable construct references a function, the result is finalized after execution of the innermost executable construct containing the reference." [paragraph 4]
so in this case, the function result would get finalized at the end of the program. But...
"If image execution is terminated, either by an error (e.g. an allocation failure) or by execution of a stop-stmt, error-stop-stmt, or end-program-stmt, entities existing immediately prior to termination are not finalized." [4.5.6.4]
Since in this case, the function result still exists at the END PROGRAM, it does not get finalized.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
I suppose that there is no way to force the finalization of the allocated function result at a specific point in the code. It is inaccessible after the assignment. Doesn't this lead to a memory leak?
By the way, IBM xlf v13.1 calls the final subroutine twice for the second assignment, right after the completion of the assignment, avoiding the leak.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
I would think that xlf's behavior is not conforming to the standard, but it might be difficult to write a conforming program that could really tell.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
[fortran]MODULE modu
TYPE typ
REAL, ALLOCATABLE :: r(:)
CONTAINS
PROCEDURE :: copy
FINAL :: destruct
END TYPE typ
CONTAINS
FUNCTION copy(a) RESULT (b)
CLASS (typ), INTENT (in) :: a
CLASS (typ), ALLOCATABLE :: b
ALLOCATE(b, source = a)
END FUNCTION copy
SUBROUTINE destruct(a)
TYPE (typ), INTENT (inout) :: a
END SUBROUTINE destruct
END MODULE modu
PROGRAM test
USE modu
TYPE(typ) :: a, b
ALLOCATE(a%r(2))
DO
b = a%copy()
END DO
END PROGRAM test
[/fortran] When compiled with ifort, the executable has a memory leak. Isn't the code standard conforming?- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
[fortran]MODULE modu
TYPE typ
REAL, ALLOCATABLE :: r(:)
CONTAINS
PROCEDURE :: copy
FINAL :: destruct
END TYPE typ
CONTAINS
FUNCTION copy(a) RESULT (b)
CLASS (typ), INTENT (in) :: a
CLASS (typ), ALLOCATABLE :: b
ALLOCATE(b, source = a)
PRINT *, "In copy, LOC(b)=",LOC(b)
END FUNCTION copy
SUBROUTINE destruct(a)
TYPE (typ), INTENT (inout) :: a
END SUBROUTINE destruct
END MODULE modu
PROGRAM test
USE modu
TYPE(typ) :: a, b
ALLOCATE(a%r(2))
DO I=1,10
b = a%copy()
END DO
END PROGRAM test
[/fortran] I was at the standards committee meeting where this topic was discussed. IBM had already implemented its approach but the vote was overwhelmingly in favor of the way the standard worded it.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
You might not be observing a memory leak. What you might be observing is a "feature". Some of the heap managers are now of GC (garbage collector) design. Meaning, returned nodes are not immediately recycled. Instead they are "quarantined" before recycled. The reason for doing this is two-fold: a) reduces the number of heap locks on returning nodes, and b) in the event of bad programming design (bug) where buffer is used after delete and this practice can/might hide the error.
To find out if leak:
if you can set upper limit on heap do so and run the program and see if it crashes after sufficient allocations to expend the upper limit on heap.
If you cannot set upper limit on heap you usually can specify upper limit on page file. Run the program andtrack page file usage. When page file maxes out, if your program continues to run, then there is no memory leak.
Jim Dempsey
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
Insufficient memory to allocate Fortran RTL message buffer, message #41 = hex 00000029
Intel Inspector finds the memory leak. Therefore, there is a bug either in the compiler or the memory checker!
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
I will look at this more closely.
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
- Als neu kennzeichnen
- Lesezeichen
- Abonnieren
- Stummschalten
- RSS-Feed abonnieren
- Kennzeichnen
- Anstößigen Inhalt melden
- RSS-Feed abonnieren
- Thema als neu kennzeichnen
- Thema als gelesen kennzeichnen
- Diesen Thema für aktuellen Benutzer floaten
- Lesezeichen
- Abonnieren
- Drucker-Anzeigeseite