I want to optimize a function of several variables with respect to one particular variable.
What is a good practice to implement function currying, i.e. given f(x,y), define g(y) = f(x=\bar x)(y) with some fixed \bar x?
From recent related topic, one can use module variables, but do I understand correctly
that this is not a threadsafe solution? Can this be done with pure procedures?
I’m not very experienced in Fortran, can I write a function that returns another function?
! gfortran -o currying currying.f90
module currying
use, intrinsic :: iso_fortran_env, only : rk => real64
real(rk), protected :: factor
contains
pure real(rk) function mult(x,y)
real(rk), intent(in) :: x
real(rk), intent(in) :: y
mult = x*y
end function mult
subroutine init_currying(factor_value)
real(rk), intent(in) :: factor_value
factor = factor_value
end subroutine init_currying
pure real(rk) function mult_currying(x)
real(rk), intent(in) :: x
mult_currying = mult(factor,x)
end function mult_currying
end module currying
program test
use currying
write(*, *) mult(2.0_rk,2.0_rk)
call init_currying(2.0_rk)
write(*, *) mult_currying(2.0_rk)
write(*, *)
write(*, *) mult(3.0_rk,2.0_rk)
call init_currying(3.0_rk)
write(*, *) mult_currying(2.0_rk)
write(*, *)
end program test
! ./currying
! 4.0000000000000000
! 4.0000000000000000
! 6.0000000000000000
! 6.0000000000000000
Currying in the LISP sense is not possible - Fortran does not allow you to construct functions. (Well, you can work around that limitation in a certain way (*))
The example code you show is quite close to what you can achieve. Maybe define a generic interface, so that mult can take either one or two arguments, so that you effectively hide the currying step.
Module variables are indeed not thread-safe, but that is actually beyond the Fortran standard. Such variables are accessible from any routine that uses the module. You could consider using coarrays if this is an important issue for you (or OpenMP/MPI as alternative multithreading paradigms).
What you can also do is use an object-oriented approach: a derived type holding the factor and the functions:
! curry.f90 --
! Illustrate currying with an OO approach
!
module currying
implicit none
type :: function_t
real :: factor
contains
procedure :: mult_xy => mult_x_y
procedure :: mult_x => mult_x_factor
generic :: mult => mult_xy, mult_x
end type
contains
real function mult_x_y( this, x, y )
class(function_t) :: this
real, intent(in) :: x, y
mult_x_y = x * y
end function mult_x_y
real function mult_x_factor( this, x )
class(function_t) :: this
real, intent(in) :: x
mult_x_factor = x * this%factor
end function mult_x_factor
end module currying
program test_currying
use currying
type(function_t) :: f
f%factor = 2.0 ! Lazy, should provide init_currying
write(*,*) f%mult(3.0, 2.0)
write(*,*) f%mult(3.0)
end program test_currying
Regards,
Arjen
(*) Constructing “functions” on the fly a be done - I have illustrated that in my 2012 book Modern Fortran in practice. Whether it is a useful technique in your case, is, however, an open question.
Great answer, thank you. Your solution can be used with array arguments of variable length (I don’t think that my can be), an allocatable component can be added to the type and an init procedure.
For now, the easiest way for me is to include all variables directly in optimization routine.
I also think the “function object” approach will be nice
RE multi-threading, the “firstprivate” directive may be useful, but I hope someone familiar with OpenMP will chime in…
module currying
...
real(rk), protected :: factor
!$omp threadprivate( factor )
...
end module
program test
use currying
implicit none
real(rk) x
integer i
!$omp parallel do default(none) private(i,x)
do i = 1, 3
x = i
print *, "mult = ", mult( x, x )
call init_currying( x )
print *, "mult_currying = ", mult_currying( x )
enddo
!$omp end parallel do
end program test
$ gfortran-10 -fopenmp test.f90 && ./a.out
mult = 1.0000000000000000
mult = 9.0000000000000000
mult = 4.0000000000000000
mult_currying = 1.0000000000000000
mult_currying = 9.0000000000000000
mult_currying = 4.0000000000000000
More directly addressing the original question, how about
module curry
real :: barx
contains
function f(xo,y)
real,optional :: xo
real :: y
if (present(xo))
x = xo
else
x = barx
! compute f using x and y
end function f
end module
Then g(y) is the same as f(y). You would need to externally have a USE of the module to define barx, or initialize it in the module is the default value is normally the same. [Correction: g(y) is the same as f(y=y)].