I am in the process of writing a Fortran API to a C header for a library and I have run into some issues when it comes to implementing optional
arguments. Specifically, the Fortran API works by calling on a C API, which allows for optional arguments by passing NULL
as the value[1]. I am curious as to what is a standard compliant way of passing Fortran optional arguments to C. These arguments can be variables, strings, arrays, arrays of strings, etc. but not Fortran pointers. Is it enough to mark them as optional
in the Fortran method and the C interface
block? Can we use the Fortran “presentness”, or lack thereof to indicate NULL
in C?
I asked this question on Stack Overflow but I have gotten mixed answers, especially whether the code is standard conformant. (Probably I could have done a better job structuring the question.)
Specific Questions
- Do I need to add
optional
in both the Fortran procedure and the Cinterface
binding block? - Can we use the Fortran
present
in a procedure, or lack thereof to indicateNULL
in C? - Is passing
array_size=size(array, kind=c_size_t)
considered standard conforming whenarray
itself might not be present? (Assuming that there is some safety check mechanism forarray
beingNULL
on the C side).
3.1. We can’t markarray_size
asoptional
because it uses thevalue
attribute (and we can’t change the C code). An alternative would be to set thearray_size=local_size
to some local variable which is set to0
if thearray
is not present, but in that case what would be the input value ofarray
when not present?
Minimal Working Example
program main
use, intrinsic :: iso_c_binding
implicit none
call null_str_f90("abc"); call null_str_f90()
call null_array_opt_f90([1, 2, 3, 4, 5]); call null_array_opt_f90()
contains
function istring_(o) result(v)
character(len=*), intent(in) :: o
character(len=:, kind=c_char), allocatable :: v
v = trim(o)//c_null_char
end function istring_
subroutine null_str_f90(str)
interface
subroutine C_API(str_c) bind(C, name="null_str")
use, intrinsic :: iso_c_binding
character(len=1, kind=c_char), dimension(*), optional, intent(in) :: str_c ! is the optional keyword here necessary?
end subroutine C_API
end interface
character(len=*), intent(in), optional :: str
! Local variables
character(len=:, kind=c_char), allocatable :: name_c
if (present(str)) name_c = istring_(str)
call C_API(str_c=name_c) ! is this standard compliant?
end subroutine null_str_f90
subroutine null_array_opt_f90(array)
interface
subroutine C_API(array, array_size) bind(C, name="null_array")
use, intrinsic :: iso_c_binding
integer(c_int), dimension(*), optional :: array
integer(c_size_t), value, intent(in) :: array_size
end subroutine C_API
end interface
integer(c_int), dimension(:), optional, intent(in) :: array
! Is this call even legal? array_size is passed by VALUE but array is not PRESENT
call C_API(array=array, array_size=size(array, kind=c_size_t))
end subroutine null_array_opt_f90
end program main
#include <stdio.h>
void null_str(const char *str) {
if (str) {
printf("str is present: str is %s\n", str);
} else {
printf("str is not present\n");
}
}
void null_array(int *array, size_t size) {
if (array) {
for (int i = 0; i < size; i++) printf("%d ", array[i]);
printf("\n");
} else {
printf("array is not present\n");
}
}
For me the MWE posted above produces the expected results, but I am not convinced my approach is correct or portable across compilers.
-
Whether or not that is a good idea is a completely separate matter, but long story short I don’t have any control over the C code. ↩︎