Map vs elemental procedures

The following came up during a short discussion on @milancurcic 's blog.
https://medium.com/modern-fortran/map-filter-reduce-in-fortran-2018-e40b93668ed9
I thought it will be a good starting point for me on this discourse.

Elemental feature is seen as a drop in replacement of map functions. However, I see, coming from some lisp background, a major difference between the two while dealing with multidimensional arrays. While Fortran indiscriminately applies same scalar function to all elements, map traditionally works on one dimension at a time.

Thus, defined a function: f(x) = 2x, both f([x1,x2,x3]) and map(f,[x1,x2,x3]) give [2x1,2x2,2x3]. However, if the f is so defined that f(x) = [x,2x] then f([x1,x2,x3]) is meaningless, while map(f,[x1,x2,x3])
is still applicable and gives: [[x1,2
x1],[x2,2x2],[x3,2x3]]. Interestingly, I find myself facing the second situation more often than first. There is even more generalization taking cue from some of the fortran intrinsics: map(f,array[,dim]). (I’m a big fan of SPREAD intrinsic, BTW.)

2 Likes

Fortran never has been, nor will ever be, a purist mathematician’s delight or a rigorous functional programmer’s ideal tool.

Nonetheless, with f(x)=[x,2x], there will be quite a few contrarian views.

That Fortran allows scalar derived types as function result and also supports elemental subroutines will be seen as “good enough” for practice by most who can vote on the language committee!

Actually, an elemental function is supposed to produce a scalar result, so you cannot define f to return [x,2x] (empirically determined with two different compilers :blush:). Like @FortranFan mentions, you can have it return a derived type.

1 Like

Yes, I think that’s the point of the OP: You can’t do that with elemental but you can with map if you design it to work as proposed. I don’t think derived types are needed here–you just need to implement map so that it accepts a function as a procedure argument of the desired shape.

1 Like

To get some experience, I’ve tried the following code (using an elemental scalar function). With gfortran-10.2, the code worked as expected when the “data” component is a fixed-size array, while it resulted in some strange runtime error. Am I doing something wrong here, or possibly a compiler issue…?

module test_m
    implicit none
    type Array_t
        integer :: data( 2 )               !! works (gfort-10.2)
        ! integer, allocatable :: data(:)  !! abort (gfort-10.2)
    endtype
contains

elemental function f( x ) result( res )
    integer, intent(in) :: x
    type(Array_t) :: res

    res% data = [ x, 2 * x ]
end

end module

program main
    use test_m

    associate( x => f( 1 ) )
      print *, "f(1) = ", x% data
    end associate

    associate( x => f( [1, 2, 3] ) )
      print *, "f([1,2,3])( 1 ) = ", x( 1 )% data
      print *, "f([1,2,3])( 2 ) = ", x( 2 )% data
      print *, "f([1,2,3])( 3 ) = ", x( 3 )% data
    end associate
end

$ gfortran-10 test.f90 (with %data → integer array of fixed size)

 f(1) =            1           2
 f([1,2,3])( 1 ) =            1           2
 f([1,2,3])( 2 ) =            2           4
 f([1,2,3])( 3 ) =            3           6

$ gfortran-10 test.f90 (with %data → integer allocatable array)

a.out(57322,0x7fff715c4000) malloc: *** error for object 0xffff: pointer being freed was not allocated

*** set a breakpoint in malloc_error_break to debug

Program received signal SIGABRT: Process abort signal.

That looks like a compiler bug. I’ve noticed gfortran isn’t great at generating finalizers for types with allocatable components. I’ve not been able to pin down exactly under what circumstances it fails. The associate block probably isn’t helping it either, as it also problems there sometimes.

tldr; the allocatable array case should be standards conforming (IMO)

1 Like

@septc ,

Whatever it’s worth, I think your code including with the ALLOCATABLE component of the derived type conforms and looks alright. I too think this is a gfortran compiler issue worthy of a submission at GCC Bugzilla.

Also, the ALLOCATABLE case works without any issue with Intel Fortran (IFORT) oneAPI 2021.2.

1 Like

I tried it on Cygwin with gfortran 10.2.0 and there the program produced the expected output. On lInux with gfortran 10.0.1 the program failed with an invalid memory reference. Intel Fortran (various versions) produced a program that simply worked.

I agree with @everythingfunctional and @FortranFan that this is vey probably a compiler bug

1 Like

Of course elemental is supposed to return a scalar. That’s why I said f([x1,x2,x3]) is meaningless. I knew that returning derived type will solve the problem. But, I think a more general elemental or a map function (in stdlib or as intrinsic – just as a new reduce has been introduced) will be useful if:

  1. one doesn’t want the OOP banana (and the monkey holding it, and the jungle in which it lives),
  2. it will be an array of structure (AoS) construction which many programmers deride for inefficiency, compared to SoA (although AoS is not necessarily bad for derived types like this, which have homogeneous components).

Fortan arrays are very versatile. Coupled with rich intrinsic library, they often allow us to forego the hassle of defining a type, and its members, getters, setters, constructors, finalizers, overloaded operators and so on (the oft repeated jungle-banana metaphor), unless extremely necessary. May be I am overstretching the utility of arrays, but this is one of the few cases where I repeatedly see a pattern that could potentially enhance their use. Take the example of an array of points in space: x(space_dim, no_points). Fortran has such a good support for arrays that I find defining a type called points unnecessary, most of the times.

PS- I have no allergy to derived types. But I try follow the dictum:code deleted is code debugged! Unless defining a type reduces overall number of lines or significantly improves readability, I would like to avoid them. Well I can go on this, but that would be a digression!

2 Likes

:slight_smile: Apparently I missed the finer points of your post and probably re-read it. As a completely off-topic remark: in Dutch the abbreviation SoA (or perhaps better SOA) has the same meaning as “VD” in English …

Yes, a good idea to not digress:
a) welcome to this forum!
b) derived types in Fortran can simply mean not intrinsic - SoA/AoS, OOP, etc. are digressions when made as such;
c) Fortran stdlib effort appears community and consensus-minded - a map facility in stdlib should pose no conflict with elemental language facility and the community will likely be completely open-minded to its inclusion.

Had to google VD. Apparently, it’s undefined in my STDlib.

Hm, I guess I referred to an obsolete abbreviation then. Times do change …