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

Final not being called for associate

antony
Beginner
598 Views

The code below does not call the object finalization code in ifort 14.0.1, and I think it should. I've submitted it as issue 6000044034 last year, but still seem to be stuck in "investigating" limbo.

    module A
    Type T
     integer :: val = 2
    contains
    final :: testfree
    end type
    contains

    subroutine testfree(this)
    Type(T) this

	print *,'freed'
    end subroutine

    subroutine Testf()

	associate(X => T())
		print *, X%val
	end associate
    print *,'ended'
    end subroutine Testf

    end module

    program tester
    use A

    call Testf

    end program

 

0 Kudos
5 Replies
FortranFan
Honored Contributor II
598 Views

The data type has to have an ALLOCATABLE attribute in order for the finalizer to be invoked.  The following code with a minor change to use an allocatable variable works ok.

MODULE A

   TYPE T
      INTEGER :: VAL = 2
   CONTAINS
      FINAL :: testfree
   END TYPE

CONTAINS

   SUBROUTINE testfree(this)
      TYPE(T) this

      PRINT *,'freed'
   END SUBROUTINE

   SUBROUTINE Testf()

      TYPE(T), ALLOCATABLE :: foo

      foo = T()
      ASSOCIATE (X => foo)
         PRINT *, X%VAL
      END ASSOCIATE
      PRINT *,'ended'

   END SUBROUTINE Testf

END MODULE

PROGRAM tester

   USE A, ONLY : Testf

   CALL Testf

END PROGRAM

 

0 Kudos
antony
Beginner
598 Views

I agree it works fine if it is a local variable. But I don't think there's any requirement for the type to be allocatable, the F08 standard says

16 4.5.6.3 When finalization occurs
17 1 When a pointer is deallocated its target is finalized. When an allocatable entity is deallocated, it is finalized.
18 2 A nonpointer, nonallocatable object that is not a dummy argument or function result is finalized immediately
19 before it would become undefined due to execution of a RETURN or END statement (16.6.6, item (3)).

Point 18 suggests here that it should be finalized at the latest at subroutine exit (and I think probably at the end of the associate scoping block). Btw, the motivation was I was thinking of using constructions like

associate (F => TTextFile('myfile.txt')) 
 call F%Write(myData) 
end associate

 

and have TTextFile's finalization routine autoamtically close the internal file handle.

 

 

 

0 Kudos
Steven_L_Intel1
Employee
598 Views

I assume you think the finalizer should be called based on the following text in the original F2008 standard:

4.5.6.3 When finalization occurs

5 If an executable construct references a structure constructor or array constructor, the entity created by the constructor is finalized before execution of the executable constructs in the scoping unit.

This text was deleted in F2008 Corrigendum 1 as part of interpretation F08/0011. Here is the text of that:

NUMBER: F08/0011
TITLE: How many times are constructed values finalized?
KEYWORDS: Finalization
DEFECT TYPE: Erratum
STATUS: Passed by WG5 letter ballot

QUESTION:

Consider the program:

      Module m
        Type t1
          Real c
        Contains
          Final :: f10,f11
        End Type
        Type,Extends(t1) :: t2
          Real d
        Contains
          Final :: f20,f21
        End Type
      Contains
        Subroutine f10(x)
          Type(t1),Intent(InOut) :: x
          Print *,'f10 called'
        End Subroutine
        Subroutine f11(x)
          Type(t1),Intent(InOut) :: x(:)
          Print *,'f11 called'
        End Subroutine
        Subroutine f20(x)
          Type(t2),Intent(InOut) :: x
          Print *,'f20 called'
        End Subroutine
        Subroutine f21(x)
          Type(t2),Intent(InOut) :: x(:)
          Print *,'f21 called'
        End Subroutine
      End Module
      Program q
        Call sub(1.5,2.5)
      End Program
      Subroutine sub(x,y)
        Use m
        Type(t1),Parameter :: p1 = t1(2.5)
        Type(t2),Parameter :: p2 = t2(3.5,-3.5)
        Call s10(t1(x))
        Call s11([p1])                     ! (a)
        Call s11([t1(x)])                  ! (b)
        Call s11([ [ [ p1,p1 ] ] ])        ! (c)
        Call s20(t2(x,y))
        Call s21([p2])                     ! (d)
        Call s21([t2(y,y)])                ! (e)
        Call s21([t2(t1=p1,y)])            ! (f)
        Call s21([t2(t1=t1(x),y)])         ! (g)
        Call s21([(p2,t2(x,y),i=1,10**7)]) ! (h)
      End Subroutine

The topic is how many times each final procedure is called on return
from each subroutine?

For s10, clearly f10 is called once.

For s11(a), clearly f11 is called once, and f10 is not called.

