Ambiguity paradox for type vs. class

Dear all,

while trying to add some convenience “destructors” to ErrorFx I hit an interesting paradox. Maybe some of you have some insight, why this appeas.

I’d like to add a generic destroy() subroutine, which can destroy both, type and class instances of a given type. However, according to the compilers I’ve tried, the interface becomes ambiguous, if the signature of two routines only differs in a type to class change (see example below). However, if I only add one of the two routines to the interface, the destruction onlys works for one of the cases (either for type or for class). But does that not mean, that the signatures of the two routines are not ambiguous?

module test
  implicit none

  private
  public :: base, destroy

  type :: base
  end type base

 ! You must comment out one of the two associations to compile it
  interface destroy
    module procedure destroy_type
    module procedure destroy_class
  end interface destroy

contains

  subroutine destroy_type(this)
    type(base), allocatable, intent(inout) :: this
    if (allocated(this)) then
      deallocate(this)
    end if

  end subroutine destroy_type


  subroutine destroy_class(this)
    class(base), allocatable, intent(inout) :: this
    if (allocated(this)) then
      deallocate(this)
    end if
  end subroutine destroy_class

end module test


program test_program
  use test
  implicit none

  type(base), allocatable :: inst_type
  class(base), allocatable :: inst_class

  allocate(inst_type)
  inst_class = inst_type
  ! Whichever subroutine was associated with the `destroy` interface,
  ! compilation fails here
  call destroy(inst_type)
  call destroy(inst_class)

end program test_program

Do I overlook something trivial, or is this “paradox” the expected behavior? And is it possible to create a destroy() interface which works for both cases?

Bálint

3 Likes

Indeed an interesting case. I currently don’t see a scenario where one could pass an allocatable type instance to an allocatable class dummy argument since the type of the object is allowed to change. The other way round, passing an allocatable class instance to an allocatable type arguments is disallowed, of course.

@aradi, please note the particulars with you show have nothing really to do with “destruction”, etc. and having a subroutine named “destroy” is besides the point: what you have is a particular situation involving disambiguation of subprograms involving dummy arguments with and without polymorphism.

The standard - as designed - to introduce polymorphism later on into the language, since it didn’t originate as object-oriented and where there are consider limits on the kind of OO use cases the language designers are willing to entertain, simply does not support what you are looking for here and that’s that.

Now, to the extent your need is finalization of objects, you can look at FINAL subroutines and see how far you can get with existing support toward finalization in the language. Here though, compiler support will vary as the language has gone through “bug fixes” in the standard itself and few are up-to-date.

In many or most situations involving Fortranners who are inclined toward scientific and technical computing, explicit finalization via FINAL subroutines is not necessary, particularly when the consumption of the “classes” involved is via ALLOCATABLE objects. This is a particular advantage with Fortran I would say.

Not sure of the requirements with ErrorFx and what OP has in mind, but should finalization be of interest, the authors in most circumstances can do the minimal with an ELEMENTAL FINAL subroutine and that should address almost all their needs:

module b_m
   type :: b_t
      character(len=10) :: name = ""
   contains
      final :: destroy_b
   end type
contains
   impure elemental subroutine destroy_b( this ) !<-- impure only because of print stmt
      type(b_t), intent(inout) :: this
      print *, "destroy_b invoked for ", this%name
   end subroutine 
end module 
module c_m
   use b_m, only : b_t
   type :: c_t
      type(b_t), allocatable :: b
   end type
end module
module d_m
   use b_m, only : b_t
   type :: d_t
      class(b_t), allocatable :: b
   end type
end module
   use b_m, only : b_t
   use c_m, only : c_t
   use d_m, only : d_t
   blk1: block
      type(c_t) :: c
      allocate ( c%b )
      c%b%name = "c%b"
   end block blk1
   blk2: block
      type(d_t) :: d
      allocate ( b_t :: d%b )
      d%b%name = "d%b"
   end block blk2
end

C:\Temp>gfortran f.f90 -o f.exe

C:\Temp>f.exe
destroy_b invoked for c%b
destroy_b invoked for d%b

@FortranFan Thanks for your detailed example. I agree with you, that whenever possible, actions which must be done before an object goes out of scope or is deallocated should be packed into a final subroutine.

Actually, I know about finalization via final and use it a lot (even in ErrorFx). However, the scenario, I want to solve, can not be realized with a finalizer. For various reasons (which you can look up here, in case you are interested), a type-bound procedure must be called from outside of the derived type immediately before its deallocation. I wanted to combine the two steps (calling the type bound procedure and deallocating the instance) into one step for convenience. And in a way, that it both works for class and type by using the same name.

(As for the name choice: I find it natural to call a routine, which task is to make some preparations and then actually to deallocate an object destroy(), but I guess, it is really a matter of taste. But I agree with you, that the particular “paradox” has nothing to do with the destruction itself. I just wanted to post a MWE, and this was the context where I have encountered the problem.)

Unfortunately, you did not answer my question about the reason for the paradox. I, and probably also some other “Fortranners who are inclined toward scientific and technical computing” would be still interested to find out, what is the actual motivation for considering the following signatures ambiguous:

subroutine routine_type(inst)
  type(whatever), allocatable, intent(inout) :: inst
end subroutine routine_type

subroutine routine_class(inst)
  class(whatever), allocatable, intent(inout) :: inst
end subroutine routine_class

The first one can only be called with a type(whatever) allocatable instance as argument, while the second one only with a class(whatever) allocatable instance. None of them can be called with both types of arguments. So, I would conclude, that they are actually not ambiguous at all!

Any insights are very welcome, but please let’s not divert the thread with best practice advice on finalization.

