Allocate interoperability and C descriptors

I’ve been confused in the past with wrappers (like in this StackOverflow thread). Typically you find examples of wrapping non-interoperable C/C++ objects in Fortran rather than the other way round. I guess not that many C/C++ developers appreciate the features of modern Fortran.

Btw, in case you are willing to use C++, the C API can be wrapped in a C++ class which has the benefit of automatic lifetime management (RAII) and other C++ goodies like std::span and the STL:

#include <numeric>
#include <span>

#include "somemodule_wrap.h"

class Sometype {
public:

    // Constructor
    Sometype(int n) : ptr{ sometype_create(n) } {}

    // Destructor
    ~Sometype() { sometype_free(ptr); }

    // Access array member `a`
    std::span<double> a() const {
        int n; double *a;
        a = static_cast<double *>( sometype_a(ptr,&n) );
        return { a, (size_t) n };
    }

    // Retrieve raw pointer to underlying object
    void *get() const { return ptr; }

private:
    void *ptr{nullptr};
};

void frout(const Sometype& x) {
    frout2_wrap( x.get() );
}

The usage becomes simpler than in C and you get to use STL algorithms with the std::span

int main(void) 
{
    Sometype x{6};
    
    auto a = x.a();    // a is a view (memory owned by x)

    // Fill with increasing numbers
    std::iota(a.begin(),a.end(),0.0);
    
    frout(x);

    return 0;
}
2 Likes

I don’t know whether I should have opened a new thread or maybe this one is close enough to my question.
I need to possibly allocate and modify C pointers from within Fortran, possibly without needing to force the C side to use ISO_Fortran_binding.h.
Consider the following:

! modify.f90
subroutine modify(ptrptr) bind(c)
   use, intrinsic :: iso_c_binding
   implicit none
   type(c_ptr), value   :: ptrptr
   type(c_ptr), pointer :: ptr
   real(8), pointer     :: value_ptr
   real(8), allocatable, target :: val

   call c_f_pointer(ptrptr, ptr)
   call c_f_pointer(ptr, value_ptr)
   if (.not. associated(value_ptr)) then
      print *, " C ptr is NULL"
    
      ! Create new memory
      allocate(val)
      ptr = c_loc(val)
      call c_f_pointer(ptr, value_ptr)

      ! Here I need to do like *ptrptr = ptr
      ! if I want to propagate changes to the outside world.
   endif
   value_ptr = 120.
end subroutine
// main.c
#include <stdio.h>

extern void modify(double **);

int main(void)
{
   double value = 0.;
   double *vaddr = &value;
   modify(&vaddr);
   printf("%12.5f\n", value);

   double *v = NULL;
   modify(&v);
   if (v)
      printf("%12.5f\n", *v);
   return 0;
}

First, is this code standard conforming? I have doubts about the second case…
Also because, I cannot understand why for this second case, which is the reason why I am reopening this thread, the memory seems to be actually allocated, but not modified.
That does not look good to me, which flags that something is not working properly.

EDIT: it would be nice to have, on the Fortran side, the companion f_c_pointer(fobj, cptr) subroutine, to assign the c-address of a Fortran entity to the pointed address of a type(c_ptr) Fortran object.

EDIT2: thinking about it, I just realise that in fact, mixed C-Fortran allocations are not really interoperable if not done via the ISO Binding API. So, what I am trying to achieve requires using ISO_Fortran_binding.h. Full stop. Sorry for bringing this one up again.

! modify.f90
subroutine modify(ptrptr) bind(c)
   use, intrinsic :: iso_c_binding
   implicit none
   type(c_ptr), intent(inout)   :: ptrptr
   real(8), pointer                 :: value_ptr
   call c_f_pointer(ptrptr, value_ptr)
   if (.not. associated(value_ptr)) then
      print *, " C ptr is NULL"
    
      ! Create new memory
      allocate(value_ptr)
      ptrptr= c_loc(value_ptr)
   endif
   value_ptr = 120.
end subroutine

variable with allocatable attribute will auto-deallocate when it leave subroutine,so it must have pointer attribute.

and may it is more clear if use c_associated

! modify.f90
subroutine modify(ptrptr) bind(c)
   use, intrinsic :: iso_c_binding
   implicit none
   type(c_ptr), intent(inout)   :: ptrptr
   real(8), pointer                 :: value_ptr
   if (c_associated(ptrptr)) then
      call c_f_pointer(ptrptr, value_ptr)
   else   
      print *, " C ptr is NULL"
      ! Create new memory
      allocate(value_ptr)
      ptrptr= c_loc(value_ptr)
   endif
   value_ptr = 120.
end subroutine
1 Like

My world, this made me realise I have been away from Fortran too much that I completely overlooked this one. Thanks for your answer :slight_smile:

I don’t get why you need the ptr intermediate pointer and val… Isn’t it OK like this?

! modify.f90
subroutine modify(ptrptr) bind(c)
   use, intrinsic :: iso_c_binding
   implicit none
   type(c_ptr), intent(inout) :: ptrptr
   real(8), pointer :: value_ptr

   if (c_associated(ptrptr)) 
      call c_f_pointer(ptrptr, value_ptr)
   else
      print *, " C ptr is NULL"
      ! Create new memory
      allocate( value_ptr )
      ptrptr = c_loc(value_ptr )
   endif
   value_ptr = 120.
end subroutine

Isn’t it c_loc() ?

1 Like

I think it’s OK as long as you allocate/deallocate on the same side.

1 Like

The c_loc() intrinsic does this on the fortran side. On the C side, passing an array or a scalar object without the value attribute in the interface results in a normal C pointer as the argument.

1 Like

Yeah, missed to realise this until @Euler-37 as well as yourself provided these examples. I guess my mistake was to pass the type(c_ptr) with value attribute. I thought too much in C-style while using Fortran.

Indeed.