Japanese Subgroup GENERIC proposal

Interesting, but will it not be easy, if something like this can be done :

let :: my_t => [integer(*), real(*)] ! expanded by compiler to all possible 
                                     ! supported values internally
type(my_t), intent(inout) :: array(:) 

define once and use everywhere :grin:
edit : let is taken from github/fortran_proposal no: 279, 221

@JohnReid, that is not adequate.

Anyways, the broader feedback by the practitioners of Fortran in various forms (papers, forums such as comp.lang.fortran, Intel Fortran forum, this one, etc.) indicate a need for a language design for Generics that is clear and also compact (e.g. not verbose) and meets a certain minimum set of use cases that the design must cover:

  1. Generic subprograms
  2. Generic containers

Both of these are absolutely critical.

The paper by @hideto really only addresses use case #1 above with Generic subprograms. Its good point is a certain level of simplicity which is missing in the J3 Generics subgroup work thus far. However with aspects such as following:

  type(integer(int8, int16, int32, int64), real(real32, real64, real128)), intent(inout)

it really loses the “plot”, as far as I am concerned - it makes no sense to have such language design, it’s poor.

I hope J3 Generics subgroup gains some useful insight, which is basically some simplicity and compactness in syntax, from the paper by @hideto and incorporates them into their work. But that should be it with that paper.

Ultimately, from a language standard perspective, all indications are J3 is the contractor who does the work for WG5 and it is the J3 output which makes it into the standard, or nothing at all.

2 Likes

What a nightmare. I hope this does not pass into the language.

And what’s wrong with type(integer(*), real(*)) ?

These are not generics, more like “compile-time unions”. They allow the entity to be one of a bunch of types. Except they make much less sense than runtime unions, as they work only for dummy arguments (you are unable to, for example, have a derived-type component of such compile-time union). And they definetely are not generics. How do you implement a generic container with that design?

This is a solution that solves only one problem and leaving out all other problems. It is a “quick fix”, impossible to extend it further as the language developement progresses. Another one that will stay forever because “backwards compatibility”. I cheer for the US proposal so we can finally can use first-class containers in less than 10 years.

What I’ve understood is that the Japanese and the US proposals are not incompatible and that they could be both adopted (and that the Japanese one could be included in the US one).

In the ideal world. But in the real world, considering the efficiency of the body responsible for the language standard, I am worried that since it is a simple proposal, it will be a distraction and the actual generics will be pushed back to 202Z or the thermal death of the universe. We have all seen that while everyone is waiting for proper error handling and generic programming, some people decided that introducing functions like cosd that nobody needed or asked for is a more urgent matter.

It would be cool to be able to write real(kind=*) and fix the broken PDT design (because even if you parametrize the kind, you still have to copy-paste the code for the type-bound procedures for each kind you want to handle – golden medal to whoever designed this). But that is about all application that I see to this variant of “compile-time unions”.

For the same reason, I fear that two proposals combined will be so complicated that we will not see it ever in the language.

I am by-definition an opponent to non-essential improvements while the ship is sinking. Just give us the simplest generics that work and that are not limited to trivial cases.

Or incorporate basic list and dict/map into the language, then 99% for the use-cases of the generics will be gone.

8 Likes

I also think that the more fortranic way of expressing that would be with array syntax:

integer([int32,int64])
integer(integer_kinds) ! from iso_fortran_env
integer(:)             ! deferred-kind integer  

And that PDTs with type-bound procedures that respond to the PDT’s kind parameters would enable most use cases with almost no further extensions to the language.

3 Likes

For this example:

template tmpl(...)
  ...
  private
  public :: generic_name
  interface generic_name
    procedure tmpl_proc
  end interface
contains
  subroutine tmpl_proc(...)
    ...
  end subroutine
end template

I recommend using generic subprogram.

template tmpl(...)
  ...
  private
  public :: generic_name
contains
  generic subroutine generic_name(...)
    ...
  end subroutine
end template

I believe that there are certain cases that can only be done with templates. On the other hand, I would like you to use the generic subprogram where it is useful.
I believe that they are not competivive but have different purposes.

If the generic subprograms (Japanese proposal) exists, how will the template generics be adversely affected? There should be none. I repeat my point: generic subprograms and template generics are independent features with different purposes and implementations. I believe that the generic subprogram and template generics may cooperate with each other, but they do not compete with each other.

The purpose of the generic subprogram is to simplify an existing or currently written program without compromising performance. There are users who certainly want that, hence this proposal. For this purpose, the change to the programming style that generates and instantiate templates is not easily accepted. And for performance, the change to the non-bottomup-evaluation compilation that postpone type evaluation is not easily accepted.

2 Likes

I have heard the exact opposite from several users. They said that if it were that easy they would definitely want to use it. Since most of Fortran’s library procedures are currently generic procedures that support multiple types and ranks, the lack of such a feature is a nightmare for users writing libraries.

1 Like

