Feedback for generics prototype

We implemented a prototype of F202Y generics in LFortran, as proposed by the generics subcommittee (@tom_clune, @everythingfunctional, @gak, @FortranFan, @rouson and others). You can test it locally by using the default LLVM backend (make sure you use the latest LFortran from git), or you can test it online at https://dev.lfortran.org/, at the top left click on Examples → experimental, select one of the 7 examples and click on Run. (The online WASM backend is less mature than our LLVM backend, but it is usable.)

Can you please try it out and give us feedback?

Here is our TODO list of things that we know about: Templates TODO · Issue #1199 · lfortran/lfortran · GitHub.

This is an important feature for Fortran and it is crucial that we get this right. Here is how we are approaching it:

  • We got support of the Fortran Standards Committee, and it formed a generics subgroup
  • The subcommittee has been meeting biweekly and iterating on the design and writing papers
  • We have written a prototype in a compiler. So far we have LFortran and I invite other compiler vendors to also create a prototype.

What we need now is an involvement of the wider Fortran community to try the prototype and provide feedback. If you like it, please let us know. If you don’t like it, please let us know, and let’s improve the design. I think it would be great if you could use it and write some algorithms using it and please share your experience actually using the generics. In my opinion, that is how to get new features in: we should use them first, and only after we get enough experience, we should standardize them.

(LFortran is in advanced alpha, so you will hit bugs, but it should be possible to workaround them, just report all bugs to our issue tracker and we’ll help you.)

12 Likes

I have previously voiced my concerns regarding this proposal. In my opinion it does not at all provide the functionality and expressiveness of generics as seen in the other languages it claims taking inspiration from. But I assume at least some of the working group members remember this from the last time it was discussed.

@plevold thanks, I forgot about that. My understanding from that thread was that you will organize a meeting to discuss this more. You should still do that, if you feel strongly that the current approach is not the right one.

The other alternative design that is at least a little bit developed is this one: Generics as type-level metaprogamming · Issue #293 · j3-fortran/fortran_proposals · GitHub.

Yes, I spoke to @everythingfunctional a while back. My intent was to send the invite to you as well, not sure why it didn’t make it through.

Thanks for the link to the proposal, I was not aware of that one.

Wow, live testing of future features is fantastic! Congrats @certik and the team on the amazing progress, I’m impressed.

I’m trying to get my head over the syntax because I’d like to write a generic implementation of a function that contains allocation. Here’s my progress thus far:

module my_derived_type
    implicit none
    private
    
    type, public :: my_base
    end type my_base
    
end module my_derived_type

module generic_poly_realloc
    implicit none
    private
    public :: pack_tmpl

    requirement nothing_else(t)
        type :: t; end type ! type, extends(my_base) :: t ?
    end requirement

    template pack_tmpl(t, pack_t)
        requires nothing_else(t)
        private
        public :: mysum_t
    contains
        pure subroutine mypack_t(x,mask)
           type(t), intent(inout), allocatable :: x(:)
           logical, intent(in) :: mask(:)
           
           type(t) :: tmp(:)
           integer :: i,it
           
           allocate(tmp(count(mask)))
           
           it = 0
           do i=1,size(mask)
              if (.not.mask(i)) cycle
              it = it+1
              tmp(it) = x(i)
           end do     
         
           call move_alloc(from=tmp,to=x)
    
        end subroutine mypack_t   
    end template 

contains

    subroutine test_template()
    
        use my_derived_type, only: my_base
    
        instantiate pack_tmpl(integer), only: pack_integer => mypack_t
        instantiate pack_tmpl(my_base), only: pack_derived => mypack_t
        
        integer :: j
        integer, allocatable :: i(:)
        type(my_base), allocatable :: d(:)
        logical, allocatable :: mask(:)
        
        ! Pack integer
        i = [1,2,3,4,5,6,7,8,9,10]
        mask = [(mod(j,2)==0,j=1,10)]
        print *, 'before pack = ',i
        call pack_integer(i,mask)
        print *, 'after pack = ',i
        
        ! Pack derived type
        allocate(d(10))
        print *, 'derived: old size=',size(d)
        call pack_derived(d,mask)
        print *, 'new size = ',size(d)
    end subroutine

end module generic_poly_realloc 

program test_realloc

    use generic_poly_realloc
    implicit none

    call test_template()

end

