Overloading an external procedure

Hi,
I am trying to write modern fortran wrappers for the exodusII library GitHub - sandialabs/seacas: The Sandia Engineering Analysis Code Access System (SEACAS) is a suite of preprocessing, postprocessing, translation, and utility applications supporting finite element analysis software using the Exodus database file format.
Their fortran wrapper system is convoluted and predates iso_c_bindings by a very long time. Re-writing them completely with iso_c_binding is not practical at this point.

For historical reason, C functions were given short 6-8 characters long names in Fortran.
I’d like to allow the use of the full C name, as well as the short name, and was thinking of doing so by writing an abstract interface. but can’t figure how to do so. For instance, the following does not compile under gfortran (GNU Fortran (Homebrew GCC 11.3.0_2) 11.3.0 macOS), when exppv is an external function implemented in C.

interface
       subroutine exppv(idexo, time_step, var_type, var_index, &
                        obj_id, start_index, num_entities,     &
                        var_vals, ierr)	
        INTEGER idexo           ! ®
        INTEGER time_step       ! ®
        INTEGER var_type        ! ®
        INTEGER var_index       ! ®
        INTEGER obj_id          ! ®
        INTEGER start_index     ! ®
        INTEGER num_entities    ! ®
        REAL    var_vals(*)     ! (W)
        INTEGER ierr            ! (W)
        end subroutine exppv
end interface

interface ex_put_partial_var
	subroutine exppv
end interface ex_put_partial_var

Any suggestion? There quite a few functions to wrap, so tensity is a plus…

1 Like

How about:

module beliavsky
abstract interface
       subroutine exppv_(idexo, time_step, var_type, var_index, &
                         obj_id, start_index, num_entities,     &
                         var_vals, ierr) bind(c) 
        INTEGER idexo           !
        INTEGER time_step       !
        INTEGER var_type        !
        INTEGER var_index       !
        INTEGER obj_id          !
        INTEGER start_index     !
        INTEGER num_entities    !
        REAL    var_vals(*)     ! (W)
        INTEGER ierr            ! (W)
        end subroutine exppv_
end interface

procedure(exppv_), pointer :: exppv, ex_put_partial_var

end module beliavsky

This compiles with both gfortran and Intel Fortran oneAPI. I left in the “bind(c)” bit, that may or may not be useful when it comes to name mangling/decoration.

The essence is that you define an abstract interface and then use it with two different entities. Fortunately the call to a procedure pointer is syntactically the same as to a regular routine.

There may be other, more concise solutions, but this works :slight_smile:

That works, thanks.

Just curious, I can’t find the EXPPV function in any current Exodus distribution at least on the Fortran side. Are you trying to implement all of the C functions including the ones not supported by the existing Fortran wrappers. I’ve already done my own C-Interop wrappers to Exodus but just implemented the ones described in the Fortran manual. My approach to the naming was to give everything the C names and then use module procedure interfaces to give access to the old Fortran 6 character names. Unfortunately, I can’t release my code without consent from my DoD sponsor.

I am writing a few of the missing wrappers, mainly the one dealing with partial input output.
Considering that exodus is developed at Sandia national lab (on the military side, if I remember correctly), I would assume that getting clearance to release this type of contribution would be feasible.

Out of curiosity, if you were to write a C-interop wrapper to a function EXPPV (not in exodus), whose prototype is

int EXPPV(int exoid, int time_step, int var_type, int var_index,
Int obj_id, int64_t start_index, int64_t num_entities,
const void *var_vals),

How would you proceed?

@Blaise

