Update on Fortran Templates

I wrote up a blog post discussing the progress made at last weeks committee meeting on the upcoming template feature for Fortran. Read all about it at:

26 Likes

This is really cool! Are there any more examples somewhere? I’d like to study this some more to understand how it would fit into some of my use cases.

https://j3-fortran.org/doc/year/22/22-165.txt and URLs therein.

I’m struggling to get my head around this approach. When there is more than one template interacting, I tend to lose the thread of what’s going on. Maybe I need to type some of these examples out myself to let it sink in…

I’m also trying to get a sense for the experience of being a user of a template library. Having to instantiate the template myself feels unusual, but I can see the benefit for compile-time checking.

Of the examples I’ve understood so far, the most compelling are matmul and vector. One classic generics use-case that I don’t see is a “stringify” template.

Overall, it’s been a very interesting read! I’m curious if there’s been any feed back (or pushback) from implementors yet.

2 Likes

One of this blog post’s commenters seems to strongly disagree with the proposed design.

1 Like

There are more examples in the J3 papers. I can send them to you if you’d like. There are also plenty of examples in the repository where we were developing this (GitHub - j3-fortran/generics). Note that many of them are from earlier designs, and they’re not all that well oganized. That may be an effort I take on at some point.

1 Like

Someone should review the examples for completeness, ie. in the vector class example a MAX_CAPACITY parameter is referenced but I don’t see it defined. Granted these are just examples, but I feel they should be as close to bug free working code (assuming a compiler supported templates) as possible.

You’re not alone. Many of the examples I didn’t write take me a while to work through. It’s clear we’re going to need some suggested patterns and style guides, and lots of practice.

The explicit instantiation is necessary because there are (quite often) cases where not all the template parameters can be inferred.

By this point, it seems like “stringable” would be a useful restriction block, but the only thing a template would do is call the provided procedure.

There are some on the committee who think we didn’t need to be so verbose, but we have use cases that really do need it. There was some hesitation about the “identical instantiate parameters refer to the same instantiation”, but a couple of implementors in the subgroup think it’s workable.

Can you elaborate on the other languages that may of influenced the Fortran Templates? I’m sure C++ is one, but at least superficially, Ada has long experience with implementing generics that might be interesting to study.

C++ was a strong influence, but also a good example of why we wanted to make sure we didn’t do it wrong the first time. We did get some suggestions about how Ada did it, but found their design not to fit well into Fortran. We also drew inspiration from Rust, Haskell, Java, and possibly some others. The thing we knew we wanted was the ability to verify that a template is valid/self-consistent before ever being instantiated.

4 Likes

What is the difference between “type, deferred :: T” and “type :: T;end type”? I have also seen a “type, template :: T”, but cannot find it anymore.
It seems that the J3 example github repository only contains the “type :: T;end type” variant? What is the reason for the “end type” addition (or put it another way, what can be put inside the block)?

1 Like

We’re still exploring some aspects of the syntax. We were originally thinking the syntax for type template parameters would mirror type definitions and might eventually be able to specify components and type-bound procedures. Since we’re not allowing that at this time, the type :: T; end type seemed unnecessarily verbose, and a type, deferred :: T was a recent suggestion that we haven’t had a chance to use in any examples.

2 Likes

Thanks a lot for your hard work bringing generics to Fortran!

I like the type, deferred :: T syntax, that seems the most in line with the current language.
To access specific functions/properties, maybe, the same syntax could be used to refer to an abstract class: that’s already a template, is it?

I’m thinking of something like:

type, abstract :: T
class, abstract :: T

Or on the same line,

class(abstract_class), deferred :: T

where of course the abstract type abstract_class would be defined somewhere else, inside or outside the template, so the templated code would know there is, say, an overridden operator, or a type-bound function of whatever name that could then be used inside the templated routines?

I think exploring this avenue may be promising for allowing polymorphic/extensible types in templates. We’re not really planning to work on that until after the current design has been fully integrated into the standard, but we’ll try and remember this suggestion.

1 Like

Absolutely, it’s a very much needed feature for Fortran. I’m no regular user of generics, just tossing some ideas out here to see how they would fit with the future standard.

Actually, another thing I think would be well fit to Fortran generics (along with templated array rank that’s already been outlined) would be to template numeric variables. In the end, Fortran already converts between all integer and real types, so it would be mostly convenient to have some syntax that tells the generics routine that will be a number. In other words a wrapper for all integer and real kinds. Imagine something like:

type, numeric, deferred :: T
type, deferred :: real(T)
type, deferred :: integer(T)
type, deferred :: complex(T)

