So for readers who may be interested in this and also those want to learn what Fortran 2008 introduced via SUBMODULEs to separate out the interface from the implementation (and also to mitigate compilation cascade issues), the equivalent approach is as shown below:
module m
private
interface
! Note the repeated interface characteristics
module function fun1(x,y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
end function
module function fun2(x,y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
end function
module function fun3(x,y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
end function
end interface
procedure(fun1), 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
submodule(m) implementations_sm
contains
module procedure fun1 !<-- Interface from the parent module
z = x + y
end procedure
module procedure fun2 !<-- Interface from the parent module
z = 2*x + 3*y
end procedure
module procedure fun3 !<-- Interface from the parent module
z = x - y
end procedure
end submodule
use m
call setfun( "fun2" )
print *, fun(3, 4)
end
with the same program behavior as shown in the previous post.
So now, to reduce verbosity, the MODULE PROCEDURE clauses are used in the implementations that permit the subprogram INTERFACEs to be “brought in” from the parent module. The problem with this can be where the parent and submodules are remote from each other; this can be error-prone or inconvenient based on whose who are authoring the implementations.
So @rgaelzer and anyone who has ideas and can “sell it” to the powers-that-be with Fortran to help with such matters involving verbosity and duplication (aspects which are usually lower on priority for Fortran standard development), please propose at GitHub - j3-fortran/fortran_proposals: Proposals for the Fortran Standard Committee.
One of the problems here is Fortran does not conceptually allow an interface-to-self.