I have a codebase which works well, but I can’t seem to be able to just define function/subroutine interfaces just once. The only reliable way to seem to get it working is to have 1000 lines of copy-pasted interfaces. I’ve made a trivially small example below to illustrate my point. For reference, I’m using gfortran, mainly on Linux. Anyway…
I have several families of subroutines f
, g
and h
. In each family is a set of subroutines with identical in/outputs, but different algorithms, for example f1
and f2
.
Moreover, in addition to ordinary parameters, subroutines are passed to others dynamically, to be selected at runtime. For example, one of the f
subroutines is always passed to any of the g
subroutines. On line, let’s say 1234, there is a call to g(f,...)
, but whether this is resolved as g1(f2,...)
or otherwise is chosen at runtime.
To my knowledge, this is done best by function pointers as
procedure (f), pointer :: f_ptr => f1
and then f_ptr
is passed to g
, for example. This compiles and runs, apparently quite efficiently. The problem is that I seemingly have to specify the interfaces explicitly in every single subroutine definition. So h(f,g,...)
seems to require an interface to f
and then another interface to g
which contains another interface to f
.
This problem seems to arise especially if I pass a subroutine, but do not call it, so let’s say g2(f,...)
never actually calls f
.
How can I robustly define the interfaces once, and have them used throughout a program?
Below are two files to illustrate this that I think should work, but don’t compile.
Definitions.F90
module Definitions
implicit none
INTEGER, PARAMETER :: num = KIND(0.d0) ! precision for floats
INTEGER, PARAMETER :: HEADER_LENGTH = 1024
REAL(num), PARAMETER :: PI = 4.0_num*ATAN(1.0_num)
interface
subroutine f (someVar)
IMPORT :: num
REAL(num) :: someVar
end subroutine f
end interface
interface
subroutine g (someVar,someInt,f)
IMPORT :: num
REAL(num) :: someVar
INTEGER :: someInt
interface
subroutine f (someVar)
IMPORT :: num
REAL(num) :: someVar
end subroutine f
end interface
end subroutine g
end interface
interface
subroutine h (someVar,anotherVar,someInt,f,g)
IMPORT :: num
REAL(num) :: someVar, anotherVar
INTEGER :: someInt
interface
subroutine f (someVar)
IMPORT :: num
REAL(num) :: someVar
end subroutine f
end interface
interface
subroutine g (someVar,someInt,f)
IMPORT :: num
REAL(num) :: someVar
INTEGER :: someInt
interface
subroutine f (someVar)
IMPORT :: num
REAL(num) :: someVar
end subroutine f
end interface
end subroutine g
end interface
end subroutine h
end interface
end module Definitions
Program.F90
module Functions
USE Definitions
implicit none
contains
subroutine f1 (someVar)
REAL(num) :: someVar
someVar = 2.0
end subroutine f1
subroutine f2 (someVar)
REAL(num) :: someVar
someVar = 2.0*sin(1.0)
end subroutine f2
subroutine g1 (someVar,someInt,f)
REAL(num) :: someVar
INTEGER :: someInt
call f(someVar)
someInt = 2
end subroutine g1
subroutine g2 (someVar,someInt,f)
REAL(num) :: someVar
INTEGER :: someInt
someVar = cos(2.0)
someInt = 3
end subroutine g2
subroutine h1 (someVar,anotherVar,someInt,f,g)
REAL(num) :: someVar, anotherVar
INTEGER :: someInt
call g(someVar,someInt,f)
anotherVar = 3.0
end subroutine h1
subroutine h2 (someVar,anotherVar,someInt,f,g)
REAL(num) :: someVar, anotherVar
INTEGER :: someInt
call f(someVar)
someInt = -1
anotherVar = 5.0
end subroutine h2
end module Functions
program testing_interfaces
procedure (f), pointer :: f_ptr => null ()
procedure (g), pointer :: g_ptr => null ()
procedure (h), pointer :: h_ptr => null ()
INTEGER :: num_args, var1
REAL(num) :: var2, var3
num_args = iargc()
if(num_args .le. 0) then
f_ptr => f1
g_ptr => g1
h_ptr => h1
else
f_ptr => f2
g_ptr => g2
h_ptr => h2
end if
call h_ptr(var2,var3,var1,f_ptr,g_ptr)
print*, var1, var2, var3
end program testing_interfaces