Fortran, Haskell, and generics

I have had fun learning a bit of Haskell, asking ChatGPT-4 to write programs for various tasks and testing them with the Glasgow Haskell Compiler (in my case on WSL2), at GitHub - Beliavsky/Haskell_and_Fortran: Haskell and Fortran programs to solve the same problems. Maybe Haskell can be used as an executable pseudocode that ChatGPT can translate to imperative languages.

A Haskell function to return a list of positions of changes in a list is short and works for any data type for which equality is defined:

-- The changePositions function takes a list of any type that supports equality testing as input.
-- If the input list is empty, it returns an empty list.
-- If the input list is not empty, it returns a list containing 0 followed by the positions of changes in the input list.
changePositions :: Eq a => [a] -> [Int]
changePositions [] = [] -- Base case: if the input list is empty, return an empty list.
changePositions xs = 0 : [i | (i, (x, y)) <- zip [1..] (zip xs (tail xs)), x /= y]
-- Recursive case: if the input list is not empty...
-- 1. Zip the input list with its tail, creating a list of pairs, where each pair consists of an element of xs and its successor.
-- 2. Zip this list of pairs with the list [1..], effectively assigning an index to each pair.
-- 3. Use a list comprehension to select the indices where a change occurred (i.e., where the two elements in a pair are not equal).
-- 4. Prepend 0 to the resulting list.

main :: IO ()
main = do -- test with lists of integer and strings
    print $ changePositions [3, 3, 6, 2, 2, 2, 1] -- Expected output: [0, 2, 3, 6]
    print $ changePositions ["a", "a", "b", "p", "p", "p", "o"] -- Expected output: [0, 2, 3, 6]

A Fortran function to do so is longer, and it must be repeated for each data type:

module list_mod
  implicit none
  interface change_positions
     module procedure :: change_positions_int, change_positions_char
  end interface change_positions
contains
  function change_positions_int(vec) result(pos)
    integer, intent(in)  :: vec(:)
    integer, allocatable :: pos(:)
    integer :: i,j,n
    n = size(vec)
    allocate (pos(n))
    if (n < 1) return
    pos = 0
    pos(1) = 1
    j = 1
    do i=2,n
       if (vec(i) /= vec(i-1)) then
          j = j+1
          pos(j) = i
       end if
    end do
    pos = pack(pos, pos > 0)
  end function change_positions_int

  function change_positions_char(vec) result(pos)
    character (len=*), intent(in)  :: vec(:)
    integer, allocatable :: pos(:)
    integer :: i,j,n
    n = size(vec)
    allocate (pos(n))
    if (n < 1) return
    pos = 0
    pos(1) = 1
    j = 1
    do i=2,n
       if (vec(i) /= vec(i-1)) then
          j = j+1
          pos(j) = i
       end if
    end do
    pos = pack(pos, pos > 0)
  end function change_positions_char
end module list_mod
!
program main
  use list_mod
  implicit none
  print*,change_positions([3, 3, 6, 2, 2, 2, 1])
  print*,change_positions(["a", "a", "b", "p", "p", "p", "o"])
end program main

output:

           1           3           4           7
           1           3           4           7

A group is working on a generics facility for Fortran. What would the generic Fortran code look like?

1 Like

I only have a phone right now so typing out a bunch of source would be a hassle, but you can see what they’ve been working on here: GitHub - j3-fortran/generics

What is currently on the anvil is something I do believe strongly most Fortranners will struggle with mightily, so much so adoption will be weak to nonexistent.

The better question to discuss is what should be the semantics and possible syntax for a generic algorithm such as this. Keep in mind, there are TWO uses for Generics in Fortran (some might argue this is adequate for the kind of specific-purpose computing Fortran seeks to serve):

  1. Generic algorithms
  2. Generic containers

The original post here squarely falls into the first use case.

So to answer the question I ask here, “what should be the semantics and possible syntax for a generic algorithm,” how I had approached was to develop KART (kind, attribute, rank, type) semantics that allows for semantics-by-substitution while providing the necessary blade-guards as per “strong concepts”. So with the example in the original post, here’s what I mean - note it is notional syntax for illustration purposes (please don’t hung up on it just because you may not like the syntax):

