Implementation of a parametrized objective function without using module variables or internal subroutines

Could someone please explain what is an “executable stack”? I did a google search, but did not see anything that looked relevant.

The example given above by @ivanpribec seems like the ideal solution for this kind of problem. When used recursively, each instance of MY_INTEGRATION() should involve also its corresponding instance of MY_F(). It is difficult to imagine how the language could be changed to make this association any easier on the programmer to use or more straightforward to understand. I think this is exactly what was intended when this feature was added to the language (I’m not sure when, maybe f2003?). If gfortran does not handle this correctly, even after a couple of decades, then I can see how that can be frustrating, but there are actually several such features like this that have taken a long time to implement correctly (e.g. parametrized data types). That is the nature of publicly supported open source software.

1 Like

Here is a pretty good explanation as a starting point and links for further information: https://grok.com/share/bGVnYWN5_d52704a6-4ac6-4dc9-a258-7d606f3b9aea.

1 Like

That’s true for simple cases, but while trying to migrate some complex code from ifort to ifx, while ifort gives me

ld: warning: <source>.o: requires executable stack (because the .note.GNU-stack section is executable)

with ifx 2025.2 I get

ld: warning: <source>.o: missing .note.GNU-stack section implies executable stack
ld: NOTE: This behaviour is deprecated and will be removed in a future version of the linker

I just haven’t been sufficiently motivated to create a small reproducer to report the issue.

1 Like

I’ve tried to create a case where the x86-64 assembly would be simple enough to follow:

subroutine doit(f)
external f
call f
end subroutine

integer function timestwo (n)    ! returns 2*n
    implicit none
    integer, intent(in) :: n
    external :: doit
    call doit(multiply_by_2)
contains
   subroutine multiply_by_2()
    timestwo = 2*n
   end subroutine
end function

When compiled using gfortran -Os -fno-inline this produces (Compiler Explorer),

multiply_by_2.0:
        mov     rax, QWORD PTR [r10]        ; load the context address
        mov     eax, DWORD PTR [rax]        ; load the value of n from the context
        add     eax, eax                    ; 2*n = n + n
        mov     DWORD PTR [r10+8], eax      ; store result back in context
        ret
doit_:
        xor     eax, eax                    ; void result
        jmp     rdi                         ; jump to procedure f 
timestwo_:
        sub     rsp, 56                             ; reserve 56 bytes on the stack
        xor     eax, eax                            ;
        mov     edx, OFFSET FLAT:multiply_by_2.0    ; take address (offset) of the internal procedure
        mov     QWORD PTR [rsp], rdi                ; store address of n on the stack
        lea     rdi, [rsp+12]                       ; load (effective) callback address (to be passed to doit)
        mov     QWORD PTR [rsp+40], rax         ; trampoline?
        mov     WORD PTR [rsp+12], -17599       ; trampoline?
        mov     DWORD PTR [rsp+14], edx         ; trampoline?
        mov     WORD PTR [rsp+18], -17847       ; trampoline?
        mov     QWORD PTR [rsp+20], rsp         ; trampoline?
        mov     DWORD PTR [rsp+28], -1864106167 ; trampoline?
        call    doit_                               ; doit takes a single argument passed in rdi
        mov     eax, DWORD PTR [rsp+8]              ; retrieve result from the stack (result is in eax)
        add     rsp, 56                             ; release reserved stack area
        ret

I’ve tried to annotate this to my best understanding. Their is a group of six mov instructions which appear to set up the trampoline in the current stack frame:

[rsp +  0]   8 bytes    address of n
[rsp +  8]   4 bytes    area to return 2*n
[rsp + 12]   2 bytes    magic value: -17599          <-- this address is passed to doit
[rsp + 14]   4 bytes    callback offset
[rsp + 18]   2 bytes    magic value: -17487 
[rsp + 20]   8 bytes    current stack pointer
[rsp + 28]   4 bytes    magic value: -1864106167
[rsp + 40]   8 bytes    zero (?)

