Procedures as arguments to operators

I would like to use operator notation to build expression trees. But somehow, this is not as easy as I thought. Calling a function func(proc, val) with a procedure argument proc works fine, but putting func into a “interface operator(.func.)” so that I can write “proc .func. val” does not work, as arguments are required to have an intent(in), which cannot be provided for procedure arguments. Both gfortran and ifort complain, so I guess this is part of the standard. Any reason for this restriction? In a way, a procedure argument has an implicit intent(in), as it obviously cannot be changed.

Here is a simple somewhat contrived example code (which does not compile) to demonstrate the above:

module expr

implicit none
private

public cmp_gt, operator(.ccmp.)

type, public :: node_t
   integer :: x
   procedure(cmp_gt), nopass, pointer :: cmp => null()
contains
   procedure :: eval
end type node_t

interface operator(.ccmp.)
   module procedure create_cmp
end interface

contains

function create_cmp(cmp, x) result(n)
   class(node_t), pointer :: n
   procedure(cmp_gt)            :: cmp
   integer,          intent(in) :: x
   allocate(node_t :: n)
   n%x = x
   n%cmp => cmp
end function create_cmp

function cmp_gt(v1, v2) result(t)
   logical :: t
   integer, intent(in) :: v1, v2
   t = (v1 > v2)
end function cmp_gt

function eval(self, x) result(t)
   logical :: t
   class(node_t), intent(in) :: self
   integer,       intent(in) :: x
   t = self%cmp(x, self%x)
end function eval

end module expr

!---------------------------------------------

program build_expression

use expr
implicit none

class(node_t), pointer :: n

n => cmp_gt .ccmp. 5
print *, n%eval(4), n%eval(5), n%eval(6)
deallocate(n)

end program build_expression

A work-around is, to use a pointer attribute, in which case an intent(in) can be added. In this case, a small helper function is required to map a procedure to a pointer to that procedure. Otherwise, compilers complain that arguments are missing. With these adjustments, gfortran compiles the code and it runs fine. However, ifort complains with “No matching user defined OPERATOR with the given type and rank has been defined. [CCMP]”. So, is this standard-conforming and ifort has a bug, or does gfortran accept invalid code?

module expr

implicit none
private

public operator(.ccmp.), cptr, cmp_gt

type, public :: node_t
   integer :: x
   procedure(cmp_gt), nopass, pointer :: cmp => null()
contains
   procedure :: eval
end type node_t

interface operator(.ccmp.)
   module procedure create_cmp
end interface

contains

function create_cmp(cmp, x) result(n)
   class(node_t), pointer :: n
   procedure(cmp_gt), pointer, intent(in) :: cmp
   integer,                    intent(in) :: x
   allocate(node_t :: n)
   n%x = x
   n%cmp => cmp
end function create_cmp

function cptr(cmp) result(pcmp)
   procedure(cmp_gt), pointer :: pcmp
   procedure(cmp_gt) :: cmp
   pcmp => cmp
end function cptr

function cmp_gt(v1, v2) result(t)
   logical :: t
   integer, intent(in) :: v1, v2
   t = (v1 > v2)
end function cmp_gt

function eval(self, x) result(t)
   logical :: t
   class(node_t), intent(in) :: self
   integer,       intent(in) :: x
   t = self%cmp(x, self%x)
end function eval

end module expr

!---------------------------------------------

program build_expression2

use expr
implicit none

class(node_t), pointer :: n

n => cptr(cmp_gt) .ccmp. 5
print *, n%eval(4), n%eval(5), n%eval(6)
deallocate(n)

end program build_expression2

The reason operators are such strict is because they can be chained, so, they are designed such that they should essentially be pure procedures.

Just an idea: because you’re using the operator to initialize a new node in the tree, one idea may be to define an overloaded initializer:

module expr

implicit none
private

public cmp_gt

type, public :: node_t
   integer :: x
   procedure(cmp_gt), nopass, pointer :: cmp => null()
contains
   procedure :: eval
end type node_t

interface node_t
   module procedure create_cmp
end interface

contains

function create_cmp(cmp, x) result(n)
   class(node_t), pointer :: n
   procedure(cmp_gt) :: cmp
   integer, intent(in) :: x
   allocate(node_t :: n)
   n%x = x
   n%cmp => cmp
