Type(c_ptr) and void *

Hello

is Fotran type(c_ptr) equivalent to C void * ?

2 Likes

Yes.

2 Likes

I think (but don’t quote me) that assumed type arguments (TYPE(*)) also work like void pointers. One thing they allow you to do is define optional arguments to C functions that get passed as a C null pointer if they are not present. Its common in C world to use a null pointer to signal that a variable is not used.

1 Like

To build upon the two previous answers, TYPE(C_PTR) can stand for any C pointer. This includes void* (the most common usage), but also int*, double*, or whatever*:

type, bind(C) :: foo
   type(c_ptr) :: x
   type(c_ptr) :: y
end type

is interopable with

typedef struct {
   void* x;
   int*  y;
} foo;

But for procedure arguments there is a gotcha: when passing a TYPE(C_PTR) argument to a C function, Fortran by default passes the address, not the value. Consequently this is a void** pointer that is received on the C side. One has to use the VALUE attribute to pass the value and not the address.

Regarding TYPE(*) it stands for any Fortran type (“assumed type”). So when passed to C it is a void* (or whatever*) on the C side. The VALUE attribute cannot be used with TYPE(*)

C side argument Fortran side argument
void** TYPE(C_PTR)
void* TYPE(C_PTR), VALUE
void* TYPE(*)
7 Likes

@PierU there is also type(c_ptr), pointer, which is also void**.

4 Likes

Could you give an exemple of how you would use type(c_ptr), pointer? It seems to me that if there is a pointer on the Fortran side, then a CFI descriptor must be used on the C side…

1 Like

if type(c_ptr) is equivalent to void * then I should be able to create a specific fortran type that contains my data, declare a member toto of that type as pointer, allocate it then transmit and store in a python class instance as a void * using c_loc(toto) and finally get the fortran member toto of the type using c_f_pointer when python calls fortran.

My final purpose is to suppress all global variables in the Fortran code in order to be able to launch several instance of the code with the python interface.

https://fortran-lang.discourse.group/t/python-class-and-fortran-code/8134

I tested this (full fortran and it works) now I am going to test it with python and python.

module test
  use iso_fortran_env
  implicit none
  
  type struct
    integer(int32)         :: i32
    integer(int64)         :: i64
    real(real32)           :: r32
    real(real64)           :: r64
    integer(int32),pointer :: tab_i32(:)
  contains
    procedure, pass :: display => display
  end type struct
  
contains
  
  subroutine display(ob)
    class(struct) :: ob
    integer       :: i
    
    print '("i32=",i0)',ob%i32
    print '("i64=",i0)',ob%i64
    print '("r32=",f12.5)',ob%r32
    print '("r64=",f12.5)',ob%r64
    print '("size(tab_i32)=",i0)',size(ob%tab_i32)
    do i=1,size(ob%tab_i32)
      print '(t3,"tab(",i2,")=",i2)',i,ob%tab_i32(i)
    enddo
    return
  end subroutine display
  
end module test


program main
  use iso_fortran_env
  use iso_c_binding, only: c_loc,c_ptr,c_f_pointer
  use test
  
  implicit none
  
  type(struct), pointer :: fptr_struct0(:)
  type(struct), pointer :: fptr_struct1(:)
  type(c_ptr)           :: cptr_struct
  integer(int32)        :: i
  
  !> On definit fptr_struct0
  print '(/"On definit fptr_struct0")'
  allocate(fptr_struct0(1))
  
  fptr_struct0(1)%i32=1_int32
  fptr_struct0(1)%i64=2_int64
  fptr_struct0(1)%r32=3.1415_real32
  fptr_struct0(1)%r64=3.1415_real64
  
  allocate(fptr_struct0(1)%tab_i32(1:10))
  do i=1,size(fptr_struct0(1)%tab_i32)
    fptr_struct0(1)%tab_i32(i)=i
  enddo
  
  !> On passe fptr_struct0 en pointeur C
  print '(/"On passe fptr_struct0 en pointeur C")'
  cptr_struct=c_loc(fptr_struct0)
  
  !> On binde fptr_struct0 et fptr_struct1 via cptr_struct
  print '(/"On binde fptr_struct0 et fptr_struct1 via cptr_struct")'
  call c_f_pointer(cptr=cptr_struct, fptr=fptr_struct1, shape=[1])
  
  !> On affiche fptr_struct1
  print '(/"On affiche fptr_struct1")'
  call fptr_struct1(1)%display()
  
  !> On modifie fptr_struct1
  print '(/"On modifie fptr_struct1")'
  deallocate(fptr_struct1(1)%tab_i32)
  allocate(fptr_struct1(1)%tab_i32(1:5))
  do i=1,size(fptr_struct1(1)%tab_i32)
    fptr_struct1(1)%tab_i32(i)=10*i
  enddo
  
  !> On affiche fptr_struct0
  print '(/"On affiche fptr_struct0")'
  call fptr_struct0(1)%display()
  
  !> On désalloue fptr_struct0
  deallocate(fptr_struct0)
  fptr_struct0=>null()
  fptr_struct1=>null()
