Type polymorphism complications

I’ve always struggled to get my head around polymorphism in Fortran. It sounds great until I actually start writing code and then realise that most things I want to do with it aren’t actually possible.

Here’s a simple example of something I’m struggling with. I have a Series type, and a SeriesInt type that extends Series. SeriesInt contains an attribute called data (which is, unsurprisingly, an integer). I’ve written an interface to SeriesInt so that you can create a Series object like s = Series(data).

This all works well when creating the objects. I can use class(Series) = s and create the object using e.g. s = Series([1,2,3,4]). But then I can’t actually get the data attribute from the object unless I wrap it in a select type construct. What I am trying to achieve is letting the end user (i.e. the person writing the main program) not have to care about what exact type s is, but I think this is impossible.

My other option would be to include data as an unlimited polymorphic (class(*)) variable in the Series type, but then I can’t actually print data, which is what I am trying to achieve.

module series_mod
    implicit none

    type Series
    end type

    type, extends(Series) :: SeriesInt
        integer, allocatable :: data(:)
      contains
        procedure :: print
    end type

    interface Series
        module procedure init_int
    end interface

  contains

    function init_int(data) result(self)
        type(SeriesInt) :: self
        integer, intent(in) :: data(:)

        self%data = data
    end function

    subroutine print(self)
        class(SeriesInt) :: self
        print *, self%data
    end subroutine
end module

program test
    use series_mod, only: Series, SeriesInt
    implicit none

    class(SeriesInt), allocatable :: s1
    class(Series), allocatable :: s2

    s1 = Series([1,2,3,4])
    s2 = Series([1,2,3,4])
    print *, s1%data        ! Works as expected
    select type(s2)         ! Also works as expected, but is very clunky
    type is (SeriesInt)
        print *, s2%data
    end select
    print *, s2%data        ! Doesn't work: `data` is not a member of `series`
end program test

Any tips or explanations as to why what I want to do is impossible would be greatly welcome!

1 Like

@samharrison7 from the compiler perspective, in the main program s2 is seen as a Series (polymorphic) object, even though, under the hood, it is assigned to a type(SeriesInt). The compiler indeed notices this, and allows it since it is valid assignment, but, yet it cannot treat the object as such since it does not match its type declaration. Hence, if you try to access data from S2, though it exists in reality, it does not exists in the definition of the Series type. So, the error. On the other hand, you don’t see this if you explicit resolve the polymorphism, using the select type construct.

One way that I might suggest is to use type bound procedures, so that no matter the base type from which you call them, you might be able resolve to the right function call regardless (I guess the behaviour is similar to C++ vTable).

So, you’d have something like:

module series_mod
    implicit none

    type Series
    contains
       procedure :: printSeries
    end type

    type, extends(Series) :: SeriesInt
        integer, allocatable :: data(:)
      contains
        procedure :: printSeries => print_int
    end type

    interface Series
        module procedure init_int
    end interface

contains

    subroutine printSeries(self)
      class(Series), intent(in) :: self
      ! do whatever you want with default implementation
    end subroutine

    function init_int(data) result(self)
        type(SeriesInt) :: self
        integer, intent(in) :: data(:)

        self%data = data
    end function

    subroutine print_int(self)
        class(SeriesInt), intent(in) :: self
        print *, self%data
    end subroutine
end module

program test
    use series_mod, only: Series, SeriesInt
    implicit none

    class(SeriesInt), allocatable :: s1
    class(Series),    allocatable :: s2

    s1 = Series([1,2,3,4])
    s2 = Series([5,6,7,8])
    call s1%printSeries()
    call s2%printSeries()
end program test

Hi @samharrison7,
As you demonstrated, the fact that s2%data does not exist is expected, since Series does not contain the component data. The select type plays the role of a type casting here.

  • A work around (as suggested bu @mEm) would be to define Series as an abstract type and had a deferred procedure to return the array of data. The point is to have data defined for all derived types.
  • If you want to use a polymorphic array, you can also overload the assignment function (=) so that your data can be used as a vector of integers or else. You can also have a look at PDT if you want to consider integers of different kinds.
  • For the print you can have a look at UDDTIO , define your type-bound write function, and from your main program only call write(*,*) s2. The select type can be hidden in the module.

