Hi all, I would have responded a little sooner, but I wanted to make sure I gave this the attention and consideration it deserves, so I read it carefully and had some discussions with others. I appreciate that a lot of effort went into it, and I am generally in favor of searching for better solutions. That said, I believe the proposed design has a few fundamental problems. Below are my notes, semi-ordered by level of importance/problem.
- Polymorphic objects with templated type-bound procedures effectively require run-time compilation. Even from the example in the paper (Listing 6.3), there are places where it is not known until runtime which procedure will be called, and since that procedure is templated, you donât know until runtime that a particular version of that procedure needs to be compiled. That means at minimum youâd need to keep some form of abstract semantic representation embedded in the executable at the call site and have a fully featured Fortran interpreter available at run time to be able to execute the templated code. The overhead would be huge, so performance terrible, and thus not very âFortranicâ.
- I donât think itâs a good idea to mix OO type extension with traits, namely because how would an extension of an abstract type know all of the traits that it must implement, given that a declaration that a type implements a specific trait may be declared separately (even in a different module)? The following example attempts to demonstrate the problem with this, i.e. where the child type doesnât know that it needs to implement some trait, and the program expects that it did, specifically wrt the statement from the end of Section 4.2.3.
We finally wish to remark that in case the âimplementingâ type is an abstract derived type, it must be allowed to provide an only partial implementation of the interfaces that it adopts. However, any non-abstract type that extends this abstract type through subclassing (i.e. implementation inheritance) must then provide a full implementation.
Example
module my_parent_m
type, abstract :: my_parent_t
end type
end module
module my_child_m
use my_parent_m
type, extends(my_parent_t) :: my_child_t
end type
end module
module interfaces_m
abstract interface somethingI
subroutine something(self)
deferred(self) :: self
end subroutine
end interface
end module
module somewhere
use interfaces_m
use my_parent_m
implements somethingI :: my_parent_t
end implements
end module
program example
use somewhere
use my_child_m
class(my_parent_t), allocatable :: my_x
allocate(my_child_t :: my_x)
call use_something(my_x)
contains
subroutine use_something{somethingI :: T}(x)
class(T) :: x
call something(x)
end subroutine
end program
- Data structures of runtime polymorphic trait objects requires a level of reflection/introspection likely to incur a large amount of overhead. The issue is that you donât even know which v-table you have to use to look up the function until runtime. I.e. you have to determine which type the object is at run time, then determine which of the functions in that v-table corresponds to the related function from the trait. I think it is still an open question how often you need runtime polymorphism without inheritance, and whether itâs feasible to implement in Fortran.
- It is not clear to me if/how the proposed traits allow the expression of relationships/operations between/involving multiple types? Consider the fully generic AXPY template (below) from recent examples/tutorials for templates. How would this be expressed/implemented with the traits proposal?
Generic AXPY
requirement bin_op(T, U, V, op)
type, deferred :: T, U, V
deferred interface
simple elemental function op(x, y)
type(T), intent(in) :: x
type(U), intent(in) :: y
type(V) :: op
end function
end interface
end requirement
simple function axpy &
( a_type, x_type, y_type, &
times_result_type, plus_result_type, &
plus, times) &
(a, x, y)
requires bin_op( &
a_type, x_type, times_result_type, times)
requires bin_op( &
times_result_type, y_type, &
plus_result_type, plus)
type(a_type), intent(in) :: a
type(x_type), contiguous, intent(in) :: x(:)
type(y_type), intent(in) :: y(size(x))
type(plus_result_type) :: axpy(size(x))
axpy = plus(times(a, x), y)
end function
integer, parameter :: sp = kind(1.0)
integer, parameter :: dp = kind(1.d0)
real(sp) :: a
integer :: x(10)
real(dp) :: y(10)
instantiate axpy( &
a_type = real(sp), &
x_type = integer, &
y_type = real(dp), &
times_result_type = real(sp), &
plus_result_type = real(dp), &
plus = operator(+), &
times = operator(*)), mixed_axpy => axpy
print *, mixed_axpy(a, x, y)
- Is it possible to address the situation where in certain contexts you want to use different implementations of certain traits for a given type? Consider the following example.
Differently Reduceable Integers
abstract interface :: reduceable
function combine(a, b) result(combined)
type(reduceable), intent(in) :: a, b
type(reduceable) :: combined
end function
function empty()
type(reduceable) :: empty
end function
end interface
function reduce{reduceable :: T}(a) result(reduced)
type(T) :: a(:)
type(T) :: reduced
integer :: i
reduced = empty()
do i = 1, size(a)
reduced = combine(reduced, a(i))
end do
end function
implements reduceable :: integer
procedure :: combine => operator(+), empty => int_zero
end implements
implements reduceable :: integer
procedure :: combine => operator(*), empty => int_one
end implements
integer :: sum_or_product
sum_or_product = reduce([1, 2, 3, 4]) !? 10 or 24?
- The type-sets feature prevents the use of third party types. Also, this feature is effectively already handled by the Japanese generic procedures proposal.
- For templated types, I find the scoping rules and correspondence between what is a parameter of the procedure and what is a parameter of the type hard to follow. Further, itâs not quite clear to me how type extension would work for templated types.
- Itâs unclear to me how exactly the correspondence between procedure arguments and template arguments is done for implicit instantiation.
I do appreciate some of the ideas this proposal put forward, and how it attempts to address a few of the shortcomings of the current templates design. Key among them are the following:
- Listing out all the functions and types a template needs can get pretty verbose pretty quickly. The traits concept helps alleviate that problem. Iâve written up, but not yet submitted to J3, an extension to the
requirement
/requires
idea to effectively provide this feature. You can read the initial draft at write a paper solving long template arg list problem by everythingfunctional ¡ Pull Request #140 ¡ j3-fortran/generics ¡ GitHub - Mixing templates and the existing run-time polymorphism features is a bit clunky currently. I have an idea for how to make that more convenient (to the extent the features actually can/should be mixed), as illustrated in the following, not thoroughly considered, example.
Dynamic Dispatch
! consider the following intrinsic, "magic" template that,
! given a type and the name of one of its type-bound procedures
! produces a standalone procedure with the same attributes and
! argument list, but still does dynamic dispatch on the type of
! the passed object dummy argument
subroutine dynamic_dispatch(T, tbp_name)(self, ...)
type, deferred, abstract :: T
class(T) :: self
call self%tbp_name(...)
end subroutine
! thus enabling something like the following example
template tmpl(T, sub)
type, deferred, extensible :: T
deferred interface
subroutine sub(self)
class(T), intent(in) :: self
end subroutine
end interface
contains
subroutine call_it(x)
class(T), intent(in) :: x
call sub(x)
end subroutine
end template
type :: t1
contains
procedure :: sub => t1_sub
end type
type, extends(t1) :: t2
contains
procedure :: sub => t2_sub
end type
subroutine t1_sub(self)
class(t1), intent(in) :: self
print *, "Hello from t1_sub"
end subroutine
subroutine t2_sub(self)
class(t1), intent(in) :: self
print *, "Hello from t2_sub"
end subroutine
instantiate tmpl(t1, dynamic_dispatch^(t1, sub)), only: call_it
call call_it(t1()) ! prints "Hello from t1_sub"
call call_it(t2()) ! prints "Hello from t2_sub"
- People like the OO style/syntax, and the current templates donât enable it for deferred types. I think thereâs a path to enabling it by specifying that a deferred type should treat certain deferred arguments as type-bound procedures. Iâve only just started thinking about the idea, let alone syntax, but I think something like the following could be doable.
TBP on Deferred Type
template tmpl(T, sub)
! The following implies T is deferred and extensible.
! abstract could be declared explicitly
prototype :: T
procedure :: sub
end type
deferred interface
subroutine sub(self)
class(T), intent(in) :: self
end subroutine
end interface
contains
subroutine call_it(x)
class(T), intent(in) :: x
call x%sub()
end subroutine
end template
Those three ideas taken together allow you to write code that looks (if you squint) a little bit like OO traits. Item 3 gives you back OO syntax inside the template, item 2 lets you pass TBPs as instantiation arguments, and item 1 means you only need to spell out the long list once for the requirement
, and once for each type that âimplementsâ it. I can try and work out the sample problem from the traits proposal at some point using these ideas if enough folks want to see what it would look like, but using the above example would look something like the following.
Traits With Templates
requirement my_trait(T, sub)
prototype :: T
procedure :: sub
end type
deferred interface
subroutine sub(self)
class(T), intent(in) :: self
end subroutine
end interface
end requirement
template tmpl(impl)
satisfaction(my_trait) :: impl
contains
subroutine call_it(x)
class(impl%T), intent(in) :: x
call x%sub()
end subroutine
end template
type :: t1
contains
procedure :: sub => t1_sub
end type
type, extends(t1) :: t2
contains
procedure :: sub => t2_sub
end type
subroutine t1_sub(self)
class(t1), intent(in) :: self
print *, "Hello from t1_sub"
end subroutine
subroutine t2_sub(self)
class(t1), intent(in) :: self
print *, "Hello from t2_sub"
end subroutine
satisfaction :: impl = requires my_trait(t1, dynamic_dispatch^(t1, sub))
instantiate tmpl(impl), only: call_it
call call_it(t1()) ! prints "Hello from t1_sub"
call call_it(t2()) ! prints "Hello from t2_sub"
I wouldnât count on those features making it into F202Y, but knowing that they are possible, and that we already have a start on them, my opinion is that the generics subgroup should continue along its current path so that templates enable all the functionality and can make it into F202Y, and then F203X can make it more âuser friendlyâ for OO enthusiasts. My impression is that if we tried to switch designs now, F202Y wouldnât end up with any generics features. (Well, maybe the Japanese proposal would still make it.)