Two interfaces pointing to a same `submodule` procedure

Dear all,

I want to have 2 separate interfaces in a module, both using the same function among their options.
The function should be located in a submodule, for example:

module example
interface det
    pure real module function my_det(a) result(det)
        real, intent(in) :: a
    end function    
end interface
interface operator(.det.)
    pure real module function my_det(a) result(det)
        real, intent(in) :: a
    end function     
end interface
end module

submodule (example) sub_ex
contains
    pure real module function my_det(a) result(det)
        real, intent(in) :: a
        det = 1.0/a
    end function
end submodule

I get the following errors:

  • gfortran → Error: Duplicate EXTERNAL attribute specified at (1)
  • Intel → error #6115: A separate interface body must have been declared in the program unit or an ancestor of the program unit for the separate module procedure. [MY_DET]
  • flang-new → error: 'my_det' is already declared in this scoping unit

full example here.

This is of course possible, and has no issues whatsoever, if everything is inside the same module file (no submodules).

So I am guessing this is not possible. I am looking for workarounds, and I wonder if the only possible solution is to create one wrapper function for each operator version? In other words, does the Fortran standard prevent this, and if so, what’s good practice to achieve what I’m trying to?

I think you can solve the issue by not repeating the interface twice:

interface operator(.det.)
    module procedure my_det
end interface
2 Likes

Wow, thanks @ivanpribec, it was that simple!
So for each module procedure, its interface has to be defined once (maybe, a generic interface of its own), and then just used as a module procedure in the usual way.

So maybe this is better framed:

module example
implicit none
interface 
    pure real module function my_det(a) result(det)
        real, intent(in) :: a
    end function 
end interface
interface det
    module procedure my_det
end interface
interface operator(.det.)
    module procedure my_det
end interface
end module
1 Like

@ivanpribec , @FedericoPerini ,

Does any of your Fortran advocacy, especially in terms of an improved ecosystem and tools for Fortran, extend to accelerated advancement of GCC gfortran toward standard conformance? It’ll be great if a group of Fortranners can take that up in earnest, either via the Sovereign Tech fund or via NumFOCUS-based sponsorship or whatever.

In the particular situation here by @FedericoPerini , one can also consider a GENERIC binding introduced starting Fortran 2018 that naturally facilitates an INTERFACE to be declared only once, as it should be.

   generic :: operator(.det.) => my_det

For any nouveau Fortranner who might like an example to try out, here’s one that can be worked out using Intel Fortran; note this convenience is pending in gfortran hence my preamble above:

module m
   interface
      module function ans( x ) result(r)
         integer, intent(in) :: x
         integer r
      end function
   end interface
   generic :: operator(.ans.) => ans 
end module
submodule(m) sm
contains
   module function ans( x ) result(r)
      integer, intent(in) :: x
      integer r
      r = x + 42
   end function
end submodule
   use m
   print *, "Using function interface, the answer is ", ans( x=0 )
   print *, "Using operator interface, the answer is ", .ans. 0
end 
C:\temp>ifx /free /standard-semantics p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.1.0 Build 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 Using function interface, the answer is  42
 Using operator interface, the answer is  42
2 Likes

Thanks for showing how this version works @FortranFan, I didn’t know about that.
I’m myself a fan of modernization but I think that especially for stdlib we shouldn’t push it too far, because it’s very important that the library is backwards compatible with at least a half decade of past compiler versions.

That said, I like seeing generic, like for a type-bound procedure (which is my preferred way to do interfaces in my codes)!