I think you can see the trampoline here, because instead of passing the address of multiply_by_2 directly, the address of the trampoline is passed instead. What I’m missing is at some point there should be an instruction like lea r10, [rsp] to connect the nested procedure to the context (lea stands for load effective address), which is then used by the internal procedure.

Anyways, the reason it would be called an executable stack is because the data stored in the current stack frame between [rsp + 12] and [rsp + 28] is treated as code (i.e. instructions).

Disclaimer: perhaps this is not the trampoline, but just a struct describing a nested function. I would appreciate if anyone can double check this.

2 Likes

What I’m missing is at some point there should be an instruction like lea r10, [rsp] to connect the nested procedure to the context

That’s on the line:

mov     WORD PTR [rsp+18], -17847       

Where -17847 = 0x49 0xBA = mov r10, imm64.

1 Like

Thanks, @certik. No, I am not asking for any new language feature. It will take toooo much time for a new feature to get into the standard (if ever) and toooo much time for it to be implemented by compilers.

I agree with @RonShepard that the current internal-procedure approach is a good solution for this kind of problem. The only issue is that it leads to security issues and makes the code non-compileable on some modern systems. Sure, some compilers are fixing this issue, but the default implementation still uses executable stacks. I hope LFortran will solve this problem for good.

It seems that most of us here agree with ChatGPT o3-pro. This is very interesing.

There is an active Fortran community on StackOverflow (although with a different culture), but not everyone there participates in this discourse. Thus a question is asked there. If you want to prove ChatGPT o3-pro wrong, you may post your solution here under this post or on StackOverflow.

Thanks.

Thank you @ivanpribec for directing me to this option. I agree that it fixes the issue for gfortran. If only this became the default behavior.

This is very interesting. So it seems that ifx has not completely solved the problem yet.

Thank you @ivanpribec for posting the example here. Your example of root finding in a previous discussion is essentially the same. Are they consistent with what you quoted above? :wink:

1 Like

The credit goes to @fedebenelli who suggested it early in this thread.

I have the impression we might be assigning slightly different meanings to the same words. I don’t see a fundamental difference between the integration example in Note 12.18 and my root-finding example involving the fraction factor. We have discussed similar issues related to passing callback functions and safe multithreading before, just to remind you of two:


A recurring limitation in this discussion has been that the subroutine solver cannot be modified to accept a context argument (e.g. a derived type or similar). But given your expectation that compiler implementors should tackle the executable stack issue, and that the Fortran standard should ideally evolve to support better mechanisms — wouldn’t it also be fair to ask whether the third-party solver could be adapted too? It’s worth remembering that the word software (as opposed to hardware) implies flexibility:

software

  1. (computing) Encoded computer instructions, usually modifiable (unless stored in some form of unalterable memory such as ROM). [emphasis added]

@certik has also remarked above that,

… most 3rd party libraries allow you to pass user data. If they don’t, that’s a deficiency of the 3rd party library I think.

In another setting, a compiler expert once told me:

“When the need for a feature can be addressed in portable open-source libraries that are available today (or in a few years), experience shows that that’s a much better solution than trying to change the language. […] If you have a library implementation today, and it’s portable and universally available, you already have the best solution.”

I wanted to conclude my post with an (ironic) quote from Alan Perlis’s Epigrams on Programming. There are several which resonate with this thread, for instance

“Adapting old programs to fit new machines usually means adapting new machines to behave like old ones.”

Sometimes, asking the language or compiler to bend is the harder road — especially when a small change to the signature of solver could go a long way.

3 Likes

I think that internal functions is a good solution to the problem, but they must be implemented by compilers without an executable stack by default. As an optimization, if the platform and user allows it, an executable stack (if it is faster) can be used, but that should not be the default.

I personally use internal functions, I think Fortran compilers just have to support it without executable stack, and most do. But if it is not an option, then extending the solver to accept a “data” argument seems like the way to go a well. I also list 5 other ways to do handle callbacks here: Fortran Best Practices — Fortran90 1.0 documentation.

2 Likes

I think the problem with this is that the solver (a general library routine) needs to declare the derived type dummy argument, even if it is not using anything within it, so that it can pass that argument eventually to the work routine (written specifically by the user for a particular task). C does this with void* type arguments, which can match any kind of actual argument.

