I have a C function coming in different “flavors”:
void form_i2(const char * label, int16_t i2);
void form_i4(const char * label, int32_t i4);
// etc.
I was thinking of defining an interface to dispatch automatically to the correct form:
interface form
subroutine form_i2(label, i2)
import :: c_char, c_int16_t
implicit none
character(c_char), dimension(*) :: label
integer(c_int16_t), value :: i2
end
subroutine form_i4(label, i4)
import :: c_char, c_int32_t
implicit none
character(c_char), dimension(*) :: label
integer(c_int32_t), value :: i4
end
! etc.
end interface
Calling the subroutine directly works well, but calling the interface triggers an error with gfortran 14 and ifx 2024.0.0 as well:
character(len=64) :: label
integer my_int
label = "My Label 1" // c_null_char
call form_i4(label, my_int)
call form(label, my_int) ! There is no specific subroutine for the generic 'form'
Digging a little, I found that:
- Changing
character(len=64) :: label
tocharacter, dimension(64) :: label
compiles fine, but the assignementlabel = "My Label 1"
doesn’t work anymore; - Changing the interface to:
subroutine form_i4(label, i4)
import :: c_ptr, c_int32_t
implicit none
type(c_ptr), value :: label
integer(c_int32_t), value :: i4
end
And the call to:
character(len=64), target :: label
integer my_int
label = "My Label 1" // c_null_char
call form_i4(c_loc(label), my_int)
call form(c_loc(label), my_int)
works fine, the compilers do find an implementation matching the arguments in the interface defined. For the caller it’s less practical however, with an extra target
and c_loc
to add.
But why isn’t it working with character(c_char), dimension(*)
arguments?
Below is a minimal reproducible example, with the integer argument stripped for simplicity:
Minimal reproducible example
program test_c_string
use iso_c_binding
implicit none
interface form_interface
subroutine form1(label) bind(c)
import :: c_char, c_double, c_float, c_int
implicit none
character(c_char), dimension(*) :: label
end subroutine
subroutine form2(label) bind(c, name="form1")
import :: c_ptr
implicit none
type(c_ptr), value :: label
end subroutine
end interface
character(len=64) :: label
character(len=64), target :: label_t
character, dimension(64) :: label_dim
label = "My Label 1" // c_null_char
label_t = "My Label 1 with target" // c_null_char
label_dim = "My Label 1 with dimension()" // c_null_char
!call form_interface(label) ! no specific subroutine
call form1(label)
call form_interface(c_loc(label_t))
call form2(c_loc(label_t))
call form_interface(label_dim)
call form1(label_dim)
end program
And a C “implementation”:
#include <stdio.h>
void form1(const char * string)
{
printf("Input C String = <%s>\n", string);
}
Running this should produce something like:
Input C String = <My Label 1>
Input C String = <My Label 1 with target>
Input C String = <My Label 1 with target>
Input C String = <MMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMy Label 1>
Input C String = <MMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMMy Label 1>