end program main

Yes, it should work. The void* pointer on the C side (which you will use in Python, but it doesn’t matter) when using this technique is often named an “opaque handle” (the data behind the pointer cannot be accessed at all from the C side)

1 Like

I am not sure, we discovered it with @Pranavchiku recently that you can do this when fixing some related bugs in LFortran. It seems you have to manually allocate the (double) pointer, kind of like you would for void** in C.

2 Likes

Inside Fortran, it works but when set_cptr is called by python (cptr stored inside a class) then transmitted to fortran and get_cptr used it crashes

module test
  use iso_fortran_env
  
  type myType
    real(real64) :: x
  end type myType
  
contains
  
  function set_cptr(cptr) result(t0)  bind(C, name="send_cptr")
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    use, intrinsic :: iso_c_binding, only: c_double, c_loc
    !>
    use mpi
    !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    type(c_ptr)  , value              :: cptr
    real(c_double)                    :: t0
    !>
    type(myType), pointer, save       :: test(:)
    !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    t0=mpi_wtime()
    !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
    
    !> Allocation d'un container pour les datas avec attribut save
    allocate(test(1:1))
    test(1)%x=1d0
    cptr=c_loc(test)
    
    t0=mpi_wtime()-t0
   
    return
  end function set_cptr

  function get_cptr(cptr) result(t0)  bind(C, name="send_cptr")
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    use, intrinsic :: iso_c_binding, only: c_double, c_loc
    !>
    use mpi
    !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    type(c_ptr)  , value              :: cptr
    real(c_double)                    :: t0
    !>
    type(myType), pointer             :: test(:)
    !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    t0=mpi_wtime()
    !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
    
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    !> Allocation d'un container pour les datas space
    call c_f_pointer(cptr=cptr, fptr=test , shape=[1])
     
    return
  end function get_cptr

end module test

in fact, inside cython self.cptr remains NULL. I tried with :

t0=set_cptr(self.cptr) and t0=set_cptr(&self.cptr)

Found with :

function set_cptr(cptr) result(t0)  bind(C, name="send_cptr")
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    use, intrinsic :: iso_c_binding, only: c_double, c_loc
    !>
    use mpi
    !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
    !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
    type(c_ptr)              :: cptr

and t0=set_cptr(&self.cptr)

but it works with Cython and Fortran. Don’t understand everything but it works

Is this a typo?

When an argument has the VALUE attribute it behaves exactly like in C: a local copy is created on the stack upon entering the routine, and it’s not copied back to the original variable upon exit. So, if the argument is updated in the routine, the caller (here the Python code) cannot get it.

1 Like

I learned the hard way when I started doing C-interop to think of TYPE(C_PTR) as void** and adding the VALUE attribute dereferenced it to const void*. I’ve moved more to using TYPE(*) in the last couple of years because its easier to wrap my head around for things like pointer structure components on the C side. You still need TYPE(C_PTR) sometimes to unroll multiple pointer indirections finto multi-dimensional arrays but even then you can make TYPE(*) an array.

Edit: forget what I said about TYPE(*) in structures. Haven’t had my second cup of coffee yet. TYPE(*) can only be a dummy argument. You still have to use TYPE(C_PTR) for structure pointer components. Not sure what I was thinking.

2 Likes

Is it feasible to pass a null pointer to c from fortran as in:


type, bind(c) fstruct
  type(c_ptr) :: ptr
end type

type(fstruct), pointer :: st => null()

call c_func(st) ! calls void c_func(st *cstruct) {...}
  type(c_ptr) :: ptr
end type

type(fstruct), pointer :: st => null()

call c_func(st) ! calls void c_func(st *cstruct) {...}

Not sure if there is a better way.

There is a named constant c_null_ptr you may use:

use, intrinsic :: iso_c_binding, only: c_ptr, c_null_ptr

call c_func(c_null_ptr)

Thanks, I believe I tried that but the bind(c) interface function requires a type(fstruct).

Can you modify the interface to add the optional attribute? Omitting the argument would be equivalent to passing NULL.

N.b. this is an F2018 feature, but AFAIK most compilers support it.

(Btw, the type(fstruct) should have the bind(c) tag too.)

1 Like

Thanks - didn’t know that about the optional attribute. I’ve edited the code above to add the tag.

Don’t quote me on this, :warning:, but if I remember correctly a non-allocated allocatable variable, or a non-associated pointer variable, will also be correctly passed as NULL, when the dummy argument in the interface contains the optional attribute.

What is the interface? Could you post it?