Take a look at the articles by Mark Leair on Fortran OOP, they are quite complete on this topic. And for disambiguation between class and type, you can read Doctor Fortran in "Not My TYPE" - Doctor Fortran .

I agree with you that types can be frustrating as compared to classes in other languages, but what you try to achieve should be doable.

Thanks both, that’s really useful info and links. I think I was just about getting there with deferred procedures, but hadn’t thought about overloading the assignment function in order to use a polymorphic array. It seems a bit hacky, but I think it would achieve what I want (which is, as you can guess, ultimately more complex than the simple example I gave above).

I only just learnt about UDDTIO and PDTs today - they look great!

It can be a tricky concept, regardless of programming language. An explanation which helped me understand it was this one from the book C++ Software Design, by Klaus Iglberger,

First and foremost, inheritance is always described as simplifying reusability. This seems intuitive, since it appears obvious that you can reuse code easily if you just inherit from another class. Unfortunately, that’s not the kind of reuse inheritance brings to you. Inheritance is not about reusing code in a base class; instead, it is about being reused by other code that uses the base class polymorphically.

It is the ability to express functionality by means of an abstraction that creates the opportunity to reuse code. This functionality is expected to create a vast amount of code, in comparison to the small amount of code the base class contains. Real reusability, therefore, is created by the polymorphic use of a type, not by polymorphic types.

As mEm has suggested, moving the print method to the base type will solve your problem. It will also create the opportunity to extend and customize your code using new types. An example might look like this:

type, abstract :: Series
contains
   ! Print information about the series to standard output
   procedure(print_service), deferred :: print
end type

The child types can now implement this method as they wish. Let’s assume now a large chunk of your code deals with these series:

subroutine manipulate(s)
   use Loggers, only: logger => DefaultLogger
   class(Series), intent(inout) :: s

   if (logging_is_on) call logger%log("s upon entry: ", s)
   
! ...

   if (logging_is_on) call logger%log("s upon exit: ", s)
end subroutine

subroutine show(a,b,c,d)
    class(Series), intent(in) :: a
    class(Series), intent(in), optional :: b, c, d
  
    print *, "-------- Series --------"

    call a%print()
    if (present(b)) call b%print()
    if (present(c)) call c%print()
    if (present(d)) call d%print()

    print *, "-----------------------"
end subroutine

program SeriesManipulator
   use SeriesModule
   implicit none

   character(128) :: series_request
   class(Series), allocatable :: a, b, c, d

   a = GeometricSeries()
   b = TaylorSeries()
   c = PowerSeries()

   read *, series_request
   d = SeriesFactory%serve(series_request)  ! potentially could fail

   call manipulate(b)
   if (allocated(d)) call manipulate(d)

   call show(a,b,c,d)

end program

If in the future you figure out you’d like to replace one of the series with a different one, the manipulate and show routines will remain equal. Only the part where you initialize the series may need to change.

Now object-oriented programming (polymorphism) tends to work well when you have a problem that can be solved by adding types. Adding a new type does not involve changing any existing code, making this an easy thing to do. On the other hand, if you find out in the future that it would be good if Series had another method, you will potentially need to modify all of them!

Here is a table taken from the same C++ book:

Programming Paradigm Strength Weakness
Procedural programming Addition of operations Addition of (polymorphic) types
Object-oriented programming Addition of (polymorphic) types Addition of operations

For this reason it’s good to spend some time thinking how to design your program. Is the set of operations fixed, and you want to add new types? In that case, polymorphism is the right tool. But if you have a fixed set of types add you’ll be adding operations, a procedural solution will be better.

2 Likes

Thanks, that is a really useful way of thinking about it. My case is the latter and I think I was slowly coming to realise that procedural would be better for this, so it’s nice to have that confirmed!