So, as discussed at comp.lang.fortran, you can investigate if the shown approach (repeated below for any reader’s sake who may not want to peruse another forum) is acceptable to you as a workaround that is kosher with the current standard. As you brought up, you can employ some “guards” by applying suitably the PUBLIC/PRIVATE attributes and even the PROTECTED one.
module implementations_m
contains
function fun1(x,y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
z = x + y
end function
function fun2(x,y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
z = 2*x + 3*y
end function
function fun3(x,y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
z = x - y
end function
end module
module m
use implementations_m
private
abstract interface
function Ifun(x,y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
end function
end interface
procedure(Ifun), protected, pointer, public :: fun => null() ! or set to default
public :: setfun
contains
subroutine setfun( fun_name )
character(len=*), intent(in) :: fun_name
select case ( fun_name )
case ( "fun1" )
fun => fun1
case ( "fun2" )
fun => fun2
case ( "fun3" )
fun => fun3
case default
! error stop?
end select
end subroutine
end module
use m
call setfun( "fun2" )
print *, fun(3, 4)
end
C:\Temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.-out:p.exe
-subsystem:console
p.objC:\Temp>p.exe
18
You still have considerable verbosity unfortunately. Additionally you have the work toward a setter method and the instructions therein. Then there is the run-time invocation of setfun. But the gain will be your consumer (who may be you yourself but often with different incarnations and memory recall in the future!) can mimic a generic interface in the use of the method i.e., if that is of any value.