2 Likes

I tried to answer in the 2nd para while being deliberately vague, this was to not ruffle some delicate feathers that lurk!

My own view of the language development starting Fortran 2003 is there is no good reason for this, this is just an oversight like other such omissions with OO in Fortran. I would argue this is along the same lines as to how Fortran 2003 did not allow disambiguation between POINTER and ALLOCATABLE attributes based on a thinking a processor will have no easy means to differentiate between the two. That was an incorrect assumption and the situation was later addressed adequately in Fortran 2008.

My opinion is you should propose this at GitHub J3-Fortran proposals site. But I still feel the use case is not all that compelling to me, at least as stated in this thread thus far with destruction, etc. and that’s why I brought up finalization.

routine_class can be called with a type(whatever) argument. That’s why they are ambiguous.

@ashe No, actually as far as I understand, it can not, because the dummy argument is allocatable, intent(inout), and therefore, routine_class could put into this dummy argument an instance of any type which extends whatever:

subroutine routine_class(inst)
  class(whatever), allocatable, intent(inout) :: inst
  type(something_extending_whatever), allocatable :: ext
  allocate(ext)
  call move_alloc(ext, inst)
end subroutine routine_class

That would conflict with the actual argument being of type(whatever) (instead of class(whatever)).

No, that’s not correct as stated by @aradi :

  1. There are no restrictions with the polymorphic dummy argument to be (re)allocated to a different dynamic type, thus the actual argument effectively needs to be polymorphic also,
  2. Type compatibility requirements essentially come down to both the actual and dummy having the same declared type and therefore in the situation at hand, both the actual and dummy need to be class(whatever).

This and a few other aspects of the standard are why I think the pieces are all technically in place in the standard that can permit a processor to generally disambiguate between the two situations.

However this would be a matter of “relaxing” some of the “rules” in the standard and there are at least 2 sets of challenges here: 1) this pertains to OO, an aspect that is generally seen to have limited relevance with respect to performance aspects of the language and it’s performance considerations that ordinarily grab much of attention in the world of Fortran and 2) are there any edge cases being overlooked that can come back to bite later should such a change go into the standard? One can never ever be sure of this, so the inclination is avoidance, to be risk-averse and to maintain the status quo i.e., unless there is strong backing or need for this. I don’t foresee such a pull here and that’s why I wrote what I did above.

I’ve tried the following code for test, and it seems gfortran-10 compiles it with no error, although I initially imagined this may be illegal or invalid because an actual argument of class(base), allocatable is passed to a dummy argument of type(base), allocatable.

Then compilers possibly assume ambiguity because class(base), allocatable is allowed to be passed to destroy_type()…?

module test
    implicit none

    type :: base
        integer :: num = 0
    end type

    type, extends(base) :: deriv
    end type

contains

subroutine destroy_type(this)
    type(base), allocatable, intent(inout) :: this
    print *, "destroy_type() called with ", this% num

    if (allocated(this)) deallocate(this)
end

end module

program main
    use test
    implicit none
    type(base),  allocatable :: inst_type
    class(base), allocatable :: inst_class, inst_class2

    !------------------------------
    print *, "passing inst_{type,class} (of dynamic type 'base') to destroy_type()"

    allocate( inst_type )
    inst_type% num = 100

    allocate( base :: inst_class )
    inst_class% num = 200

    print *, allocated( inst_type ), allocated( inst_class )

    call destroy_type( inst_type )
    call destroy_type( inst_class )

    print *, allocated( inst_type ), allocated( inst_class )

    !------------------------------
    print *, "passing inst_class2 (of dynamic type 'deriv') to destroy_type()"

    allocate( deriv :: inst_class2 )
    inst_class2% num = 300

    call destroy_type( inst_class2 )

    print *, allocated( inst_class2 )
end

Result (gfortran-10.2)

 passing inst_{type,class} (of dynamic type 'base') to destroy_type()
 T T
 destroy_type() called with          100
 destroy_type() called with          200
 F F
 passing inst_class2 (of dynamic type 'deriv') to destroy_type()
 destroy_type() called with          300
 F

Thanks for testing it! As far as I understand, you have found a compiler bug. Passing a class instance to a type dummy argument would in this case mean, that you would finalize the passed argument as type(base) although it may contain any arbitrary derived type of it. Compiling it with ifort and nag actually gives an appropriate error mesage.

Sorry, I had it backwards. I believe that routine_type can be called with a class(whatever) actual argument. That’s what @septc’s example shows.

So they can’t be specific procedures of the same generic.

I am pretty convinced, that this is not standard conforming (see the reasoning above), and is only a compiler bug in gfortran.

@ashe @septc I think, the Intel compilers error message on the example above explains it “more professional” as I did above:

If a dummy argument is allocatable or a pointer, and the dummy or its associated actual argument is polymorphic, both dummy and actual must be polymorphic with the same declared type or both must be unlimited polymorphic.

If the allocatable attribute was not there, the situation would be different. Then one should be able to call routine_class(whatever) with type(whatever) and any type extending it. But still not the other way around!

1 Like

That looks right, thanks for the explanation.

The relevant part of the standard is para. 2 of 15.5.2.5 Allocatable and pointer dummy variables:

The actual argument shall be polymorphic if and only if the associated dummy argument is polymorphic, and either both the actual and dummy arguments shall be unlimited polymorphic, or the declared type of the actual argument shall be the same as the declared type of the dummy argument.

I see this is not a numbered constraint but instead a “shall” statement. So that seems to be a requirement on the programmer, not the compiler. But it certainly seems like something the compiler should enforce.

1 Like