module list_mod
  implicit none
  template, object :: T  !<-- by default, an object template means any type with any of its KIND and LEN parameters
     rank => 1 !<-- T here specifies a RANK-1 object
  supports
     operator( /= ) !<-- the only stipulation is that the template is for an object that supports /= operation
  end template
contains
  function change_positions<T>(vec) result(pos)  !<-- templated subprogram
    <T>, intent(in)  :: vec  !<-- use of the template object; note no `( : )` since template is for rank-1 object
    integer, allocatable :: pos(:)
    integer :: i,j,n
    n = size(vec)
    allocate (pos(n))
    if (n < 1) return
    pos = 0
    pos(1) = 1
    j = 1
    do i=2,n
       if (vec(i) /= vec(i-1)) then
          j = j+1
          pos(j) = i
       end if
    end do
    pos = pack(pos, pos > 0)
  end function change_positions
end module list_mod

program main
  use list_mod
  implicit none
  print*,change_positions<integer>( [3, 3, 6, 2, 2, 2, 1] )                 !<-- default integer per current senantics
  print*,change_positions<character>( ["a", "a", "b", "p", "p", "p", "o"] ) !<-- len=1 given per current semantics
end program main

The main points, as per my illustration above, for any new Generics facility must address:

  1. Do simple things simply

  2. Compact code toward a generic algorithm,

  3. As similar a look-and-feel as what an author might write currently in Fortran,

  4. The generic algorithm can be templated using either objects or interfaces, here what is shown is with a template object,

  5. The template for an object provides generic means to characterize the kind, attribute, rank, type of the object. The above notional syntax is simply to illustrate
    a. any type with any of its KIND and LEN parameters
    b. but with a RANK of 1 because that’s what the author’s algorithm is based on,
    c. the template is declared such that the processor is informed the object shall support the /= inequality operator because the algorithm depends on this. Note all intrinsic types support this operation and derived types can be declared to support them.

  6. The specialization, the so-called compile-time instantiation, on the caller side is in situ, at least for simple cases as this one.

See an earlier discussion along the same lines.

1 Like

It would look something like

module list_mod
  implicit none
  template change_positions_tmpl(T, ne)
    private
    public :: change_positions
    type, deferred :: T
    interface
      function ne(lhs, rhs)
        type(T), intent(in) :: lhs, rhs
        logical :: ne
      end function
    end interface
    interface change_positions
       procedure :: change_positions_T
    end interface change_positions
  contains
    function change_positions_T(vec) result(pos)
      type(T), intent(in)  :: vec(:)
      integer, allocatable :: pos(:)
      integer :: i,j,n
      n = size(vec)
      allocate (pos(n))
      if (n < 1) return
      pos = 0
      pos(1) = 1
      j = 1
      do i=2,n
        if (ne(vec(i), vec(i-1))) then
          j = j+1
          pos(j) = i
        end if
      end do
      pos = pack(pos, pos > 0)
    end function
  end template
end module

program main
  use list_mod, only: change_positions_tmpl
  implicit none
  instantiate change_positions_tmpl(integer, operator(/=))
  instantiate change_positions_tmpl(character(len=1), operator(/=))
  print *, change_positions([3, 3, 6, 2, 2, 2, 1])
  print *, change_positions(["a", "a", "b", "p", "p", "p", "o"])
end program

You might be able to try this out with dev.lfortran.org.

1 Like

It looks very interesting to learn a computer language interactively via ChatGPT (as in the 1st post). I guess such kind of online service might appear in a very near future…

Btw, I think this code snippet (taken from the 1st post)

  interface change_positions
     module procedure :: change_positions_int, change_positions_char
  end interface change_positions
contains
  function change_positions_int(vec) result(pos)
    integer, intent(in)  :: vec(:)
    integer, allocatable :: pos(:)
    integer :: i,j,n
    n = size(vec)
    allocate (pos(n))
    if (n < 1) return
    pos = 0
    pos(1) = 1
    j = 1
    do i=2,n
       if (vec(i) /= vec(i-1)) then
          j = j+1
          pos(j) = i
       end if
    end do
    pos = pack(pos, pos > 0)
  end function change_positions_int

  function change_positions_char(vec) result(pos)
    character (len=*), intent(in)  :: vec(:)
    integer, allocatable :: pos(:)
    integer :: i,j,n
    n = size(vec)
    allocate (pos(n))
    if (n < 1) return
    pos = 0
    pos(1) = 1
    j = 1
    do i=2,n
       if (vec(i) /= vec(i-1)) then
          j = j+1
          pos(j) = i
       end if
    end do
    pos = pack(pos, pos > 0)
  end function change_positions_char

