Below is a toy program that calls an optimization solver to optimize a simple parametrized objective function (see a similar example of root finding by @ivanpribec in a previous discussion if mine is not clear enough; see also the example in Note 12.18 on page 290 of WD 1539-1 J3/10-007r1, F2008 Working Document).
!----------------------------------------------------------------------!
! optim.f90: a simple program that calls an optimization solver to
! optimize a simple parameterized objective function.
!----------------------------------------------------------------------!
!----------------------------------------------------------------------!
! solver_mod: a module defining an optimization solver
module solver_mod
implicit none
private
public:: solver
! OBJ: an abstract interface for an objective function
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. It is provided by a
! third library, so we CANNOT change its signature to accept a hyper-
! parameter for `objective`.
subroutine solver(objective)
procedure(OBJ):: objective
real f
call objective(0.0, f)
end subroutine solver
end module solver_mod
!----------------------------------------------------------------------!
!----------------------------------------------------------------------!
program optimize
use solver_mod, only: solver
implicit none
! `hyper_parameter`: a hyperparameter for the objective function. In
! real applications, this parameter is not a constant, but a variable
! that cannot be predicted before the optimization starts.
real hyper_parameter
hyper_parameter = 42.0
call solver(objective)
contains
!--------------------------------------------------------------!
! objective: a simple objective function for demonstration.
! F2008 allows to pass internal procedures as actual arguments.
! See Note 12.18 on page 290 of WD 1539-1 J3/10-007r1 (F2008
! Working Document). We implement `objective` internally so that
! `hyper_parameter` is visible to it. We choose not to pass the
! parameter by a module variable, which is thread-unsafe.
subroutine objective(x, y)
real, intent(in):: x
real, intent(out):: y
y = (x+hyper_parameter)**2
end subroutine objective
!--------------------------------------------------------------!
end program optimize
!----------------------------------------------------------------------!
We assume that the code to call the solver is simply
call solver(objective)
In other words, solver
accepts only one input, which is the subroutine that defines the objective function. In practice, it should also take inputs like the starting point and generate outputs such as the optimal point. We omit them for simplicity.
The signature of the objective function objective
is simply
objective(x, f)
where x
is the input, and f
is the function value. However, the specific definition of objective
depends on some hyperparameters that cannot be determined beforehand.
In our program, objective
is implemented as an internal subroutine of the main program, so that the hyperparameter defined in the program is visible to objective
. This enables us to pass the parameterized objective
to solver
without explicitly passing the hyperparameter. Fortran 2008 allows passing an internal subroutine to another subroutine as an actual argument. See Note 12.18 on page 290 of WD 1539-1 J3/10-007r1 (F2008 Working Document).
However, starting from gfrotran 13, such an internal subroutine will incur a linker warning about executable stack:
$ gfortran --version && gfortran optim.f90 -Wall
GNU Fortran (Ubuntu 13.3.0-6ubuntu2~24.04) 13.3.0
Copyright (C) 2023 Free Software Foundation, Inc.
This is free software; see the source for copying conditions. There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
/usr/bin/ld: warning: /tmp/cc4i8jW5.o: requires executable stack (because the .note.GNU-stack section is executable)
More seriously, it causes a segfault in MATLAB R2025a, which is probably a bug of MATLAB. MathWorks will take a long time to fix the bug if it is confirmed.
An alternative is to make the hyperparameter available to objective
by a module variable, but this is not thread-safe recursion-safe.
Question: How to modify the implementation so that it is thread-safe without using internal subroutines without using module variables or internal subroutines? Of course, the implementation must be completely standard-conforming.
Any comments or criticism will be appreciated. Thank you very much.
The following is a very personal opinion. In terms of programming techniques, the example discussed here is almost the same as the one in Note 12.18 on page 290 of WD 1539-1 J3/10-007r1, F2008 Working Document. If an example in the Fortran standard leads to a safety issue (executable stack) in a major compiler (gfortran / Intel), this is something alarmingly wrong with the language or the compiler. The two cannot be simultaneously innocent in this case (sorry for complaining without providing a solution).