Type(c_ptr) and void *

out_result is ignored if you pass NULL to the function. For some SQL queries you are not interested in the result of the query like create table, inserts, etc.

You cannot pass an actual argument that is null() if the dummy argument is not declared as a pointer (edit: as pointed out by someone in a private message, this is also possible is the dummy argument is declared as optional).

What does work:

use iso_c_binding
implicit none

interface 
    subroutine foo(x) bind(C,name="foo")
    import c_ptr
    type(c_ptr) :: x
    end subroutine
end interface

integer(c_int), target :: i=42
type(c_ptr), pointer :: x

allocate(x)
x = c_loc(i)
call foo(x)

end
#include <stdio.h>

void foo(void** x) {
    int* i = (int*)(*x);
    printf("%d\n",*i); // effectively prints 42
}

But it’s no different from the behavior with any other kind: if a dummy argument is <anytype> :: x, an actual argument that is <anytype>, pointer or <anytype>, allocatable is somehow automatically “casted” to <anytype> for the call.

In above code, replacing type(c_ptr) :: x by type(c_ptr), pointer in the interface, breaks the code (it no longer prints 42)

@certik ,

Please note the POINTER attribute you show on the Fortran side effectively requires support of Fortran 2018 (or later revision) with enhanced interoperability with the C companion processor using ISO_Fortran_binding.h.

Ordinarily a double pointer (**) in C simply means an array of addresses that can reduce to an array of type(c_ptr) on the Fortran side such as type(c_ptr), .. :: x(*) for void** x.

Here is a really silly example with a case that seems to interest more users in the teams I work with i.e., char ** strings and interoperation with Fortran:

  • C code
#include <stdio.h>

void Cprint(size_t n, char ** s) {
   for ( size_t i=0; i < n; i++ ) {
      printf("%s\n", s[i]);
   }
}
  • Fortran driver
   use, intrinsic :: iso_c_binding, only : c_char, c_null_char, c_size_t, c_ptr, c_loc
   interface
      subroutine Cprintf( n, ps ) bind(C, name="Cprint")
         import :: c_size_t, c_ptr
         integer(c_size_t), intent(in), value :: n
         type(c_ptr), intent(in) :: ps(*)
      end subroutine 
   end interface
   character(kind=c_char,len=:), allocatable, target :: s1, s2
   type(c_ptr), allocatable :: ps(:)
   s1 = c_char_"Hello World!" // c_null_char
   s2 = c_char_"There is a lot you can do with C interoperability in Fortran." // c_null_char
   ps = [ c_loc(s1), c_loc(s2) ]
   call Cprintf( size(ps, kind=c_size_t), ps )
end 
  • A processor in action:
C:\temp>cl /c /W3 /EHsc c.c
Microsoft (R) C/C++ Optimizing Compiler Version 19.36.32537 for x64
Copyright (C) Microsoft Corporation.  All rights reserved.

c.c

C:\temp>ifx /c /standard-semantics /free p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.1.0 Build 20240308
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.


C:\temp>link p.obj c.obj /subsystem:console /out:p.exe
Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>p.exe
Hello World!
There is a lot you can do with C interoperability in Fortran.

C:\temp>

Does LFortran support this case? If not, you may add a ticket using this example - it may help other LFortran users and allow you to extend it to other cases such as int **, double **, etc.

1 Like

Thanks, reported at Advanced string C interop fails with "LCompilersException: Not implemented 16" · Issue #4292 · lfortran/lfortran · GitHub.

1 Like