Donna
Donna

Reputation: 1540

Deallocating arrays defined from c_f_pointer

The following code compiles in both GNU gfortran and Intel ifort. But only the gfortran compiled version will run successfully.

    program fort_tst
        use iso_c_binding

        INTEGER, POINTER :: a(:) 
        TYPE(C_PTR) :: ptr 

        INTEGER, POINTER :: b(:) 

        ALLOCATE(a(5)) 

        ptr = c_loc(a) 

        CALL c_f_pointer(ptr,b,[5]) 

        DEALLOCATE(b) 
    end program fort_tst

The error in the Intel compiled code is :

forrtl: severe (173): A pointer passed to DEALLOCATE points to an object that cannot be deallocated
Image              PC                Routine            Line        Source             
fort_tst           000000000040C5A1  Unknown               Unknown  Unknown
fort_tst           0000000000403A17  Unknown               Unknown  Unknown
fort_tst           0000000000403812  Unknown               Unknown  Unknown
libc-2.17.so       00002AAAAB20F555  __libc_start_main     Unknown  Unknown
fort_tst           0000000000403729  Unknown               Unknown  Unknown

The gfortran code runs to completion. A quick valgrind check does not find any leaks.

Can someone confirm whether the code above is valid/legal code?

I am running

    ifort (IFORT) 2021.2.0 20210228

and

    GNU Fortran (GCC) 9.2.0
    Copyright (C) 2019 Free Software Foundation, Inc.

UPDATE :

What is interesting is that gfortran does the right thing, (i.e. deallocates only allocated memory), even when the user tries to confound it with improper index remapping, or a bogus shape argument. So the internal array descriptor is being properly copied over with gfortran's c_f_pointer.

Upvotes: 5

Views: 701

Answers (4)

Donna
Donna

Reputation: 1540

Posts above inspired the following solution. The idea is to create a type that wraps the actual data array. Then, c_loc/c_f_pointer sequence works fine with a pointer to a scalar object. The data array stored in the type can be safely allocated, along with the array type itself.

MODULE arraytype_m
    TYPE, PUBLIC :: arraytype
        INTEGER, ALLOCATABLE :: data(:)
    END TYPE arraytype  
END MODULE arraytype_m


PROGRAM fort_tst
    USE iso_c_binding
    USE arraytype_m

    TYPE(arraytype), POINTER  :: a, b
    TYPE(C_PTR) :: ptr 

    ALLOCATE(a)
    ALLOCATE(a%data(5))

    !! Set to C-style pointer, and then copy back to Fortran pointer.
    ptr = c_loc(a) 
    CALL c_f_pointer(ptr,b)

    DEALLOCATE(b%data)
    DEALLOCATE(b) 
END PROGRAM fort_tst

This works with both Intel and gfortan, and is really a better solution than what I was trying to do.

Special thanks for @Federico for posting the C++/Fortran code that made this solution obvious.

Update : A complete code, which shows how the ptr above can be stored in C.

// C code
typedef void* arraytype;

void allocate_array(arraytype *ptr);
void deallocate_array(arraytype *ptr);
void do_something(arraytype *ptr);

int main()
{
    arraytype ptr;
    allocate_array(&ptr);    
    do_something(&ptr);
    deallocate_array(&ptr);
    return 0;
}

and the corresponding Fortran :

!! Fortran code
MODULE arraytype_mod
    TYPE, PUBLIC :: arraytype
        DOUBLE PRECISION, POINTER :: data(:)
    END TYPE arraytype  
END MODULE arraytype_mod

SUBROUTINE allocate_array(ptr) BIND(C,name='allocate_array')
    USE iso_c_binding
    USE arraytype_mod
    TYPE(c_ptr) :: ptr
    TYPE(arraytype), POINTER :: a
    ALLOCATE(a)
    ALLOCATE(a%data(5))
    ptr = c_loc(a)
END

SUBROUTINE deallocate_array(ptr) BIND(C,name='deallocate_array')
    USE iso_c_binding
    USE arraytype_mod
    TYPE(C_PTR) :: ptr
    TYPE(arraytype), pointer :: a
    CALL c_f_pointer(ptr,a)
    DEALLOCATE(a%data)
    DEALLOCATE(a)
