Feedback for generics prototype

Awesome, thanks @simong. Go ahead and try the templates and let us know what you think.

1 Like

I have tried a simple example on which to base my generics but it doesn’t compile so I’ve raised the issue on the lfortran site.
In the add example you create functions for real/real and integer/integer. I thought the point of generics was to obviate the need to do exactly that. In C++ you’d have something like

template<typename T>
T add(T a, T b) {
    return a+b;
}

What have I missed?
Thanks

Can you share the link to your bug report? I don’t see it at: Issues · lfortran/lfortran · GitHub

Are you talking about this example: https://github.com/lfortran/lfortran/blob/9a67f4916328e355276f033fea0eadb8c2ff703f/integration_tests/template_add.f90 ?

In there, the generic code is:

        function add_generic(x, y) result(z)
            type(T), intent(in) :: x, y
            type(T) :: z
            z = F(x, y)
        end function

Similar to your C++ example. It’s calling a user defined F function, so you have to define it as a user.

In order to just use the + operator, we have a work in progress pull request here: https://github.com/lfortran/lfortran/pull/1268, and more is needed, see our TODO list here: Templates TODO ¡ Issue #1199 ¡ lfortran/lfortran ¡ GitHub, eventually for these simple cases the compiler will be able to just work for builtin types and arithmetic operators. Until then just define these operations explicitly.

My point is that in C++ the user doesn’t define the specific function unless it’s a specialisation, usually the compiler does the work.
I have taken your add_t example (texample.f90) and created a non-template version using generic interfaces (ntexample.f90) along with a c++ version (texample.cxx) In terms of lines of code I have

texample.f90 => 93
ntexample.f90 => 74
texample.cxx => 46

For me a large part of the reason to use templates is to obviate the need to write the boiler-plate code and thereby void copy/paste errors. So as in the c++ code I expect the compiler to write the ‘add’ code and for me to write the specialisations of check_result.
As a syntactic aside, perhaps instead of

type T; end type

you could have

typename T

! texample.f90
module template_add_m
    implicit none
    private
    public :: add_t

    requirement R(T, F) 
        type :: T; end type
        function F(x, y) result(z)
            type(T), intent(in) :: x, y
            type(T) :: z
        end function
    end requirement

    template add_t(T, F)
        requires R(T, F)
        private
        public :: add_generic
    contains
        function add_generic(x, y) result(z)
            type(T), intent(in) :: x, y
            type(T) :: z
            z = F(x, y)
        end function
    end template
    
    ! Old world
    interface check_result
        module procedure func_check_result_i
        module procedure func_check_result_r
    end interface check_result

contains
    
    real function func_arg_real(x, y) result(z)
        real, intent(in) :: x, y
        z = x + y
    end function

    integer function func_arg_int(x, y) result(z)
        integer, intent(in) :: x, y
        z = x + y
    end function

    subroutine func_check_result_i(r, ref)
        integer, intent(in) :: r, ref
        write(*,advance='no',fmt='(a,i0)') "The result is ",r
        call res(r == ref)
    end subroutine func_check_result_i
    
    subroutine func_check_result_r(r, ref)
        real, intent(in) :: r, ref
        write(*,advance='no',fmt='(a,g0.7)') "The result is ",r
        call res(abs(r-ref) < 1.e-5)
    end subroutine func_check_result_r
   
    subroutine res(ok)
        logical, intent(in) :: ok
        if (ok) then
            write(*,'(a)') ' => passed'
        else
            write(*,'(a)') ' => FAILED'
        end if
    end subroutine res

    subroutine test_template()
        ! Issue: moving this into the block below causes a segmentation fault
        instantiate add_t(real, func_arg_real), only: add_real => add_generic
        block
            real :: x, y, r
            x = 5.1
            y = 7.2
            r = add_real(x, y)
            call check_result(r, 12.3)
        end block
        
        instantiate add_t(integer, func_arg_int), only: add_integer => add_generic
        block
            integer :: a, b, r
            a = 5
            b = 9
            r = add_integer(a, b)
            call check_result(r, 14)
        end block
    end subroutine
end module

program template_add
    use template_add_m
    implicit none

    call test_template()

