Apologies if I’ve missed something, but in all this talk of simplified generics we seem to talking about how to specify that the function takes specific types. Have we instead considered the possibility of specifying that a function takes specific behaviours? Something like (I’m completely making up syntax here)
function sum(xs)
generic(T), dimension(:), intent(in) :: xs
generic(T) :: sum
applicable :: operator(+)(T, T) result(T)
integer :: i
if (size(xs) == 0) then
error stop
end if
sum = xs(lbound(xs))
do i = lbound(xs)+1,ubound(xs)
sum = sum + xs(i)
end do
end function
function mean(xs)
generic(T), dimension(:), intent(in) :: xs
generic(T) :: mean
applicable :: operator(+)(T, T) result(T), operator(/)(T, integer) result(T)
mean = sum(xs) / size(xs)
end function
function dot(xs, ys)
generic(T), dimension(:), intent(in) :: xs
generic(U), dimension(size(xs, 1)), intent(in) :: ys
generic(V) :: dot
applicable :: operator(*)(T, U) result(V), operator(+)(V, V) result(V), zero() result(V)
integer :: i
dot = zero()
do i = 1,size(xs)
dot = dot + xs(i)*ys(i)
end do
end function
If you omit the applicable
statements, then the compiler could emit error messages like (imagine I forgot the applicable
statement in mean):
ERROR: Application 'operator(+)(T, T) result(T)' is required.
NOTE: Required because 'sum' requires application 'operator(+)(T, T) result(T)' here:
23:12: mean = sum(xs) / size(xs)
^
Or if I tried to call mean(['a', 'b', 'c'])
:
ERROR: No application 'operator(+)(character, character) result(character)' exists.
NOTE: Required because 'mean' requires application 'operator(+)(T, T) result(T)' here:
132:9: m = mean(['a', 'b', 'c'])
^
I feel like this is more in line with the original generics proposal, and could even be made compatible with it, while still being much less verbose.
Although having written all this out, I’m now wondering if it’s still too complex and not sufficiently powerful enough to warrant that complexity… Still, maybe it will spark some extra thought for someone.