On interface ambiguity

Hello,

First time posting, though I’ve been reading for a while. I’m trying to make use of interfaces to simplify calling subroutines (e.g. call my_sub instead of my_sub_XXX, where XXX changes for kinds).
I have previously used them for differentiating kinds, and had no problem.
Now what I have is a subroutine with one of its arguments a function (with its relevant interface in the module). One subroutine uses a function f(x), the other a function f(x,y).

module my_mod
    implicit none
    interface
        real function fx(x)
            real, intent(in) :: x
            ...
        end function
        real function fxy(x,y)
            real, intent(in) :: x
            ...
        end function
    end interface

contains
    subroutine sub1(my_funx, ...)
        procedure(fx) :: my_funx
        ...
    end subroutine sub1
    subroutine sub2(my_funxy, ...)
        procedure(fxy) :: my_funxy
        ...
    end subroutine sub2
end module my_mod

Those functions would be defined in the main program, for example, that uses my_mod
Is there a way of creating a generic interface for sub1 and sub2? Naming the interface of the functions, and then using procedure(generic_f) does not work. Neither does creating a named interface for sub1 and sub2. In the former case, the compiler complains that “the interface may not be generic”; in the latter, it says there is ambiguity in the interface. Those are errors from gfortran 10.2 (on windows, through mingw).
Alternatives to using procedure(...) :: my_fun within the subroutines are also welcome too (I am aware of the possibility of using pointers, though I haven’t tried that route yet).

Thank you.

3 Likes

That is an interesting question. However, I am afraid what you need is impossible, unless the return type, kind, or shape of the function results are different. For example, the following would work:

module my_mod

    implicit none

    abstract interface
        function fx(x) result(result)
            use iso_fortran_env, only: SP => real32
            real(SP), intent(in) :: x
            real(SP)             :: result
        end function
    end interface

    abstract interface
        function fxy(x,y) result(result)
            use iso_fortran_env, only: DP => real64
            real(DP), intent(in) :: x, y
            real(DP)             :: result
        end function
    end interface

    interface sub
        module procedure :: sub1, sub2
    end interface sub

contains

    subroutine sub1(my_funx)
        procedure(fx) :: my_funx
    end subroutine sub1
    
    subroutine sub2(my_funxy)
        procedure(fxy) :: my_funxy
    end subroutine sub2
    
end module my_mod

The only difference between the two functions is the kind of the real type of their output. One returns real32 and the other real64. That is enough for the compiler to distinguish the two interfaces from each other. For extensive details, see for example, “Overloading and generic interfaces” page 96 of “Modern Fortran Explained” by Metcalf et al. If anyone knows any other resources, would be great to post it here.

Thank you for your reply shahmoradi. In my case all return parameters are the same (type and kind), the only difference is the function f(x) or f(x,y).
It doesn’t make sense that an interface is ambiguous when one function has one input parameter, and the other has two (non-optional).
There is an example in the Fortran 2018 Standard (C.10.6, paragraph 19, with interface good5). Those are subroutines, with one and two arguments, but I assumed it would work for functions.
I will have to write several subroutines if there is no other solution.

That book is not in the public domain, so I don’t think it is legal and suggest that you remove the link. Quoting a paragraph of the book to answer a question is fair use.

1 Like

In that case, it would be good to also remove it also from the quote in your response.

My naive guess is that this could be resolved in future standards. But I am not sure, @sblionel, @certik, @milancurcic as the Fortran committee members that I know of, might know better.

1 Like

@witenion ,

Have you considered OPTIONAL attribute? Depending on what you’re trying to do, that may simplify your code considerably.

module my_mod

   implicit none

   abstract interface
      real function Ifunc(x, y)
         implicit none !<-- Don't forget this; INTERFACE body doesn't inherit IMPLICT statements from host scope
         real, intent(in) :: x
         real, intent(in), optional :: y
      end function
   end interface

contains

    subroutine sub(my_fun, ..)
       procedure(Ifunc) :: my_fun
       ..
    end subroutine sub

end module my_mod
1 Like

If OPTIONAL is not an option (!) for you, “containers” for procedure pointers is something you can consider:

module my_mod2

   implicit none

   abstract interface
      real function Ifuncx(x)
         implicit none
         real, intent(in) :: x
      end function
      real function Ifuncxy(x, y)
         implicit none
         real, intent(in) :: x
         real, intent(in) :: y
      end function
   end interface
   type :: Cfuncx
      procedure(Ifuncx), nopass, pointer :: funcx => null()
   end type
   type :: Cfuncxy
      procedure(Ifuncxy), nopass, pointer :: funcxy => null()
   end type

   generic :: sub => subx, subxy

contains

    subroutine subx( Cfunc, .. )
       type(Cfuncx), intent(in) :: Cfunc
       ..
    end subroutine subx

    subroutine subxy( Cfunc, .. )
       type(Cfuncxy), intent(in) :: Cfunc
       ..
    end subroutine subxy

