- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi All -
I'm trying to understand the correct way to use the FINAL routines with the Intel compiler. My intuition about the routine is correct and works with gfortran. My expectation is the constructor is called when the object is created and the destructor/final routine is called when the object goes out of scope. Because I'm using the constructor and final routines to make calls into a c++ library, the un-paired calls cause memory issues. I've attached a minimal working example as well as output from gfortran and Intel ifort 19.1 (which I've confirmed is the same as Intel ifort 18 and 19.0)
MODULE SAMPLE IMPLICIT NONE TYPE STYPE INTEGER :: A CHARACTER(200) :: whoami = "__NONAME__" CONTAINS FINAL :: destructor END TYPE STYPE INTERFACE STYPE PROCEDURE :: constructor END INTERFACE STYPE CONTAINS FUNCTION constructor(me) RESULT(this) IMPLICIT NONE TYPE(STYPE) :: this CHARACTER(*),INTENT(IN) :: me WRITE(*,'(2A)') "Initializing: ",TRIM(me) this%whoami = me this%a = 0 END FUNCTION constructor SUBROUTINE destructor(this) IMPLICIT NONE TYPE(STYPE) :: this WRITE(*,'(2A)') "Deconstructing: ",TRIM(this%whoami) END SUBROUTINE END MODULE SAMPLE MODULE MYFUNCTIONS USE SAMPLE IMPLICIT NONE CONTAINS SUBROUTINE FN1() IMPLICIT NONE TYPE(STYPE) :: C C = STYPE("FN1") CALL FN2() END SUBROUTINE FN1 SUBROUTINE FN2() IMPLICIT NONE TYPE(STYPE) :: D D = STYPE("FN2") END SUBROUTINE FN2 END MODULE MYFUNCTIONS PROGRAM MAIN USE SAMPLE USE MYFUNCTIONS IMPLICIT NONE TYPE(STYPE) :: A TYPE(STYPE) :: B A = STYPE("main_A") B = STYPE("main_B") CALL FN1() END PROGRAM MAIN
The expected output and what I get from gfortran shows the destructor is called when the object goes out of scope, which is what I expect. Note that the destructor for main_a and main_b are not called automatically which does match my understanding of the standard.
Initializing: main_A Initializing: main_B Initializing: FN1 Initializing: FN2 Deconstructing: FN2 Deconstructing: FN1
However, the output from the Intel compiler it's very different. It seems there are at least two destructor calls for every constructor call, one of the objects that is deconstructed seems to be an uninitialized copy, and they occur out of sequence, meaning I expect: Construct A --> Construct B --> Deconstruct B --> Deconstruct A.
Initializing: main_A Deconstructing: __NONAME__ Deconstructing: main_A Initializing: main_B Deconstructing: __NONAME__ Deconstructing: main_B Initializing: FN1 Deconstructing: __NONAME__ Deconstructing: FN1 Initializing: FN2 Deconstructing: __NONAME__ Deconstructing: FN2 Deconstructing: FN2 Deconstructing: FN1
Is there a mismatch in my understanding of how to implement this sort of operation or is there a more correct way to achieve this?
Thanks
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
To add to Quote #2, a scenario that brings it closer to the object 'construction' and 'deconstruction' as envisaged in the original post is with the ALLOCATABLE attribute:
module SAMPLE implicit none type STYPE integer :: A character(200) :: whoami = "__NONAME__" logical :: temp = .false. contains final :: destructor procedure, pass(this) :: init => init_t end type STYPE interface STYPE procedure :: constructor end interface STYPE contains function constructor(me) result(this) type(STYPE) :: this character(len=*),intent(in) :: me write(*,'(2A)') "'Constructing': ",trim(me) this%whoami = me this%a = 0 this%temp = .true. end function constructor subroutine destructor(this) type(STYPE), intent(inout) :: this write(*,'(2A)',advance='no') "Finalizing: ",trim(this%whoami) if (this%temp) write(*,'(2A)') ", the RHS object" write (*,*) end subroutine subroutine init_t(this, me) class(STYPE), intent(inout) :: this character(len=*),intent(in) :: me this%whoami = me end subroutine end module SAMPLE module MYFUNCTIONS use SAMPLE implicit none contains subroutine FN1() implicit none type(STYPE), allocatable :: C C = stype("FN1") C%temp = .false. call FN2() end subroutine FN1 subroutine FN2() implicit none type(STYPE), allocatable :: D D = stype("FN2") D%temp = .false. end subroutine FN2 end module MYFUNCTIONS program MAIN use SAMPLE, only : STYPE use MYFUNCTIONS, only : FN1 implicit none type(STYPE), allocatable :: A type(STYPE), allocatable :: B A = stype("main_A") B = stype("main_B") call FN1() end program MAIN
Upon execution with Intel Fortran,
'Constructing': main_A Finalizing: main_A, the RHS object 'Constructing': main_B Finalizing: main_B, the RHS object 'Constructing': FN1 Finalizing: FN1, the RHS object 'Constructing': FN2 Finalizing: FN2, the RHS object Finalizing: FN2 Finalizing: FN1
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@Zach C.,
I suggest you review this modified example based on your original post and please note the following:
- The semantics of finalization in the Fortran standard has gone through several refinements (some might say corrections or bug fixes) during the interpretation phase post-Fortran 2008. The changes were documented only in the Corrigenda to Fortran 2008 standard and later in Fortran 2018 but it appears to me some compiler implementations missed out on studying the Corrigenda.
- My recollection is gfortran is one of those compilers which didn't pick up on the 2008 Corrigenda nor 2018 standard so it does not fully conform to the current standard,
- What you are noticing with Intel has to do with semantics of the assignment 'var = expr' and how 'var' gets defined and what happens to the function result of 'expr'. Look in Section 7.5.6.3 When finalization occurs in the standard, paragraph 1. I've some doubts about Intel's implementation though,
- Even though there are some similarities between other languages (esp. C++) and Fortran when it comes to object construction with a generic function interface that has the same name as the type in question, there are subtle differences too that come into play, particularly with the lack of elision with the function result,
- Given the point 3 above and also given how objects get defined in Fortran with component initialization, my take is the use of structure constructor as in 'obj = type(..)' assignment operation is not useful with types that require finalization. I would suggest the use of explicit 'initialization' procedures instead as show in the example below; one can define generic interfaces as needed.
module SAMPLE implicit none type STYPE integer :: A character(200) :: whoami = "__NONAME__" logical :: temp = .false. contains final :: destructor procedure, pass(this) :: init => init_t end type STYPE interface STYPE procedure :: constructor end interface STYPE contains function constructor(me) result(this) type(STYPE) :: this character(len=*),intent(in) :: me write(*,'(2A)') "'Constructing': ",trim(me) this%whoami = me this%a = 0 this%temp = .true. end function constructor subroutine destructor(this) type(STYPE), intent(inout) :: this write(*,'(2A)',advance='no') "Finalizing: ",trim(this%whoami) if (this%temp) write(*,'(2A)') ", the RHS object" write (*,*) end subroutine subroutine init_t(this, me) class(STYPE), intent(inout) :: this character(len=*),intent(in) :: me this%whoami = me end subroutine end module SAMPLE module MYFUNCTIONS use SAMPLE implicit none contains subroutine FN1() implicit none type(STYPE) :: C call C%init("Initial C") C = stype("FN1") C%temp = .false. call FN2() end subroutine FN1 subroutine FN2() implicit none type(STYPE) :: D call D%init("Initial D") D = stype("FN2") D%temp = .false. end subroutine FN2 end module MYFUNCTIONS program MAIN use SAMPLE, only : STYPE use MYFUNCTIONS, only : FN1 implicit none type(STYPE) :: A type(STYPE) :: B call A%init("Initial A") call B%init("Initial B") A = stype("main_A") B = stype("main_B") call FN1() end program MAIN
'Constructing': main_A Finalizing: Initial A Finalizing: main_A, the RHS object 'Constructing': main_B Finalizing: Initial B Finalizing: main_B, the RHS object 'Constructing': FN1 Finalizing: Initial C Finalizing: FN1, the RHS object 'Constructing': FN2 Finalizing: Initial D Finalizing: FN2, the RHS object Finalizing: FN2 Finalizing: FN1
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
To add to Quote #2, a scenario that brings it closer to the object 'construction' and 'deconstruction' as envisaged in the original post is with the ALLOCATABLE attribute:
module SAMPLE implicit none type STYPE integer :: A character(200) :: whoami = "__NONAME__" logical :: temp = .false. contains final :: destructor procedure, pass(this) :: init => init_t end type STYPE interface STYPE procedure :: constructor end interface STYPE contains function constructor(me) result(this) type(STYPE) :: this character(len=*),intent(in) :: me write(*,'(2A)') "'Constructing': ",trim(me) this%whoami = me this%a = 0 this%temp = .true. end function constructor subroutine destructor(this) type(STYPE), intent(inout) :: this write(*,'(2A)',advance='no') "Finalizing: ",trim(this%whoami) if (this%temp) write(*,'(2A)') ", the RHS object" write (*,*) end subroutine subroutine init_t(this, me) class(STYPE), intent(inout) :: this character(len=*),intent(in) :: me this%whoami = me end subroutine end module SAMPLE module MYFUNCTIONS use SAMPLE implicit none contains subroutine FN1() implicit none type(STYPE), allocatable :: C C = stype("FN1") C%temp = .false. call FN2() end subroutine FN1 subroutine FN2() implicit none type(STYPE), allocatable :: D D = stype("FN2") D%temp = .false. end subroutine FN2 end module MYFUNCTIONS program MAIN use SAMPLE, only : STYPE use MYFUNCTIONS, only : FN1 implicit none type(STYPE), allocatable :: A type(STYPE), allocatable :: B A = stype("main_A") B = stype("main_B") call FN1() end program MAIN
Upon execution with Intel Fortran,
'Constructing': main_A Finalizing: main_A, the RHS object 'Constructing': main_B Finalizing: main_B, the RHS object 'Constructing': FN1 Finalizing: FN1, the RHS object 'Constructing': FN2 Finalizing: FN2, the RHS object Finalizing: FN2 Finalizing: FN1
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This is excellent and worked perfectly. I really appreciate your help.

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page