What is currently on the anvil is something I do believe strongly most Fortranners will struggle with mightily, so much so adoption will be weak to nonexistent.
The better question to discuss is what should be the semantics and possible syntax for a generic algorithm such as this. Keep in mind, there are TWO uses for Generics in Fortran (some might argue this is adequate for the kind of specific-purpose computing Fortran seeks to serve):
- Generic algorithms
- Generic containers
The original post here squarely falls into the first use case.
So to answer the question I ask here, “what should be the semantics and possible syntax for a generic algorithm,” how I had approached was to develop KART
(kind, attribute, rank, type) semantics that allows for semantics-by-substitution while providing the necessary blade-guards as per “strong concepts”. So with the example in the original post, here’s what I mean - note it is notional syntax for illustration purposes (please don’t hung up on it just because you may not like the syntax):
module list_mod
implicit none
template, object :: T !<-- by default, an object template means any type with any of its KIND and LEN parameters
rank => 1 !<-- T here specifies a RANK-1 object
supports
operator( /= ) !<-- the only stipulation is that the template is for an object that supports /= operation
end template
contains
function change_positions<T>(vec) result(pos) !<-- templated subprogram
<T>, intent(in) :: vec !<-- use of the template object; note no `( : )` since template is for rank-1 object
integer, allocatable :: pos(:)
integer :: i,j,n
n = size(vec)
allocate (pos(n))
if (n < 1) return
pos = 0
pos(1) = 1
j = 1
do i=2,n
if (vec(i) /= vec(i-1)) then
j = j+1
pos(j) = i
end if
end do
pos = pack(pos, pos > 0)
end function change_positions
end module list_mod
program main
use list_mod
implicit none
print*,change_positions<integer>( [3, 3, 6, 2, 2, 2, 1] ) !<-- default integer per current senantics
print*,change_positions<character>( ["a", "a", "b", "p", "p", "p", "o"] ) !<-- len=1 given per current semantics
end program main
The main points, as per my illustration above, for any new Generics facility must address:
-
Do simple things simply
-
Compact code toward a generic algorithm,
-
As similar a look-and-feel as what an author might write currently in Fortran,
-
The generic algorithm can be templated using either objects or interfaces, here what is shown is with a template object,
-
The template for an object provides generic means to characterize the kind, attribute, rank, type of the object. The above notional syntax is simply to illustrate
a. any type with any of itsKIND
andLEN
parameters
b. but with a RANK of 1 because that’s what the author’s algorithm is based on,
c. the template is declared such that the processor is informed the object shall support the/=
inequality operator because the algorithm depends on this. Note all intrinsic types support this operation and derived types can be declared to support them. -
The specialization, the so-called compile-time instantiation, on the caller side is in situ, at least for simple cases as this one.
See an earlier discussion along the same lines.