end function create_cmp

function cmp_gt(v1, v2) result(t)
   logical :: t
   integer, intent(in) :: v1, v2
   t = (v1 > v2)
end function cmp_gt

function eval(self, x) result(t)
   logical :: t
   class(node_t), intent(in) :: self
   integer,       intent(in) :: x
   t = self%cmp(x, self%x)
end function eval

end module expr

!---------------------------------------------

program build_expression2

use expr
implicit none

class(node_t), pointer :: n

n => node_t(cmp_gt,5)
print *, n%eval(4), n%eval(5), n%eval(6)
deallocate(n)

end program build_expression2

I was playing with this to see of what is allowed and what gives the most readable code (as close to the expression to be evaluated as possible). A DSL with its own parser would be good, but definitely overkill in my case. There are definitely some variations. However, just using the functions itself to chain expressions was not very readable. A small coding actually got me started with these experiments. And the infix notation of operators helps to avoid endless parenthesis (e.g. the second argument ‘x’ to create/node_t is a node in itself).

PS: Allocation of function/operator result is nothing unusual, so this should not be an argument against such operators, which build trees from node arguments.
It is just that an implicitly-intent(in) procedure argument is not handled as intent(in). As I demonstrated with the pointer variant, you can circumvent this restriction. Still wondering, whether ifort has a bug here or is correct in rejecting this code.

@martin ,

You can give this alternative a try, see if it works - my thought here is simply that what’s easier for a 3rd party to read your code is often what is easier for the Fortran processor (or at least it’s front-end parser). So I rejigged your code a little in terms of what makes sense ordinarily in an “expression” module (your expr) which is that it will employ ABSTRACT INTERFACEs for functions and setup procedure POINTERs to such interfaces which will then yield the INTENT(IN) you seek.

module expr_m

   private

   public Icomparer, operator(.ccmp.)

   abstract interface
      function Icomparer(v1, v2) result(t)
         logical :: t
         integer, intent(in) :: v1, v2
      end function 
   end interface 
   type, public :: node_t
      integer :: x
      procedure(Icomparer), nopass, pointer :: cmp => null()
   contains
      procedure :: eval
   end type node_t

   interface operator(.ccmp.)
      module procedure create_cmp
   end interface

contains

   function create_cmp(cmp, x) result(n)
      class(node_t), pointer :: n
      procedure(Icomparer), pointer, intent(in) :: cmp
      integer,          intent(in) :: x
      allocate(node_t :: n)
      n%x = x
      n%cmp => cmp
   end function create_cmp

   function eval(self, x) result(t)
      logical :: t
      class(node_t), intent(in) :: self
      integer,       intent(in) :: x
      t = self%cmp(x, self%x)
   end function eval

end module

!---------------------------------------------

program build_expression

use expr_m

   class(node_t), pointer :: n
   procedure(Icomparer), pointer :: comparer

   comparer => cmp_gt
   n => comparer .ccmp. 5
   print *, n%eval(4), n%eval(5), n%eval(6)
   deallocate(n)

contains

   function cmp_gt(v1, v2) result(t)
      logical :: t
      integer, intent(in) :: v1, v2
      t = (v1 > v2)
   end function cmp_gt

end program

P.S.> My suggestion above is untested; I typed above on my kid’s tab while on th road.

Thanks for the suggestions. I condensed the code and dropped the abstract interface(s), in a real code, abstract interfaces should be used of course.
However, I still prefer the “function returns pointer to procedure argument” (function “cptr”), as it avoids local function pointer variables. However, using the function “cptr” does not work in ifort, and aborts with

“When a dummy argument is a function, the corresponding actual argument must also be a function.”

Looks like a bug or is it not standard conforming? Your original code compiles with ifort, so procedure pointers as arguments to operators does seem to work, sometimes.

Now that I can refer to the standard document, my read is your code with this cptr business does not conform: “The dummy arguments shall be nonoptional dummy data objects and shall have the INTENT (IN) … attribute” (note the emphasis is mine; you can look up data objects in the standard)

With what you’re trying to achieve, the Fortran standard does not appear to cooperate. This you may want to take up as a Fortran standard enhancement proposal, especially if “black-board abstraction” with Fortran is of keen interest. Here, you may find @rouson a kindred spirit.

