Error: The leftmost part-ref in a data-ref cannot be a function reference

So in Fortran Discord (highly recommend, cool place), we were discussing with @Aurelius_Nero what is exactly the reason the chain() % function() % calls(), which actually are the basis of large part of modern programming (including the high-performance, see PyTorch) are forbidden in Fortran, and if there is any. I am not able to see any area for ambiguity or issues compiler might have in resolving it. Consider the following Python code:

from math import sqrt
from __future__ import annotations

class NumT:
    def __init__(self, x: float):
        super().__init__()
        self.x = x

    def squared(self) -> NumT:
        return NumT(x=self.x**2)

    def root(self) -> NumT:
        return NumT(x=sqrt(self.x))

    def __str__(self) -> str:
        return f'{self.x}'

print(NumT(x=10).squared().root())

And how beautifully it could translate to Fortran, if not the language restrictions:

module num_m

    implicit none
    private
    public :: NumT

    type :: NumT
        real :: x
    contains
        procedure :: squared, root
    end type

contains

    function squared(self)
        class(NumT) :: self
        type(NumT) :: squared
        squared % x = (self % x)**2
    end function

    function root(self)
        class(NumT) :: self
        type(NumT) :: root
        root % x = sqrt(self % x)
    end function

end module


program test
    use num_m
    implicit none

    ! can do this
    print *, NumT(x=10)

    ! can't do this
    ! print *, NumT(x=10) % squared() % root()
    !                     1
    ! Error: The leftmost part-ref in a data-ref 
    ! cannot be a function reference at (1)

    ! two legit ways to do that, but you see the 
    ! problem compared to one line call
    block
        type(NumT) :: result
        result = NumT(x=10)
        result = result % squared()
        print *, result % root()
    end block

    associate (t10 => NumT(x=10))
        associate (t10sq => t10 % squared())
            print *, t10sq % root()
        end associate
    end associate
end program

Any insights into this? :slight_smile:

PS. Happy New Year!

5 Likes

@gronki ,

Happy New Year!

What you suggest was proposed by @rouson back in Feb. 2018 but it failed:
https://j3-fortran.org/doc/year/18/18-134.txt

I don’t have much of an insight, I can only offer opinion (always and never h) and it is that the facility you refer to appears to be seen as considerable cost to compiler implementors but with little real benefit, just some added convenience. Thus if anyone is keen on it, they will have to do really good “marketing” and “sell” it to the Community (get a lot of likes) and then also fully convince the voting members to get it added. For whatever it’s worth, I too do not “see any area for ambiguity or issues compiler might have in resolving it.”

3 Likes

Here is an old issue for this feature: Remove restrictions on proc-component-ref · Issue #27 · j3-fortran/fortran_proposals · GitHub

As written there, I think this is similar to indexing a returned array from a function like this:

f()(3)

where f is some function returning an array. There might be some parsing issues. But semantically it seems it might work, given that Python can do it.

1 Like

Is there any notable benefit of postfix chaining to the more classic and arguably clearer “functional” alternative?

module num_m
    implicit none
    private
    public :: NumT, root, squared
    type :: NumT
        real :: x
    end type
contains
    function squared(T)
        type(NumT), intent(in) :: T
        type(NumT) :: squared
        squared % x = (T % x)**2
    end function
    function root(T)
        type(NumT), intent(in) :: T
        type(NumT) :: root
        root % x = sqrt(T % x)
    end function
end module

program test
    use num_m
    implicit none
    print *, NumT(x=10)
    print *, root(squared(NumT(x=10)))
end program

Edit: in this example I’d be compelled to use the standard names, why force the user to learn use %squared() and %root(), when ** and sqrt are known to everyone:

module num_m
    implicit none
    private
    public :: NumT
    public :: operator(**)
    public :: sqrt
    
    type :: NumT
        real :: x
    end type
    interface operator(**)
        module procedure NumT_pow
    end interface
    interface sqrt
        module procedure NumT_sqrt
    end interface