Is there a way for fortran to do something similar by declaring within solver a class(base) dummy argument, where base is a derived type with nothing in it but has been extended by the user with whatever relevant data is needed? Then the work routine could declare its dummy argument with the appropriate type, or work within a select type block with the appropriate type being specified.

1 Like

I totally agree with you @certik . The internal-procedure approach is mathematically straightforward and simple, which is important for me as a mathematician. I think it may be equally important for most programmers who want to focus on math & logic & algorithms instead of programming techniques.

2 Likes

TL;DR: change is slow.

Gfortran started as a fork of g95, and probably at the time having an F95/F03 compiler was more important than avoiding all stack-related security issues —and the gcc extension for nested functions was already there, so taking advantage of it was straightforward.

Besides, back then, Moore’s law was still a thing —the multicore era would come later.

ld started issuing the “executable stack” warning only with v2.39 (in 2022), so it’s understandable if not all compilers are up-to-speed in that regard.

And in the case of Standard Fortran, even if users have lots of use-cases for some language features (e.g., parameterized derived types), if the compiler vendors don’t like the feature, it might take 20+ years to implement.

(Did the Standard Committee skip Fortran 2013 because of the slow implementation of new standard features?)

Finally, your issue is mostly related to interoperability with MATLAB, and the fact that a fix from MathWorks, if ever, might also be slow to arrive.

1 Like

Ok, I tried to implement what I described, and this is a little toy example:

module lib
   implicit none
   type base  ! base type to be extended by the user of this library.
   end type base
   interface
      subroutine work( a, b )
         import :: base
         class(base), intent(inout) :: a
         integer, intent(inout) :: b
      end subroutine work
   end interface
contains
   subroutine lib_sub( callback, a, b )
      implicit none
      procedure(work) :: callback
      class(base), intent(inout) :: a
      integer, intent(inout) :: b
      print*, 'lib_sub entry: b=', b
      call callback( a, b )
      print*, 'lib_sub return: b=', b
      return
   end subroutine lib_sub
end module lib

program classx
   use lib
   implicit none
   type, extends(base) :: ext_t
      integer :: c
   end type ext_t
   type(ext_t) :: a = ext_t( c=3 )
   integer :: b = 42
   print*, 'initial a%c=', a%c, ' b=', b
   call lib_sub( mywork, a, b )
   print*, 'after lib_sub: a%c=', a%c, ' b=', b
contains
   subroutine mywork( a, b )
      class(base), intent(inout) :: a
      integer, intent(inout) :: b
      print*, 'mywork:'
      select type (a)
      type is (ext_t)
         a%c = a%c + 1
         b   = b + 1
      end select
      return
   end subroutine mywork
end program classx

$ gfortran classx.f90 && a.out
 initial a%c=           3  b=          42
 lib_sub entry: b=          42
 mywork:
 lib_sub return: b=          43
 after lib_sub: a%c=           4  b=          43

In this case, the lib module defines a base type with no components. It contains a subroutine that declares a dummy argument of that type but does not access anything within it, the contents are anonymous, it only passes it on to the dummy procedure argument.

In the main program, the type is extended with useful stuff, and that extended type is passed along with the contained subroutine to the library subroutine. The mywork() subprogram does know all about the extended type, so it can modify the members of the derived type as necessary.

I think this accomplishes the same kind of thing as the void* argument in C. It allows the derived type to be passed through lib_sub() without lib_sub() knowing its contents, but it allows full access to its contents within the callback routine.

If I had more time, maybe the code could be simplified a little. I find this kind of object oriented programming in fortran clumsy. For example, I would like to just declare

type(ext_t) :: a

within mywork(), because that is the only type of argument that I ever want to pass to that routine, but I don’t think you can do that. If you could, then argument mismatches could be detected at compile time instead of run time. You must instead declare it as class(base) and then do select type within. The programmer can test for unsupported derived types at run time (I didn’t do that in the above code).

Anyway, this shows how to pass anonymous information through lib_sub() in fortran.

1 Like

I hoped to have an implementation based on derived types as follows. Unfortunately, it is NOT valid Fortran.

