So far the Japanese proposal only applies to procedures.
That said, I am interested in figuring out how to solve the “variant” use case. I think you’ll always need the “container” type, although it could possibly be made more convenient/ergonomic/transparent. What I think you’ll want to have without using inheritance though is a pattern matching mechanism on the other side. My initial thought is something in the direction of:
type, variant :: shape = circle, square
type(shape), allocatable :: my_shapes(:)
my_shapes = [shape :: circle(), square(2.0), circle(3.0)]
do i = 1, size(my_shapes)
match type (s => my_shapes(i))
type is (circle)
print *, "Circle with radius = ", s%radius
type is (square)
print *, "Square with width = ", s%width
end match ! Invalid for this to not be exhaustive
end do
Actually, we could have an intrinsic template to supply the first part. I.e.
instantiate variant(type(circle), type(square)), only: shape => variant_type
With an implementation (kind of) like
template variant(T1, T2)
type, deferred :: T1, T2
enumeration type :: variant_types
enumerator :: alt_1, alt_2
end enumeration type
type :: variant
type(variant_types) :: which_type
type(T1) :: alt1
type(T2) :: alt2
end type
interface variant
procedure construct_from_t1
procedure construct_from_t2
end interface
contains
function construct_from_t1(alt1) result(variant_)
type(T1), intent(in) :: alt1
type(variant) :: variant_
variant_%which_type = alt_1
variant_%alt1 = alt1
end function
function construct_from_t2(alt2) result(variant_)
type(T2), intent(in) :: alt2
type(variant) :: variant_
variant_%which_type = alt_2
variant_%alt2 = alt2
end function
end template
Then the match type
construct gets transformed like:
select case (my_shapes(i)%which_type)
case (alt_1)
associate(s => my_shapes(i)%alt1)
print *, "Circle with radius = " s%radius
end associate
case (alt_2)
associate(s => my_shapes(i)%alt2)
print *, "Square with width = ", s%width
end associate
end select
Of course if it’s intrinsic, the variant type can be packed much more efficiently, the variant template can be variadic (take however many type arguments as you want), and the transformation of the match type construct can be handled by the compiler based on the type of the selector.