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

Should C611 apply to a parent component?

Mark_Lewy
Valued Contributor I
446 Views

Consider the following program:

    module base_mod
        implicit none
        private

        type base_state_t
            integer :: i
        end type

        ! Comment out to define base_t as concrete
        type, abstract, public :: base_t
            integer :: i
            type(base_state_t) :: saved_base_state
        contains
            procedure(self), deferred, pass :: allocate
            procedure :: save_state
        end type base_t

        ! Uncomment to define base_t as concrete
        !type, public :: base_t
        !    integer :: i
        !    type(base_state_t) :: saved_base_state
        !contains
        !    procedure :: allocate
        !    procedure :: save_state
        !end type base_t

        abstract interface
            subroutine self(this)
                import
                class(base_t), intent(inout) :: this
            end subroutine
        end interface
    contains

        ! Uncomment to define base_t as concrete
        !subroutine allocate(this)
        !    class(base_t), intent(inout) :: this
        !
        !    ! Nothing to see here
        !end subroutine allocate

        subroutine save_state(this)
            class(base_t), intent(inout) :: this
            associate(st => this%saved_base_state)
                st%i = this%i
            end associate
        end subroutine save_state
    end module base_mod

    module ext_mod
        use base_mod

        implicit none
        private

        type ext_state_t
            integer, allocatable :: array(:)
        end type ext_state_t

        type, extends(base_t), public :: ext_t
            integer, allocatable :: array(:)
            integer :: array_size
            type(ext_state_t) :: saved_ext_state
        contains
            procedure, public :: allocate
            procedure, public :: save_state
        end type ext_t
    contains
        subroutine allocate(this)
            class(ext_t), intent(inout) :: this

            allocate(this%array(this%array_size))
        end subroutine allocate

        subroutine save_state(this)
            class(ext_t), intent(inout) :: this

            ! Trips #8314 and #8422 if base_t is abstract
            call this%base_t%save_state

            associate(st => this%saved_ext_state)
                allocate (st%array(size(this%array)))
                st%array = this%array
            end associate
        end subroutine save_state
    end module ext_mod

    program Console16
        use ext_mod

        implicit none

        type(ext_t) :: ext

        ext%i = 42
        ext%array_size = 2
        call ext%allocate
        ext%array = 0
        call ext%save_state
    end program Console16

If I compile this with XE 2015 Update 1 (15.0.1.148) or XE 2017 (17.0.0.109) then I get these errors:

1>D:\Source\VS Projects\Console16\Console16\Console16.f90(79): error #8314: If the rightmost part-name is of abstract type, data-ref shall be polymorphic.   [BASE_T]
1>D:\Source\VS Projects\Console16\Console16\Console16.f90(79): error #8422: If the component immediately preceding the type-bound procedure is abstract, the entire data reference before the procedure name must be polymorphic.   [BASE_T]

Now, error #8314 has the same wording as C611 in 6.4.2 of the Fortran 2015 draft, but should this constraint apply when the component is the parent component of the extended type? If so, how do you call a method in an abstract base class from a class extended from it?  The obvious workaround is to make the base class concrete (commented code), but seems a bit messy to me.

 

 

0 Kudos
1 Solution
IanH
Honored Contributor II
446 Views

The syntax rules of the language are deliberately written to prevent a non-polymorphic designator to an abstract object or to have an polymorphic object that has a dynamic type that is abstract.  Such an object is potentially (and usually) incomplete - as it may have deferred bindings.

The syntax that raises the error in the original post - `call this%base_t  %save_state`, has such a designator - the bit before the binding name.  In this case that designator is being used to nominate a non-deferred binding in that object, but that's a specific case that makes sense at that instant, the reference at that point, or inside the procedure invoked by the save_state binding (the dynamic type of this%base_t would be base_t!), could equally have been to `%allocate`, which has not been defined for that type.

In some respects, the syntax `object%binding` is all about dynamic dispatch - look at the dynamic type of `object`, based on that pick the relevant procedure that is nominated by `binding`.  When code attempts to invoke a binding of the parent object, it is not doing dynamic dispatch - it is just invoking a particular procedure that is known at compile time. 

There are a few ways of invoking a particular procedure that is known at compile time, but the most natural one is perhaps to make a name for the procedure accessible in the scope that needs to invoke it, and then just reference the procedure as you would have prior to Fortran 2003.

module base_mod
    ...
    type, abstract, public :: base_t
        integer :: i
        type(base_state_t) :: saved_base_state
    contains
        procedure(self), deferred, pass :: allocate
        procedure :: save_state
    end type base_t

    ! The design of this code requires clients to be able to 
    ! directly reference this procedure, so the procedure needs 
    ! to be accessible.
    public :: save_state     ! you might want to rename this.
    ...
end module base_mod


module ext_mod
    use base_mod, base_save_state => save_state
    ...
