Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

How to specify a generic interface as a procedure argument

Mahajan__Bharat1
Beginner
2,621 Views

I am trying to create a module that provides (to the module user) a subroutine that accepts a procedure argument. The module user is responsible for implementing the procedure, which can have two different interface specifications. Module provides the interface definitions for the two type of procedure arguments. So, let the following be the generic interface in the module:

interface func

integer function f1(i)

integer :: i

end function f1

integer function f2(i,j)

integer :: i,j

end function f2

end interface

And the following is the procedure in the module that accepts a function argument which can either have specification as f1 or f2. 

subroutine modlib(my_int, user_func)

integer, intent(in) :: my_int
procedure(func) user_func

integer :: res

res = user_func(my_int)

end subroutine

The above is not valid code (procedure(func) user_func), so I am looking for best way to implement this. One obvious way is to declare user_func as external using

integer :: user_func

Is there any better way to specify to the module user that subroutine modlib accepts only those procedures as arguments that has specification either as f1 or f2 and nothing else?

0 Kudos
1 Solution
IanH
Honored Contributor II
2,621 Views

If I understand correctly, what you want it to pass a single specific procedure that is consistent with an interface from a set of interfaces.  Presumably once inside your subroutine, you invoke C_FUNLOC or similar on the procedure to get a C function pointer, that is then passed onto the C library code - you could do that C_FUNLOC in the caller of your Fortran subroutine, but then there's no type checking in the caller.

In addition to previous ideas, methods of passing a single specific procedure that matches an interface from a set of interfaces could also use optional arguments (requires client code to not break the contract implied by the ERROR STOP check):

! func1 xor func2 shall be present
SUBROUTINE modlib(other, func1, func2)
  ...
  PROCEDURE(ifunc1), OPTIONAL :: func1
  PROCEDURE(ifunc2), OPTIONAL :: func2
  
  IF (PRESENT(ifunc1) .EQV. PRESENT(ifunc2)) THEN
    ERROR STOP 'One or the other, not both, not neither'
  END IF
  
  IF (PRESENT(ifunc1)) THEN
    ... do something with ifunc1 ...
  ELSE
    ... do something with ifunc2 ...
  END IF
  
  ...
END SUBROUTINE modlib

or using an type hierarchy:

TYPE, PRIVATE :: tbase
END TYPE tbase

TYPE, EXTENDS(tbase) :: tfunc1
  ! Shall be associated.
  PROCEDURE(ifunc1), NOPASS, POINTER :: p
END TYPE tfunc1

TYPE, EXTENDS(tbase) :: tfunc2
  ! Shall be associated.
  PROCEDURE(ifunc2), NOPASS, POINTER :: p
END TYPE tfunc2

! func_object is either a tfunc1 object or a tfunc2 object.
SUBROUTINE modlib(other, func_object)
  ...
  CLASS(tbase), INTENT(IN) :: func_object
  
  ...
  SELECT TYPE (func_object)
  CLASS IS (tfunc1)
    ... do something with func_object%p ...
  CLASS IS (tfunc2)
    ... do something with func_object%p ...
  CLASS DEFAULT
    ... complain to vendor supplying Fortran processor ...
  END SELECT 
  
  ...
END SUBROUTINE modlib

 

(Note that a callback intended to be called back from C should be BIND(C).)

A generic identifier in Fortran is a single identifier for a set of specific procedures with distinguishable interfaces.  If that is what you actually want, then just pass the set of specific procedures, either as individual arguments or in an object of type that has a heap of procedure pointer components.  (You could also use such an object for the single procedure case, just require that only one component be associated.)

View solution in original post

0 Kudos
12 Replies
FortranFan
Honored Contributor II
2,621 Views

Dummy procedure argument cannot be generic per Fortran standard.

Should the code shown in the original post reflect the actual need, the easiest option might be to use a single interface for the user function where the second argument (e.g., 'j') is given the OPTIONAL attribute:

