In the example below the following types are defined:
type, abstract :: base_t
type, extends(base_t) :: my_t
where my_t
has a defined assignment subroutine. When I use a variable of type my_t
, both ifort and gfortran invokes the defined assignment as I expect:
type(my_t), allocatable :: x
x = my_t()
However, neither do so when using a polymorphic variable of class base_t
:
class(base_t), allocatable :: x
x = my_t()
Section 7.2.1.4 Defined assignment statement paragraph 2 of the Fortran standard has the following to say about defined assignments:
A subroutine defines the defined assignment x1 = x2 if
(1) the subroutine is specified with a SUBROUTINE (12.6.2.3) or ENTRY (12.6.2.6) statement that specifies two dummy arguments, d1 and d2,
(ā¦)
the types of d1 and d2 are compatible with the dynamic types of x1 and x2, respectively,
The way I interpret this, the defined assignment should be invoked in both cases. Am I overseeing something or is this a compiler bug in both compilers?
Complete example:
module my_mod
implicit none
type, abstract :: base_t
end type
type, extends(base_t) :: my_t
contains
procedure, private :: assign
generic :: assignment(=) => assign
final :: finalize
end type
interface my_t
module procedure :: init
end interface
contains
type(my_t) function init() result(this)
write(*,*) 'init ', loc(this)
end function
subroutine assign(lhs, rhs)
class(my_t), intent(out) :: lhs
type(my_t), intent(in) :: rhs
write(*,*) 'assign', loc(lhs), ' -> ', loc(rhs)
end subroutine
subroutine finalize(this)
type(my_t), intent(inout) :: this
write(*,*) 'finalize ', loc(this)
end subroutine
end module
program main
use my_mod, only: base_t, my_t
implicit none
write(*,*) 'Concrete type example'
block
type(my_t), allocatable :: x
x = my_t()
end block
write(*,*) 'Concrete type example done'
write(*,*)
write(*,*) 'Abstract base class example'
block
class(base_t), allocatable :: x
x = my_t()
end block
write(*,*) 'Abstract base class example done'
end program
gfortran output:
Concrete type example
init 140722846631504
finalize 0
assign 0 -> 140722846632048
Concrete type example done
Abstract base class example
init 140722846631504
finalize 94805880428816
Abstract base class example done
ifort output:
Concrete type example
init 140734944992808
assign 0 -> 140734944992808
finalize 140734944992808
Concrete type example done
Abstract base class example
init 140734944992800
finalize 140734944992800
finalize 13571168
Abstract base class example done