end module
1 Like

Generic resolution is based on the type, kind and rank (TKR) of the dummy argument for things that have a type. The standard says:

Two dummy arguments are distinguishable if
• one is a procedure and the other is a data object,
• they are both data objects or known to be functions, and neither is TKR compatible with the other,
• one has the ALLOCATABLE attribute and the other has the POINTER attribute and not the INTENT (IN) attribute, or
• one is a function with nonzero rank and the other is not known to be a function.

Functions are treated as data objects of their return TKR. The interface of a procedure dummy is not considered. I don’t see this changing.

It’s possible that the work in progress at adding more general “generic programming” to the language might address the need here - it’s not a subject I am very familiar with.

1 Like

@FortranFan

Have you considered OPTIONAL attribute?

Somehow I didn’t try that option. From a quick test it may work, but I really need to check with all possible cases. Basically within the subroutines I have operations of the form tmp = f(a, b) or tmp = f(a); I need to test if using optional :: y does the job without having to resort to if (present(y)) ... and then an if every time there is a function call, of two copies of the same code with just the function calls being different.

“containers” for procedure pointers is something you can consider

But that still requires me to define two different subroutines for fx and fxy, does it not? That wouldn’t make much of a difference.

@sblionel
Thank you for the explanation. Perhaps I am missing something, but given the TKR resolution, how does this example work?

INTERFACE GOOD5
    SUBROUTINE S5A(X)
        REAL :: X
    END SUBROUTINE S5A
    SUBROUTINE S5B(Y,X)
        REAL :: Y,X
    END SUBROUTINE S5B
END INTERFACE GOOD5

This can be called with good5(..., ...).

@witenion_v2

That example meets the rule (which I didn’t quote, as it wasn’t relevant to the original question):

(1) there is a non-passed-object dummy data object in one or the other of them such that
(a) the number of dummy data objects in one that are nonoptional, are not passed-object, and with which that dummy data object is TKR compatible, possibly including that dummy data object itself,
exceeds
(b) the number of non-passed-object dummy data objects, both optional and nonoptional, in the other that are not distinguishable from that dummy data object,

In your new example, calling GOOD5 with two arguments means it can’t be S5A, which has only one argument.

Where people sometimes get into trouble is a situation such as:

INTERFACE FOOBAR
  SUBROUTINE FOO1 (X,Y)
   INTEGER :: X
   REAL :: Y
  END SUBROUTINE FOO1
  SUBROUTINE FOO2 (Y,X)
    INTEGER :: X
    REAL :: Y
  END SUBROUTINE FOO2
END INTERFACE FOOBAR

They forget that you can use argument keywords in a call, so these two are not distinguishable.

1 Like

Right, and that was my initial thought when creating the interface for f(x) and f(x,y) (first post), but apparently that is not possible (only distinguishable on the return TKR, as you mentioned).

I suggest you attempt a mockup of your expected scenario(s) including the operations of the form tmp = f(a, b) or tmp = f(a) and review your needs vis-a-vis the copy of the standard you have and chances are you can figure out by yourself what works best you.

Otherwise, it’s likely readers offer you possible options that you bat away because they don’t fit what you have in mind that you haven’t quite explained here.

For example, there is also the option since Fortran 90 with a generic interface to external procedures:

module m
   implicit none
   private
   interface
      real function fx(x)
         implicit none
         real, intent(in) :: x
      end function
      real function fxy(x, y)
         implicit none
         real, intent(in) :: x
         real, intent(in) :: y
      end function
   end interface
   interface f          !<-- Generic interface to external procedures
      procedure :: fx   !<-- External procedure
      procedure :: fxy  !<-- ditto
   end interface
   public :: sub
contains
    subroutine sub( n, x, y, z )
       integer, intent(in) :: n
       real, intent(in)    :: x
       real, intent(in)    :: y
       real, intent(inout) :: z
       if ( n == 1 ) then
          z = f(x) !<-- invoke generic interface with one argument
       else
          z = f(x, y) !<-- invoke generic interface with two arguments 
       end if
    end subroutine sub
end module

but then you may say external procedures are not what you have in mind. For external procedures may appear so pas​sé when the caller side looks like so:

! Caller side code below
   real function fx(x)
   ! External procedure for fx
      implicit none
      real, intent(in) :: x
      fx = -x
   end function
   real function fxy(x, y)
   ! External procedure for fxy
      implicit none
      real, intent(in) :: x, y
      fxy = x + y
   end function
program p
   use m, only : sub
   implicit none
   real :: a, b, c
   a = 1.0; b = 2.0
   call sub(1, a, b, c )
   print *, "with n = 1: c = ", c, "; expected is -1.0"
   call sub(2, a, b, c )
   print *, "with n =/= 1: c = ", c, "; expected is 3.0"