It does not compile on the lfortran playground (out of memory error) yet, but that’s expected. What I’d like to ask the generics gurus is:

  • is this supposedly the easiest way to have a generic implementation of a function that includes allocation and works for a derived type and any of its extended types?
  • Does the generics proposal include some different mechanism to handle that?
3 Likes

@certik you are a God of Fortran. :slight_smile: It made my day, I cannot wait to test out this thing!!!

You’re example is almost correct. Remove the extra argument from your template. I.e.

to

template pack_tmpl(t)

We don’t support polymorphism directly yet. (i.e. you can’t extend from deferred types or assume they are extensible). We do believe our current design can be extended to allow for this. If someone can provide a use case that requires this, the generics subgroup would like to see it.

1 Like

Thank you, now that I’ve tried it, I think the syntax makes a lot of sense. Shout out for the hard work on this propsal, maybe still subject to some polishing (I don’t like type::t; end type, but it’s just syntactic sugar), but I think it’s very clear once you start using it.

I stumble upon this problem pretty often. Whether we like it or not, allocatable variables are safer, so maybe they deserve a spot in the generics proposal :slight_smile: The easiest example I can make is with MPI communications. If I want to broadcast, gather, scatter, etc. an array of any derived type and rank, I need to redefine (copy+paste) the same interfaces for each of them (error-prone, etc.); imagine:

type, extends(messageable) :: my_type
end type

interface broadcast
   module procedure my_type_broadcast_array
end interface

subroutine my_type_broadcast_array(comm,array,from_rank)
   type(mpi_comm), intent(in) :: comm
   type(my_type), allocatable, intent(inout) :: array(:)
   integer, optional, intent(in) :: from_rank
end subroutine my_type_broadcast_array

All these routines need to be re-written for basically each and every class in the MPI program, while a generic implementation would provide something like:

template broadcast_messageable(t)
        class(messageable), requirement :: t ! Simpler syntax if the type is all we need?
        private
        public :: broadcast_array_t
  contains
        pure subroutine broadcast_array_t(comm,array,from_rank)
           type(mpi_comm), intent(in) :: comm
           type(t), allocatable, intent(inout) :: array(:)
           integer, optional, intent(in) :: from_rank
        end subroutine broadcast_array_t   
 end template 

This would still need

  • some mechanism to be instantiated only once where the base (abstract) class messageable is defined, but would save a whole lot of duplicate code.
  • a way to use it in type-bound procedures? maybe I’m going too far.

Same goes for intrinsic numeric types (real(*) :: t? or kind :: t?) , that already share all default operators.

The proposed syntax will actually be

type, deferred :: t

As for your example, I actually don’t see why you would want t to be extensible. All that would buy you is

1 Like

Ok, we should update LFortran then with this new syntax. @everythingfunctional do you see any other incorrect syntax?

Not that jumped out. I’ll let you know if I notice anything.

1 Like

I’ve tried to build it but failed. This is usual for me with cmake - I just don’t understand what it (cmake) brings to the party other than exasperation, frustration and general making life difficult. As you can see below it’s saying it can’t find zlib whilst helpfully quoting the version it has found. Nothing about what it’s expecting and even if it did require a different version rummaging around for that is a step too far. Does lfortran really require the latest zlib (1.2.13)?

Simon

[simon@localhost lfortran (main)]$ build1.sh
#++ pwd
+ cmake -DCMAKE_BUILD_TYPE=Debug -DWITH_LLVM=yes -DLFORTRAN_BUILD_ALL=yes -DWITH_STACKTRACE=yes '-DCMAKE_PREFIX_PATH=;' -DCMAKE_INSTALL_PREFIX=/home/simon/development/lfortran/lfortran/inst .
+ ci/version.sh
++ git describe --tags --dirty
+ version=v0.18.0-692-g4b163d4dc
+ version=0.18.0-692-g4b163d4dc
+ echo 0.18.0-692-g4b163d4dc
+ python src/libasr/asdl_cpp.py grammar/AST.asdl src/lfortran/ast.h
+ python src/libasr/asdl_cpp.py src/libasr/ASR.asdl src/libasr/asr.h
+ python src/libasr/wasm_instructions_visitor.py
Assuming default values of wasm_instructions.txt and wasm_visitor.h
+ cd src/lfortran/parser
+ re2c -W -b tokenizer.re -o tokenizer.cpp
+ cd src/lfortran/parser
+ re2c -W -b preprocessor.re -o preprocessor.cpp
+ cd src/lfortran/parser
+ bison -Wall -d -r all parser.yy
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
time limit exceeded: 6.000000
+ grep -n \' src/lfortran/parser/parser.yy
OK
+ echo OK
CMake Error at /usr/share/cmake/Modules/FindPackageHandleStandardArgs.cmake:218 (message):
  Could NOT find ZLIB (missing: ZLIB_LIBRARY) (found version "1.2.12")
Call Stack (most recent call first):
  /usr/share/cmake/Modules/FindPackageHandleStandardArgs.cmake:582 (_FPHSA_FAILURE_MESSAGE)
  /usr/share/cmake/Modules/FindZLIB.cmake:115 (FIND_PACKAGE_HANDLE_STANDARD_ARGS)
  cmake/FindStaticZLIB.cmake:7 (find_package)
  CMakeLists.txt:113 (find_package)

That’s a bug in Bison: Bison 3.7 fails · Issue #290 · lfortran/lfortran · GitHub, use Bison 3.4. Use the following Conda environment to see what exact versions of dependencies are known to work: lfortran/environment_linux.yml at main · lfortran/lfortran · GitHub.

Hmm. Bison3.4 (probably too old for my compiler) doesn’t build on my machine:

Making all in .
make[2]: Entering directory '/home/simon/Downloads/bison-3.4'
  GEN      doc/bison.help
tests/bison: line 37: 382345 Segmentation fault      (core dumped) $PREBISON "$abs_top_builddir/src/bison" ${1+"$@"} 2> "$stderr"

Bison3.8 builds okay but has the same failure as 3.7 when trying to build lfortran.

@simong are you able to use Conda? If so, that would be the easiest to install all dependencies.

Yes I have 4.9.2 on my system, how do I use it?

The instructions here should work with your Conda (just skip the conda setup, since you already have conda): https://docs.lfortran.org/en/installation/#build-from-git. If they don’t, please let me know!

The conda part seems to have worked okay but cmake is still failing:

(lf) [simon@localhost lfortran (main)]$ cmake -DCMAKE_BUILD_TYPE=Debug -DWITH_LLVM=yes -DCMAKE_INSTALL_PREFIX=`pwd`/inst .
+ ci/version.sh
++ git describe --tags --dirty
+ version=v0.18.0-692-g4b163d4dc
+ version=0.18.0-692-g4b163d4dc
+ echo 0.18.0-692-g4b163d4dc
+ python src/libasr/asdl_cpp.py grammar/AST.asdl src/lfortran/ast.h
+ python src/libasr/asdl_cpp.py src/libasr/ASR.asdl src/libasr/asr.h
+ python src/libasr/wasm_instructions_visitor.py
Assuming default values of wasm_instructions.txt and wasm_visitor.h
+ cd src/lfortran/parser
+ re2c -W -b tokenizer.re -o tokenizer.cpp
+ cd src/lfortran/parser
+ re2c -W -b preprocessor.re -o preprocessor.cpp
+ cd src/lfortran/parser
+ bison -Wall -d -r all parser.yy
+ grep -n \' src/lfortran/parser/parser.yy
OK
+ echo OK
-- Found LLVM 11.0.1
-- Using LLVMConfig.cmake in: /home/simon/.conda/envs/lf/lib/cmake/llvm
CMake Error at /home/simon/.conda/envs/lf/share/cmake-3.25/Modules/FindPackageHandleStandardArgs.cmake:230 (message):
  Could NOT find BFD (missing: BFD_INCLUDE_DIR BFD_LIBRARY)
Call Stack (most recent call first):
  /home/simon/.conda/envs/lf/share/cmake-3.25/Modules/FindPackageHandleStandardArgs.cmake:600 (_FPHSA_FAILURE_MESSAGE)
  cmake/FindBFD.cmake:8 (find_package_handle_standard_args)
  CMakeLists.txt:257 (find_package)


-- Configuring incomplete, errors occurred!

The BFD library is used for stacktrace support, see here for more info:

https://docs.lfortran.org/en/installation/#stacktraces

It should be off by default, but you can also pass -DWITH_STACKTRACE=no to turn it off. Then it should work.

Thank you. I’ve now built lfortran okay and it passes all the tests.

2 Likes