END

SUBROUTINE do_something(ptr) BIND(C,name='do_something')
    USE iso_c_binding
    USE arraytype_mod
    TYPE(c_ptr) :: ptr
    TYPE(arraytype), POINTER :: a
    CALL c_f_pointer(ptr,a)
    a%data = 2.5
    WRITE(6,*) a%data
END 

Upvotes: 1

Federico Perini
Federico Perini

Reputation: 1416

Usage of c_f_pointer is pretty standard behavior in case a Fortran derived type is to be passed to a C++ class as an opaque pointer type, see e.g. the following interoperable class:

module mytype_m
    use iso_c_binding
    implicit none
    private

    type, public :: mytype
        real, allocatable :: data(:)
        contains
        procedure :: destroy
        procedure :: init
        procedure :: printout
    end type mytype

    public :: mytype_print_c
    public :: mytype_init_c
    public :: mytype_destroy_c

    contains

    subroutine init(this,data)
       class(mytype), intent(inout), target :: this
       real, intent(in) :: data(:)
       call destroy(this)
       this%data = data
    end subroutine init

    elemental subroutine destroy(this)
       class(mytype), intent(inout), target :: this
       integer :: ierr
       deallocate(this%data,stat=ierr)
    end subroutine destroy

    subroutine printout(this)
       class(mytype), intent(inout), target :: this
       integer :: ndata,i
       ndata = merge(size(this%data),0,allocated(this%data))
       write(*,1) ndata,(this%data(i),i=1,ndata)
       1 format('mytype object has data(',i0,')',:,' = ',*(f3.1,:,', '))
    end subroutine printout

    subroutine mytype_print_c(this) bind(C,name='mytype_print_c')
        type(c_ptr), intent(inout) :: this
        type(mytype), pointer      :: fortranclass
        call c_f_pointer(this, fortranclass)
        call fortranclass%printout()
    end subroutine mytype_print_c

    subroutine mytype_destroy_c(this) bind(C,name='mytype_destroy_c')
        type(c_ptr), intent(inout) :: this
        type(mytype), pointer      :: fortranclass

        call c_f_pointer(this, fortranclass)
        if (associated(fortranclass)) then
            call fortranclass%destroy()
            deallocate(fortranclass)
        end if
        ! Nullify C pointer
        this = c_null_ptr
    end subroutine mytype_destroy_c

    subroutine mytype_init_c(this,ndata,data) bind(C,name='mytype_init_c')
        type(c_ptr), intent(inout) :: this
        integer(c_int), intent(in), value :: ndata
        real(c_float), intent(in) :: data(ndata)

        type(mytype), pointer :: fortranclass
        integer :: ierr

        ! In case it was previously allocated
        call c_f_pointer(this, fortranclass)
        allocate(fortranclass,stat=ierr)
        call fortranclass%init(data)
        this = c_loc(fortranclass)

    end subroutine mytype_init_c

end module mytype_m

that would be bound to an opaque pointer in c++:

#include <iostream>
#include <vector>

using namespace std;

// Fortran interoperability
typedef void* mytype;
extern "C" { void mytype_print_c(mytype self);
             void mytype_destroy_c(mytype self);
             void mytype_init_c(mytype self, const int ndata, float *data); }

// Class definition
class mytype_cpp
{
    public:
        mytype_cpp(std::vector<float> data) { mytype_init_c(this,data.size(),data.data()); };
        ~mytype_cpp() { mytype_destroy_c(this); };
        void printout() { mytype_print_c(this); };
};

int main()
{

    // Print 8--size
    std::vector<float> data {1.,2.,3.,4.,5.,6.,7.,8.};
    mytype_cpp obj(data); obj.printout();

    return 0;
}

which, with gfortran-10, returns

mytype object has data(8) = 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0

I don't have a chance to test with ifort, but it works seamlessly with gcc, how can this approach not be Fortran standard-compliant?

Upvotes: 2

The error is issued, because the compiler claims that the pointer that is being allocated was not allocated by an allocate statement.