module m
   abstract interface
      function Ifunc(i, j) result(r)
         integer, intent(in) :: i
         integer, intent(in), optional :: j
         integer :: r
      end function
   end interface
contains
   subroutine modlib( a, func, res )
      integer, intent(in)    :: a
      procedure(Ifunc)       :: func
      integer, intent(inout) :: res
      res = func(a)
   end subroutine
end module

In more complex scenarios, it may be more convenient to use a generic interface for the library procedure such as 'modlib':

module m
   abstract interface
      function Ifunc1(i) result(r)
         integer, intent(in) :: i
         integer :: r
      end function
      function Ifunc2(i, j) result(r)
         integer, intent(in) :: i
         integer, intent(in) :: j
         integer :: r
      end function
   end interface
   generic :: modlib => modlib1, modlib2 ! Fortran 2018 facility; 2008 option below
   !interface modlib
   !   module procedure modlib1
   !   module procedure modlib2
   !end interface
contains
   subroutine modlib1( a, func, res )
      integer, intent(in)    :: a
      procedure(Ifunc1)      :: func
      integer, intent(inout) :: res
      ! NOTE: common instructions can be in an include file to avoid code duplication
      res = func(a)
   end subroutine
   subroutine modlib2( a, b, func, res )
      integer, intent(in)   :: a
      integer, intent(in)   :: b
      procedure(Ifunc2)     :: func
      integer,intent(inout) :: res
      ! NOTE: common instructions can be in an include file to avoid code duplication
      res = func(a, b)
   end subroutine
end module

 

0 Kudos
FortranFan
Honored Contributor II
2,621 Views

This is to add to the test of Intel Fortran 2020 BETA compiler using the second option shown above:

program p
   use m, only : modlib
   integer :: r
   call modlib(1, func1, r)
   print *, "result with func1 = ", r
   call modlib(1, 2, func2, r)
   print *, "result with func2 = ", r
contains
   function func1(i) result(r)
      integer, intent(in) :: i
      integer :: r
      r = i + 100
      return
   end function
   function func2(i, j) result(r)
      integer, intent(in) :: i
      integer, intent(in) :: j
      integer :: r
      r = i*j
   end function
end program

Upon execution with 2020 BETA version, the program output is:

 result with func1 =  101
 result with func2 =  2

 

0 Kudos
Mahajan__Bharat1
Beginner
2,621 Views

Should the code shown in the original post reflect the actual need, the easiest option might be to use a single interface for the user function where the second argument (e.g., 'j') is given the OPTIONAL attribute:

Actually the user function is a C-bound procedure so optional attribute cannot be used for my application.

In more complex scenarios, it may be more convenient to use a generic interface for the library procedure such as 'modlib':

Yes I thought about it, but not very enthusiastic about this way because then I will have 2 modlib library procedures and both will essentially have the same code. I saw that comment about using include files to avoid code duplication.

0 Kudos
Steve_Lionel
Honored Contributor III
2,621 Views

Interoperable procedures may have OPTIONAL arguments as of F2018. Intel Fortran 16 and later supports this.

0 Kudos
FortranFan
Honored Contributor II
2,621 Views

Steve Lionel (Ret.) (Blackbelt) wrote:

Interoperable procedures may have OPTIONAL arguments as of F2018. Intel Fortran 16 and later supports this.

and which, if I recall correctly via some tests I had done a while ago, is also supported by GCC/gfortran and this Fortran 2018 standard facility relies on the reasonably common practice in C to rely on "pass by reference" for the optional parameter and where a NULL pointer denotes an 'absent' parameter.  That is, C language does not directly have a similar facility as Fortran with optional arguments (or for that matter, C does not explicitly include support for function overloading either) and so some "hack" or other with some limitation or subtlety will come into play, no matter what, in a mixed-language scenario involving Fortran and the companion C processor.