Here is how I would implement ex_put_partial_var
Sorry for the length

  Subroutine ex_put_partial_var(exoid,  time_step,  var_type, var_index, &
                                  obj_id, start_index, num_entities,       &
                                  var_vals, ierr)

    USE ISO_FORTRAN_ENV
    USE ISO_C_BINDING
    USE exodus_data,   ONLY : EX_IK, EX_ENTITY_ID

    Integer(EX_IK), Intent(IN)  :: exoid
    Integer(EX_IK), Intent(IN)  :: time_step
    Integer(EX_IK), Intent(IN)  :: var_type
    Integer(EX_IK), Intent(IN)  :: var_index
    Integer(EX_IK), Intent(IN)  :: obj_id
    Integer(INT64), Intent(IN)  :: start_index
    Integer(INT64), Intent(IN)  :: num_entities
    Type(*),        Intent(IN)  :: var_vals(*)
    Integer(EX_IK), Intent(OUT) :: ierr

    Integer(C_INT)        :: exoid_c, ierr_c, var_index_c, time_step_c
    Integer(C_INT64_T)    :: start_index_c, num_entities_c
    Integer(EX_ENTITY_ID) :: var_type_c, obj_id_c

    Interface
      Function ex_put_partial_var_c(exoid,  time_step,   var_type, var_index,   &
                                  obj_id, start_index, num_entities,          &
                                  var_vals)                                   &
                                  BIND(C, NAME="ex_put_partial_var")

        IMPORT :: C_INT, C_INT64_T, EX_ENTITY_ID

        Integer(C_INT),        VALUE      :: exoid
        Integer(C_INT),        VALUE      :: time_step
        Integer(EX_ENTITY_ID), VALUE      :: var_type
        Integer(C_INT),        VALUE      :: var_index
        Integer(EX_ENTITY_ID), VALUE      :: obj_id
        Integer(C_INT64_T),    VALUE      :: start_index
        Integer(C_INT64_T),    VALUE      :: num_entities
        Type(*),               Intent(IN) :: var_vals(*)
        Integer(C_INT)                    :: ex_put_partial_var_c

      End Function ex_put_partial_var_c
    End Interface

    exoid_c        = INT(exoid,        C_INT)
    time_step_c    = INT(time_step,    C_INT)
    var_index_c    = INT(var_index,    C_INT)
    start_index_c  = start_index
    num_entities_c = num_entities
    var_type_c     = INT(var_type,     EX_ENTITY_ID)
    obj_id_c          = INT(obj_id,         EX_ENTITY_ID)
    ierr_c = ex_put_partial_var_c(exoid_c,     timestep_c, var_type_c,        &
                                  var_index_c, obj_id_c,   start_index_c,     &
                                  num_entities_c, var_vals)

    ierr = INT(ierr_c, EX_IK)

  End Subroutine ex_put_partial_var

A few comments.

  1. I define my own parameter for EX_ENTITY_ID (its C_INT64_T in exodusii.h) just to make the interfaces visually consistent with the C interfaces

  2. I create extra C specific variables for the arguments passed to C and convert the Fortran arguments defined with the EX_IK type to the required C data types. I do this so I can create a Fortran version that uses 64 bit integers on the Fortran side and converts to the required C types prior to calling the underlying C function

  3. I would try passing var_vals as an assumed TYPE value since it can be any of several different types in the C code. Depending on how mature your compiler support is for assumed TYPE you might have to resort to passing it as a TYPE(C_PTR)
    instead

Also I put all these routines in a module and use a module procedure interface to give it a pre-historic Fortran 6 character name. ie

Interface EXPPV
module procedure ex_put_partial_var
End Interface

Hope this helps. I’ll check into releasing my code but I might be up against ITAR restrictions

@Blaise, it appears what is of interest to you is a renaming facility and not “overloading”, you may want to give this further thought.

If you do decide what you’re after is simple renaming, look into whether basic USE functionality along with ONLY which has been available since Fortran 90 might suit your purpose - see below.

#include <stdio.h>

void Cfunction1() {
    printf("Hello World!\n");
}

void Cfunction2() {
    printf("Who wants to KISS anymore!\n");
}
module m
   interface
      subroutine Cfunction1() bind(C, name="Cfunction1")
      end subroutine
      subroutine Cfunction2() bind(C, name="Cfunction2")
      end subroutine
   end interface
end module
   use m, only : Cfunction1, Cfunction2
   use m, Cfunc1 => Cfunction1
   call Cfunc1()
   call Cfunction1()
   call Cfunction2()
end 
C:\Temp>gfortran -c c.c

C:\Temp>gfortran -c p.f90

C:\Temp>gfortran p.o c.o -o p.exe

C:\Temp>p.exe
Hello World!
Hello World!
Who wants to KISS anymore!