How to implement in iso_c_binding

struct myfloat 
{
   float float_tmp;
};

struct myint 
{
   int int_tmp;
};

int game_(myint1,myfloat2)
myint **myint;
myfloat **myfloat2;
{
  return(0);
}

you could see some examples here.

1 Like

Could you please clarify what you want to archive with this C code snippet? Without further information it will be difficult to give you any useful answer.

1 Like

Given that isn’t actually valid C code, and you aren’t telling us what it’s for or what the goal is, this is close(ish) to the given example C code, and an example of calling it.

typedef struct mf {
    float float_tmp;
} myfloat;

typedef struct mi {
    int int_tmp;
} myint;

int game(myint x, myfloat y) {
    return 42;
}
program main
    use iso_c_binding, only: c_int, c_float

    implicit none

    type, bind(c) :: myfloat
        real(c_float) :: float_tmp
    end type

    type, bind(c) :: myint
        integer(c_int) :: int_tmp
    end type

    interface
        function game(x, y) bind(c, name="game")
            import :: myfloat, myint, c_int
            implicit none
            type(myint), intent(in), value :: x
            type(myfloat), intent(in), value :: y
            integer(c_int) :: game
        end function
    end interface

    type(myfloat) :: y
    type(myint) :: x

    print *, game(x, y)
end program
1 Like

Then hire me to work on the project, send me an NDA, show me the actual code and tell me how you’d like to be able to interact with it. Because you still haven’t provided valid C code (the compiler errors are shown below), or told us what you want to be able to do with it from Fortran.

$ gcc -c stuff.c -o stuff.o                                                                                                         (master)
stuff.c: In function ‘game_’:
stuff.c:12:1: error: unknown type name ‘myint’; use ‘struct’ keyword to refer to the type
   12 | myint **myint1;
      | ^~~~~
      | struct 
stuff.c:13:1: error: unknown type name ‘myfloat’; use ‘struct’ keyword to refer to the type
   13 | myfloat **myfloat2;
      | ^~~~~~~
      | struct 
2 Likes
    use, intrinsic :: iso_c_binding, only: c_int, c_float, c_ptr

    type, bind(c) :: myfloat
        real(c_float) :: float_tmp
    end type

    type, bind(c) :: myint
        integer(c_int) :: int_tmp
    end type

    interface
        function game(myint1, myfloat2) bind(c, name="game_")
            import :: c_int, c_ptr
            implicit none
            type(c_ptr) :: myint1
            type(c_ptr) :: myfloat2
            integer(c_int) :: game
        end function
    end interface

That’s the interface to that C code. Note that due to Fortran’s “pass by reference”, a pointer to the pointer myint1 is what will be passed to C (as you suspected).

2 Likes

Convince management to bring somebody on that knows what they’re doing?

I don’t mean to offend, but it would take me an hour to write a coherent and comprehensive description of why what you’ve done is wrong, what the right way to do it is, and why you’re going to have problems if you don’t do it the right way. And even with that, I’m not convinced you wouldn’t come back with several variations on the same question, effectively having this community trying to do your work for you without being compensated.

3 Likes

When you write an expression like cptr1+j-1 in fortran, what exactly do you think is the result? Do you think it is the same as the same expression in C where cptr1 is a C pointer?

Friendly reminder that everyone is welcome to post questions and ask for help on Fortran Discourse as long as they’re not disrespectful or otherwise violating the CoC. It’s perfectly OK to not respond to the topic if you don’t want to help.

3 Likes

It’s only free consultancy if you choose to respond. Please use the flag feature if you think any post is inappropriate or somehow abusing the Fortran Discourse and we’ll review it. Otherwise, please ignore the posts if you don’t like them.

1 Like

There are several problem, first integer*8 is not in the Fortran standard even though it is a common extension that means an integer variable stored in 8 bytes.

The compiler is telling you that you cannot pass an integer variable to an opaque type as type(c_ptr).
An eight byte integer variable, from the point of view of the Fortran processor, is different from an opaque type equivalent to a C pointer like type(c_ptr). Like in C a long is different from a void* even if they were of the same length in bytes.

Now in some old Fortran program integer*8 is used to store C pointers on the assumption that the compiler will support that extension, you are on a 64 bit machine, and you don’t want the compiler to make any check.

ISO_C_BINDING is far better as it helps you to restrict the places where you have to manually be sure that what is written in C has a correct correspondence in Fortran (in the interfaces of the C routines), letting the compiler to help you in checking that you are calling the C routines correctly. Moreover it is standard and it will work in old 32 bit machines and future strange machines as well.

Personally I always use iso_c_binding, for example when I need to call a Fortran routine from python through the ctypes, the Fortran routine will appear as a C routine and everything is fine.

Basically you are saying that you have an array and you pass elements of this array to the routine “game” or that you get back an array of objects. The only meaning (in C) to add a number to an address is when you want to get the addresses of successive array elements.

If so, well, use an array.

C_F_POINTER has a shape argument, so you can access successive array elements (if allocated inside the C function), this is the only equivalent way to add a number to the “integer*8” as far as I may understand.
Or use an array of type(c_ptr), and pass each element of the array to the “game” routine, if that is what you want to do instead.

Look also at C_ASSOCIATED if it may help you.

As @milancurcic said, please do not respond to a post if you think it is not worth your time.

If you ask a question here, please be polite and respectful to people that try to respond to it. Also try to provide as many details as you can, the background and motivation of the question, to increase chances of getting good actionable answers.

1 Like