Hello everyone, I am writing codes of a data structure, and surprisingly they do not compile with gfortran. It seems that gfortran just crashes and does not print error information. But when using ifort, the codes can successfully compile and produce expected results. The codes below are simplified from original codes as a minimal case.
module polymorphic_array
implicit none
type :: base_wrapper
class(base), allocatable :: val
end type
type :: base
character(len=10) :: name
type(base_wrapper), allocatable :: list(:)
end type
type, extends(base) :: child
end type
end module polymorphic_array
program main
use polymorphic_array
implicit none
type(child) :: obj
obj%name = "child"
end program main
As far as I know, an allocatable component is allowed to be defined in such a recursive way. And since the codes can be compiled with ifort, I guess it is gfortran’s bug that causes this failure. I want to know if there is some workaround when using gfortran. Or if I should define the derived types in an alternative way?
Did you try this simple case? If I recall correctly, gfortran - for which a lot of such support started with the Fortran 2003 standard revision - does not fully support what is essentially a Fortran 2008 feature that is allocatable component of a recursive type (including polymorphic):
As a workaround for gfortran not supporting recursive types you can use an unlimited polymorfic insted, e.g. class(*), allocatable :: val in base_wrapper. When using the value you’ll need to use select type to match against base. Clumsy and inefficient, but at least it doesn’t crash the compiler…
With @FortranFan’s case, gfortran (11.2.0) gives an internal compiler error so this is most likely something that is supposed to be supported but just doesn’t work. If it was an unsupported feature the compiler would report that or give some other normal source error. Unless this has been fixed on the development trunk, it ought to be reported to the gfortran bugzilla.
Generally that is not advisable, the use of unlimited polymorphic types is best avoided, or at the very least kept at a minimum to those situations where the author knows exactly what she is doing and the Fortran processors are robust enough for the author’s intentions (which is not the case now).
Under the circumstances at present, it will be better to employ a “root” abstract “class” for the other “classes” one is working with including the recursive derived types of interest here. I expect gfortran to be able to support the following:
module m
type, abstract :: root_t
end type
type :: base_wrapper !<-- or even type, extends(root_t) :: base_wrapper
class(root_t), allocatable :: val
end type
type, extends(root_t) :: base
character(len=10) :: name
type(base_wrapper), allocatable :: list(:)
end type
type, extends(base) :: child
end type
end module
use m
type(child) :: obj
obj%name = "child"
end
Yes, this piece of code does not compile in gfortran.
And this works in gfortran.
I have just read the code of an XML library (xml-fortran/tree_struct.f90 in paulromano/xml-fortran). It uses pointer instead of allocatable attribute. So I tried a pointer implementation for the code I posted, and it compiles in gfortran. I think it might be a feasible way too, although I am less willing to use pointer in general.