For s11(b), the standard (4.5.6.3 para 5) seems to indicate that f10
  is called.  That would not make much sense - the value of the
  structure constructor is part of the value of the array constructor,
  so calling f10 would mean that that array element would be finalized
  twice (once by f11, once by f10, in no set order).

For s11(c), the standard standard appears to say that f11 is called
  three times, once for each (nested) array constructor.  Seeing as
  how nesting array constructors is a syntactic thing that makes zero
  difference to the value - the value of [[anything]] is identical in
  every respect to the value of [anything] - this does not seem to
  make sense.

For s20, clearly f20 is called once, and f10 is called afterwards to
  finalize the parent component.

For s21(d), clearly f21 is called once, followed by f11 to finalize the
  parent components.  f20 and f10 are not called.

For s21(e), f21 and f11 are called as in s21(d); the standard implies
  that f20 and then f10 are called, but that does not make sense, the
  same as case s11(b).

For s21(f), the situation seems to be the same as s21(e); the wanted
  f21 and f11, and (unordered) the unwanted f20 and f10.

For s21(g), f21 and f11 are called as in s21(d); the standard implies
  that f10 is called to finalize t1(3) and also that f20 and then f10
  are called to finalize t2(t1=t1(3),4).  This makes even less sense
  than before, since the t1 part of the array constructor element is
  going to be finalized 3 times just because of the syntax we used.

For s21(h), f21 and f11 are called as in s21(d) to finalize the whole
  array constructor value; the standard also implies that f20 and then
  f10 are called on all of the 5000000 even-numbered elements.
  Requiring the processor to keep track of all those elements to be
  finalized on return from s21 seems rather severe.

Furthermore, an object that has been finalized is not permitted to be
referenced or defined.  That makes the multiple finalization
interpretation even more hard to understand.

Philosophically, finalization should finalize objects exactly once.

There seem to be three possibilities here.
(1) The finalizers are called multiple times, but on the separate
    entities created by the constructors.  For example s21(g), that is
    t1(3) is created as object X, when t2(...) is evaluated a new
    separate object Y is created and that value is copied into it, and
    when [...] is evaluated a third object Z is created with the value
    of Y copied into it; afterwards, we effectively have
       call f10(X); call f20(Y); call f21(Z); call f11(Z%t1)
    For s21(h) that burden is going to be extreme because the standard
    says these are "finalized after execution of the innermost
    executable construct containing the reference" (and it is possible
    to detect this in a conforming program); changing that to
    "finalized after the value has been used" would be better if
    slightly vague.
(2) These entities are indeed finalized multiple times, just as the
    standard implies.
(3) Constructors that are merely providing part of the value of a
    bigger constructor are not finalized.
(4) Constructors should never be finalized in themselves, this was
    just a design error that inevitably leads to multiple or
    unwanted finalization.

Which is the correct approach?

ANSWER:
Approach 4.  Constructors don't do anything that needs finalization.
Edits are provided to correct the mistake.

NOTE: This answer subsumes interp F08/0012 (10-159r1).

EDITS to 10-007r1:

[24:9] Change the first word of 1.6.2p1
       "This" -> "Except as identified in this subclause, this".

[24:11+] Insert new paragraph after 1.6.2p1:
  "Fortran 2003 specified that array constructors and structure
   constructors of finalizable type are finalized.  This part of
   ISO/IEC 1539 specifies that these constructors are not
  finalized.".

[76:17-18,21-22] Delete paragraphs 5 and 7 of 4.5.6.3
                 (When finalization occurs).

SUBMITTED BY: Malcolm Cohen

HISTORY: 10-158    m192  F08/0011 submitted
         10-158r1  m192  Revised - Passed by J3 meeting
         10-202    m192  Passed as amended by J3 letter ballot
                          #21 10-199
         11-006Ar1 m196  Adjust edits to reference 10-007r1
         N1878	         Passed by WG5 letter ballot

 

0 Kudos
antony
Beginner
598 Views

Thanks Steve for the standard update, interesting.

The level of support you provide here is amazing, I wish the official support channels were equally responsive (my issue 0000456671, still a regular annoyance, dates back to 2007!) - it seems like it is always much better to post here.

0 Kudos
Steven_L_Intel1
Employee
598 Views

Sorry to hear that you've had issues with Intel Premier Support. I pinged the support engineer who owned this issue. I sometimes lose track of issues I'm supposed to be working (the tool we use doesn't forget, but if I don't look at it....)

Regarding 456671, this was escalated to development, as was noted.  As Patrick said in the last update there, the behavior of Visual Studio regarding "step over" or "run to cursor" in the debugger is not something under our control. I think the problem here is that a LOT of instructions can be executed for an array assignment, and if the debugger is single-stepping, which it sometimes does, that can take a long time.

0 Kudos
Reply