contains
    function NumT_pow(T,p) result(Y)
        type(NumT), intent(in) :: T
        integer, intent(in) :: p 
        type(NumT) :: Y
        Y = NumT(T%x**p)
    end function
    function NumT_sqrt(T) result(Y)
        type(NumT), intent(in) :: T
        type(NumT) :: Y
        Y = NumT(sqrt(T%x))
    end function
end module

program test
    use num_m
    implicit none
    print *, sqrt(NumT(10)**2)
end program

This would be in line with C++ core guideline C.162:

C.162: Overload operations that are roughly equivalent

Having different names for logically equivalent operations on different argument types is confusing, leads to encoding type information in function names, and inhibits generic programming.

2 Likes

@gronki and anyone else keen on this:

As you can see from some of the reactions, when it comes to mathematical formulae you will find considerable differences in viewpoints.

But then note in the context of chaining methods which operate of classes particularly in a type composition coding pattern, there are other use cases where such facilities prove convenient for coders, compact and elegant enough to improve readability, and appreciably abstract that a compiler might be able to include performant implementation and good optimization (e.g., eliding of function results, RAII facilities, etc.) under the hood. Examples include string utilities or basically with user-defined classes, such as those in utility libraries, that help with processing of domain-specific heterogeneous data. See the comment by @jacobwilliams for an immediate and simple example here: s%lower()%split(',').

Then the challenge becomes that the conveyed use cases need to be broader and far too appealing for feature proposals, what you state in the original post is such a suggestion toward a proposal. But if the use cases are too broad, many don’t study them adequately and don’t care to envision the other possibilities that can eventually help Fortran be a more full-featured, efficient, and powerful tool for modern scientific computing. Then you have the constant resource-constrained environment that clouds the vision leading to rationing of features to work on and the rationalizing away the rest of ignored proposals as cost, no benefit, etc.

So it’s quite a struggle in the Fortran world that many other languages, especially Python, C++, Ada, Julia, etc. don’t face - the leaders of these languages , almost as a matter of principle, support and drive the inclusion of a host of new facilities at great (one-time) feature design cost, particularly if they feel it leads to better coding practices, more coder conveniences, enhanced developer productivity, etc. the benefits of which keep on coming for years and years with countless users worldwide.

As the work for Fortran 202X had started and I had noticed the travails with ENUM feature and the resistance to doing anything other the mostly-useless, bare-bones Pascal year 1980 feature, I was looking up online as Python folks were just completing their official work on ENUMs.

The contrast with how Guido van Rossum enthusiastically supported an extensive and very full featured design toward ENUMs in Python with that of the do-the-minimal, that-will-be-less-cost, kick-the-can-down-the-road (e.g., any features known to be useful with ENUMs since year 1980 can be addressed in a future Fortran revision, mind you this in year 2019!) attitude with Fortran could not be more stark.

1 Like

