Japanese Subgroup GENERIC proposal

Could the Japanese generics be extended to polymorphic entities? This could potentially be useful for situations where unions (C) or std::variant (C++) are used.

Say I want to have an array of different shapes. The options one has in Fortran now are

  • inheritance hierarchies
  • unlimited polymorphic entities
  • pair of an integer enumerator and a type(c_ptr) value (the good ol’ C solution)
type :: circle
  real :: radius = 1.0
end type

type :: square
  real :: width = 1.0
end type

! container type
type :: any_shape 
  class(*), allocatable :: s
end type

type(any_shape), allocatable :: my_shapes(:)

my_shapes = [any_shape(circle()), &
             any_shape(square(2.0)), &
             any_shape("not a shape!")]

! Process shapes
do i = 1, size(my_shapes)
  select type(s => my_shapes(i)%s)
  type is (circle)
    print *, "Circle with radius = " s%radius
  type is (square)
    print *, "Square with width = " s%width
  class default
     error stop "Expected shape, but got something else"
  end select
end do

Instead it would be convenient if one could do the following, without the need to introduce a container type:

class(circle,square), allocatable :: my_shapes

! For convenience we may introduce a variant syntax
! 
!   variant :: shape => circle, square
!
! or repurpose the one for procedures
!
!   generic :: shape => circle, square

my_shapes = [circle(), square(2.0), circle(3.0)]

! Process shapes
do i = 1, size(my_shapes)
  select type(s => my_shapes(i))
  type is (circle)
    print *, "Circle with radius = " s%radius
  type is (square)
    print *, "Square with width = " s%width
  class default
     ! This clause is unreachable and the compiler knows it
  end select
end do

Addendum: here is how an analogous program looks like in C++20:

// shape.cpp
//
// compile with: clang++ -std=c++20 -Wall shape.cpp

#include <variant>
#include <iostream>
#include <vector>

struct circle {
    float radius = 1.0;
};
struct square {
    float width = 1.0;
};

// helper constant for the visitor #3
template<class>
inline constexpr bool always_false_v = false;

using shape = std::variant<circle,square>;
 
int main() {
    
    std::vector<shape> my_shapes;

    my_shapes.emplace_back(circle{1.0});
    my_shapes.emplace_back(square{2.0});
    my_shapes.emplace_back(circle{3.0});

    for (auto &s: my_shapes) {
        
        std::visit([](auto && arg){

            using T = std::decay_t<decltype(arg)>;
        
            if constexpr (std::is_same_v<T,circle>)
                std::cout << "Circle with radius " << arg.radius << '\n';
            else if constexpr (std::is_same_v<T,square>)
                std::cout << "Square with width " << arg.width << '\n';
            else
                static_assert(always_false_v<T>, "non-exhaustive visitor!");
        }, s);
    }

}