Prototype implementation of Fortran generics in LFortran

Ref: the current paper on syntax for Generics viz. https://j3-fortran.org/doc/year/23/23-155r1.txt

Consider the example provided:

MODULE A

   REQUIREMENT R(T,F)
      TYPE, DEFERRED :: T
      FUNCTION F(x, i) RESULT(y)
         TYPE(T) :: y
         TYPE(T), INTENT(IN) :: x
         INTEGER, INTENT(IN) :: i
      END FUNCTION F
   END REQUIREMENT R

   TEMPLATE B(T,F,C)
      REQUIRES R(T,F)            ! provides interface for deferred F
      TYPE, DEFERRED :: T        ! redundant decl of deferred type T
      INTEGER, CONSTANT :: C(..) ! deferred rank constant
   CONTAINS
      SUBROUTINE SUB1(x)
         TYPE(T), INTENT(INOUT) :: x
         x = F(x, SUM(C))
      END SUBROUTINE SUB1
      SUBROUTINE SUB2(x)
         TYPE(T), INTENT(INOUT) :: x
         x = F(x, MAXVAL(C))
      END SUBROUTINE SUB2
   END TEMPLATE B

END MODULE A

MODULE B
  USE MODULE A

  INSTANTIATE B(REAL, OPERATOR(*), [3,4]), ONLY: &
              & tot_sub1 => sub1
  INSTANTIATE B(REAL, OPERATOR(+), [3,4]), ONLY: & ! different instance
              & max_sub1 => sub2

CONTAINS

   SUBROUTINE DO_SOMETHING(x)
      REAL, INTENT(INOUT) :: x

      x = 2.
      CALL tot_sub(x)
      PRINT*,'TOT: ', x ! expect 2. * (3+4) = 14.

      x = 3.
      CALL max_sub(x)
      PRINT*,'MAX: ', x ! expect 3. + max(3,4) = 7.

   END SUBROUTINE DO_SOMETHING

END MODULE B

This really feels strong concepts gone haywire. And a complete departure from the initial premise laid for the design which was semantics via substitution in this paper.

Say one has already authored or has to author a subroutine in Fortran to compute a quantity
y = x*{\sum}_{i=1}^nc, why reinvent anything other than y = x*sum(c) and end up at x = F(x, SUM(C)). And when the standard states the multiplication operator * is stipulated for the intrinsic types of REAL and INTEGER, to obfuscate the operation with a generic F makes no sense.

For the example shown, an option with the current standard is

module ops_m
   generic :: tot_sub => tot_sub_real ! and other specific implementations
   generic :: max_sub => max_sub_real ! and other specific implementations
contains
   subroutine tot_sub_real( x, c )
      real, intent(inout) :: x
      real, intent(in) :: c(:)
      x = x * sum(c)
   end subroutine
   subroutine max_sub_real( x, c )
      real, intent(inout) :: x
      real, intent(in) :: c(:)
      x = x + maxval(c, dim=1)
   end subroutine
end module

For such an example, using the semantics via substitution to minimize code duplication while adhering to strong concepts, one simply needs to inform the processor the template involves a generic type that supports the three operations of addition, multiplication, and comparison. That is it. Anything more than that is an absolute overkill. Notionally, one might illustrate this pseudosyntax like so:

module ops_m
   template, object :: T1
      type => numeric_type  !<-- look in the standard for SUM intrinsic
      kind => *  !<-- notional syntax to convey any kind for the stated types
   end template
   template, object :: T2
      type => < real, integer > !<-- look in the standard for MAXVAL intrinsic 
      kind => *  !<-- notional syntax to convey any kind for the stated types
   end template
contains
   subroutine tot_sub<T1>( x, c )
      <T1>, intent(inout) :: x
      <T1>, intent(in)    :: c(:)
      x = x * sum( c )
   end subroutine
   subroutine max_sub<T2>( x, c )
      <T2>, intent(inout) :: x
      <T2>, intent(in)    :: c(:)
      x = x + maxval( c, dim=1 )
   end subroutine
end module

Now something like along such lines will follow the semantics via substitution principle and allow a practitioner for take existing programs that work for one or a few types and genericize them easily while cutting down on verbosity by reducing code duplication and avoiding unnecessary complications by first writing too broad a template which then needs to be specialized later for actual use.

2 Likes