So the compiler would by default enable all intrinsics operations with them (think +,-,*,/,** but maybe also other intrinsics like math functions…what do you think? IMHO Fortran’s going to be number crunching-centered anyways, so probably 80% of its templated codes would involve numbers…

2 Likes

We will explore ways to provide shorthands, but for now we wanted to make the feature as generally applicable as possible. For example, would it be possible to create a derived type that behaves like (i.e. supports all the same operations as) an intrinsic numeric type and use it with such a template? Would you really want to prevent that? It seemed like an arbitrary and unnecessary restriction to say a template can only work with intrinsic types, so we didn’t feel compelled to support such a thing for now. Not saying it won’t be possible later, just not initially.

In understand and fully agree on the roadmap: given Fortran’s slowness, the more general the approach is defined since the beginning the better.

As I said, take my comments just as “discourse”, I very much appreciate the work you’re doing!. The numeric thing could just be some syntactic sugar that simplifies the programmer’s life, by avoiding him to define/list all overloaded operators if they’re already intrinsic to the type.

Think about most *PACK libraries that have 2x real and 2x complex versions, the source code for them (the complex ones may be a bit more complex, goes without saying) could be reduced by almost 75% by enabling all numeric intrinsics by default!

1 Like

By the time Fortran generics are implemented by mainstream compilers and adopted by most *PACK libraries, Fortran itself and these libraries may have already been abandoned.

The LINPACK codes were developed orginally from a single source. A macro processor called TAMPR was then used to generate the four output cases corresponding to real, double precision, complex, and complex*16 (the latter being an extension to the fortran standard). In addition to the declarations, and the subprogram names (e.g. SDOT, DDOT, CDOT, ZDOT), literal constants were also converted. I’m not certain, but I don’t think the earlier EISPACK or the later LAPACK were done that way.

I think this is quite an elegant design, especially for Fortran, all things considered. type, deferred is a nice little syntax. It’s obviously a little verbose, but then, isn’t everything in Fortran. There’s probably some bikeshedding to be done around names – why not constraint or requirement instead of restriction? – but I can see the actual design working.

I do agree with @FedericoPerini, that having some intrinsic restrictions predefined is going to be essential for any kind of serious numerical work. Otherwise, every single code is going to have their own numeric restriction, along with comparable, equatable, assignable, etc. Even in the examples, there is comparable and orderable! (I know they’re slightly different, but this is exactly the sort of pseudo-replication we’ll get).

I wonder if there is a way to have default arguments for the restrictions? For example, for comparable, it currently looks like the user has to supply the type T, an equals function, and a less_than function. If T already has the operators == and < defined for T, is there some way the restriction could pick those up automatically, while still allowing users to supply them if they’re free functions or named differently?

And building on that, how does one express a restriction that T should have type-bound procedures? Is it like this?

restriction stringable(T, to_string_interface)
  type :: T
  contains
    procedure(to_string_interface) :: to_string
  end type T

  interface
    function to_string_interface(T)
      class(T), intent(in) :: T
      character(:), allocatable :: to_string_interface
    end function to_string_interface
  end interface
end restriction

Lastly, how does one express a template that’s rank-agnostic? One of the pain points of the current assumed-rank stuff is that you basically can’t do anything with an assumed-rank object, and having overloads for each combination of type, kind, and rank gets boring fast, especially when all the bodies are essentially exactly the same.

Off-topic: An unrelated thing this highlights is the need for a non-block associate statement. In the sort example, there’s this bit:

          associate( &
              pivot => (n/2 + 1), &
              indices => [(i, integer :: i = 1, n)])
            associate( &
                less_than_pivot => array < array(pivot), &
                greater_than_pivot => array > array(pivot))
              associate( &
                  indices_less_than_pivot => pack(indices, less_than_pivot), &
                  indices_greater_than_pivot => pack(indices, greater_than_pivot), &
                  indices_equal_pivot = pack( &
                      indices, .not.(less_than_pivort.or.greater_than_pivot)))
                associate( &
                    sorted_less_than => sorted_order( &
                        array(indices_less_than_pivot)), &
                    sorted_greater_than => sorted_order( &
                        array(indices_greater_than_pivot)))
                  sorted_indices = &
                        [ indices_less_than_pivot(sorted_less_than) &
                        , indices_equal_pivot &
                        , indices_greater_than_pivot(sorted_greater_than) &
                        ]
                end associate
              end associate
            end associate
          end associate

which would surely be so much nicer as:

          associate pivot => (n/2 + 1)
          associate indices => [(i, integer :: i = 1, n)]
          associate less_than_pivot => array < array(pivot)
          associate greater_than_pivot => array > array(pivot)
          associate indices_less_than_pivot => pack(indices, less_than_pivot)
          associate indices_greater_than_pivot => pack(indices, greater_than_pivot)
          associate indices_equal_pivot = pack(indices, .not.(less_than_pivot .or. greater_than_pivot))
          associate sorted_less_than => sorted_order(array(indices_less_than_pivot))
          associate sorted_greater_than => sorted_order(array(indices_greater_than_pivot))
          sorted_indices = &
                        [ indices_less_than_pivot(sorted_less_than) &
                        , indices_equal_pivot &
                        , indices_greater_than_pivot(sorted_greater_than) &
                        ]
4 Likes