Japanese Subgroup GENERIC proposal

Maybe I’m misunderstanding something, but the language already has this feature. I.e.

subroutine s(a, b)
  type(whatever) :: a, b
end subroutine

a and b must be the same type.

Yes. I.e.

template tmpl(T)
  type, deferred :: T
contains
  subroutine s(a, b)
    type(T) :: a, b
  end subroutine
end template

a and b will have to be the same type. Even the Japanese proposal has this aspect. I.e.

generic subroutine s(a, b)
  type(T, U, V) :: a, b
end subroutine

a and b could be type either T, U, or V, but they must both be the same type.

If you want either (or both) of the arguments to be polymorphic, you have to do a run-time check, and we already have that too. same_type_as.

So the declarations

type(T, U, V) :: a, b

and

type(T, U, V) :: a
type(T, U, V) :: b

are different? In the latter case, there would be nine combinations in the product of the sets, right?

It does not have the feature with class() declarations. The class() declarations are required with type bound procedures and extended types. In the case of the class() declarations, it is the same whether they are on a single line or on separate lines.

The reason I brought up this issue is that I think it is a mistake the way fortran does the class() declarations in this respect. The language could help the programmer avoid mistakes more than it currently does, and the resulting code (e.g. within nested select type constructs) is more verbose than necessary. I’m hoping the generic proposals do not make this same mistake.

Yes,

type(T, U, V) :: a
type(T, U, V) :: b

allows 9 different combinations of types of a and b.

Using the class keyword says that the object is polymorphic, that it, its type varies at run time and is always an extension of the declared type. The declaration

class(T, U, V) :: a, b

says that a and b both have declared type T, U, or V. It does not say that the dynamic types are the same.

Exactly.

This is why generics is not reusing the abstract derived type with deferred type-bound procedures as the mechanism for specifying “my algorithm needs a procedure with this interface”. Now you can say “I need a procedure where these two arguments have the same type, even though I don’t know what type that is yet”. I.e.

template example(T, F)
  type, deferred :: T
  interface
    function F(x, y)
      type(T), intent(in) :: x, y
      type(T) :: F
    end function
  end interface
contains
  subroutine foo(x, y, z)
    type(T) :: x, y, z
    z = F(x, y)
  end subroutine
end template

Hello everyone.

I think we need to discuss conceptual issues first.

The Japanese proposal is being actively discussed in WG5, but what we want to avoid is “Fortran has two ways of expressing generics/templates”.

Generics is characterized by the use of data types to-be-specified-later (deferred) and by the fact that they are instantiated [1]. In this sense, the proposed ‘generic subprogram’ is not a generics. Therefore generic subprogram and template generics are definitely different and should not be one.

The generic subprogram is a means to write down the generic procedure directly. I do NOT think It should be written as if it were generating and instantiating a template.

