Procedure pointer to contained function?

First off, what I’m trying to achieve:

I have a function A that takes a procedure pointer P, interface DOUBLE in, DOUBLE out, which is executed inside this function A. Now some procedures of that pointer type only require the “in” variable to calculate the “out” result but I’d also like to be able to use a local variable inside such a function (because passing it as a dummy would of course alter the interface and would thus not be accepted). Kind of like a capture (closure?) in a lambda function.

What I tried is using a contained function, something like this:

! procedure pointer spec:
INTERFACE
   FUNCTION T_FUN_DD(d_in) RESULT(d_out)
      DOUBLE PRECISION, INTENT(IN) :: d_in
      DOUBLE PRECISION :: d_out
   END FUNCTION T_FUN_DD
END INTERFACE

! the function receiving the procedure pointer
FUNCTION PROCESS_ARRAY(fun, pd_array) RESULT(d_out)
   IMPLICIT NONE
   PROCEDURE(T_FUN_DD), POINTER, INTENT(IN) :: fun
   DOUBLE PRECISION, DIMENSION(:), INTENT(IN) :: pd_array
   DOUBLE PRECISION :: d_out

   INTEGER :: i
   d_out = 0.0d0

   DO i = 1, SIZE(pd_array)
      d_out = d_out + fun(pd_array(i))
   END DO
END FUNCTION PROCESS_ARRAY

! a wrapper function trying to use a CONTAINed function for the function pointer
FUNCTION PROC_INT(pd_array) RESULT(d_out)
   IMPLICIT NONE
   CLASS(T_TEST) :: self
   DOUBLE PRECISION, DIMENSION(:) :: pd_array
   DOUBLE PRECISION :: d_out

   PROCEDURE(T_FUN_DD), POINTER :: p_fun
   INTEGER :: i
   i = 5
   p_fun => ADD_CONST
   d_out = PROCESS_ARRAY(p_fun, pd_array)

CONTAINS

   FUNCTION ADD_CONST(d_in_cont) RESULT(d_out_cont)
      IMPLICIT NONE
      DOUBLE PRECISION, INTENT(IN) :: d_in_cont
      DOUBLE PRECISION :: d_out_cont

      ! I want to use i from the containing function here:
      d_out_cont = d_in_cont + i
   END FUNCTION ADD_CONST

END FUNCTION PROC_INT

But it seems that ADD_CONST is not recognized as a valid target of p_fun, I get

Error: Procedure pointer target ‘add_const’ at (1) must be either an intrinsic, host or use associated, referenced or have the EXTERNAL attribute

Is what I want to achieve possible? How could I solve this?

1 Like

Which compiler are you using. If you do the following

  1. Put your code inside a module
  2. Put a CONTAINS statement in front of FUNCTION PROCESS_ARRAY
  3. Remove the CLASS(T_TEST) statement

Your current code compiles correctly with

ifort 2021.10
ifx 2023.2
nvfortran 24.3
gfortran 13.1

Without seeing all your code, I suspect that what the error message is telling you
is you need to specify a procedure as external or provide another interface if you
are compiling all this outside a module.

If you remove the pointer attribute from the dummy argument you can pass the contained function directly. I.e. d_out = PROCESS_ARRAY(p_fun, ADD_CONST)

You may also want to have a read through Doctor Fortran in “Think, Thank, Thunk” - Doctor Fortran (stevelionel.com) to be aware of possible pitfalls with this approach.

2 Likes

Wow! Thank you so much! Thinking about it, the POINTER attribute does not make sense as I actually don’t want to change the function pointer in PROCESS_ARRAY, but just use the function passed. And this is what I actually want; I had not understood why I can’t just pass the function but have a pointer pointer point to it and pass that. I just assumed the POINTER attribute was necessary because of function pointers I know from C.

I actually I do not want to change the local variable and do successive calls to the function using that local procedure. But did I get that right – what I want to achieve (which requires a “thunk”, which provides the context of the parent routine) is generally not possible by the Fortran 2003 standard (unless the compiler implements an extension for it) but it should be possible with a compiler implementing the Fortran 2008 standard?

P.S.: I feel honored that you chimed in on my question!

I’m currently limited to using gfortran 8.5.0 20210514.

Yes, the standard permits an internal procedure to be the target of a procedure pointer assignment. Just make sure that the pointer stays in scope while any references to it are made.

I note that F2018 introduced IMPORT, NONE which would have protected you from accidentally referencing host variables. One thing to keep in mind when moving code from external subprograms to internal subprograms, or more generally, to larger scopes.

There’s some subtlety here that’s worth thinking through for the general case. Steve’s article does a pretty good job of addressing the compiler magic that has to happen for this to work, but doesn’t quite say an important point explicitly (or at least as clearly as I would). Variable/value “capture” does not happen in Fortran. This means if an internal procedure references a variable (or argument) from its host procedure it cannot be called after execution has returned from that host procedure. For example, the following program is fine because demonstrate has not returned when do_thing calls show_it, and thus the variable i still “exists”.

module mod
    implicit none
    abstract interface
        subroutine thing_i
        end subroutine
    end interface
contains
    subroutine do_thing(thing)
        procedure(thing_i) :: thing
        call thing
    end subroutine

    subroutine demonstrate
        integer :: i
        i = 42
        call do_thing(show_it)
    contains
        subroutine show_it
            print *, i
        end subroutine
    end subroutine
end module
use mod
call demonstrate
end
$ gfortran good-example.f90 -o good-example.exe && ./good-example.exe
/usr/bin/ld: warning: /tmp/ccCGYfqi.o: requires executable stack (because the .note.GNU-stack section is executable)
          42

but in the following example, by the time do_thing calls show_it, demonstrate has returned and the variable i no longer “exists”, so when show_it tries to reference it, kaboom.

module mod
    implicit none
    abstract interface
        subroutine thing_i
        end subroutine
    end interface
contains
    subroutine do_thing(thing)
        procedure(thing_i) :: thing
        call thing
    end subroutine

    subroutine demonstrate(ptr)
        procedure(thing_i), pointer, intent(out) :: ptr
        integer :: i
        i = 42
        ptr => show_it
    contains
        subroutine show_it
            print *, i
        end subroutine
    end subroutine
end module
use mod
procedure(thing_i), pointer :: ptr => null()
call demonstrate(ptr)
call do_thing(ptr)
end
$ gfortran bad-example.f90 -o bad-example.exe && ./bad-example.exe 
/usr/bin/ld: warning: /tmp/ccuxUxj5.o: requires executable stack (because the .note.GNU-stack section is executable)

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x7dbbb725a76f in ???
#1  0x7ffdfb78004f in ???
zsh: segmentation fault (core dumped)  ./bad-example.exe

I think the general rule of thumb that pointers to internal procedures are dangerous is a good place to start, even if (AFAIK) there’s nothing in the standard prohibiting it.

The famous “man or boy” test : Man or boy test - Rosetta Code

1 Like

I did cover that explicitly in the part that starts:

What happens to the thunk when MainWndProc returns? It’s gone since the invocation that created it has returned. The place in memory where it resided may or may not still contain valid contents. If the thunk is then called through, there can be unexpected behavior including access violations or data corruption. Not nice.

Yeah, I just didn’t find it particularly clear. I figured an additional way of explaining it would be helpful.

1 Like