Perhaps I was not understood right. I absolutely feel the same desperate need for generics or working PDTs. But listing them one-by-one every time is a very bad solution which hopefully will not make it.

My heart is closest to:

Just fix PDTs and this will be enough for now.

2 Likes

There are, more or less, four different ways to specify the kind values proposed in this discussion: 1) through the ISO arrays integer_kinds(:), real_kinds(:), etc., 2) through literal constants (1, 2, 4, 8,16 and so on), 3) through parameters (specified with selected_*_kind(), or from iso_fortran_env(), or 4) transferred from previously specified variables with KIND(arg) or TYPEOF(arg). Considering that, for example, the integer_kinds() array can be a super set of the ISO parameters (int8, int16, int32, int64), there probably needs to be a way to do combinations of those four options. This means the final result is going to be some odd mishmash of integers and scalars specified in various ways, perhaps with duplicates with some compilers but not others. I hope these complications don’t get out of hand.

As I stated above, just mandating that the KIND parameters be unique would go a long way to fixing the explosion of verbosity that some of us fear in the current proposals. Currently you can use TYPE to specify an intrinsic type but the choice of syntax makes it for the most part redundant. ie. for a REAL(REAL64) value you have to specify

type(real(real64)) :: a

If REAL64 and INT64 didn’t have the same value in most compilers (8 and as far as I know NAG is the only compiler that doesnt) then you could just do

type(real64) 

Then as @gronki implied you could construct PDTs (assuming the committee can find a way to fix the broken PDT facility) by just doing

type :: generic_ container(wk)
   integer, kind :: wk
   type(wk) :: a
end type

type(generic_container(real64)) :: areal
type(generic_container(int64))  :: anint

The issue with backwards compatability could be addressed by allowing all of the current values for the kinds below 16 to be the same as before to support folks that want to use literal constants (real(8) et). Then you modify ISO_FORTRAN_ENV parameters so they fall in specified decades (ie 20-29 would be integers, 30-39 would be reals, 40-49 would be logicals etc).

That gives you a facility for constructing generic containers etc that requires very little modification to the current syntax. However, the ultimate solution as I stated above is to make the things you need generic containers for (ADTs - lists, maps/dicts, queues, sets) etc an intrinisic part of the language on par with Fortrans current container class (arrays). To rush headlong into a template based solution without any research to determine what the real needs for generics is for Fortran programmers writing scientific applications is to me short sighted.

I don’t like the idea of conflating type with kind. Yes, that kind numbers are often shared across different types can lead to errors, but my initial reaction to using kind numbers as an indicator of type is unfavorable. I do agree that it would have been better to require disjoint kinds but am uncertain that it makes sense to retrofit that now, and exempting kinds <= 16 would just mean that the “new” kinds would rarely be used.

I think this means that each supported integer (or real, logical, character) would have two different kind values associated with it, the legacy one below 16 and the new unique one. This situation would then arise:

integer parameter :: ik = 4
write(*,*) ik, kind(1_ik)   ! 4 20

All of the TKR matching throughout the language would require that KIND values of 4 and 20 match, and any user-programs that match or check kind values would also have to take that into account. This could be localized into a new intrinsic, but existing code that simply compares integer values would fail.

My two cents here

Not only do I agree with this, I would said that we could in fact live with having integers and reals “unfortunately” sharing indicators. In the sense that it is ok to distinguish between the set of natural numbers and the set of real numbers and most of the time one would device algorithms on either one or the other… yes, in many cases one could use the same algorithm… but already going from 6 or more permutations to only two for the two main numeric kinds ( and if one wanted to include complex which can be derived from the former, then 3) it seems like a big step forward with less complications for the design… maybe?

:pray::pray::pray:

Using integer_kind instead of the wildcard * might be a good idea. Since this is only a syntactical issue, I don’t think it is necessary to draw a conclusion right now.

For RANK, I think that : is the only choice as the wildcard. But for KIND, I do not think that : is the best because the values of kind parameters are not always contiguous. So we choose * , which also has a small problem. In the current proposal, it can be written as follows for the character type, but this may be unnatural since the meaning is slightly different between the two *'s.

character(len=*, kind=*)

The first * means any integer value, and the second * means all integer values that the processor allows. In this regard, the following style may be superior.

character(len=*, kind=character_kind)

However, the programmer must always write “USE ISO_FORTRAN_ENV” in this case.

1 Like

Thank you @AniruddhaDas, but if the user wants to use only the above two instances, the generic subprogram will be also simple.

    type(real(wp), integer(wp)), intent(inout) :: array(:)

In both cases, wp can only be a constant.
Therefore, I don’t see how this improves anything, since the same number of types and kind parameters will appear.

The reason why the type declaration statement is so verbose is to handle verbose sets of library procedures easily. If the template/instantiation mechanism were used to write such a library, it would be more verbose.

I think it is dangerous that the kind value is not unique for each kind. This is especially true for the interface with C. Users write code such as “IF ( C_INT == INT32 ) …”