end program template_add

! ntexample.f90
module template_add_m
    implicit none
    private
    public :: add_t, test_template

    interface add_t
        module procedure func_arg_real
        module procedure func_arg_int
    end interface add_t

    interface check_result
        module procedure func_check_result_i
        module procedure func_check_result_r
    end interface check_result
    
contains
    
    real function func_arg_real(x, y) result(z)
        real, intent(in) :: x, y
        z = x + y
    end function

    integer function func_arg_int(x, y) result(z)
        integer, intent(in) :: x, y
        z = x + y
    end function

    subroutine func_check_result_i(r, ref)
        integer, intent(in) :: r, ref
        write(*,advance='no',fmt='(a,i0)') "The result is ",r
        call res(r == ref)
    end subroutine func_check_result_i
    
    subroutine func_check_result_r(r, ref)
        real, intent(in) :: r, ref
        write(*,advance='no',fmt='(a,g0.7)') "The result is ",r
        call res(abs(r-ref) < 1.e-5)
    end subroutine func_check_result_r
   
    subroutine res(ok)
        logical, intent(in) :: ok
        if (ok) then
            write(*,'(a)') ' => passed'
        else
            write(*,'(a)') ' => FAILED'
        end if
    end subroutine res
    
    subroutine test_template()
        block
            real :: x, y, r
            x = 5.1
            y = 7.2
            r = add_t(x,y)
            call check_result(r,12.3)
        end block
        
        block
            integer :: a,b, r
            a = 5
            b = 9
            r = add_t(a, b)
            call check_result(r, 14)
        end block
    end subroutine test_template
end module

program template_add
    use template_add_m
    implicit none

    call test_template()

end program template_add

#include <iostream>

using namespace std;

namespace template_add_m {

    template<typename T>
    T add(T a, T b) {
        return a + b;
    }
    
    template<typename T>
    void check_result(T, T) {}
    template<>
    void check_result(int r, int ref) {
        cout << "The result is " << r << " => ";
        cout << (r != ref ? "FAILED" : "passed") << endl;
    }
    template<>
    void check_result(double r, double ref) {
        cout << "The result is " << r << " => ";
        cout << ((abs(r-ref) > 1e-5) ? "FAILED" : "passed") << endl;
    }
    
    void test_template() {
        {
            double x, y, r;
            x = 5.1;
            y = 7.2;
            r = add(x,y);
            check_result(r, 12.3);
        }
        {
            int a, b, r;
            a = 5;
            b = 9;
            r = add(a, b);
            check_result(r, 14);
        }
    }
}

int main(int, char**) {
    template_add_m::test_template();
    return 0;
}
    

@simong your C++ example is not equivalent. See here: generics/comparison.md at main · j3-fortran/generics · GitHub, what you wrote is “Traditional Templates”, but you need to use the section “C++20 Concepts Light”. The Fortran proposals are “strong concepts”, which you cannot do in C++, but you can do it in Go, Rust, Haskell and other languages, see the document. I don’t have time right now to write examples of all the above. Yes, for this simple example you shouldn’t need to have much boilerplate, as I mentioned above (work in progress).

This thread about generics / templates, as well as this other one about exceptions, reminded me of a talk at CppCon back from 2014:

Some of you might be familiar with it. Although the talk is related to a completely different world (AAA games), the underlying goal is arguably the same as the reason for using Fortran: performance. In that talk, starting around 8.30 min, he shows a list (incomplete list here):

  • Exceptions
  • Templates
  • (Multiple inheritance)
  • Operator overloading

Those are the things NOT to be used, avoided at all costs (only with minor exceptions). A familiar list looking at the latest/upcoming standards.

Food for thought.

1 Like

I don’t think this analysis is correct. Game development doesn’t care about performance. It cares about performance predictability. In HPC I would happily take a compiler pass that makes my program run 2x faster 80% of the time and 2x slower 20% of the time. In game dev, performance doesn’t matter as long as you can reliably put out the next frame in 15ms.

1 Like

