j3-fortran / fortran_proposals

Proposals for the Fortran Standard Committee
178 stars 15 forks source link

Finalization order for complex objects: official interpretation needed? #146

Open nncarlson opened 4 years ago

nncarlson commented 4 years ago

@certik asked that I share this here.

I've encountered an issue with finalization that is illustrated by the example that follows. There is a parent type and child type that extends the parent, each with a final subroutine. The child type has two derived type components, one allocatable, the other not. The component types also have final subroutines. The point of the example is to reveal the order in which the final subroutines are called.

Two compilers produce the results I expected, namely the string "CABP" for Child, component A, component B, and Parent. "CBAP" would have been equally acceptable. A third compiler produces the string "CBPA". The preliminary response from the vendor of the latter compiler is that the standard is ambiguous with conflicting requirements and that choice of behavior is arguably valid. They did go into some explanation, but I haven't yet understood their argument. I'll be following up with them, and as I understand more I'll comment here with it. Section 7.5.6.2 (2018) seems pretty clear to me (arguing for "CABP") but there may well be other parts of the standard that are inconsistent with it -- I have a lot of respect for this vendor. If an official interpretation and standard clarification is required I would strongly urge for "CABP".

[Edit] The core question here is why does the third compiler vendor believe the allocatable component A have to be finalized last after the parent, whereas the non-allocatable component B should be finalized before the parent.

Here is the example

module child_type

  implicit none
  private

  type :: objectA
  contains
    final :: finalize_objectA
  end type

  type :: objectB
  contains
    final :: finalize_objectB
  end type

  type :: parent
  contains
    final :: finalize_parent
  end type

  type, extends(parent), public :: child
    type(objectA), allocatable :: A
    type(objectB) :: B
  contains
    procedure :: init
    final :: finalize_child
  end type

contains

  subroutine finalize_objectA(this)
    type(objectA), intent(inout) :: this
    write(*,'("A")',advance='no')
  end subroutine

  subroutine finalize_objectB(this)
    type(objectB), intent(inout) :: this
    write(*,'("B")',advance='no')
  end subroutine

  subroutine finalize_parent(this)
    type(parent), intent(inout) :: this
    write(*,'("P")',advance='no')
  end subroutine

  subroutine finalize_child(this)
    type(child), intent(inout) :: this
    write(*,'("C")',advance='no')
  end subroutine

  subroutine init(this)
    class(child), intent(inout) :: this
    allocate(this%A)
  end subroutine

end module

program main
  use child_type
  call run
contains
  subroutine run
    type(child) :: c
    call c%init
  end subroutine
end program
nncarlson commented 4 years ago

A bit of background for those who might be wondering. In the actual use case, the child type is a "solver". The solver makes use of a third party framework library AMReX that the solver starts up as part of its initialization and then shuts down when the solver is deallocated or goes out of scope. The solver also has components that have framework objects as subobjects. These must be finalized before the framework is shutdown. In order to ensure that things happen in the right order, the solver extends a dummy parent type whose main purpose is to shut down the framework as part of the parent's final subroutine. Unfortunately this doesn't work with the way the third compiler behaves.