end program

And for which Fortran 90-conforming compilers should give:

C:\temp>gfortran -c -Wall p.f90

C:\temp>gfortran -Wall p.f90 -o p.exe

C:\temp>p.exe
with n = 1: c = -1.00000000 ; expected is -1.0
with n =/= 1: c = 3.00000000 ; expected is 3.0

So then a reader might suggest to you to work around the semantics that lead to external procedures in this solution by adopting Fortran 2003 (and later) option with C interoperability and the bind(C, name= clause and you may not like that either given what that entails with working with C interoperable functions that are authored in Fortran for use in Fortran-only code!!

1 Like

After testing for a couple days with different cases, the choice of setting the second parameter of the function optional i.e.

interface
    function f(x, y)
        real, intent(in) :: x
        real, intent(in), optional :: y
    end function f
interface

seems to work. Then in the subroutines there are various lines similar to tmp = f(some_x, some_y). What I have noticed is that the function calls work with either one or two arguments (as expected from the interface), but in the case of two arguments, there is no need to use if (present(y)) .... I don’t know if that is working as it should or I am being lucky that it is using the correct element in memory. At most, I get a compiler warning when f = f(x) stating that the argument y is missing.

@FortranFan thanks for a new suggestion. I have never used external procedures before, and it looks like they won’t be needed for this particular case.

1 Like

Follow up question. I noticed both @shahmoradi and @FortranFan used abstract interface, not just interface. Any particular reason? Despite reading about them I don’t quite get how they work, and so far never used them myself (perhaps unnecessarily defining multiple interfaces).

And another, slightly unrelated question, but probably opening a new topic is not needed. In these same subroutines that make use of the functions, there is a pattern for the other input arguments, such that there are always one int + 3/4 arrays of reals:

subroutine foo(func_xy, ...., my_int, my_arr1, my_arr2, my_arr3, ...)

They are all intent(in). There several groups the 4/5 arguments. Right now, I have them declared in a module, as parameters, and used from the modules with the subroutines.

! t1
integer, parameter :: i1
real, parameter :: ar11, ar12, ar13

! t2
integer, parameter :: i2
real, parameter :: ar21, ar22, ar23
...

Would using a type (including the integer and arrays, and possibly other elements and/or procedures) offer any advantage, performance wise? “Looks” are not the most important (it would save some code length, e.g. one input argument instead of 4/5), but these are “lower level”, private subroutines that are called within the public subroutines (which only have 2 or 3 arguments), so not a big deal.
From my tests I have not been able to see any noticeable improvement in time (granted, these subroutines are not too load heavy), but perhaps some has some insight on the matter.

@witenion_v2 @witenion

The abstract interface has the benefit of being applicable to any external procedure or procedure pointer component or abstract type-bound procedure whose interface match that of the abstract interface defined. An abstract interface gives a name to a set of characteristics and argument keyword names that would constitute an explicit interface to a procedure, without declaring any actual procedure to have those characteristics. This abstract interface name may be used in the procedure statement to declare procedures which might be external procedures, dummy procedures, procedure
pointers, or deferred type-bound procedures. Once defined, anyone could use the abstract interface in any other module for any function or subroutine with a matching interface.

In your particular example, there is likely not much of a clear benefit, but in general, I prefer abstract to procedure-specific interfaces.

Regarding the performance of derived types, @sblionel or other Fortran committee members may have better clues. All I can add is that a structure of arrays typically results in better performance than an array of structures (derived types). The reason has to do with data locality (Data that are frequently accessed together temporally, must be also stored close to each other spatially in memory.)

1 Like

Derived types, of themselves, don’t affect performance. What matters is patterns of memory access. The closer together your accesses are, the more likely fast cache will be used and the better performance. @shahmoradi mentioned “structure of arrays” (often referred to as SOA) can help if you are accessing more than one array per loop iteration. The goal is to have as many memory accesses near each other as possible.

1 Like

TL;DR:

If you’re working with specific external procedures1 , use INTERFACE.

Otherwise, use ABSTRACT INTERFACE for you’ll then be essentially working with the characteristics of a procedure. By characteristics, you can view it as the function prototype per C convention, or a “signature” in general parlance.

1 external procedure: “procedure defined by an external subprogram or by means other than Fortran”

1 Like

Thank you for your replies, the three of you.

@shahmoradi Part of that paragraph sounds familiar. MFE? I previously read about SOA and AOS, though unfortunately nothing definitive and with very opinionated conclusions for different scenarios.
In any case, going with your advice, and in line with what @sblionel mentioned (use of the same arrays in each loop iteration), parameters will do. I might come back at a later point and see if there are any improvements around the use of the arrays.

@FortranFan That is a very concise, useful TL;DR regarding abstract interfaces. Will follow it from now on, unless someone complains.