Firstly, it’s worth noting that templates in C++ are very different from the generics being proposed here. Templates are kind of like compiler-assisted copy-pasting which can lead to very difficult to understand error messages and requires the compiler to expand the templates first before it’s able to check if their use is valid (which is partly what contributes to the previous problem). The generics being proposed here are more like traits, concepts, or interfaces where the onus is on the developer to specify what actions the type must be able to perform and the compiler can check the validity of the generic early in the compilation process with much more useful error messages.

Secondly, his issue with templates is to do with compilation performance, not runtime performance. While that’s a valid reason for certain code bases to avoid heavy generic use, I don’t think it’s a valid reason to not implement it in a language considering the benefits it brings. In fact it actually brings benefits to runtime performance when compared to the current alternative (class polymorphism).

Operator overloading is probably off-topic for this thread, but I think it’s worth noting that Fortran already has operator overloading (and again his issue is with comprehensibility of operator overloading, not performance).

5 Likes

In a previous thread @Arjen posted an algorithm to reverse an array.

I have now written this algorithm with the new generics:

module reverse_module
  
    implicit none
    private
    public :: reverse_tmpl, test_reverse
  
    requirement default_behavior(T)
      type :: T; end type
    end requirement
  
    template reverse_tmpl(T)
      requires default_behavior(T)
      private
      public :: reverse
    contains
        subroutine reverse(array)
            type(T), intent(inout) :: array(:)
            type(T) :: tmp
            integer :: i, j
        
            do i = 1,size(array)/2
                j        = size(array) + 1 - i
                tmp = array(i)
                array(i) = array(j)
                array(j) = tmp
            end do
        end subroutine reverse
    end template
    
contains

  subroutine test_reverse()
      instantiate reverse_tmpl(integer), only: irev => reverse
      integer :: a(5)
      a = [1,2,3,4,5]
      call irev(a)
      print *, a
  end subroutine
  
end module

  program main
  use reverse_module
  call test_reverse()
  end program

Unfortunately I hit a code generation error.

Edit: for comparison here is the way you’d do it in C++:

#include <array>
#include <iostream>
#include <algorithm> // reverse
 
template<class C>
void myreverse(C &array)
{
    using T = C::value_type;
    using I = C::size_type;
    
    T tmp; I i, j;
    for (i = 0; i < array.size()/2; i++) {
        j = array.size() - i - 1;
        tmp = array[i];
        array[i] = array[j];
        array[j] = tmp;
    }
}

template<class C>
void print(const C &array)
{
    for (auto i: array)
        std::cout << i << ' ';
    std::cout << '\n';    
}

int main(int argc, char const *argv[])
{
    std::array<int,5> a{1,2,3,4,5};

    // reverse
    myreverse(a);
    print(a);

    // built-in reverse
    std::ranges::reverse(a);
    print(a);

    return 0;
}

I haven’t used C++20 concepts here, so the requirements on the class are implicit.

2 Likes

Here’s what I believe would be a partial_sum subroutine:


    requirement r(t,binary_op)
        type :: t; end type
        pure function binary_op(a,b) result(c)
           type(t), intent(in) :: a, b 
           type(t) :: c
        end function
    end requirement

    template partial_sum_tmpl(t,binary_op)
        ! would it be possible to have a default binary_op, say operator(+) ?
        requires r(t,binary_op)
    contains
        subroutine partial_sum(n, lst)
            integer, intent(in) :: n
            type(t), intent(inout) :: lst(n)
            integer :: i 
            do i = 1, n-1
              lst(i+1) = binary_op(lst(i),lst(i+1))
            end do
        end subroutine
    end template

contains

    subroutine test_partial_sum()

      instantiate partial_sum_tmpl(integer,operator(+)), only: ipsum => partial_sum
      instantiate partial_sum_tmpl(integer,operator(*)), only: ipprod => partial_sum

      integer :: a(4)

      a = 2
      call ipsum(4,a)
      print *, "The first 4 even numbers are: ", a    ! 2 4 6 8

      a = 2
      call ipprod(4,a)
      print *, "The first 4 powers of 2 are: ", a     ! 2 4 8 16

    end subroutine

Will it be possible to have default value for template parameters? E.g. a partial_sum should use the addition operator by default, but a user could replace it with a different binary operator.