In the actual use case the allocatable component is polymorphic (hence making it non-allocatable isn't an option), but that is an extraneous feature to the core question. Interestingly, one of the compilers that gets the example "right" totally blows it for the allocatable polymorphic component case -- it never bothers to call its finalizer at all.

klausler commented 4 years ago

Apart from the lack of specification on the order of finalization of components, F'2018 is very clear to me on this point. "CABP" and "CBAP" are the only valid outputs. In particular, the parent component absolutely may not be finalized in step (3) until after the non-parent components have been finalized in step (2) (see 7.5.6.2).

The child's final procedure can effectively force the order "ACBP" if necessary by deallocating A in finalize_child before doing anything else.

certik commented 4 years ago

I agree with @nncarlson and @klausler that "CABP" and "CBAP" should be the only two valid outputs in this case.

FortranFan commented 4 years ago

To me, this looks worthy of an interpretation request.

certik commented 4 years ago

How do we submit one?

On Tue, Feb 25, 2020, at 3:58 PM, FortranFan wrote:

To me, this looks worthy of an interpretation request.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/146?email_source=notifications&email_token=AAAFAWBXEE7GS2YSDDAAM33REWWBZA5CNFSM4KZKUGP2YY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOEM6DOHI#issuecomment-591148829, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWBZWO2TYYCZA2RRLFDREWWBZANCNFSM4KZKUGPQ.

FortranFan commented 4 years ago

@certik wrote:

How do we submit one? ..

Start with an email to the J3 mailing list. Then as needed based on clarity and/or suitability of the response(s), draft a paper like this: https://j3-fortran.org/doc/year/20/20-102.txt

zjibben commented 4 years ago

There is an interp paper on this for discussion tomorrow: https://j3-fortran.org/doc/year/20/20-117.txt.

certik commented 4 years ago

Actually I think this paper is a little bit different if you look at the example carefully. But maybe it exposes the same issue.

On Wed, Feb 26, 2020, at 4:46 PM, Zach Jibben wrote:

There is an interp paper on this for discussion tomorrow: https://j3-fortran.org/doc/year/20/20-117.txt.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/146?email_source=notifications&email_token=AAAFAWGWNROTW7LYMV6ADETRE4EPJA5CNFSM4KZKUGP2YY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOENCOUMY#issuecomment-591718963, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWGKUOQX3DUG7BV5HS3RE4EPJANCNFSM4KZKUGPQ.

nncarlson commented 4 years ago

I'm not sure of what to make of the document. Rather opaque on my first reading. I hope the outcome, whatever the means, is that the required behavior is what we seem to agree is wanted. Please push for that tomorrow.

nncarlson commented 4 years ago

@certik the example from the document is precisely the same as the one gave in here.

FortranFan commented 4 years ago

@certik the example from the document is precisely the same as the one gave in here.

There is a difference in that the example in the interpretation document at the J3 website does NOT have the equivalent of 'objectB' as a component in the child derived type:

image

Plus there is the aspect where discussion in the interp doc addresses quite a bit the concern about an object ('OtherF') being finalized twice.

That doesn't appear in the original post here since that would have led to comments about 'A' appearing twice in the output of the program in the original post.

certik commented 4 years ago

Indeed, it seems different. For that reason I submitted a new one:

https://mailman.j3-fortran.org/pipermail/j3/2020-February/011838.html

For now just as an email. Based on the response and discussion tomorrow, we can submit a full request.

nncarlson commented 4 years ago

As @FortranFan pointed out the only difference was the addition of an objectB component. I added that simply to highlight how finalization of non-allocatable component is done differently from that for an allocatable for the one problem compiler. I should probably say "cleanup" instead of "finalization", because I sense from the interp doc, that finalization is being used in a very strict technical sense that isn't completely synonymous with what I think of naively as cleanup. I know of no compiler that does the finalization twice like the interp doc discusses. In fact, the problem compiler of the OP is the NAG compiler, and its odd behavior is precisely to avoid finalizing twice per an explanation passed on to me from Malcolm. I still don't understand why he believes one possible interp requires finalizing twice -- I'm missing something, hopefully @certik and @zjibben will be able to explain what the problem is after today's deliberation.

certik commented 4 years ago

So after the discussion at plenary the paper https://j3-fortran.org/doc/year/20/20-117.txt got passed.

With the standard, as amended by 20-117, the CBPA output is allowed and ok, per standard.

nncarlson commented 4 years ago

Argh... Was there much disagreement? apparently there weren't enough people who saw (or cared) how stupid (imo) that is.

klausler commented 4 years ago

I've been studying the edits in that paper, and (discussion in the room notwithstanding) I don't see anything that changes the organization of the section in the standard (7.5.6.2) that puts finalization of the parent component in step (3), after the finalization of the extended type's instance and its components.

EDIT: This is wrong; these edits do break the order of finalization of a parent component w/r/t allocatable components in instances of its extended derived types.

klausler commented 4 years ago

I also think that there was a lot of ambiguous usage of the word "parent" in the meeting, and at least two people were using the word to mean "the object being finalized, as opposed to its 'child' components", and not "the parent component of the extended derived type".

certik commented 4 years ago

@klausler per your understanding, is the CBPA output allowed by the standard (for the code above)?

klausler commented 4 years ago

Parent components are finalized in step (3) in the standard. I don't see anything in the edits in the actual paper (https://j3-fortran.org/doc/year/20/20-117.txt) that changes that. But the discussion was highly confused (or at least confusing).

EDIT: Now I see them; never mind.

nncarlson commented 4 years ago

@klausler, what about

[80:9] 7.5.6.2 The finalization process, p1, item (2), "All finalizable" -> "All nonallocatable finalizable".

With that change, 7.5.6.2 does't appear to have anything to say about what happens to allocatable finalizable components.

klausler commented 4 years ago

I've come to the same conclusion here, Neil. And that seems broken to me.

certik commented 4 years ago

The issue was that the standard said to finalize the allocatable components twice. So we had to remove it from one place ---- unfortunately we removed it from the wrong place. So this edit 20-117 breaks the standard in our opinion. We need to reverse it.

FortranFan commented 4 years ago

If I understood the discussion at the meeting correctly, the Fortran standard will try its damndest to leave the order of finalization of components in a finalizable type up to the compiler - "processor-dependent" per standardese. That is, the finalization of an object in a standard-conforming program can occur in different order as long the possibilities cover the sequence as indicated in section 7.5.6.2 which includes

reubendb commented 4 years ago

My reading of the standard as it is, is that only both of the following output are allowed: "CBAP" and "CABP". The standard is currently under-specified such that "CBAPA" is also a legal, that is, A is doubly-finalized. I don't think "CBPA" is a valid output with the current standard (and could be a compiler bug).

Out of the four compilers I tried, three produces "CABP" (correctly), and one produces "CBPA", which in my opinion is a bug.

Paper 20-117 actually attempts to fix the double finalization issue mentioned above. Unfortunately, I think the (unintended?) consequence is that all three output---"CBAP", "CABP", and "CBPA"--- would be legal and is processor dependent.

I think "CBPA" is, at least, very counter-intuitive to users and should not be allowed, although at the moment I can't come up with a good technical reason for why it should not be allowed. But it does seem that it would defy user's expectation. There were some further discussions on coming up with a better fix that would address all of these issues at once.

klausler commented 4 years ago

Here's another test for your enjoyment. Of the compilers that I have on site, only ifort and xlf seem to finalize in a non-surprising order (1-10, or 6-10/1-5). I will ensure that f18 is also non-surprising.

module m
  type :: t1
    integer :: n1
   contains
    final :: finalt1Elem, finalt1Vec
  end type
  type :: t2
    integer :: n2
    type(t1), allocatable :: a2(:)
   contains
    final :: finalt2Elem, finalt2Vec
  end type
  type, extends(t2) :: t3
    integer :: n3
    type(t2), allocatable :: a3(:)
   contains
    final :: finalt3Elem, finalt3Vec
  end type
 contains
  impure elemental subroutine finalt1Elem(x)
    type(t1), intent(inout) :: x
    print *, "finalt1Elem", x%n1
  end subroutine
  subroutine finalt1Vec(x)
    type(t1), intent(inout) :: x(:)
    print *, "finalt1Vec", x(:)%n1
  end subroutine
  impure elemental subroutine finalt2Elem(x)
    type(t2), intent(inout) :: x
    print *, "finalt2Elem", x%n2
  end subroutine
  subroutine finalt2Vec(x)
    type(t2), intent(inout) :: x(:)
    print *, "finalt2Vec", x(:)%n2
  end subroutine
  impure elemental subroutine finalt3Elem(x)
    type(t3), intent(inout) :: x
    print *, "finalt3Elem", x%n3
  end subroutine
  subroutine finalt3Vec(x)
    type(t3), intent(inout) :: x(:)
    print *, "finalt3Vec", x(:)%n3
  end subroutine
end module

subroutine test
  use m
  type(t3) :: x0, x1(1)
  integer :: n
  n = 1
  call populatet3(x0)
  call populatet3(x1(1))
  print *, 'expect ', n-1, ' finalizations'
 contains
  integer function next()
    next = n
    n = n + 1
  end function
  subroutine populatet1(x)
    type(t1), intent(inout) :: x
    x%n1 = next()
  end subroutine
  subroutine populatet2(x)
    class(t2), intent(inout) :: x
    x%n2 = next()
    allocate(x%a2(1))
    call populatet1(x%a2(1))
  end subroutine
  subroutine populatet3(x)
    type(t3), intent(inout) :: x
    x%n3 = next()
    allocate(x%a3(1))
    call populatet2(x%a3(1))
    call populatet2(x)
  end subroutine
end subroutine

program main
  call test
end program
klausler commented 4 years ago

Does anybody understand the change that's out for letter ballot at the moment for this problem?

I think it precludes multiple finalization of A, which is good, but would allow a compiler to implement any of CABP, CBAP, and CBPA call orders (in terms of the original example), if I understand it accurately.

A program could force CABP by explicitly deallocating the allocatable component in the final procedure for the containing object, yes?

certik commented 4 years ago

@klausler that is my understanding, but I am going to ask at the J3 mailinglist to clarify this. Update: submitted here: https://mailman.j3-fortran.org/pipermail/j3/2020-June/012101.html

reubendb commented 4 years ago

@klausler Those are my understanding as well (see my comments above). Some of us worked this out in our subgroup and I believe came out with the same conclusion.

klausler commented 4 years ago

Ok, thanks. I want f18 to do CBAP to be least surprising to those familiar with C++ destructors; does that sound okay?

certik commented 4 years ago

@klausler that sounds like what all compilers should do, as that is what users expect.

certik commented 4 years ago

Malcolm just posted a partial and a full analysis of @nncarlson's code above. The answer is as @klausler wrote, i.e., if the interp is accepted, all three of the answers are valid: CABP or CBAP or CBPA. And yes, one can force CABP by explicitly deallocating the allocatable component in the final procedure for the containing object.

nncarlson commented 4 years ago

As someone who uses Fortran, I find the behaviour CBPA to be bizarre and unacceptable. Has anyone stepped forward (Malcolm?) to defend that behavior as sensible? Sure I can live with it by writing a final procedure that I otherwise would not have had to do, but if this goes through it's going to be another black mark on the language compared to other alternative languages.

certik commented 4 years ago

I think there is a wide agreement that CBPA is not wanted, and so I am going to vote NO for LANL on this interp.

On Sat, Jun 6, 2020, at 5:16 PM, Neil Carlson wrote:

As someone who uses Fortran, I find the behaviour CBPA to be bizarre and unacceptable. Has anyone stepped forward (Malcolm?) to defend that behavior as sensible? Sure I can live with it by writing a final procedure that I otherwise would not have had to do, but if this goes through it's going to be another black mark on the language compared to other alternative languages.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/146#issuecomment-640130653, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWCPTFBQAXQ6FE4QTZLRVLE5NANCNFSM4KZKUGPQ.

FortranFan commented 4 years ago

@nncarlson wrote June 6, 2020 7:16 PM PDT:

As someone who uses Fortran, I find the behaviour CBPA to be bizarre and unacceptable. Has anyone stepped forward (Malcolm?) to defend that behavior as sensible? Sure I can live with it by writing a final procedure that I otherwise would not have had to do, but if this goes through it's going to be another black mark on the language compared to other alternative languages.

The "full' analysis mentioned by @certik above attempts to explain how the standard permits 'CBPA'. The rationale appears to again come back to the major role played by backwards compatibility (#79) in Fortran, this time with the semantics of auto-deallocation of ALLOCATABLEs whose introduction preceded by well over a decade that of the finalization facility. To allow 'CBPA' appears to have consequences with ALLOCATABLEs.

ALLOCATABLEs is among the most valuable features in the language and Fortran is rather unique in providing such support intrinsically.. This allows programmers to get closer to formula translation rather than deal with memory management, GC (garbage collection), etc. in the codes toward scientific and technical computing.

Given the use case provided by OP in https://github.com/j3-fortran/fortran_proposals/issues/146#issuecomment-589857885 with AMReX, implementing a finalizer for the case at hand appears a safe approach regardless of the language standard. And which then would avoid the concerns with this particular situation.

FortranFan commented 4 years ago

@certik wrote June 6, 2020 8:05 PM PDT:

I think there is a wide agreement that CBPA is not wanted, and so I am going to vote NO for LANL on this interp.

@certik , as I mentioned in https://github.com/j3-fortran/fortran_proposals/issues/146#issuecomment-640217739, please review the full analysis on the J3 mailing list with your colleagues at LANL wrt the history and semantics of ALLOCATABLEs in Fortran. Perhaps that might change your vote?

nncarlson commented 4 years ago

@FortranFan, yes I have studied Malcolm's analysis. He does a nice job of explaining how allocatables and finalization evolved separately and how we arrived at the state things are today. It also explains how some compilers have arrived at implementing Strategy One, including presumably NAG's, and that the goal of his proposed interp is to preserve such implementations. However as a user looking from the outside, that internal implementation detail carries little weight with me. To me the fundamental question is does it make sense for A to be finalized after P, and in particular does it make sense for A to be finalized after P when its sibling component B is finalized before merely because one is allocatable and one is not. I find that behavior to be very surprising and at odds with C++, for example, and I would imagine other OO languages.

You specifically called out allocatable. I wholeheartedly agree about their value, but I don't see that an alternative interp that would reject the CBPA order (implemented using Malcolm's Strategy Two perhaps) would need to do anything whatsoever to damage them or change their semantics. Am I mistaken there? Nor would it break code that used to be unambiguously valid; this is not a backwards compatibility question that I can see.