0 Kudos
Mahajan__Bharat1
Beginner
2,621 Views

>>> Interoperable procedures may have OPTIONAL arguments as of F2018. Intel Fortran 16 and later supports this.

That is good to know! 

Using optional arguments will work in the simple example I posted but may not for a more general case when number of function parameters are equal and only types differ (that is indeed my case).

0 Kudos
FortranFan
Honored Contributor II
2,621 Views

As stated earlier, C does not include intrinsic support toward the overloading of functions.  Then to the extent anyone wants to use a generic interface in the context of interoperation of Fortran with C is looking at workarounds.  The one involving 'void *' i.e., an opaque pointer as parameter in the C function is fairly common and that is workable in this case but it's a matter of preference/taste and one's often biased sense of efficiency as to whether such an approach should be utilized.  Keeping it simple with specific procedures rather than generic interfaces is something even Microsoft adopts when interoperation comes into play e.g., between .NET and COM.

0 Kudos
Mahajan__Bharat1
Beginner
2,621 Views

FortranFan wrote:

As stated earlier, C does not include intrinsic support toward the overloading of functions.  Then to the extent anyone wants to use a generic interface in the context of interoperation of Fortran with C is looking at workarounds.  The one involving 'void *' i.e., an opaque pointer as parameter in the C function is fairly common and that is workable in this case but it's a matter of preference/taste and one's often biased sense of efficiency as to whether such an approach should be utilized.  Keeping it simple with specific procedures rather than generic interfaces is something even Microsoft adopts when interoperation comes into play e.g., between .NET and COM.

I understand your point of using void pointers to accommodate different types. But the assumption here is that C code makes calls to f1 or f2 using pointers. That is not possible in my case as the C code is an external library. 

To be more specific, f1 and f2 are basically callbacks, implemented in fortran and called by C. The calling signature is determined by C and is fixed. It can be like this in C code:

f1(int, int);
f2(int, double); 

(C doesnt need overloading in this case, as which call signature to use can be determined by appropriate flags in C)

Now the fortran module provides, to the module user, a procedure to set the callback function pointer. This pointer will be passed on to C, which will ultimately invoke the callback function. So the question was how to enforce at the compile time that module user passes a function argument that can point to a C-interoperable fortran procedure with signature same as either f1 or f2 and nothing else.

Your solution of using 2 different module procedures with generic name for setting the callbacks will work. I was wondering is there any other way.
 

0 Kudos
Daniel_Dopico
New Contributor I
2,621 Views

If you don't like to define 2 modlib library procedures you can always let this work to the user. The following solution is based on type-bound procedures. The user can eventually define wichever function with whichever arguments, but I would prefer Fortran Fan solution if you don't need such a level of generalization because this solution lets more work to the user.

MODULE myfortranlib
    IMPLICIT NONE
    TYPE,ABSTRACT::mytype
    CONTAINS
        PROCEDURE(templatefunc),PASS,DEFERRED::user_func
    END TYPE mytype

    ABSTRACT INTERFACE
        INTEGER FUNCTION templatefunc(f)
            IMPORT mytype
            IMPLICIT NONE
            class(mytype),INTENT(IN)::f
        END FUNCTION templatefunc
    END INTERFACE
END MODULE myfortranlib

MODULE USER_MODULE
    USE myfortranlib
    IMPLICIT NONE

    TYPE,EXTENDS(mytype)::userExtendedf2type
        INTEGER::i=5,j=-3
    CONTAINS
        PROCEDURE::user_func=>function_f2
    END TYPE userExtendedf2type

    TYPE(userExtendedf2type)::myf2object
    
    CONTAINS

    INTEGER FUNCTION function_f2(f)
        CLASS(userExtendedf2type),INTENT(IN)::f
        INTERFACE
            integer function f2(i,j)
            integer :: i,j
            end function f2
        END INTERFACE
    
        function_f2=f2(f%i,f%j)
    END FUNCTION function_f2