As to Intel Fortran, I’m unsure its basis, it appears to have a nonstandard extension but with what semantics, I don’t know. Perhaps @greenrongreen may know better. But I won’t be surprised if Intel Fortran is simply failing to detect and diagnose nonconforming behavior here; in its defense, the standard does not require it to detect and diagnose. And with nonstandard code, the processor can do whatever such as indulge in undefined or inconsistent behavior and that’s what you may be noticing to wonder if there is a “bug”.

A simplified illustration of what I think is non-standard code but which is processed by Intel Fortran with no diagnostic messages:

module m
   abstract interface
      function Ifunc( a ) result(r)
         integer, intent(in) :: a
         integer r
      end function 
   end interface
   interface operator(.op.)
      module procedure foo
   end interface
contains
   function foo( x, func ) result(r)
      integer, intent(in) :: x
      procedure(Ifunc), intent(in), pointer :: func
      integer r
      r = x + func( x ) 
   end function 
end module 
C:\temp>ifx /c /standard-semantics /free /stand m.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.1.0 Build 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.


C:\temp>

You can try this with NAG compiler if you can and check what it tells you, it likely raises an error for you because the second received argument (func) is not a data object.

You are right, NAG doesn’t like this. Both gfortran 13.2.1 and my nightly main branch of ifx both compile this w/o any diagnostic. I’ll write up bug report for ifx.

1 Like

Thanks for pointing out the “data object” part. I missed that, probably because of my rather haskellarian view on data.
However, upon further research of what a “data object” is, I am not really able to establish that a pointer to a procedure is not a data object (looking at definitions in section 1.3 of F08).

Thus: A procedure pointer intent(in) argument to an operator is non-standard conforming. So it does not matter, whether a local pointer variable for the function is declared (compiles with ifort and gfortran) or whether a function “cptr”, returning such a pointer, is used (compiles with gfortrain, fails with ifort). Both variants are non-conforming.

There are no “pointer to” anything in Fortran. There are data that have the POINTER attribute (“data pointers”) and procedures that have the POINTER attribute (“procedure pointers”).

Ah, but a procedure kind of becomes data once you add a pointer attribute and for example put it into the data section of a derived type. So, I think it is not that easy. But I guess your interpretation should agree with the standard.

1 Like

What is data and what is procedure varies with context.

But as long as Fortran is our context (and not the network, or the machine, or the compiler internals or output), what is data and what is procedure is definitively and unambiguously spelt out.

For instance, there is no “data section of a derived type”. There is a “component part” (comprising of “data component definition(s)” and/or “procedure component definition(s)”) and a “type-bound procedure part”.

For the “data component definition”, you cannot put procedures in there, only data.
For the “procedure component definition”, you cannot put data in there, only procedures, and you cannot NOT put POINTER in there. So there is no way to “add a pointer attribute” or “put it in the data section”.

I think what’s happening is that you are mixing up contexts in your mental model of what Fortran is.

I have no experience with this kind of thing (so just curious), but isn’t is an option to “promote” a procedure to a derived type? (such that it is regarded as “data”). Something like…

!------------------------------
module expr_mod
    implicit none

    abstract interface
        function Ifunc(v1, v2) result(flag)
            integer, intent(in) :: v1, v2
            logical :: flag
        end function
    end interface

    type func_t
        procedure(Ifunc), nopass, pointer :: fptr => null()
    end type

    type :: node_t
        integer :: x
        type(func_t) :: func
    contains
        procedure :: eval
    end type

    interface operator (.ccmp.)
        module procedure create_cmp
    end interface

contains

function create_cmp(cmp, x) result(node)
    type(func_t), intent(in) :: cmp
    integer, intent(in) :: x
    class(node_t), pointer :: node

    allocate(node_t :: node)
    node% x = x
    node% func% fptr => cmp% fptr
end

function cmp_gt(v1, v2) result(flag)
    integer, intent(in) :: v1, v2
    logical :: flag
    flag = (v1 > v2)
end

function eval(node, x) result(flag)
    class(node_t), intent(in) :: node
    integer, intent(in) :: x
    logical :: flag

    flag = node% func% fptr(x, node% x)
end

end module