Perhaps I overlooked something in Malcolm's analysis that you think should sway my opinion; if so, please point it out to me.

certik commented 4 years ago

@FortranFan from a user perspective it does not seem to break backwards compatibility to exclude CBPA, because users couldn't have relied on that anyway, given that CABP has always been allowed.

The main argument here is that Fortran does something unexpected, forcing users to force de-allocation order, that in other languages such as C++ works out of the box. We don't want users to move to C++, we want to keep them in Fortran. Allowing CBPA would hurt the cause here. I am sure @nncarlson is not the only one that got surprised by it.

pbrady commented 4 years ago

Anything that makes c++ more intuitive than Fortran is very, very bad

klausler commented 4 years ago

Is there any existing Fortran compiler or runtime that implements the CBPA order? Is there any current application that relies on the CBPA order? I'm struggling to understand why the language standard would need to preserve that option.

zjibben commented 4 years ago

NAG implements CBPA.

klausler commented 4 years ago

NAG implements CBPA.

Well, a lot of pieces just fell into place with my understanding of this problem.

certik commented 4 years ago

I just asked at the J3 mailinglist if there are other arguments to allow the CBPA order. (The last line in my email starting with >From the user perspective has a quote > at front that was added by Mailman, the online email archive. It is not there in my original email...)