contains
    ...
    subroutine save_state(this)
        class(ext_t), intent(inout) :: this
        
        ! Directly reference the procedure made accessible 
        ! above.
        call base_save_state(this)
        ....
    end subroutine save_state
end module ext_mod

A typical pattern (and this applies to C++ as well) is for the interface of an object exposed to clients to be through non-virtual functions (C++ terms)/not-type-bound procedures (Fortran terms), with the non-virtual functions/non-type-bound procedures then invoking the specific behaviours relevant to the subject object though virtual members/type bound procedures.  The code arrangement immediately above is just a simpler version of that.

View solution in original post

0 Kudos
7 Replies
FortranFan
Honored Contributor II
446 Views

At the offending line #79, any particular reason why you do not want to do something like this?

[fortran]        call this%save_state()[/fortran]

Look in the Fortran standard document on derived type extension and accessibility of type components and bound procedures from a base type in the extended type.

0 Kudos
Mark_Lewy
Valued Contributor I
446 Views

FortranFan wrote:

At the offending line #79, any particular reason why you do not want to do something like this?

 

        call this%save_state()

 

Look in the Fortran standard document on derived type extension and accessibility of type components and bound procedures from a base type in the extended type.

The problem with that is that it will call ext_t%save_state, i.e. itself!  The intention of the code that inspired the example is to save the state of the extended type which also includes the state of the parent type, so I want to call the parent's save_state procedure from the extended type's save_state procedure.

0 Kudos
FortranFan
Honored Contributor II
445 Views

Mark Lewy wrote:

Quote:

FortranFan wrote:

 

At the offending line #79, any particular reason why you do not want to do something like this?

 

        call this%save_state()

 

Look in the Fortran standard document on derived type extension and accessibility of type components and bound procedures from a base type in the extended type.

 

 

The problem with that is that it will call ext_t%save_state, i.e. itself!  The intention of the code that inspired the example is to save the state of the extended type which also includes the state of the parent type, so I want to call the parent's save_state procedure from the extended type's save_state procedure.

@Mark Lewy,

My 2 cents worth: based on your comments, you should take a step back and ask yourself how keen are you into object-oriented (OO) paradigm and associated programming practices and facilities and how deep you want to go into the computer science principles surrounding it all and whether you can develop a set of concepts you can propose for extension in the Fortran standard; or whether you just want to quickly UTILIZE what's feasible today and move on.  If you're inclined toward the former, that's all beyond me at this stage but true experts who follow this forum will be able to guide you further,

If you're more about the latter and then just want to get something going, you can consider a practical workaround (klugey even) as shown below involving generic interfaces and a key for disambiguation for the procedure binding for the base type:

module base_mod
   implicit none
   private

   type base_state_t
      integer :: i
   end type

   ! Comment out to define base_t as concrete
   type, abstract, public :: base_t
      integer :: i
      type(base_state_t) :: saved_base_state
   contains
      procedure(self), deferred, pass :: allocate
      procedure, pass(this):: base_save_state
      procedure(Isave_state), pass(this), deferred :: ext_save_state
      generic, public :: save_state => base_save_state, ext_save_state
   end type base_t

! Uncomment to define base_t as concrete
!type, public :: base_t
!    integer :: i
!    type(base_state_t) :: saved_base_state
!contains
!    procedure :: allocate
!    procedure :: save_state
!end type base_t

abstract interface

   subroutine self(this)
      import
      class(base_t), intent(inout) :: this
   end subroutine

   subroutine Isave_state(this)
      import :: base_t
      class(base_t), intent(inout) :: this
   end subroutine Isave_state

end interface

contains

   ! Uncomment to define base_t as concrete
   !subroutine allocate(this)
   !    class(base_t), intent(inout) :: this
   !
   !    ! Nothing to see here
   !end subroutine allocate

   subroutine base_save_state(this, is_base_state)

      class(base_t), intent(inout) :: this
      logical :: is_base_state

      if (is_base_state) then
         associate(st => this%saved_base_state)
            st%i = this%i
         end associate
      end if

   end subroutine base_save_state

end module base_mod

module ext_mod
   use base_mod

   implicit none
   private

   type ext_state_t
      integer, allocatable :: array(:)
   end type ext_state_t

   type, extends(base_t), public :: ext_t
      integer, allocatable :: array(:)
      integer :: array_size
      type(ext_state_t) :: saved_ext_state
   contains
      procedure, public :: allocate
      procedure, public :: ext_save_state
   end type ext_t

contains

   subroutine allocate(this)
      class(ext_t), intent(inout) :: this

      allocate(this%array(this%array_size))
   end subroutine allocate

   subroutine ext_save_state(this)

      class(ext_t), intent(inout) :: this

      ! notice the silly extra argument to disambiguate the base procedure
      call this%save_state( is_base_state=.true. )

      associate(st => this%saved_ext_state)
         allocate (st%array(size(this%array)))
         st%array = this%array
      end associate

   end subroutine ext_save_state