!------------------------------
program main
    use expr_mod
    implicit none
    class(node_t), pointer :: node

    !! node => cmp_gt .ccmp. 5
    node => func_t(cmp_gt) .ccmp. 5   !! not sure if this is valid though...

    print *, node% eval(4), node% eval(5), node% eval(6)
end

$ gfortran test.f90 && ./a.out
F F T

(Same output with ifx/ifort/flang-new + CompilerExplorer.) But I am afraid the code may become ugly when used in a chained fashion (because a lot of func_t() appears).

1 Like

That’s why I wrote “kind of”. Moreover if you wrap the procedure pointer into a derived type as suggested by @septc, it becomes data. And sorry for the wrong names. I rather like to understand how a (fortran) compiler works and translates high level constructs to machine level statements (like how pointers are used to realise associate constructs, even if the associate-name is not a pointer/has no pointer attribute). It is all fine to hide this from the practitioner, but I have just too often hit bugs (my own/compiler/performance) to not appreciate a deeper understanding.
And as the idea with putting the procedure pointer into a derived type shows, from a low lever point of view, there should not be any objections to passing function pointer to an operator. Though might be other reasons to forbid that.

Anyway I tried to understand “data object” and failed. Let see Section 1.3 of F08 standard draft:

1.3.40 data object
constant, variable, or subobject of a constant

1.3.143 variable
data entity that can be defined and redefined during execution of a program

1.3.39 data entity
data object, result of the evaluation of an expression, or the result of the execution of a function reference

First of all, this looks like a circular reference: data object → variable → data entity → data object. Really?

Second a function result like that of cptr is “the result of the execution of a function reference”, thus it is at least a data entity, right?

Third a “result of the evaluation of an expression, or the result of the execution of a function reference” can not be defined or redefined during execution of a program, thus is not a variable. Hence a variable is just a “data object”. Why does it say a “data entity” and then excluding all except “data object”. If I read this correctly (which is doubtful).

I am still lost as to why a variable such like
procedure(f_ifx), pointer :: var
is (or is not) a data object, I am lost in that circular reference.

Thanks for this idea, I somehow missed it. In particular as I already have these wrapper classes for other purposes. However, I would use the func_t wrapper class just for providing the function pointer as a data object to create_cmp, but not as component of node_t. The create_cmp routine can easily reference the wrapped function pointer, like node%fptr => cmp%fptr. Then this becomes almost as easy as my cptr function approach. And building trees by infix-notated expression provides indeed the most readable code.

1 Like

This crops up occasionally in J3 archives
https://mailman.j3-fortran.org/pipermail/j3/2016-January/009137.html
https://mailman.j3-fortran.org/pipermail/j3/2023-September/014307.html

Compiler writers seem to have no trouble agreeing with each other about what is data and what is not, so if it is a problem it is not a pressing one.

No. It is implied that the function result shall not be a procedure pointer, and cptr is. You are expected to read the Standard assuming there is no contradiction. With the implied addition, there will be no contradiction. Without it, there will be, because entities cannot be data and procedure at the same time.

I am not sure I understand your aporia. Perhaps you can rephrase.

Because


The clue is in the word PROCEDURE.

Thanks for digging this out. As a mathematician I am not really inclined into diving deep into something as informal (non-formal?) as the standard document. But I appreciate that for a language such as Fortran the standard document is probably as formal as you can get, even if there are some contradictions and implied understandings.

From your second link:

>data object (1.3.45) → variable (1.3.54) → data entity (1.3.44) → >data object (1.3.45).
>Is that a problem?
No. Variable could be defined as “data object that …”, which is even more tightly circular, but anyway it is the “can be defined” etc. bit of the definition which is the important bit."

This sounds like pretty much what I had in mind.

Anyway, changing a procedure pointer into a data object by wrapping it with a derived type looks like a reasonable solution. It also shows that the distinction between data and procedure becomes blurred with these modern elements.

I wouldn’t say that anything “changed”, as I wouldn’t say that the existence of a mathematical construction (e.g. circumscribed circle of a triangle) changes the object the construction starts with (the triangle).

The interpretation by the standard changes. The same 8 bytes changes from a pointer procedure to a data object.

The only way to know for sure is to disassemble the output and make sense of it, if you are interested in how the machine is asked to implement it.