Overload C-bound function?

Hi all,

Depending on the filesystem, I’d like to call the C function realpath (Unix) or _fullpath (Windows). However, these two functions have a different set of parameters.

This works on Unix:

function realpath(path, resolved_path) result(ptr) &
   bind(C, name="realpath")
   import :: c_ptr, c_char
   character(kind=c_char, len=1), intent(in) :: path(*)
   character(kind=c_char, len=1), intent(out) :: resolved_path(*)
   type(c_ptr) :: ptr
end function realpath

And this works on Windows:

function fullpath(resolved_path, path, maxLength) result(ptr) &
   bind(C, name="_fullpath")
   import :: c_ptr, c_char, c_int
   character(kind=c_char, len=1), intent(out) :: resolved_path(*)
   character(kind=c_char, len=1), intent(in) :: path(*)
   integer(c_int), value, intent(in) :: maxLength
   type(c_ptr) :: ptr
end function fullpath

Typically, I guess I’d do sth like:

function realpath(path, resolved_path) result(ptr) &
#ifndef _WIN32
            bind(C, name="realpath")
#else
            bind(C, name="_fullpath")
#endif
...

But this doesn’t work with a different set of arguments, right? :thinking: Does anyone have an idea on how to solve it without defining two different functions that are called from code depending on the filesystem (that doesn’t work). To me this looks like realpath should be overloaded, but I’m not sure how this looks like when it’s bound to a C function.

Add a Fortran wrapper procedure to your code and add a pre-processor macro to call one of the interfaces depending on the operating system:

subroutine path(...)
! ...

#ifndef _WIN32
    ptr = realpath(path, resolved_path)
#else
    ptr = fullpath(resolved_path, path, maxlength)
#endif

! ...
end subroutine path
1 Like

That solved it, thank you. :pray:t4:

Now I’m a bit puzzled why I’m always running in the #ifndef _WIN32 case (not the else case), even on Windows. Do you have an idea why that is?

That’s because the macro _WIN32 is not exported by GNU Fortran by default. For a list of predefined macros, run:

$ touch empty.f90
$ gfortran -cpp -E -dM empty.f90

The output is, for example:

#define __ATOMIC_ACQUIRE 2
#define __CHAR_BIT__ 8
#define __FLOAT_WORD_ORDER__ __ORDER_LITTLE_ENDIAN__
#define __ORDER_LITTLE_ENDIAN__ 1234
#define __ORDER_PDP_ENDIAN__ 3412
#define __GFC_REAL_10__ 1
#define __FINITE_MATH_ONLY__ 0
#define __GNUC_PATCHLEVEL__ 0
#define __GFC_INT_2__ 1
#define __SIZEOF_INT__ 4
#define __SIZEOF_POINTER__ 8
#define __GFORTRAN__ 1
#define __GFC_REAL_16__ 1
#define __STDC_HOSTED__ 0
#define __NO_MATH_ERRNO__ 1
#define __SIZEOF_FLOAT__ 4
#define _LANGUAGE_FORTRAN 1
#define __SIZEOF_LONG__ 8
#define __GFC_INT_8__ 1
#define __SIZEOF_SHORT__ 2
#define __GNUC__ 12
#define __SIZEOF_LONG_DOUBLE__ 16
#define __BIGGEST_ALIGNMENT__ 16
#define __ATOMIC_RELAXED 0
#define _LP64 1
#define __GFC_INT_1__ 1
#define __ORDER_BIG_ENDIAN__ 4321
#define __BYTE_ORDER__ __ORDER_LITTLE_ENDIAN__
#define __SIZEOF_SIZE_T__ 8
#define __SIZEOF_DOUBLE__ 8
#define __ATOMIC_CONSUME 1
#define __GNUC_MINOR__ 1
#define __GFC_INT_16__ 1
#define __LP64__ 1
#define __ATOMIC_SEQ_CST 5
#define __SIZEOF_LONG_LONG__ 8
#define __ATOMIC_ACQ_REL 4
#define __ATOMIC_RELEASE 3
#define __VERSION__ "12.1.0"

To export the macro manually:

$ gfortran -cpp -D_WIN32 -c example.f90
1 Like

@minhdao,

From a strictly Fortran point-of-view, establishing a generic interface (what you call “overloading”) for functions that have bind(C) clause is effectively the same as with Fortran subprograms generally. So placing aside the preprocessing directive for Windows vs Linux, it is straightforward to establish the generic interface to similar C functions but from different libraries that may be interfaced with Fortran. Here’s a silly example:

function func1( s ) result(r) bind(C, name="func1")
! Imagine an external procedure from C library 1 (possibly OS-specific)
   use, intrinsic :: iso_c_binding, only : c_char, c_int
   character(kind=c_char,len=1), intent(in) :: s(*)
   integer(c_int) :: r
   r = ichar(s(1))
end function 
function func2( s, n ) result(r) bind(C, name="func2")
! Imagine an external procedure from C library 2 (possibly OS-specific)
   use, intrinsic :: iso_c_binding, only : c_char, c_int
   character(kind=c_char,len=1), intent(in) :: s(*)
   integer(c_int), intent(in) :: n
   integer(c_int) :: r
   r = ichar(s(1)) + n
end function 
   use, intrinsic :: iso_c_binding, only : c_char, c_int
   interface func  !<--  Generic interface to external C functions
      function func1( s ) result(r) bind(C, name="func1")
         import :: c_char, c_int
         character(kind=c_char,len=1), intent(in) :: s(*)
         integer(c_int) :: r
      end function 
      function func2( s, n ) result(r) bind(C, name="func2")
         import :: c_char, c_int
         character(kind=c_char,len=1), intent(in) :: s(*)
         integer(c_int), intent(in) :: n
         integer(c_int) :: r
      end function 
   end interface 
   print *, "Generic with effective call to func1: ", func([ c_char_"a" ])
   print *, "Generic with effective call to func2: ", func([ c_char_"a" ], 42_c_int)
end 
C:\temp>gfortran p.f90 -o p.exe

C:\temp>p.exe
 Generic with effective call to func1:           97
 Generic with effective call to func2:          139
1 Like

Thanks – yes, this is what I was initially looking for. :hugs:

But, independent of whether to use a generic interface or not, I now have the problem that in fpm, the _WIN32 macro doesn’t seem to get exported by default, therefore #ifndef _WIN32 is always .true. :sweat_smile: