j3-fortran / fortran_proposals

Proposals for the Fortran Standard Committee
178 stars 15 forks source link

Templates for functions/subroutines #4

Open certik opened 4 years ago

certik commented 4 years ago

A very common request is to allow templates for subroutines or functions, in order to allow code like the following:

    <T> function f(x)
    <T>, intent(in) :: x
    f = x + 1
    end function

instead of

interface f
    module procedure f_int
    module procedure f_single
    module procedure f_double
end interface

contains

    integer function f_int(x) result(f)
    integer, intent(in) :: x
    f = x + 1
    end function

    real function f_single(x) result(f)
    real, intent(in) :: x
    f = x + 1
    end function

    real(dp) function f_double(x) result(f)
    real(dp), intent(in) :: x
    f = x + 1
    end function

More use cases available at https://github.com/certik/fortran-generics.

arjenmarkus commented 4 years ago

I have written a proposal on templates that uses a very different approach. It was inspired by a note on the subject of generic programming features already in Fortran (to be published with ACM Fortran Forum, but a draft can be found at http://flibs.sourceforge.net/generic_programming_features.pdf). I will add the note as a new issue.

certik commented 4 years ago

@arjenmarkus thank you, that would be great if you send it. There are a lot of approaches here, and the committee is looking at all approaches and it wants to get something done for 202y (the standard that comes after 202x, which will be the next standard)

certik commented 4 years ago

@arjenmarkus your pdf references the paper from Magne Haveraaen, who sits next to me right now. We'll discuss your paper today and I'll report back.

arjenmarkus commented 4 years ago

Small world :).

Regards,

Arjen

Op do 17 okt. 2019 om 18:10 schreef Ondřej Čertík <notifications@github.com

:

@arjenmarkus https://github.com/arjenmarkus your pdf references the paper from Magne Haveraaen, who sits next to me right now. We'll discuss your paper today and I'll report back.

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/4?email_source=notifications&email_token=AAN6YR6FS6TXJRCF3XIORLTQPCFAZA5CNFSM4JBFWSXKYY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOEBQVAQQ#issuecomment-543248450, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAN6YR7O7Q2NYEBKG5L2M5DQPCFAZANCNFSM4JBFWSXA .

cmacmackin commented 4 years ago

I agree that templates are desperately needed. They should be applied to derived types as well as to procedures. I remember coming across a proposal from some time ago for "parameterised modules", which I thought looked quite promising, but nothing ever came of it I guess. (I see you have an example of something like that in your fortran-generics repository and it is by far the cleanest syntax of those you show).

I will say that I'm rather tired of the committee perpetually pushing this onto the standard after next. The two most recent releases have been relatively minor revisions, so it's not as though the decision was made to focus elsewhere. People have been wanting this feature for years and it really is crippling to development. If this is pushed back until 202y then we likely won't see widespread compiler support until the 2030s. We'd almost be better off trying to back a newer language like Chapel, which does include these features, in that case.

certik commented 4 years ago

@cmacmackin thanks for the feedback here and the other issues, we really appreciate it. I am new to the committee, this is my second meeting. I am still learning about what the committee did in the past and the history behind various proposals. The way I see it is that this is a requested feature, and we should try to get it right and included. If the committee wasn't moving as fast in the past, then here is what we can all do to help:

  1. Join the committee (like I did --- if you can at all, please join, so that you can help push these proposals forward)

  2. Help us figure out a good way to do generics in Fortran, then help us write a good proposal, and help us advocate for it

To help with 2., I created this repository, and we are trying to keep it updated with the proposals that the committee is considering. Regarding generics in particular, I will keep updating this issue on the latest status. This will go into 202y, as we do not have any good proposal that is ready to go into 202x, and it is important to get this right. The committee needs help, and my experience with organizing open source communities such as SymPy makes me hopeful that opening up the commitee's work to the wider community will allow us to organize ourselves more efficiently. If you have other ideas what the committee can do to improve, please let us know.

marshallward commented 4 years ago

Templating would strongly support our current development efforts at GFDL. I am a contributor to the FMS framework used by weather and climate models at GFDL (including my main job of MOM6 development), and it relies heavily on preprocessing of template-like code for many interface functions, such as for MPI operations.

Some example code is below, where a file is #included multiple times, each time replacing MPP_TYPE_ and similar macros with different types, size, and rank (scalar, 2d, 3d, etc.):

