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!