nSircombe commented 4 years ago

Ok, thanks. I want f18 to do CBAP to be least surprising to those familiar with C++ destructors; does that sound okay?

@klausler - just to check (since much of the discussion in the tread appears to favour CABP) did you mean CBAP, or CABP?

certik commented 4 years ago

did you mean CBAP, or CABP?

Hi @nSircombe nice to see you here. My understanding is that both CBAP and CABP are acceptable from the user perspective, I don't think there is any ordering between A and B based on the semantics. The key is that P is at the end. Maybe @klausler can correct me.

klausler commented 4 years ago

C++ destructors are invoked in the opposite order of constructors. If the component order is AB, then it makes sense to me to deallocate &/or finalize B before A for least surprise.

nncarlson commented 4 years ago

In 7.5.6.1 p2 it says: "A derived type is finalizable if and only if it has a final subroutine or a nonpointer, nonallocatable component of finalizable type."

Does any one understand why allocatable components were excluded in the definition of "finalizable"?

sblionel commented 4 years ago

Malcolm replied today on the J3 list:

Hi folks,

Some probably-final comments from me on this topic

There is no doubt in my mind that finalization was not intended to, and does not cause deallocation (evidence: the standard does not say that it does).

There is equally no doubt in my mind that deallocation of allocatable and pointer entities was intended to, and does cause finalization (evidence: the standard says that).

There is similarly no doubt in my mind that allocatable components were not intended to be finalized as part of the containing object finalization, but as part of the automatic deallocation process (evidence: the definition of finalizable in the standard ignores allocatable components).

Thus I think the interp should remain as it is now.

Interestingly, of the four compilers that I have access to and which support FINAL, two out of the four produce CBPA for Ondrej’s example, and two produce CABP. Changing the A component to “CLASS(*)” and the allocation to allocate it as type OBJECTA, the two CBPA-producing compilers remain producing CBPA (as one might expect if they’re following the deallocation-causes-finalization model), but one of the other two now produces CBP which is clearly erroneous.

I am not necessarily opposed in principle to the idea of changing finalization to cause deallocation of allocatable components, though it seems to me that the user already has the tools available to force an ordering when he wants to, so I am yet to be convinced of its usefulness. I do however, think this would be a significant change to the design (virtually a new feature), and so should be considered (should we decide that it is in fact desirable) in a future revision.

sblionel commented 4 years ago

FWIW, it's ifort that gives CBP in the revision Malcolm mentions. I will let them know.