This does work, and has worked for a long time, but it's a lot of bloat and gets even more complicated when trying to manage some of the conditional support for things like complex numbers and non-default kinds for integers or reals.

I feel like this must be a common problem, and it would be great to find a template-like solution which can unify this sort of code.

FortranFan commented 4 years ago

@cmacmackin thanks for the feedback here and the other issues, ..

Thanks to @cmacmackin for frank comments.

@certik, it'll be most useful and beneficial if there is a way to (almost) force WG5 and ALL its member body representatives to read user feedback. You may note your great initiative for GitHub Fortran proposals was immediately noticed online e.g., comp.lang.fortran - see this thread there:

And some of the comments there:

There is a lot to learn from the comments by practitioners of Fortran.

FortranFan commented 4 years ago

A very common request is to allow templates for subroutines or functions, in order to allow code like the following:

    <T> function f(x)
    <T>, intent(in) :: x
    f = x + 1
    end function

instead of

interface f
    module procedure f_int
    module procedure f_single
    module procedure f_double
end interface

contains

    integer function f_int(x) result(f)
    integer, intent(in) :: x
    f = x + 1
    end function

    real function f_single(x) result(f)
    real, intent(in) :: x
    f = x + 1
    end function

    real(dp) function f_double(x) result(f)
    real(dp), intent(in) :: x
    f = x + 1
    end function

More use cases available at https://github.com/certik/fortran-generics.

Considering the semantics and syntax for generic interfaces were introduced way back in Fortran 90 and were simplified further in the latest 2018 revision as follows:

   generic :: f => f_int, f_single, f_double

contains

   integer function f_int(x) result(f)
      integer, intent(in) :: x
      f = x + 1
   end function

   real function f_single(x) result(f)
      real, intent(in) :: x
      f = x + 1
   end function

   real(dp) function f_double(x) result(f)
      real(dp), intent(in) :: x
      f = x + 1
   end function

and keeping in mind how much of the semantics for PGAS SPMD approach toward parallel computing was achieved using [..] notation in COARRAYS. a key aspect to deduce perhaps is the importance of conveying semantics via syntax and focusing on the latter. Sure this can run counter to the current work process of Fortran standard development: get the use cases, generate requirements, then develop specifications, and finally the syntax. For concepts that are well-established in computer engineering widely such as generics and that are so well-known now and where every new language that crops up has sophisticated support for generics from the get-go or soon thereafter (e.g., Julia and Haskell), may be the approach should be the other way around? Settle on syntax that conveys to the coders and processors of Fortran all they need and allow the semantics to simply fall out of that?

Say the language introduces an attribute 'TYPE' with the existing statement of GENERIC: why can't the following convey for a processor everything it needs to setup generic interfaces for the 3 types shown in the original post here?

   function f(x) result(r)
      generic, type :: T => int, real, real(dp)
      type(T), intent(in) :: x
      type(T) :: r
      x = x + 1 
   end function

Is committee overthinking this and needlessly procrastinating the development of generics in Fortran?

certik commented 4 years ago

@marshallward thanks for the feedback! Yes, every code has an MPI layer like yours and we all struggle with the lack of templates for this one. We might not need full templates for this one, perhaps just some better way to handle arbitrary arrays and types. But the committee is well aware of this use case, as almost any parallel Fortran MPI code faces the exact same issue.

I will keep you involved on this effort if you are interested. Tom Clune is leading this template effort, he will send instructions soon and I will update this issue once he does.

certik commented 4 years ago

@FortranFan thanks for the encouragement. If you don't mind, why don't you open a new issue or new issues, put [META] in the title and let's discuss there how to best organize ourselves. So that we can keep issues like this one for pure technical content regarding this particular issue.

certik commented 4 years ago

@FortranFan I created the meta issue at #26. Let's discuss the workflow there.

marshallward commented 4 years ago

@certik Thanks, I am very interested to hear about progress on this issue. I was not sure how to best use these GitHub issues, but hoped that pointing to additional example might help in some small way.

Thanks as well for creating this repo, I hope it will help to streamline the process for working with the J3 committee!

certik commented 4 years ago

@marshallward you are welcome. I am excited that people want to collaborate this way.

@tclune is leading an effort on templates. He just posted instructions how people can get involved:

https://mailman.j3-fortran.org/pipermail/j3/2019-October/011704.html

Tom, do you want to take it from here and coordinate with all the people who expressed interest in this thread?