Well, I thought I could modernize an old technique, and it does run but
not very satisfying. When I tried to make it more reasonable it quit working.
Hit some weird bugs (with gfortran use one REAL with f1, f2, f3, f4 instead of individually, for starters) but it does raise some interesting `issues. Might revisit this but if this makes anyone
else think of something, feel free. Really off the well-traveled road. Sorta fun though …

module M_chainlink
implicit none
private
public :: NumT, root, squared
   type :: NumT
      real :: x
   contains
      procedure :: chain
      procedure :: squared => NumT_squared
      procedure :: root => NumT_root
   end type
contains
function chain(self,f1,f2,f3,f4,f5,f6,f7,f8,f9)
class(NumT) :: self
type(NumT) :: chain
real,optional :: f1
real,optional :: f2
real,optional :: f3
real,optional :: f4
real,optional :: f5
real,optional :: f6
real,optional :: f7
real,optional :: f8
real,optional :: f9
   chain % x = self % x
   if(present(f1))chain % x = f1(chain % x)
   if(present(f2))chain % x = f2(chain % x)
   if(present(f3))chain % x = f3(chain % x)
   if(present(f4))chain % x = f4(chain % x)
   if(present(f5))chain % x = f5(chain % x)
   if(present(f6))chain % x = f6(chain % x)
   if(present(f7))chain % x = f7(chain % x)
   if(present(f8))chain % x = f8(chain % x)
   if(present(f9))chain % x = f9(chain % x)
end function
! wrappers 
function NumT_squared(self)
class(NumT) :: self
type(NumT) :: NumT_squared
   NumT_squared % x = squared(self % x)
end function

function NumT_root(self)
class(NumT) :: self
type(NumT) :: NumT_root
   NumT_root % x = root(self % x)
end function
! functions
real function squared(val)
real,intent(in) :: val
   squared = val**2
end function

real function root(val)
real,intent(in) :: val
   root = sqrt(val)
end function

end module

program test
use M_chainlink, only : NumT, root, squared
implicit none
intrinsic :: sin, sqrt, cos, abs
type(NumT) :: result
    result=NumT(10)
    print *, result
    print *, result%chain()
    print *, result%chain(sqrt)
    print *, result%chain(sqrt,sin)
    print *, result%chain(sqrt,sin,cos)
    print *, result%chain(squared,root,abs)
    print *, result%chain(squared,root,abs,sqrt,sin,cos)
    print *, result%squared()
    print *, result%root()

end program
   10.0000000    
   10.0000000    
   3.16227770    
  -2.06835698E-02
  0.999786079    
   10.0000000    
  0.999786079    
   100.000000    
   3.16227770    

I believe use of the intrinsic procedures are not allowed as procedure arguments. I expect this is because they are generic names. I.e. which sqrt, for default real or double precision or some other kind? I believe no generic name may be used as a procedure argument.

@everythingfunctional ,

sqrt is also a specific name for default real argument, so the code by @urbanjost in principle should work ok when used with default real.

Note the standard states, “If the specific name is also a generic name, only the specific procedure is associated with the dummy argument.”

So a code like so shall conform per the standard:

module m
   abstract interface
      function Ifunc( x ) result(r)
         real, intent(in) :: x
         real :: r
      end function
   end interface
contains
   subroutine sub( a, func )
      real, intent(in) :: a
      procedure(Ifunc) :: func
      print *, func(a)
   end subroutine
end module
   use m
   intrinsic :: sqrt
   call sub( 4.0, sqrt )
end
C:\temp>gfortran p.f90 -p.exe

C:\temp>p.exe
   2.00000000
2 Likes

Probably true if I used the newer format for specifying a passed procedure, unless the compiler allows an exception. The list in the standard indicates what can be passed. Passing intrinsics is about the only reason I would have to use
a non-generic except for some oddities with REAL and DBLE and FLOAT. Using the original
method appears to have produced no issues with gfortran, ifort, and ifx. The example runs
with those compilers. Given Fortran does not allow what the OP originally envisioned, this was
the closest I could think of. It is one of those things that when it works you really wonder if it was intended to, but except that the simple method of passing a procedure has been superceded I think it is conformant. It lets you play with the idea of a stacked chain of procedure calls, which is close to the oriignal request. Definitely limited as far as passing additional options to the chained procedures, etc. ; not sure how many real-world cases it would be useful for; but personally not sure how many cases there are for the original request either, so I don’t feel like a good judge of that – thus I put the example in the wild. Using this method I cannot think of a way the functions can still be private, which is a drawback. And to use the same functions with chain and as type-bound procedures you have to wrap them, I believe. I will change the example to show that.

Well, the following should be a standard-conforming option:

module m
   abstract interface
      function Ifunc_sp( x ) result(r)
         real, intent(in) :: x
         real :: r
      end function
      function Ifunc_dp( x ) result(r)
         double precision, intent(in) :: x
         double precision :: r
      end function
   end interface
   interface sub
      module procedure sub_sp
      module procedure sub_dp
   end interface
contains
   subroutine sub_sp( a, func )
      real, intent(in) :: a
      procedure(Ifunc_sp) :: func
      print *, func(a)
   end subroutine
   subroutine sub_dp( a, func )
      double precision, intent(in) :: a
      procedure(Ifunc_dp) :: func
      print *, func(a)
   end subroutine
end module
   use m
   intrinsic :: sqrt, dsqrt
   call sub( 4.0, sqrt )
   call sub( 4.0D0, dsqrt )
end 

Or, the less verbose option but which may perhaps be less clearer to certain readers:

module m
   interface sub
      module procedure sub_sp
      module procedure sub_dp
   end interface
contains
   subroutine sub_sp( a, func )
      real, intent(in) :: a
      intrinsic :: sqrt
      procedure(sqrt) :: func
      print *, func(a)
   end subroutine
   subroutine sub_dp( a, func )
      double precision, intent(in) :: a
      intrinsic :: dsqrt
      procedure(dsqrt) :: func
      print *, func(a)
   end subroutine
end module
   use m
   intrinsic :: sqrt, dsqrt
   call sub( 4.0, sqrt )
   call sub( 4.0D0, dsqrt )
end 
1 Like

Thanks. When I get a minute I will combine that with the program and try some more intrinsics.
The quotes from the standard shows it is more nuanced than I remembered; so it is a good example program for playing with the difference procedure passing methods.

Using this method, I cannot think of a reliable way to also pass arguments to the passed procedures, as in “split(’ ')” to split on spaces. Putting them in as elements of the type or as metamorphic arguments was too error-prone or only allowed one value and was ugly the way I tried.

Thank you for all the replies!

@ivanpribec These are two tools for two different purposes. The way you rewrote the code is relevant for simple, mathematical functions, which I used as an example, but there could be many other operations which accept additional arguments, such as the mentioned string example (Remove restrictions on proc-component-ref · Issue #27 · j3-fortran/fortran_proposals · GitHub). There are common ways we design software, and especially thanks to the bloom of machine learning and data science, we have seen many great examples on how to build numeric codes using OOP. Chain calls has been a popular way to implement any kind of operations, showing superior syntax to nested function calls. Consider the following two examples:
array % detach() % transpose([0,2,1]) % sum(dim=1)
How that would look using functional interface? Hmm…
sum(transpose(detach(array), [0,2,1]), dim=1)
Clearly, it is a complete mess, and it takes lot of focus to see which which arguments apply to which functions.

@certik @rouson Do you think it is possible to re-file the proposal? If so, do you think showing how such construct is used in modern numerical processing would be helpful? Objectively speaking, this ban has no benefit of any kind, no practical application and is not a result of any ambiguity that might arise as a result. Even the classic “this would break legacy” code argument would not hold here! So it is a truly remarkable situation, that a restriction is imposed just to make language more limited.

Fortran could be a competitor to python. But it is not, because of such things.

I think that since there is no foundation for the restriction in the first place, there is a strong case that keeping this restriction hurts the language, and showing many design patterns (for example from Python) that are not possible because of this restriction, there is no way someone with good intent could disagree. If there is any way I could contribute, I would like to.

Dominik

2 Likes

I would be in favor of just going all the way to Uniform Function Call Syntax. The basics are that the % gets treated as a left associative operator that calls the procedure to the right with the thing on the left as the first argument. There’s some complexity involved in defining it so that it still works with type-bound procedures that have the passed object dummy argument as something other than the first argument, but I think it’s doable.

3 Likes

@gronki, As usual with these things, here is my plan that I am executing:

  • Get LFortran to compile all Fortran codes (huge progress there, we can compile and run Minpack now, and we are working on fpm now).

  • Implement these proposals as an extension and see if there are any issues with it.

If you or anyone want to help, please get in touch.

Other people try to push these things directly via the committee, but first of all, the barrier is very high (for various reasons), and even if successful, the compilers still have to implement it. So a better workflow is to implement it in a compiler first and then go from there.

4 Likes