! N.B.: The following code is NOT valid. For concept demonstration only.


!----------------------------------------------------------------------!
! solver_mod: a module defining an optimization solver
module solver_mod

implicit none
private
public:: solver

! OBJ: an abstract interface for an objective function
! We CANNOT change it.
abstract interface
    subroutine OBJ(x, y)
    real, intent(in):: x
    real, intent(out):: y
    end subroutine OBJ
end interface

contains

! solver: a doing-nothing solver for demonstration. 
! We CANNOT change its interface.
subroutine solver(objective)
procedure(OBJ):: objective
real y
call objective(0.0, y)
end subroutine solver

end module solver_mod
!----------------------------------------------------------------------!


!----------------------------------------------------------------------!
! N.B.: This part of the code is for concept demonstration only. 
! It is NOT valid Fortran.
module problem_mod
implicit none
private
public:: PROB_T

type PROB_T
    real hyper_parameter
    contains

    subroutine objective(x, y)
    ! A simple objective function for demonstration, 
    ! hoping that it has access to hyper_parameter.
        real, intent(in):: x
        real, intent(out):: y
        y = (x+hyper_parameter)**2
    end subroutine objective

end type PROB_T


end module problem_mod
!----------------------------------------------------------------------!


!----------------------------------------------------------------------!
program optimize

use solver_mod, only: solver
use problem_mod, only: PROB_t
implicit none
type(PROB_t):: problem

problem%hyper_parameter = 42.0

call solver(problem%objective)


end program optimize
!----------------------------------------------------------------------!

I also tried an alternative implementation of PROB_T similar to the following, which is still INVALID.

module problem_mod

implicit none
private
public:: PROB_T


type PROB_T
    real hyper_parameter
    contains
        procedure:: objective
end type PROB_T

contains

    subroutine objective(self, x, y)
        class(PROB_T), intent(in):: self
        real, intent(in):: x
        real, intent(out):: y
        ! A simple objective function for demonstration.
        y = (x+self%hyper_parameter)**2
    end subroutine objective


end module problem_mod

Your second case is invalid due to interface mismatch —i.e., you are providing a procedure with three arguments to the solver, which expects a procedure with two arguments.

Without changing the solver’s signature, there’s not much you can do.

But by changing it, even a little, you can accomplish things like:

module solver_mod
    implicit none
    private

    abstract interface
        subroutine OBJ(x, y, DATA)
            real, intent(in):: x
            real, intent(out):: y
            class(*), optional, intent(in) :: DATA
        end subroutine OBJ
    end interface

    public:: solver

contains
    subroutine solver(objective, DATA)
        procedure(OBJ):: objective
        class(*), optional, intent(in) :: DATA
        real y
        call objective(0.0, y, DATA = DATA)
    end subroutine solver
end module solver_mod

module problem_mod
    implicit none
    private

    type, public :: prob_t
        real :: hyper_parameter
    end type

    public:: objective

contains
    subroutine objective(x, y, DATA)
        real, intent(in):: x
        real, intent(out):: y
        class(*), optional, intent(in) :: DATA

        real :: hyper_parameter

        hyper_parameter = 42 ! default, if not provided
        if (present(DATA)) then
            select type (DATA)
            type is (real)
                hyper_parameter = DATA
            class is (prob_t)
                hyper_parameter = DATA%hyper_parameter
            end select
        endif

        print*,'Solving... for ',hyper_parameter
        y = (hyper_parameter)**2
    end subroutine objective
end module problem_mod

program optimize
    use solver_mod, only: solver
    use problem_mod

    implicit none

    type(prob_t) :: p = prob_t(24.)

    call solver(objective)
    call solver(objective, 12.)
    call solver(objective, p)
end program optimize

The above is inspired by Gtk’s use of a void pointer as a last, optional argument.

2 Likes

Even though it is valid to call problem%objective(x, y), the interface of problem%objective does not comply with OBJ(x, y). This felt a bit inconsistent to me.

This is similar to my earlier posted code, but you use class(*) rather than class(base). What are the advantages and disadvantages of these two approaches?