@ivanpribec beautiful. It works!

$ lfortran reverse.f90 
5
4
3
2
1

$ lfortran --version
LFortran version: 0.18.0-762-g67f37e3a8
Platform: macOS ARM
Default target: arm64-apple-darwin21.3.0

Use the latest master of LFortran and use the (default) LLVM backend. The WASM backend doesn’t work yet for this (WASM bug: Dimension length for index 0 does not exist · Issue #1386 · lfortran/lfortran · GitHub).

3 Likes

My suspicion is that there will be very few edge cases where the default actually makes sense. I.e. What would be the default binary_op for my_type in

use my_mod, only: my_type

instantiate partial_sum_tmpl(my_type), only: my_psum => partial_sum

I think in this case

explicit is better than implicit

  • the Zen of Python

I see, no defaults.

Here’s what it might look like to wrap the C qsort function:

Click to display
    requirement comparable(t,lt)
      type, deferred :: t
      interface
        ! Less Than Operator
        pure logical function lt(a,b)
          type(t), intent(in) :: a, b
        end function
      end interface
    end requirement

    template qsort_tmpl(t,lt)
      requires comparable(t,lt)
    contains
      subroutine qsort(array)
        use, intrinsic :: iso_c_binding
        type(t), intent(inout), contiguous :: array(:)
        interface
          subroutine c_qsort(array,elem_count,elem_size,compare) bind(c,name="qsort")
            import c_ptr, c_size_t, c_funptr
            type(c_ptr), value :: array
            integer(c_size_t), value :: elem_count
            integer(c_size_t), value :: elem_size
            type(c_funptr), value :: compare
          end subroutine
        end interface
        integer, parameter :: bits_per_byte = 8
        if (size(array) < 2) then
          ! nothing to sort
          return
        end if
        call c_qsort( &
            c_loc(array(1)), &
            size(array,kind=c_size_t),&
            integer(storage_size(array(1))/bits_per_byte,c_size_t), &
            c_funloc(cmp))
      contains
        pure function cmp(a,b) bind(c)
          type(c_ptr), value :: a, b
          integer(c_int) :: cmp
          type(t), pointer :: pa, pb
          call c_f_pointer(a,pa)
          call c_f_pointer(b,pb)
          if (lt(pa,pb)) then
            cmp = -1
            return
          end if
          if (lt(pb,pa)) then
            cmp = 1
            return
          end if
          cmp = 0 
        end function
      end subroutine
    end template

I rewrote your reverse using a dedicated swap generics, but hit a bug in LFortran: generics: bug with function dependencies · Issue #1385 · lfortran/lfortran · GitHub. After we fix it, I’ll try more things (update: fixed!). This is good, thanks @ivanpribec !

Nice to see it working!

If more test cases are needed, they can be picked from the std::ranges algorithms library. The insertion_sort in Fortran stdlib is also an easy target (and already written as a fypp template). To verify it was sorted correctly, you need a generic is_sorted:

template is_sorted_tmpl(t,lt)
requires comparable(t,lt)
contains
logical function is_sorted(array)
   type(t), intent(in) :: array(:)
   is_sorted = .true.
   do i = 1, size(array)-1
      if (lt(array(i+1),array(i)) then
         is_sorted = .false.
         return
      end if
   end do
end function
end template
1 Like

Will instantiations only be allowed in subroutine and main programs, or also at module level? The latter could lead to severely bloated libraries (in the sense of shared libraries or static archives).

1 Like

Or Fortran Generics could start with t as default type, deferred and be rid of that silly declaration!! :stuck_out_tongue_winking_eye:

Can template implementations be hidden in submodules?

Instantiations can appear in any specification section (i.e. places declarations of variables can appear). This includes module specification sections.

Perhaps, but I wouldn’t expect it anymore than what people are doing now with fypp and the like.

Not at the moment. We intend to explore ways to facilitate that, but expect it will be difficult for compilers to find the implementation for instantiation so whatever solution we come up with will have to consider that.

What exactly does that instantiate statement do? Is that what triggers the actual compilation of the routine with the appropriate types and kinds?