Module procedures and abstract interfaces

I have a comment/question regarding the mechanism provided by the standard to store a number of identical interfaces and the level of verbosity involved.

Say I write a bunch of functions, all with the same interface and the same function result. The only difference involved are the methods employed to evaluate the same function.

One of the things I can do in this case is to create a module, with a single INTERFACE block containing the interfaces of the different implementations inside it. If I declare the interfaces with the “module function” keywords I can write the source codes inside a submodule, with the header “module procedure” for each individual function code. In this way, i achieve the recommended data abstraction.

This works very well and is very useful. The only irksome detail here is that the interface block inside the module ended up containing several almost identical declarations, whose only differences were the actual names of the various functions.
Then I thought of declaring an abstract interface andPreformatted text only include the list of the proper names inside the interface block with the PROCEDURE() declaration, in order to achieve a lower verbosity level. But it seems that the standard forbids this alternative.

This is the sample code:

MODULE module_procedures_abstract_interface
use, intrinsic :: iso_fortran_env, only: dp => real64
implicit none

ABSTRACT INTERFACE
   function fun_2_args(x, y)
   import :: dp
   real(dp) :: fun_2_args
   real(dp), intent(in) :: x, y
   end function fun_2_args
END INTERFACE

! INTERFACE ! version 1
!    PROCEDURE(fun_2_args) :: fun1, fun2 
! END INTERFACE

INTERFACE ! version 2
   module function fun1(x,y)
!    import :: dp
   real(dp) :: fun1
   real(dp), intent(in) :: x, y
   end function fun1
!***
   module function fun2(x,y)
!    import :: dp
   real(dp) :: fun2
   real(dp), intent(in) :: x, y
   end function fun2
END INTERFACE 
END MODULE module_procedures_abstract_interface

Compilation with version 1 commented works all right, but if I uncomment version 1, error messages appear. The intel compiler gives:

$> ifort -c module_procedures_abstract_interface_MOD.f90
module_procedures_abstract_interface_MOD.f90(16): error #6651: The PROCEDURE specification is allowed only if the interface-block has a generic-spec.
   PROCEDURE(fun_2_args) :: fun1, fun2 
---^
compilation aborted for module_procedures_abstract_interface_MOD.f90 (code 1)

So it seems to me that I only have the more verbose solution allowed.

Or am I missing something?

Try the following:

MODULE module_procedures_abstract_interface
use, intrinsic :: iso_fortran_env, only: dp => real64
implicit none

ABSTRACT INTERFACE
   function fun_2_args(x, y)
   import :: dp
   real(dp) :: fun_2_args
   real(dp), intent(in) :: x, y
   end function fun_2_args
END INTERFACE

   PROCEDURE(fun_2_args) :: fun1, fun2 

END MODULE module_procedures_abstract_interface

I don’t see how that would help:

  • The PROCEDURE statement helps declare two external procedures with names fun1 and fun2 but beyond that it is of little use:
  • The problem with what you suggest is - given the current standard - neither at the implementation level nor at the level of the users consuming such library code will there will be any checking-based use of that abstract interface or the procedure declarations.

Any interested readers can see my comments at the comp.lang.fortran thread where @rgaelzer first posted this issue.

@rgaelzer may be able to have some checking done by using the module that was given. Here is one example, where the implementation of function FUN1 is not consistent with the interface.

subroutine consume(y)
use module_procedures_abstract_interface
implicit none
real(dp) :: x,y
x = 2.5d0
y = fun1(x)
return
end subroutine

Compiling with Gfortran:

T:\LANG>gfortran -c rg.f90
rg.f90:22:4:

   22 | y = fun1(x)
      |    1
Error: Missing actual argument for argument 'y' at (1)

Indeed. mecej4’s solution works fine for external procedures, but for my objectives it won’t work, because:

  1. An abstract interface is apparently not permitted to contain a module procedure. The intel compiler will throw an error.
  2. If I include the sources of fun1 and fun2 in a submodule, both compilers will abort with error messages.

So, I guess the standard does not allow that.

1 Like

@rgaelzer ,

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.obj

C:\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.

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.

Thanks for the suggestions.
Looks like that for the current standard, there is no way to avoid repetitive and (in my view) unnecessary repetition of the same interface in order to tackle the problem I posed.
As I said, both mine and FortranFan’s implementations work all right, so it’s not really a shortcoming of the standard, but rather an easthetic issue regarding the conciseness of the language.
Eventually, I’d like to put forward a proposition on fortran_proposals as you suggested. As I recall, the complaint of verbosity is something that comes up regularly in Fortran forums. So I guess some proposals on this regard have been made already.