Interfaces for passing subroutines to subroutines

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
2 Likes

Maybe I misunderstood the issue, but wouldn’t abstract interfaces work here?
For example:

module definitions
    use ISO_FORTRAN_ENV
    abstract interface
        subroutine i_f (someVar)
            import
            real(REAL64) :: someVar
        end subroutine
        subroutine i_g(someVar, someInt, f)
            import
            real(REAL64) :: someVar
            integer :: someInt
            procedure(i_f) :: f
        end subroutine
        subroutine i_h(someVar, anotherVar, someInt, f, g)
            import
            real(REAL64) :: someVar, anotherVar
            integer :: someInt
            procedure(i_f) :: f
            procedure(i_g) :: g
        end subroutine
    end interface
end module definitions
1 Like

What compiler do you use? And what are the error messages? I merely glanced at the code, but it seems fine to me.

Right, compiling the code brought up quite a few error messages. For instance, subroutine g2 does not define argument f. If you copy the interface definition for that procedure argument into the subroutine’s code, then that should work.
@jwmwalrus 's solution may be what you are looking for.

Thanks, but it doesn’t seem to work with abstract, or normal interfaces equally. In particular, it seems to be tripping over cases where I pass in a subroutine without calling it.

For instance, in the example above, g1 calls f and is fine, while g2 does not call f and causes a compiler error. Both, of course, receive f as an input.

Yes, this is my problem - in my actual code I have to copy-paste like 1000 lines of interfaces repeatedly. Is it possible to make the specified code work without copy-pasting? In other words, how can subroutine g2 automatically import the interface for f from Definitions.F90?

I’ve tried making a minimal working example for the abstract interface of @jwmwalrus below. Does it possibly work for the purpose…?

!! def.f90
module Definitions
  implicit none
  INTEGER, PARAMETER :: num = KIND(0.d0)
  INTEGER, PARAMETER :: HEADER_LENGTH = 1024
  REAL(num), PARAMETER :: PI = 4.0_num*ATAN(1.0_num)

  abstract interface
    subroutine f_i (someVar)
      IMPORT :: num   !!<--- this can be just "import" (then import everything outside)
      REAL(num) :: someVar
    end
    subroutine g_i (someVar,someInt,f)
      IMPORT :: num, f_i
      REAL(num) :: someVar
      INTEGER :: someInt
      procedure(f_i) :: f
    end
    subroutine h_i (someVar,anotherVar,someInt,f,g)
      IMPORT :: num, f_i, g_i
      REAL(num) :: someVar, anotherVar
      INTEGER :: someInt
      procedure(f_i) :: f
      procedure(g_i) :: g
    end
  end interface

end module Definitions
!! func.f90
module Functions

  USE Definitions, only: num, f_i, g_i, h_i
  implicit none

contains

  subroutine f1 (someVar)
    REAL(num) :: someVar
    !!
    print *, ">> f1"
    someVar = 2.0
  end
  subroutine f2 (someVar)
    REAL(num) :: someVar
    !!
    print *, ">> f2"
    someVar = 2.0*sin(1.0)
    print *, "        2 * sin(1.0) = ", someVar
  end

  subroutine g1 (someVar,someInt,f)
    REAL(num) :: someVar
    INTEGER :: someInt
    procedure(f_i) :: f
    !!
    print *, ">> g1"
    call f(someVar)
    someInt = 2
  end
  subroutine g2 (someVar,someInt,f)
    REAL(num) :: someVar
    INTEGER :: someInt
    procedure(f_i) :: f
    !!
    print *, ">> g2"
    someVar = cos(2.0)
    someInt = 3
  end
  subroutine h1 (someVar,anotherVar,someInt,f,g)
    REAL(num) :: someVar, anotherVar
    INTEGER :: someInt
    procedure(f_i) :: f
    procedure(g_i) :: g
    !!
    print *, ">> h1"
    call g(someVar,someInt,f)
    anotherVar = 3.0
  end
  subroutine h2 (someVar,anotherVar,someInt,f,g)
    REAL(num) :: someVar, anotherVar
    INTEGER :: someInt
    procedure(f_i) :: f
    procedure(g_i) :: g
    !!
    print *, ">> h2"
    call f(someVar)
    someInt = -1
    anotherVar = 5.0
  end

end module Functions
!! main.f90
program testing_interfaces

  use Definitions, only: num, f_i, g_i, h_i
  use Functions,   only: f1, f2, g1, g2, h1, h2
  implicit none

  procedure (f_i), pointer :: f_ptr => null ()
  procedure (g_i), pointer :: g_ptr => null ()
  procedure (h_i), pointer :: h_ptr => null ()

  INTEGER :: num_args, var1
  REAL(num) :: var2, var3
  num_args = iargc()

  print *, "num_args = ", num_args

  if (num_args <= 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

Test

$ gfortran def.f90 func.f90 main.f90
$ ./a.out
 num_args =            0
 >> h1
 >> g1
 >> f1
           2   2.0000000000000000        3.0000000000000000
$ ./a.out arg1
 num_args =            1
 >> h2
 >> f2
         2 * sin(1.0) =    1.6829419136047363     
          -1   1.6829419136047363        5.0000000000000000  

(Here, I’ve inserted print statements for the subroutine name, so that which subroutine is called specifically.)

1 Like

I don’t know what it is exactly meant with this, but the following seems to be working (based on abstract interfaces as per @jwmwalrus 's initial suggestion):

EDIT: I give kudos to @septc , he basically wrote the same as I did, but earlier. I would say it’s what OP’s looking for.

1 Like

Almost completely the same code! :laughing: (I think it’s nice to repeat a similar code, because it means many people come to the same thing…)

1 Like

OK, thank you and @mEm very much, that seems to work.

I haven’t had time to test this yet - is this performant, or would I be better off defining specific h_111 to be hard-coded with h1(g1(f1...)))?