Dear all,
I am trying to extend an abstract type with a (kind) parameterized derived type (PDT) in Fortran. My problem is that I can’t figure out how to override deferred, type bound procedures in this special setting. Below is a short, completely made up example that hopefully illustrates the issue:
module vector_m
implicit none
integer, parameter :: sp = selected_real_kind(6, 37)
integer, parameter :: dp = selected_real_kind(15, 307)
type, abstract :: vector_t
contains
procedure(first_component_as_strg_i), deferred :: first_component_as_strg
end type vector_t
abstract interface
function first_component_as_strg_i(this) result(c)
import :: vector_t
implicit none
class(vector_t) :: this
character(len=:), allocatable :: c
end function first_component_as_strg_i
end interface
type, extends(vector_t) :: real_vector_t(kr)
integer, kind :: kr
real(kr), allocatable :: comp(:)
contains
! QUESTION: How do I override first_component_as_strg?
!
! This works with ifx in this particular example (only the 1st procedure in
! the comma separated list seems to be considered)
procedure :: first_component_as_strg => &
first_component_as_strg_sp,first_component_as_strg_dp
! This doesn't work with ifx:
! procedure :: first_component_as_strg => &
! first_component_as_strg_dp,first_component_as_strg_sp
!
! My feeling is that I need some sort of generic construct here, but can't
! figure out the right syntax.
end type real_vector_t
contains
function first_component_as_strg_sp(this) result(c)
implicit none
class(real_vector_t(sp)) :: this
character(len=:), allocatable :: c
character(len=24) :: chelp
write(chelp,*) this % comp(1)
c = trim(chelp)
end function first_component_as_strg_sp
function first_component_as_strg_dp(this) result(c)
implicit none
class(real_vector_t(dp)) :: this
character(len=:), allocatable :: c
character(len=24) :: chelp
write(chelp,*) this % comp(1)
c = trim(chelp)
end function first_component_as_strg_dp
end module vector_m
program testprog
use vector_m
implicit none
type(real_vector_t(sp)) :: rvec
character(len=:), allocatable :: strg
rvec % comp = [1._sp,2._sp]
strg = rvec % first_component_as_strg ()
print*, strg
end program testprog
In this (rather silly) example, the goal is to have an abstract type “vector_t”, that might not only be extended by a non-parameterized type, but also by a PDT - in this example by the type “real_vector_t”. The abstract type “vector_t” defines a deferred function “first_component_as_strg” which returns the first component of a vector as a string, which should be possible for arbitrary vectors.
My Problem now is: How do I override the function “first_component_as_strg” in the definition of real_vector_t?
I know how to do this for the case where vector_t is parameterized (using a generic statement in its type definition), but in this special case, I just don’t get it. I don’t feel that this example is too exotic either - similar situations readily arise if one fully embraces the PDT concept in complex codes.
Finally, I know that PDTs are still not widely used because of generally poor compiler support, but the Intel compiler seems to be doing quite well by now.
Any help is highly appreciated!