[1] Wikipedia: generic programming
(https://en.wikipedia.org/wiki/Generic_programming)

2 Likes

Thank you FortranFan

My answer described in the latest version of the proposal seems more simple.

generic function foo(x)
  ! does the following expand to 2, 4 and 2, 6 
  type(mytype(2, 4), mytype(2, 6)), intent(in) :: x 
  integer :: foo
  ...

This is easier to understand if we think of it this way. If there were no generic subprogram and only using the current Fortran, how would it be written? It would be as follows.

interface foo
  module procedure foo_1
  module procedure foo_2
end interface
contains
  function foo_1(x)
    mytype(2, 4), intent(in) :: x 
    integer :: foo
    ...
  end function foo_1
  function foo_2(x)
    mytype(2, 6), intent(in) :: x 
    integer :: foo
    ...
  end function foo_2

The generic subprogram foo is a subprogram that simply combined specific subprograms foo_1 and foo_2.

@hideto ,

Welcome to this forum and thank you very much for your great work on your proposal. Please continue pushing the fundamentals of your proposal forcefully for it, as I have stated upthread, strives for a certain simplicity and compactness which is absolutely critical for Fortran given how important is Generics toward continued and perhaps growing practice of Fortran in scientific and technical computing.

Please note in my comment above, I had made clear it is illustrative syntax. That is, whether the actual syntax is as you propose now

..
type(mytype(2, 4), mytype(2, 6)), intent(in) :: x
..

or what I showed with

..
type(mytype(k1=2, k2=<4,6>), intent(in) :: x  !<-- note this was illustrative only
..

it is still a matter of syntactical variation only. The semantics is effectively the same in that there is a compact generic type declaration mechanism which allows a program author to convey succinctly a list of specific KINDs (and later RANKs) to be supported by the generic subprogram. This has to be top priority.

Once there is agreement on such semantics that permits compact instructions, the details of the syntax can be worked out such that the compiler implementors and the Community aim for some consensus in terms of code readability and ease/clarity of parsing, etc.

I don’t think any one person - neither you and especially not me - can lay claim that one form of syntax is better than or more simple the other.

1 Like

I’m somewhat hesitant of including all types inside a single variable declaration.

The statements like REAL(REAL32,REAL64,REAL128), RANK(0), INTENT(IN) :: X will need to be modified in future if new types are needed by the user.

This would create lot of git-diff noise, and require more lines to be changed.

We have some solutions for that issue.

If the new type is a derived type, you can define the type in your module and use the type name using the USE statement, as follows.

generic subroutine sub1(x)
    use users_module, only: users_type
    type(real(real32, real64, real128), users_type), rank(0), intent(in) :: x
    ...

The user can use generic subprogram sub1 for the new type users_type defined in users_module. Note that the user must recomple sub1 every after recompiling users_module. If you want to avoid recompiling of sub1 after compiling users_module, select the template generics.

If the new types are intrinsic types, it is recommended that all possible types and ranks be written down in advance, as follows:

generic subroutine sub1(x)
    type(real(*), complex(*), integer(*)), rank(:), intent(in) :: x
    ...

Here, ‘*’ means all kind type parameters for the intrinsic types and ‘:’ means all rank values, supported by the processor. When written in this way, the generated library tends to be very large because it contains the code for all specific procedures, but the size of the user program is the same as before because only the specific procedures that are actually used are selected and linked to the user program.

The last solution is to keep the old generic subprogram and add a new generic subprogram with the same name.

!!  Old sub1, which does not require recompilation. 
generic subroutine sub1(x)
    real(real32, real64, real128), rank(0), intent(in) :: x
    ...
end subroutine

!!  Can be placed in a different place or in a different file.
generic subroutine sub1(x)
    type(new_type1, new_type2), rank(0), intent(in) :: x
    ...  !! Can be either a copy or a different code from the old sub1.
end subroutine

This is not a proposed new mechanism. In Fortran 90 and later, a generic name can be redefined to add its specific entities.

First of all, it is important to note that the term ‘generic’ in the generic subroutine does not mean the generics proposed by the generics subgroup; it is the term ‘generic’ of ‘generic name’ or ‘generic identifier’ used in Fortran 90 and later. So it does not use the template and instantiation model but uses the specific procedure/generic identifer rule.

I don’t think so. Taking names inside the construct (x, y, T, U, REAL32, etc.) outside brings up a nasty scoping rule problem. For example, if the parameter REAL32 is defined inside the subroutine printPair, it cannot go outside.

In general, generic subprograms can easily be converted equivalently to a pair of a generic interface block and specific subprograms. For example,

generic subroutine printPair(x, y)
  type(REAL32, REAL64) :: x
  type(INT32, INT64) :: y
  print *, "Pair: ", x, y
end subroutine

can be converted to a pair of a generic interface block printPair and pseudo code for four specific subprograms:

interface printPair
#FORALL $T$=REAL32, REAL64
#FORALL $U$=INT32, INT64
  module subprogram printPair$T$$U$
#END FORALL $U$
#END FORALL $T$
end interface
#FORALL $T$=REAL32, REAL64
#FORALL $U$=INT32, INT64
subroutine printPair$T$$U$(x, y)
  type($T$) :: x
  type($U$) :: y
  print *, "Pair: ", x, y
end subroutine
#END FORALL $U$
#END FORALL $T$
1 Like

From the perspective of kernel programming, templates should be the preferred way to implement generics:

[Introduction | SpringerLink] (on page 14 in the printed book):

“Kernel code has certain restrictions to allow broader device support and massive parallelism. The list of features not supported in kernel code includes dynamic polymorphism, dynamic memory allocations (therefore no object management using new or delete operators), static variables, function pointers, runtime type information (RTTI), and exception handling. No virtual member functions, and no variadic functions, are allowed to be called from kernel code. Recursion is not allowed within kernel code. “
“…”
“The rest of C++ is fair game in a kernel, including lambdas, operator overloading, templates, classes, and static polymorphism. “

Even if it will be very hard to implement, the effort could be worth it on a long-term basis.

I am going full risk (resp. fun) myself doing early kernel programming using Coarray Fortran paired with coreRMA techniques (i.e. SYNC MEMORY), also with the possibility of being (completely) wrong. But also with a certain prospect of using the same Fortran kernel codes to implement an algorithm as Von-Neumann (CPU) as well as the corresponding Data Flow (FPGA and others in the future) representation. Or, with other words, to do Data Flow programming on a Von-Neumann architecture already: Algorithms are fully implemented as kernels (inside Fortran’s BLOCK construct), and kernels are grouped into module procedures. Subroutines/functions can hardly be used to implement such algorithms. (In fact, I did start this with the kernels implemented inside subroutines/functions, the coding became a mess.) : GitHub - MichaelSiehl/Spatial_Fortran_1

From what I can see, no other programming language couldn’t come even close to Fortran yet. You may see also this recent discussion at the Intel Forum: https://community.intel.com/t5/Intel-Fortran-Compiler/ifx-ifort-Coarray-Teams-are-still-not-properly-implemented-with/td-p/1470752

As John wrote, the TYPEOF statement can be used for the entity that inherits the type and the kind parameter form another entity. Your example can be slightly modified as follows.

  integer(int32) generic function QuickSortPartition(array, istart, iend) result(ipivot)
    implicit none

    !
    ! Arguments
    !

    integer(real32, int8, int16, real64, int32, int64,  real128), intent(inout) :: array(:)
    integer(int32), intent(in) :: istart, iend

    !
    ! Data
    !

    integer(int32) :: i, j
!!! modified
!!!    integer(int8, int64, real32, real64,  int32, real128) :: pivotVal
    typeof(array) :: pivotVal

    !
    ! Code
    !

    ! Set the pivot value to the last number in array
    pivotVal = array(iend)

    ! Swap elements until all elements left of pivot, are smaller than pivot,
    ! and all elements right of pivot, are bigger than pivot
    i = istart - 1
    do j = istart, iend - 1
      if (array(j) < pivotVal) then
        i = i + 1
        call Swap(array(i), array(j))
      end if
    end do
    call Swap(array(i + 1), array(iend))

    ! Set pivot index and return it
    ipivot = i + 1
  end function

As a result, the only extensions from conventional Fortran are the addition of the keyword ‘generic’ and the multiple-type declaration statement for the variable array.
Everyone feels differently, but I don’t think this expansion is difficult.

There are few things that I don’t find to be user-friendly …

  • The generic variable declarations for array and pivotVal are extremely verbose:

Using TYPEOF statement, the declaration for pivotVal became not verbose.
I believe the declaration for array is not verbose either. Thanks to this feature, we only need to write one subprogram instead of writing 7 copies for 7 types: real32, int8, int16, real64, int32, int64 and real128.

  • It is hard to spot errors:

I do not think so. The behavior of the compiler for generic subprograms is no different than before. The compiler will still produce the file name and line and column numbers where the error was detected.

One concern is error messages for errors that depend on the type of entity declared in the multi-type declaration statement. It may be necessary to indicate the type name in addition to the file name and line number to locate the error.

  • It is hard to modify code:

I think this is quite the opposite. The aim of the generic subprogram is to improve development productivity that includes reducing the cost of code modification.

If we write the example program above without the generic subprogram feature, the code size becomes 7 times larger to write down all specific subprograms for the 7 types of the argument ‘array’. In more general case, multiplying type and rank variations can result in dozens or hundreds of specific subprograms. The generic subprogram has the effect of compacting such large and redundant code. And that in turn facilitates code modification and increases program productivity.

Coding such large and redundant code may not be so difficult if we use tools such as fypp, an interigent editor, and sed, Perl, Python, etc. However, considering the lifetime productivity of the program, taking into account future debugging, performance tuning, feature additions, and other various maintenance efforts, it does not seem like a good choice.

1 Like

There is one potential stumbling block for the Japanese Proposal that relates to using the intrinsic kind parameters (int32, real32 etc). Most compilers assign the same values for the kind parameters for equivalent length integer and real types. ie int32 and real32 both have a value of 4. I guess the compiler can go by the label (int32 etc) as opposed to the value to decide what type you are requesting but on the surface this looks like the compiler developers would be forced to modify their codes to make the values unique (say int32 = 4 and real32=14 etc). I think this would be a good thing since it opens up other possibilities with PDTs but the “breaks backward compatability” mantra would make such a mod impossible.

I don’t quite understand this declaration. Is integer a typo there?

A general problem with (current) fortran is that it is difficult to write code that works for all supported integer, real, logical, and possibly character kinds. There is the intrinsic integer_kinds(:) array that has all the values, and len() of that array gives you the number of kind values, but then it is still difficult to write portable code that uses that information. In this proposal, I think there is supposed to be a declaration like integer(*) that expands automatically to all integer kinds. But then, how would one declare an entity that can be any of, say, real, integer, and logical types that encompasses all the kinds of all three types?

For example, intrinsic functions like dot_product() and matmul() work with all kinds of all three of those types. How can a programmer easily write a generic subroutine that has that same generality?

This is not a problem in the Japanese Proposal because an alternative kind value always appears with a type, for example,
generic subroutine s(arg)
type(integer(int32,int16), real(real32,real64)) :: arg

I think you just made my case why unique values for the kind parameters should have been mandated by the committee. Do you really think you are going to attract new users to the language when the committee keeps adding layer on top of layer of verbosity to an already verbose language. Really? Frankly, there is no reason for the intrinsic kind parameters in ISO_FORTRAN_ENV to have a value at all. They are just labels that the compiler could parse and use to define the appropriate type without having a value. Obviously you would need some kind of value returned by the SELECTED_xx_KIND functions but even then the number of codes that need that kind of fine grain control over precision are not as great as the committee assumes there are.I also think the issue with backward compatability is something of a red
herring if KINDS are used in what I consider a correct manner. No competent programmer needs to know the explicit value of any KIND parameter. I doubt there is a lot of code written by someone who knows what they are doing that has a lot of

If (INT32 == 4) Then

statements in them.

Even with values defined by SELECTED_XX_KIND statements. you are only going to test to see if two variables have the same kind. Again that should not require you knowing the values of the parameters. ie

If (KIND(A) == KIND(B)) then

I guess the only reason that REAL64 has a value of 8 etc was to appease the people who are still trapped in the stone age and insist on using

real*8 
or
real(8)

On the other hand, nothing forces you to use the values per se at all…

There are popular standard conforming compilers that do not follow that convention.

While you may not see things like if(INT32==4), you might well see things like if( storage_size(1_ik)==32). The only constraint in the language that comes to mind is that REAL and COMPLEX types must share the same KIND values. It doesn’t require those KIND values to have specific values, just that they are the same for the two types.

When aliasing entities (through pointers, with TRANSFER, EQUIVALENCE, etc.), it would sometimes be nice to be able to easily find the matching-size KIND values. For example, if I want a logical KIND value that matches a real KIND value specified with the parameter WP, how does one do that? The expression storage_size(1.0_WP) gives me the number of bits, but then how do I select the correct logical KIND with that same number of bits?

I am sorry I overlooked that error in the program. Thank you John.

If all alternatives have the same intrinsic type, the type specifier can omit TYPE, as follows.

  integer(int8, int16, int32, int64), intent(inout) :: array(:)

However, if alternatives have a derived type or have two or more types, the type specifier shall have TYPE, as follows.

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

Please see the latest specifications for more information:
GenericSubprogram15.pdf

I am sorry to say this but, this is really verbose. Cannot some aspects of the US proposal be combined with this. Like the code below:

generic function QuickSortPartition{T}(array, istart, iend) result(ipivot) 
   ! {} bracket have been used instead of the <> as in c++.
    implicit none

    type, deferred :: T                      !<- deferred argument taken from US proposal 
    Type(T), intent(inout) :: array(:)
    integer(int32), intent(in) :: istart, iend

    integer(int32) :: i, j
    typeof(array) :: pivotVal

    ! Set the pivot value to the last number in array
    pivotVal = array(iend)

    ! Swap elements until all elements left of pivot, are smaller than pivot,
    ! and all elements right of pivot, are bigger than pivot
    i = istart - 1
    do j = istart, iend - 1
      if (array(j) < pivotVal) then
        i = i + 1
        call Swap(array(i), array(j))
      end if
    end do
    call Swap(array(i + 1), array(iend))

    ! Set pivot index and return it
    ipivot = i + 1
  end function

and use the above function as:

QuickSortPartition{T:real(wp)}(array, istart, iend) ! wp is working precision
QuickSortPartition{T:integer(wp)}(array, istart, iend)

and as for restricting type to integer or real maybe some form of predefined requires can be used in some way

! no need for kinds here as these can be left to compilers
requires valid_reals()
requires valid_integers()

so the above couple of lines will become

generic function QuickSortPartition{T}(array, istart, iend) result(ipivot) 
   ! {} bracket have been used instead of the <> as in c++.
    implicit none
    requires valid_reals()         
    requires valid_integers()    

    type, deferred :: T        

or something like what donev suggested here, file monoid_m.f90, so

requires vtypes => valid_types(T) ! no need for type, deferred :: T , already defined in there
! and 
type(vtypes%T), ...

maybe :grinning:

The Japanese proposal allows for the use of * to represent a list of all kinds supported by the processor for the type. The above example becomes

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