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