certik commented 4 years ago

One idea how you can collaborate on this is to use @tclune's repository to work deeply on the various ideas, and then we can use this https://github.com/j3-fortran/fortran_proposals repository to just keep track of a summary as well as how each template proposal goes through the committee.

certik commented 4 years ago

@klausler this is an interesting idea, different from any other idea so far proposed (we discussed parametrized modules before, but not in this way). It deserves its own issue, so I created #74 for this.

jacobwilliams commented 4 years ago

I'm curious to know why the template work repo is under a different GitHub account? Not a good sign for the future... Why not put it here on the j3-fortran one?

certik commented 4 years ago

@jacobwilliams The repository that I linked to (https://github.com/certik/fortran-generics) was created long before this j3-fortran GitHub repository. So I just linked it. As we develop these ideas more, it should all happen here.

If you are talking about @tclune's repository at https://github.com/sourceryinstitute/generics, that repository was created by @tclune to more efficiently collaborate just on templates. As they make progress, I will make sure to update this j3-fortran repository with any big updates and proposals.

jacobwilliams commented 4 years ago

I was referring to the sourceryinstitute one. It just seems like it makes more sense to put that here.

certik commented 4 years ago

@jacobwilliams Yes, it would be nice to at least have the discussions here, and we can also move the repository under the j3-fortran github group.

cmacmackin commented 4 years ago

Just to add another proposal to the mix...

As I've reflected upon previously, one of the issues with templates in Fortran is how the type system really consists of four different aspects:

In most programming languages these would all be grouped together to define a single type, but in Fortran they are semi-independent. What's more, there are different approaches for what needs to be known at compile-time and what can be deferred to run-time. At one extreme is kind, which must be known at compile-time (even for parameterised derived types), and at the other is size/length, which can be deferred to run-time via allocatable and assumed-shape variables.

In C++ a single brief string can specify all of this information (e.g., double[10][20]), making it easy to template over all of it at once. In Fortran this would be more difficult. Currently, parameterised derived types (PDTs) attempt to provide some features along these lines for kind and size. While I haven't personally made use of them, its approach to parameterising size actually looks pretty good. However, parameterising kind is not very useful because all kinds must be known at compile-time. This means that we can't defer the kind until run-time, even for dummy arguments of procedures. It is this last bit which is really crippling, because it means that the user must write separate implementations of a procedure for each kind parameter value, making PDTs essentially worthless.

It would be nice if a new templating system could both fix this shortcoming and build on the current PDT syntax. I think there could be a relatively straightforward way to achieve the first of these: the introduction of parameterised procedures. The syntax could be something like the following:

subroutine example(a, b, c) parameters(k, l)
  integer, kind :: k
  integer, len :: l
  real(k), dimension(l), intent(in) :: a, b
  real(k), dimension(2*l), intent(out) :: c

  c(1:l) = a
  c(l+1:2*l) = b
end subroutine example

Type-bound procedures, finalisers, and abstract interfaces can also be made parameterised, allowing PDTs to be used in object-oriented manner. Unlike with PDTs, where the kinds get specified by the user when declaring a variable (or revert to a default value), for parameterised procedures the compiler would be required to determine the parameter values from the arguments which are passed in. If they are invalid (e.g, if the above subroutine were called with inconsistent kinds) then it should produce a compile-time error or (for len parameters, where this may not be possible) a run-time error.

It would then just be a matter of defining two additional sorts of type/procedure parameters, corresponding to type and rank. The exact syntax of this is a matter for further discussion, especially with regards to rank where I can't see an obvious approach. For types it could look something like this:

subroutine example(a, b, c) parameters(t, k, l)
  typespec :: t
  integer, kind :: k
  integer, len :: l
  t(k), dimension(l), intent(in) :: a, b
  t(k), dimension(2*l), intent(out) :: c

  c(1:l) = a
  c(l+1:2*l) = b
end subroutine example

It might be possible to restrict the type-spec somewhat by allowing some sort of "concepts" or "typeclasses" to be defined in advance, as suggested by @arjenmarkus in #29.

cmacmackin commented 4 years ago

Yes it would and more concisely. The reason I'm proposing parameterising procedures is it would fit in better with the existing parameterised derived types. If you parameterised the module as well as derived types, then that would create the question of which should be used.

On Mon, 11 Nov 2019, 17:37 Peter Klausler, notifications@github.com wrote:

@cmacmackin https://github.com/cmacmackin Would a parameterized module facility cover the same use cases?

— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/j3-fortran/fortran_proposals/issues/4?email_source=notifications&email_token=AB6ESPLDW3JRXZYJREKAIUTQTGJ4FA5CNFSM4JBFWSXKYY3PNVWWK3TUL52HS4DFVREXG43VMVBW63LNMVXHJKTDN5WW2ZLOORPWSZGOEDXRSVY#issuecomment-552540503, or unsubscribe https://github.com/notifications/unsubscribe-auth/AB6ESPJS2PSHFYVJSOWULIDQTGJ4FANCNFSM4JBFWSXA .

jacobwilliams commented 4 years ago

Can't we all just pretend PDTs never happened. I know I have. 😆

aradi commented 4 years ago

@cmacmackin I like your approach a lot, as it looks like an extension of the parameterized types.

What is not clear to me (in none of the presented approaches), in what scope the generated routines will be embedded? Do they have their own scope? How do we pass operators (e.g. assignment) if they are not implemented as type bound procedures?

Given the following hypothetical code:

module testmod
contains

  subroutine swap(a, b) generators(T, R)
    generator, type :: T
    generator, rank :: R
    T, dimension(R), intent(inout) :: a, b

    T, dimension(R), allocatable :: buffer

    allocate(buffer, mold=a)
    buffer = a
    a = b
    b = buffer

  end subroutine swap

end module testmod

module typedef

  type :: mytype
    integer :: a
  end type mytype

  interface assignment(=)
    module procedure assign_mytype
  end interface assignment(=)

contains

  subroutine assign_mytype(a, b)
    type(mytype), intent(inout) :: a, b
    a%a = b%a
  end subroutine assign_mytype

end module typedef

program testprog
  use testmod
  use typedef
  implicit none

  integer :: a(:,:), b(:,:)
  type(mytype) :: ta, tb

  call swap(a, b)    ! should generate swap with T=integer, R=2, everything OK.
  call swap(ta, tb)  ! Would it call assign_mytype at assignment???

end program testprog

Would it be possible, that the swap() routine calls the user defined assignment? How do we achieve that?

I think, it would be nice, if we could come up with a simple example (like the swap above) as a proof-of-concept test for generics. Then, every suggested approach should show how it would deal with it, so that we can discuss possible pitfalls more concrete.

cmacmackin commented 4 years ago

What is not clear to me (in none of the presented approaches), in what scope the generated routines will be embedded? Do they have their own scope? How do we pass operators (e.g. assignment) if they are not implemented as type bound procedures?

Does anyone know how other languages handle this? Here is one approach I've seen: https://nim-lang.org/docs/manual.html#generics-symbol-lookup-in-generics. So the Fortran equivalent would be for any generic interface identifier to wait to be bound until the function is called, whereupon it would search through the calling scope.

cmacmackin commented 4 years ago

@aradi I've thought some more about the scoping issue and have a proposal. Any calls to non-generic procedures in a parameterised function would use the scope of the parameterised module/procedure. If a generic operator/function is used then the compiler will search through the scope of the defining parameterised module and then the scope of the module useing/calling it. A parameterised procedure would be implicitely implicit none(external) (or else require that to be stated explicitly), to avoid any confusion. If it uses a generic interface which has not been defined within its own scope, that generic could be declared as follows:

generic :: function_or_operator_name

Because defined-assignment is already generic that wouldn't strictly be necessary in your example above. However, to give a more concrete example, I'll do it explicitly:

module testmod
contains

  subroutine swap(a, b) generators(T, R)
    generator, type :: T
    generator, rank :: R

    generic :: assignment(=)

    T, dimension(R), intent(inout) :: a, b

    T, dimension(R), allocatable :: buffer

    allocate(buffer, mold=a)
    buffer = a
    a = b
    b = buffer

  end subroutine swap

end module testmod
sblionel commented 4 years ago

I think a lot of us on the committee were disappointed that this got deferred, but pretty much everyone agreed it was important to get it right. The main problem was that there was not anything close to a consensus on an approach and there was real worry that we'd rush into a design that ultimately didn't meet enough needs. That we said we wanted to start work on it now and not wait for the next round of work-list decisions was unusual and important.

By all means, please submit papers with proposals. Ideally these should include examples of real-world problems and how the proposal would address them with code (or pseudo-code) samples. Many of us need to see these to understand the issues.