END MODULE USER_MODULE

PROGRAM MAIN
USE USER_MODULE
integer res

res=userExtendedf2type%user_func()

END PROGRAM

 

0 Kudos
Mahajan__Bharat1
Beginner
2,621 Views

Daniel Dopico wrote:

The user can eventually define wichever function with whichever arguments

That is exactly what i was trying to avoid. From my previous post: 

So the question was how to enforce at the compile time that module user passes a function argument that can point to a C-interoperable fortran procedure with signature same as either f1 or f2 and nothing else.

There may not be a solution to this problem without FortranFan's approach of using multiple Fortran procedures to set the callback functions corresponding to each f1, f2, etc. In my case I have 5 different callback functions.

I wish procedure arguments can be declared using generic interface names in Fortran like this (from my original post):

procedure(func) user_func

But I dont know all the implications of that, so food for thought for experienced Fortran developers.

0 Kudos
IanH
Honored Contributor II
2,622 Views

If I understand correctly, what you want it to pass a single specific procedure that is consistent with an interface from a set of interfaces.  Presumably once inside your subroutine, you invoke C_FUNLOC or similar on the procedure to get a C function pointer, that is then passed onto the C library code - you could do that C_FUNLOC in the caller of your Fortran subroutine, but then there's no type checking in the caller.

In addition to previous ideas, methods of passing a single specific procedure that matches an interface from a set of interfaces could also use optional arguments (requires client code to not break the contract implied by the ERROR STOP check):

! func1 xor func2 shall be present
SUBROUTINE modlib(other, func1, func2)
  ...
  PROCEDURE(ifunc1), OPTIONAL :: func1
  PROCEDURE(ifunc2), OPTIONAL :: func2
  
  IF (PRESENT(ifunc1) .EQV. PRESENT(ifunc2)) THEN
    ERROR STOP 'One or the other, not both, not neither'
  END IF
  
  IF (PRESENT(ifunc1)) THEN
    ... do something with ifunc1 ...
  ELSE
    ... do something with ifunc2 ...
  END IF
  
  ...
END SUBROUTINE modlib

or using an type hierarchy:

TYPE, PRIVATE :: tbase
END TYPE tbase

TYPE, EXTENDS(tbase) :: tfunc1
  ! Shall be associated.
  PROCEDURE(ifunc1), NOPASS, POINTER :: p
END TYPE tfunc1

TYPE, EXTENDS(tbase) :: tfunc2
  ! Shall be associated.
  PROCEDURE(ifunc2), NOPASS, POINTER :: p
END TYPE tfunc2

! func_object is either a tfunc1 object or a tfunc2 object.
SUBROUTINE modlib(other, func_object)
  ...
  CLASS(tbase), INTENT(IN) :: func_object
  
  ...
  SELECT TYPE (func_object)
  CLASS IS (tfunc1)
    ... do something with func_object%p ...
  CLASS IS (tfunc2)
    ... do something with func_object%p ...
  CLASS DEFAULT
    ... complain to vendor supplying Fortran processor ...
  END SELECT 
  
  ...
END SUBROUTINE modlib

 

(Note that a callback intended to be called back from C should be BIND(C).)

A generic identifier in Fortran is a single identifier for a set of specific procedures with distinguishable interfaces.  If that is what you actually want, then just pass the set of specific procedures, either as individual arguments or in an object of type that has a heap of procedure pointer components.  (You could also use such an object for the single procedure case, just require that only one component be associated.)

0 Kudos
Mahajan__Bharat1
Beginner
2,621 Views

Yes both of your solutions work and are quite simple in their approach. Not sure why i did not think of those!

I may just use your 1st approach of making all interface types as optional arguments and have custom logic to make sure user passes only 1 of those.

With yours and FortranFan's solution of using multiple procedures with generic interfaces, we have 3 solutions.

 

Thanks All!

 

 

0 Kudos
Reply