end module ext_mod

 

0 Kudos
Mark_Lewy
Valued Contributor I
445 Views

Yes, I appreciate that this can be worked around, but my question relates to an idiom that is common in other object-orientated languages: you extend the functionality of a method in the base class by calling the method in the base class and then any specialisations for the derived class in the method with the same name in the derived class.

For example, in C++, you can call a method in a base class by qualifying the method with the the name of the base class and, as far as I know,  this will work regardless or whether the base class is abstract or not.  So, in a C++ version of the code, the ext_t::save_state() method would contain the statement base_t::save_state() and this would work regardless or not base_t is abstract or not.

In Fortran, the fact that you refer to the parent by using a component and thus it is subject to the same restrictions as components is the issue here.

In my (real world) problem I have an existing class hierarchy that has an abstract type as the base.  A new feature requires me to save and restore the state of instances of types derived from this class (aka serialisation).  It would appear that the Fortran standard is preventing me from doing this conveniently (or it could be Intel's interpretation of the standard?).

0 Kudos
FortranFan
Honored Contributor II
445 Views

Mark Lewy wrote:

.. my question relates to an idiom that is common in other object-orientated languages: ..

For example, in C++, you can call a method in a base class by qualifying the method with the the name of the base class and, as far as I know,  this will work regardless or whether the base class is abstract or not.  ..  it could be Intel's interpretation of the standard?

I too don't think it has anything to do with Intel's implementation; it's the standard itself that comes into play.

What I have learnt is Fortran has its own take on things, similar to how other languages view, say, multiple inheritance and how they include or exclude it depending on their own perspective.  Many OO experts decry multiple inheritance even though C++ provides it; other, newer OO languages seem to vehemently avoid the feature.

The point being that just because something can be done in C++ rarely seems to hold water, especially with the Fortran standard committee.  If you can encapsulate what you are seeking with well thought out concepts, devoid of C++, and provide use cases and associated benefits and all that, perhaps things may change in a future revision.  And you're looking at a time horizon of 5 to 10 years following the standard revision before any implementation becomes available.  Humankind may have no need to code by then!

Your best options may be to work with a 'dummy' concrete extension of the abstract base, or a workaround along the lines I showed.

Cheers,

0 Kudos
Mark_Lewy
Valued Contributor I
445 Views

@FortranFan,

I suspect you are right on both points: 1) This is a deliberate (lack of?) design decision in the standard, and 2) The best way to address this is to workaround it!  I can see several easy ways to do this.

 

0 Kudos
IanH
Honored Contributor II
447 Views

The syntax rules of the language are deliberately written to prevent a non-polymorphic designator to an abstract object or to have an polymorphic object that has a dynamic type that is abstract.  Such an object is potentially (and usually) incomplete - as it may have deferred bindings.

The syntax that raises the error in the original post - `call this%base_t  %save_state`, has such a designator - the bit before the binding name.  In this case that designator is being used to nominate a non-deferred binding in that object, but that's a specific case that makes sense at that instant, the reference at that point, or inside the procedure invoked by the save_state binding (the dynamic type of this%base_t would be base_t!), could equally have been to `%allocate`, which has not been defined for that type.

In some respects, the syntax `object%binding` is all about dynamic dispatch - look at the dynamic type of `object`, based on that pick the relevant procedure that is nominated by `binding`.  When code attempts to invoke a binding of the parent object, it is not doing dynamic dispatch - it is just invoking a particular procedure that is known at compile time. 

There are a few ways of invoking a particular procedure that is known at compile time, but the most natural one is perhaps to make a name for the procedure accessible in the scope that needs to invoke it, and then just reference the procedure as you would have prior to Fortran 2003.

module base_mod
    ...
    type, abstract, public :: base_t
        integer :: i
        type(base_state_t) :: saved_base_state
    contains
        procedure(self), deferred, pass :: allocate
        procedure :: save_state
    end type base_t

    ! The design of this code requires clients to be able to 
    ! directly reference this procedure, so the procedure needs 
    ! to be accessible.
    public :: save_state     ! you might want to rename this.
    ...
end module base_mod


module ext_mod
    use base_mod, base_save_state => save_state
    ...
contains
    ...
    subroutine save_state(this)
        class(ext_t), intent(inout) :: this
        
        ! Directly reference the procedure made accessible 
        ! above.
        call base_save_state(this)
        ....
    end subroutine save_state
end module ext_mod

A typical pattern (and this applies to C++ as well) is for the interface of an object exposed to clients to be through non-virtual functions (C++ terms)/not-type-bound procedures (Fortran terms), with the non-virtual functions/non-type-bound procedures then invoking the specific behaviours relevant to the subject object though virtual members/type bound procedures.  The code arrangement immediately above is just a simpler version of that.

0 Kudos
Reply