Difficulties passing parameters to C

This is probably a very simple thing I’m missing, but I’m having difficulties passing parameters from Fortran to C. Here are the program listings:

c_func.c:

#include<stdint.h>
#include<stdio.h>

int32_t c_func(int32_t x)
{
    printf("in c_func, x: %d\n",x);
    return 42;
}

…and the corresponding Fortran:

test_interop.f90:

program test_interop
    use iso_c_binding
    implicit none

    interface
        integer(c_int32_t) function c_func(x) bind(c, name="c_func")
            use iso_c_binding
            integer(c_int32_t), intent(in) :: x
        end function c_func
    end interface

    print *, "c_func(0): ", c_func(0_c_int32_t)

end program test_interop

The program compiles and links without apparent issue:

$ make
gcc -Wall -Wextra -pedantic -c c_func.c
gfortran -Wall -Wextra -c test_interop.f90
gfortran -Wall -Wextra test_interop.o c_func.o -o test_interop

Running the program, I get for example:

in c_func, x: -1878081492
c_func(0): 42

…which shows that the input parameter is bogus (expected 0), but that c_func is called, prints to stdout and passes back the 42 correctly as expected. There is nothing special about the c_int32_t, I’ve also tried c_double and c_int, with similar results; the passed in argument is not correct, but the passed back argument works. I’ve tried with: gfortran v13.2.0, v14.0.1 on Ubuntu, and v13.2.0 on Cygwin. All with similar results. On the Ubuntu system, the passed in value changes with every run of the program, which makes it seem like it is passing in a pointer, and this changes from invocation to invocation with the address space layout randomization.

Thanks!

In the C function the arguments are by default paased by value, whereas by default they are passed by reference in Fortran unless there is a ‘value’ quaifier.

2 Likes

Ah, ha! That fixed it:

integer(c_int32_t), intent(in), value :: x

Thanks!

One of the confusing cases of using the value attribute is when passing void pointers, e.g.

#include <stdio.h> // printf

struct my_f_params { 
    double a; 
    double b; 
    double c; 
};

double my_f (double x, void *p) {
    struct my_f_params *params = p;
    double a = (params->a);
    double b = (params->b);
    double c = (params->c);
    return  (a * x + b) * x + c;
}

int main(void) {
    struct my_f_params params = 
        { .a = 3.0, .b = 2.0, .c = 1.0 };

    double x = 3.0;
    double y = my_f(x, &params);
    printf("y = %f\n", y);
    return 0;
}

In Fortran, you’d do this as follows:

program test
use, intrinsic :: iso_c_binding
integer, parameter :: dp = c_double
type, bind(c) :: my_f_params
real(dp) :: a, b, c
end type

type(my_f_params), target :: params
real(dp) :: x, y

params = my_f_params(a=3.0_dp,b=2.0_dp,c=1.0_dp)
x = 3.0_dp
y = my_f(x, c_loc(params))
write(*,'("y = ", G0)') y

contains
    ! double my_f(double, void *);
    real(dp) function my_f(x,p) bind(c)
        real(dp), value :: x
        type(c_ptr), value :: p
        type(my_f_params), pointer :: params
        call c_f_pointer(p,params)
        my_f = (params%a*x + params%b)*x + params%c
    end function
end program

It may not be obvious why a C void pointer is used in the Fortran example, but hopefully you can imagine the case where the function was being passed to an optimization procedure written in C:

// Minimize the function f(x) on the interval [xl,xu]
extern double fmin(
    double (* fun) (double /* x */, void * /*params*/)
    double x0, double xl, double xu, 
    void *params);
1 Like

@GregB ,

To elaborate a bit further on @ivanpribec 's advice to you, you may have noted:

  1. The interoperability facilities in standard Fortran are presently limited to a C companion processor which conforms to a certain ISO IEC standard reference listed in a given Fortran standard publication,
  2. Now, C programming language, as you may know, has long permitted declaration of “incomplete types” that has helped foster the concept of opaque pointers, as explained by Wikipedia contributors here, and references to them via `void * and typedef’s around them also,
  3. The facility in Fortran with a type of c_ptr and a companion one of unlimited polymorphic with function parameters (dummy arguments in Fortran parlance) i.e., type(*) permit interoperation with such pointers in C.

Now, the idiosyncracy with semantics in Fortran toward “safe” working with type(c_ptr) and void * in C is the attributes of VALUE and INTENT(IN), as illustrated by @ivanpribec .

The use cases with opaque pointers include:

  1. hiding of implementation details of a given type (a “class” in OO parlance) from consumers and/or
  2. interoperation of objects which are not strictly interoperable, see an old example I had provided at the Intel Fortran forum here.
1 Like