- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hello:
It appears to me that the finalization process is not working properly.
I am using IVF v12.1.1.258 [IA-32] in Windows 7 (64-Bit).
I have played a bit with the example from the Fortran 2003 Draft, Oct. 2003, page 448f.
The example as published there works without problems: on return of SUBROUTINE "example"
the finalization routines t2f and t3f are called implicitely.
But, because of some questions that arose in another program due to uncalled finalization routines
1. Shouldn't the compiler cause allocated variables to deallocate on return automatically?
2. Shouldn't a FINAL routine be called on DEALLOCATE of the object to which the FINAL routine is bound?
Thank you for your comments.
Kind regards,
Jrg Kuthe
QT software
It appears to me that the finalization process is not working properly.
I am using IVF v12.1.1.258 [IA-32] in Windows 7 (64-Bit).
I have played a bit with the example from the Fortran 2003 Draft, Oct. 2003, page 448f.
The example as published there works without problems: on return of SUBROUTINE "example"
the finalization routines t2f and t3f are called implicitely.
But, because of some questions that arose in another program due to uncalled finalization routines
I used the example and changed it to find out how IVF handles finalization.
[bash]! Example from Fortran 2003 Draft, Oct. 2003, page 448f:
!
! C.1.8 Final subroutines (4.5.5, 4.5.5.1, 4.5.5.2, 4.5.5.3)
! ...
! Example of extended types with final subroutines:
MODULE m
TYPE :: t1
REAL a,b
END TYPE
TYPE,EXTENDS(t1) :: t2
REAL,POINTER :: c(:),d(:)
CONTAINS
FINAL :: t2f
END TYPE
TYPE,EXTENDS(t2) :: t3
REAL,POINTER :: e
CONTAINS
FINAL :: t3f
END TYPE
CONTAINS
SUBROUTINE t2f(x) ! Finalizer for TYPE(t2)s extra components
TYPE(t2) :: x
IF (ASSOCIATED(x%c)) DEALLOCATE(x%c)
IF (ASSOCIATED(x%d)) DEALLOCATE(x%d)
PRINT*,'Finalizer for TYPE(t2) executed.'
END SUBROUTINE
SUBROUTINE t3f(y) ! Finalizer for TYPE(t3)s extra components
TYPE(t3) :: y
IF (ASSOCIATED(y%e)) DEALLOCATE(y%e)
PRINT*,'Finalizer for TYPE(t3) executed.'
END SUBROUTINE
END MODULE
SUBROUTINE example
USE m
TYPE(t1) x1
!0 TYPE(t2) :: x2 ! if this line is activated, then the finalizer t2f is called
!0 TYPE(t3) :: x3 ! if this line is activated, then the finalizer t3f is called (and in sequence t2f too)
TYPE(t3), POINTER :: px3
CLASS(t1), POINTER :: px
TYPE(t3), ALLOCATABLE :: x3a ! if x3a is not declared and allocated, then program performs without crash
!0 Returning from this subroutine will effectively do
!0 ! Nothing to x1; it is not finalizable
!0 CALL t2f(x2)
!0 CALL t3f(x3)
!0 CALL t2f(x3%t2)
ALLOCATE(px3) ! this creates an object of TYPE t3, px3 points to
ALLOCATE(t3::px) ! this should create an object of TYPE t3, px points to (the debugger makes believe that a TYPE t1 object has been created!)
ALLOCATE(x3a) ! this also creates an object of TYPE t3
IF (ASSOCIATED(px)) DEALLOCATE(px) ! the finalizer t3f is NOT called
!IF (ASSOCIATED(px3)) DEALLOCATE(px3) ! if this line is activated, this CRASHES the program
! on return: the finalizer t3f is NOT called, although an object of t3
! has been allocated and should be deallocated on return.
DEALLOCATE(x3a) ! the finalizer t3f is called (but crashes)
! either on explicit DEALLOCATE or implicit (just leaving the routine
! without DEALLOCATE) a crash in t3f occurs
PRINT*,'In SUBROUTINE "example".'
END SUBROUTINE
PROGRAM Ex31FinalSub1
PRINT*,'PROGRAM Ex31FinalSub1 started.'
CALL example
PRINT*,'After call of SUBROUTINE "example" (in PROGRAM Ex31FinalSub).'
END PROGRAM Ex31FinalSub1
[/bash] I have tried 3 ways to create the "t3" object:[bash] ALLOCATE(px3)Then I expected that on return of SUBROUTINE "example" the finalization routine t3f is called implicitely, because I believe that automatic deallocation should take place. But this is only the case for variable x3a. However then the program crashes in the finalization routine t3f for some unknown reason (this looks like a bug).Here are my questions, I could not answer neither from searching through F2003 draft nor from searching through the IVF documentation.
ALLOCATE(t3::px)
ALLOCATE(x3a) [/bash]
1. Shouldn't the compiler cause allocated variables to deallocate on return automatically?
2. Shouldn't a FINAL routine be called on DEALLOCATE of the object to which the FINAL routine is bound?
Thank you for your comments.
Kind regards,
Jrg Kuthe
QT software
Link Copied
10 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
>>...
>>1. Shouldn't the compiler cause allocated variables to deallocate on return automatically?
>>...
In general:
All automatic variables allocated\created on the stack must be released by a compileras soon as a
function exits.
All dynamic variables allocated\created on the heap are not released by a compiler as soon as a function
exits.
Best regards,
Sergey
>>1. Shouldn't the compiler cause allocated variables to deallocate on return automatically?
>>...
In general:
All automatic variables allocated\created on the stack must be released by a compileras soon as a
function exits.
All dynamic variables allocated\created on the heap are not released by a compiler as soon as a function
exits.
Best regards,
Sergey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Sergey,
I appreciate your trying to help, but in this case you are not correct. The Fortran language requires that procedure-local ALLOCATABLE variables that do not have the SAVE attribute are to be automatically deallocated when the procedure exits. I will look at Joerg's questions in more detail next week.
I appreciate your trying to help, but in this case you are not correct. The Fortran language requires that procedure-local ALLOCATABLE variables that do not have the SAVE attribute are to be automatically deallocated when the procedure exits. I will look at Joerg's questions in more detail next week.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Quoting Steve Lionel (Intel)
Sergey,
I appreciate your trying to help, but in this case you are not correct. The Fortran language requires that
procedure-local ALLOCATABLE variables that do not have the SAVE attribute are to be automatically
deallocated when the procedure exits.
[SergeyK] Thank you, Steve! Does it mean that there is some problem with theSAVE
attribute inthe IntelFortran compiler?
I will look at Joerg's questions in more detail next week.
I appreciate your trying to help, but in this case you are not correct. The Fortran language requires that
procedure-local ALLOCATABLE variables that do not have the SAVE attribute are to be automatically
deallocated when the procedure exits.
[SergeyK] Thank you, Steve! Does it mean that there is some problem with theSAVE
attribute inthe IntelFortran compiler?
I will look at Joerg's questions in more detail next week.
Best regards,
Sergey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I have no idea, yet, what the problem is, but I doubt it is related to SAVE. I mentioned that in my correction to your earlier post that the user is responsible for deallocating all heap-allocated storage.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thank you, Steve!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Add a constructor to =>NULL() your pointers on allocation, and in your FINAL routine, NULLIFY the pointer after deallocation. See if this fixes your crash problem.
Jim Dempsey
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yes, changing the definition of t3
[bash] TYPE,EXTENDS(t2) :: t3
REAL,POINTER :: e => NULL() ! without => NULL() , the program crashes in t3f when deallocating y % e
CONTAINS
FINAL :: t3f
END TYPE
[/bash]helps. But to be honest, I have no idea why.
Thank you, Jim.
Joerg
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Joerg,
Assume you have
subroutine ...
.....
type(t3) :: foo
(code without using foo)
end subroutine ...
Without the e => NULL()
the pointer is (or will likely have) "junk data"
When the above subroutine exits, the "junk data" will be deallocated, resulting in corruption of heap.
A similar situation is involved when you directly deallocate the pointer in the object - but keep the object around, say until return from subroutine. Should you expressly deallocate the object pointed to by e and leave the pointer alone, then upon exit from the subroutine the object pointed to by e will be returned a second time (by way of your FINAL routine), corrupting the heap or crashing the application.
It is the programmer's responsibility to assure that which is the programmer's responsibility to be returned is returned, but only returned once.
Jim Dempsey
Assume you have
subroutine ...
.....
type(t3) :: foo
(code without using foo)
end subroutine ...
Without the e => NULL()
the pointer is (or will likely have) "junk data"
When the above subroutine exits, the "junk data" will be deallocated, resulting in corruption of heap.
A similar situation is involved when you directly deallocate the pointer in the object - but keep the object around, say until return from subroutine. Should you expressly deallocate the object pointed to by e and leave the pointer alone, then upon exit from the subroutine the object pointed to by e will be returned a second time (by way of your FINAL routine), corrupting the heap or crashing the application.
It is the programmer's responsibility to assure that which is the programmer's responsibility to be returned is returned, but only returned once.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Note that DEALLOCATE(pointer) also disassociates (nullifies) pointer if deallocation is successful.
(Putting pointer => NULL() after DEALLOCATE(pointer) is redundant.)
(Putting pointer => NULL() after DEALLOCATE(pointer) is redundant.)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I stand corrected. Thank you for pointing this out.
Jim
Jim
Reply
Topic Options
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page