The rules are (F2018):

9.7.3.3 Deallocation of pointer targets

1 If a pointer appears in a DEALLOCATE statement, its association status shall be defined. Deallocating a pointer that is disassociated or whose target was not created by an ALLOCATE statement causes an error condition in the DEALLOCATE statement. If a pointer is associated with an allocatable entity, the pointer shall not be deallocated. A pointer shall not be deallocated if its target or any subobject thereof is argument associated with a dummy argument or construct associated with an associate name.

Your pointer b was associated using the c_f_pointer subroutine. The error condition mentioned is the

forrtl: severe (173): A pointer passed to DEALLOCATE points to an object that cannot be deallocated

Now we have to be careful, the exact wording is

or whose target was not created by an ALLOCATE statement

The target arguably was created by an allocatable statement. And then went through this indirect chain of association. I am not such an expert language lawyer to be sure whether this makes the target to be applicable or not, when it passed through c_loc() and c_f_pointer().

Gfortran does not issue this error condition and then it works fine because at the end of the day, under the hood, what matters is that the address passed to the system free() function was allocated by the matching system malloc() function.

I think we can conclude that one of the compilers is wrong here, because the mention of the error condition is clear in the standard and either it should be issued or it should not. A third option, that gfortran just leaves it too work, should not happen. Either it is allowed, or an error condition shall be issued.


Re UPDATE: What gfortran does is really sending the address to free(). As long as the pointer is contiguous and starts at the first element, it will work in practice. The size is not necessary and is not passed to free(). The system allocator malloc()/free() stores the size of each allocated system in its own database.

There are even worse abuse cases that can happen and will work just by chance due to this, even if completely illegal in Fortran.

See this:

use iso_c_binding

character, allocatable, target :: a
type(c_ptr) :: p
real, pointer :: b(:)

allocate(a)

p = c_loc(a)

call c_f_pointer(p, b, [1000])

deallocate(b)

end

Upvotes: 4

francescalus
francescalus

Reputation: 32366

gfortran is arguably missing a diagnostics opportunity when it comes to the DEALLOCATE statement. ifort is arguably too conservative when it comes to the DEALLOCATE statement.

The error message from ifort is an explicit design choice prohibiting the pointer from C_F_POINTER appearing in a DEALLOCATE statement:

Since the resulting data pointer fptr could point to a target that was not allocated with an ALLOCATE statement, fptr cannot be freed with a DEALLOCATE statement.

There seems little in Fortran 2018 explicitly to support that restriction (even in the case where the target was created by an ALLOCATE statement), and ifort itself isn't consistent in applying it:

  use iso_c_binding

  integer, pointer :: a, b
  type(c_ptr) :: ptr 

  allocate(a)
  ptr = c_loc(a) 
  call c_f_pointer(ptr,b) 
  deallocate(b)

end program

However, consider the case

  use iso_c_binding

  integer, pointer, dimension(:) :: a, b
  type(c_ptr) :: ptr 

  allocate(a(5))
  ptr = c_loc(a) 
  call c_f_pointer(ptr,b,[4])
  deallocate(b)

end program

One would surely expect deallocation here to be problematic but this doesn't cause an error condition with gfortran: gfortran isn't carefully checking whether the target is deallocatable (note that it doesn't have to).

There is some subtlety in Fortran 2018's wording of C_F_POINTER (F2018 18.2.3.3)

If both X and FPTR are arrays, SHAPE shall specify a size that is less than or equal to the size of X, and FPTR becomes associated with the first PRODUCT (SHAPE) elements of X (this could be the entirety of X).

and whether "the entirety" of a forms a valid thing to deallocate but ifort's documentation is seemingly too strict and gfortran's checking is not going to catch all invalid cases. There is a case for talking to the vendor of each compiler.


That said, the use of a C_F_POINTER's pointer in a DEALLOCATE statement clearly is more prone to error than "simpler" pointers, and these errors are not ones where we can rely on a compiler to point them out. Even with a conclusion of "clearly this is allowed" I personally would recommend that one avoids this approach where possible without other bad things.

Upvotes: 3

Related Questions