may also be written as one-liner in Fortran (can ChatGPT “compress” such a code…?)

:sunglasses:

program change_pos
     character, parameter :: clist(*) = ["a", "a", "b", "p", "p", "p", "o"]
     integer, parameter :: ilist(*) = [3, 3, 6, 2, 2, 2, 1]

     print *, pack([(j-1,j=1,size(clist))],mask=clist/=cshift(clist,-1) .or. [(j-1,j=1,size(clist))]==0)
     print *, pack([(j-1,j=1,size(ilist))],mask=ilist/=cshift(ilist,-1) .or. [(j-1,j=1,size(ilist))]==0)
end program
2 Likes

That gives output of

           0           1           2           3           4           5           6
           0           1           2           3           4           5           6

which is not what I want.

1 Like

You’re right, j==0 was a bug: see edit

I’ve also tried one-liner and now the code became slightly shorter (with a bit of cheating with cpp macro :gear:):

    integer,   parameter :: ilist(*) = [3, 3, 6, 2, 2, 2, 1]
    character, parameter :: clist(*) = ["a", "a", "b", "p", "p", "p", "o"]
    integer :: i

#define ChangePos(x) [ 1, pack( [(i, i=2,size(x))], x(2:) /= x(1:size(x)-1) ) ]

    print *, "i -> ", ChangePos( ilist )
    print *, "c -> ", ChangePos( clist )
end

I guess this “attribute” part will be very tricky in the design of Fortran generics, but I share the feeling that it is an important part (though currently have no idea how to do it…)

I agree entirely with the “tricky” part.

That’s the case with every programming that sets off with the ambition to chart a new path, whether IBM’s FORTRAN in the early 1950s with Backus et al. down to Zig very recently. Backus and co. not only were striving for a high-level language, first of its kind on scale, but also one that enabled significant compiler optimization, a massive, massive undertaking at the time. And they achieved big goals well under 5 years.

So what is the point!?

It’s that if there is will, there is a way.

Fortran has always had “compiler magic”, a very simple example is intrinsic functions with variadic arguments, “impossible” when it comes to “how to do it” even now for nonintrinsic (user) functions. But even back in the 1950s and 1960s, processors could handle.

Nothing with Generics for Fortran now is all that different conceptually from what Ada had in its standard by the 1990s.

What Fortran needs is proper compiler development guidance and support toward good but possibly highly difficult semantics that can be achieved, even against odds. And not “can’t do this, can’t do that”.

Gfortran can take a long time to compile code with an implied do-loop with a large upper bound. For example it takes about a minute on my PC to compile

program main
implicit none
integer, parameter :: n = 10**7
integer :: v(n)
integer :: i, j
do i=1,n
   v(i) = int(sqrt(real(i)))
end do
print*, pack([(j,j=1,size(v))],mask=v/=cshift(v,-1) .or. [(j-1,j=1,size(v))]==0)
end program main

Some other languages and Fortran libraries have a function that returns a sequence of consecutive integers. Using such a function, one can avoid an implied do-loop and still have concise code that compiles quickly:

module m
implicit none
contains
function seq(n) result(iseq)
! return [1, 2, ..., n]
integer, intent(in) :: n
integer             :: iseq(n)
integer             :: i
do i=1,n
   iseq(i) = i
end do
end function seq
end module m
!
program main
use m, only: seq
implicit none
integer, parameter :: n = 10**7
integer :: v(n)
integer :: i, j
do i=1,n
   v(i) = int(sqrt(real(i)))
end do
print*, pack(seq(n), mask=[.true., v(2:) /= v(:n-1)])
end program main
1 Like

Is your thread about how the Generics facility in Fortran might be for an arbitrary algorithm or the compact way to author that algorithm using the current language standard?