- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
The following mixed C/Fortran program fails with Intel Fortran, but works fine with gfortran:
double* alloc(int size); void dealloc(double *ptr, int size); int main(int argc, char **argv) { double *array = alloc(10); dealloc(array, 10); return 0; }
MODULE dealloc_test USE, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE CONTAINS FUNCTION alloc(size) BIND(C,NAME='alloc') RESULT(rv) INTEGER (C_INT), VALUE, INTENT(IN) :: size REAL (C_DOUBLE), DIMENSION(:), POINTER :: array TYPE (C_PTR) :: rv ALLOCATE(array(size)) rv = C_LOC(array) ENDFUNCTION SUBROUTINE dealloc(ptr, size) BIND(C,NAME='dealloc') TYPE (C_PTR), VALUE, INTENT(IN) :: ptr INTEGER (C_INT), VALUE, INTENT(IN) :: size REAL (C_DOUBLE), DIMENSION(:), POINTER :: array CALL C_F_POINTER(ptr, array, [size]) DEALLOCATE(array) ENDSUBROUTINE ENDMODULE
In fact, gfortran doesnt seem to care about the type and size at all, and will always successfully deallocate.
Any thoughts?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I would expect the DEALLOCATE to fail as you've lost the additional descriptor info from the allocated array in "alloc", Just saving the address is not sufficient. Not a valid program. That it "works" in gfortran is coincidence/luck.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I would expect the DEALLOCATE to fail as you've lost the additional descriptor info from the allocated array in "alloc", Just saving the address is not sufficient. Not a valid program. That it "works" in gfortran is coincidence/luck.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Check out Intel Fortran Developer Guide/c_f_pointer:
CALL C_F_POINTER(cptr, fptr [,shape])
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.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Schoonjans, Tom wrote:.. Any thoughts?
Fortran standard gives enough verbiage to guide friendly implementations to disallow deallocation of the kind of target in the original post.
But note one might be better off employing a named (and protected) target of ALLOCATABLE attribute, always a "safer" option, on the Fortran side instead of anonymous targets and also the so-called opaque pointer on the C side for the kind of use case implied here, as shown below:
module dealloc_test use, intrinsic :: iso_c_binding, only : c_double, c_ptr, c_size_t, c_associated, c_loc implicit none real(c_double), allocatable, target, protected, save :: data_array(:) ! Named, protected target data object contains function alloc(size) bind(C, name='alloc') result(rv) ! Argument list integer(c_size_t), value, intent(in) :: size ! Function result type (c_ptr) :: rv ! Local variables integer(c_size_t) :: i ! Handling elided for an existing allocation of data_array allocate( data_array(size) ) data_array = [( int(-i, kind=kind(data_array)), i = 1, size )] rv = c_loc(data_array) return end function subroutine dealloc(ptr) bind(C, name='dealloc') ! Argument list type(c_ptr), value, intent(in) :: ptr ! Check if input pointer is associated with module variable if ( c_associated(ptr, c_loc(data_array)) ) then deallocate( data_array ) end if return end subroutine end module
#include <stdio.h> typedef void * FDATA; // An opaque pointer to some "data" in Fortran FDATA alloc( size_t ); void dealloc( FDATA ); int main() { FDATA dat; size_t n = 10; dat = alloc(n); // Employing "domain knowledge" data in Fortran points to a "double array"! double *array = (double *)dat; printf("C main: array = \n"); for (size_t i=0; i < n; i++) { printf("%lf ", array); } dealloc(dat); return 0; }
Both the compilers mentioned in this thread should work with such code and give output like so:
C main: array = -1.000000 -2.000000 -3.000000 -4.000000 -5.000000 -6.000000 -7.000000 -8.000000 -9.000000 -10.000000 p.exe (process 16888) exited with code 0.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Many thanks for the comments.
I will from now on then use the following approach:
MODULE dealloc_test USE, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE PRIVATE REAL (C_DOUBLE) :: dummy_d INTEGER (8), PARAMETER :: sizeof_double = C_SIZEOF(dummy_d) INTERFACE FUNCTION malloc(size) BIND(C,NAME='malloc') RESULT(rv) USE, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE INTEGER (C_SIZE_T), VALUE, INTENT(IN) :: size TYPE (C_PTR) :: rv ENDFUNCTION ENDINTERFACE CONTAINS FUNCTION alloc_and_something_useful(length) BIND(C,NAME='alloc_and_something_useful') RESULT(rv) USE, INTRINSIC :: ISO_C_BINDING IMPLICIT NONE INTEGER (C_SIZE_T), VALUE, INTENT(IN) :: length REAL (C_DOUBLE), DIMENSION(:), POINTER :: array TYPE (C_PTR) :: rv rv = malloc(length * sizeof_double) CALL C_F_POINTER(rv, array, [length]) ! do something useful with with array before returning ENDFUNCTION ENDMODULE
#include <stdlib.h> double* alloc_and_something_useful(int length); int main(int argc, char **argv) { double *array = alloc_and_something_useful(10); // do some other useful things with array //... free(array); return 0; }
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I consider the example code in the first post a pretty basic part of C interoperability. Where in the standard does it state that the code is non-conforming?
This thread,and specific response, on the j3 list may be of interest - https://mailman.j3-fortran.org/pipermail/j3/2010-August/003380.html. ;
The logic in the quoted text in the compiler's documentation is a bit odd.
(Edit - and another one at https://mailman.j3-fortran.org/pipermail/j3/2016-June/009307.html. There may be more - I recall this coming up a few times over the years...).
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It's a bit tricky, really, and on reconsideration, I think the code is valid but problematic. The standard says, "If a pointer appears in a DEALLOCATE statement, it shall be associated with the whole of an object that was created by allocation." The problem here is how to know if the pointer is associated with "the whole of an object". Intel Fortran relies on a flag in the pointer descriptor that says whether it's safe to deallocate it. The flag is set on an ALLOCATE, copied on a whole-object pointer assignment, but cleared if you do a pointer assignment to part of an object (or pointer assign to a non-pointer.) Calling C_F_POINTER does not set this flag, since it has no idea what the target is.
The problem is that it's possible to pointer-assign to "the whole of an object" in a way the compiler can't detect. There are implementation methods that allow this, and maybe gfortran uses one - Intel Fortran doesn't. Indeed, while I was at Intel I filed a bug report giving an all-Fortran example that was valid by the standard but that Intel Fortran rejected. That report is still open, as far as I know.
I really don't like the approach Tom's code takes, as it forces the compiler to assume that the deallocate is of the whole object. A more reliable approach is to not use C_PTR and C_F_POINTER at all, but instead the F2018 "C descriptor" feature which Intel Fortran fully supports. Instead of a C_PTR argument, the argument in Fortran would be POINTER, DIMENSION(:) and on the C side a CFI_cdesc_t. If the C code wanted to do something with the data, it can reference the base address in the descriptor. Another choice would be to do the allocate and deallocate in C and use C_F_POINTER if one wanted to manipulate the data in Fortran.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks Steve for the update. Unfortunately the code I am writing cannot rely on such recent additions to the Fortran standard :-(
Would you agree that my second approach is safe as well?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Schoonjans, Tom wrote:.. Unfortunately the code I am writing cannot rely on such recent additions to the Fortran standard :-(
Would you agree that my second approach is safe as well?
Your second approach involves C 'malloc' on the Fortran side but 'free' on the C side; can you not achieve all the memory management of dynamic program data on the C side and make your Fortran code only perform operations on such data? That would be safer and cleaner, I think. Your second approach appears along the lines of giving yourself "enough rope to shoot yourself in the foot".
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve Lionel (Ret.) (Blackbelt) wrote:It's a bit tricky, really, .. The standard says, "If a pointer appears in a DEALLOCATE statement, it shall be associated with the whole of an object that was created by allocation." The problem here is how to know if the pointer is associated with "the whole of an object". ..
The standard also says in section 9.7.3.3, "Deallocating a pointer .. whose target was not created by an ALLOCATE statement causes an error condition in the DEALLOCATE statement."
In the code in the original post with subroutine dealloc, how does the compiler know the target of 'array' object was created by an ALLOCATE statement? What happens when 'size' dummy argument is passed an incorrect value?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FortranFan wrote:The standard also says in section 9.7.3.3, "Deallocating a pointer .. whose target was not created by an ALLOCATE statement causes an error condition in the DEALLOCATE statement."
In the code in the original post with subroutine dealloc, how does the compiler know the target of 'array' object was created by an ALLOCATE statement? What happens when 'size' dummy argument is passed an incorrect value?
The compiler doesn't necessarily know, These words in the standard are a restriction on the program, not the compiler. If a program tries to do something else, the results are not specified by the standard.
A possible implementation is to allocate some extra space before the data that contains length and maybe some other validation info that DEALLOCATE can test to see if it is in fact "the whole of an object" that was created by an ALLOCATE. I'd guess that this is what gfortran is doing.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
How many of these objects are you intending on allocating at any one time?
If you do not wish to use the F2018 "C descriptor" feature, and wish to have the ability to allocate on either the C or Fortran side and deallocate on the Fortran or C side, I suggest you use an extension of FortranFan's suggestion in #4 and have the module you make for this contain an array of allocatable arrays, or an array of pointers (allocatable arrays is a better choice). The size of the array of allocatable arrays/pointers is set to the maximum permitted allocations. If this is not desirable (max number not determinable and likely to exceed a reasonable guess), then construct a user defined type containing a link pointer to same type, and then this type contains a reasonable number of allocatable arrays or pointers.
Allocation of the Fortran side would search the array of arrays/pointers (link to next node if/when necessary) and when unallocated array is found (or pointer not associated), then use that entry for the allocation. Return the C_LOC of the allocated array(1).
Deallocation is as follows:
The Fortran deallocate_function is called by both C and Fortran. The array or arrays/points is searched as suggested by FortranFan for an allocated entry with associated pointer to the C_PTR passed in. If/when the array/pointer is located it is deallocated. If/when the associated entry is not found, the Fortran code calls the (your) C routine to perform the delete. I suggest you call a shell function you write that can optionally check a list/table to see if this allocation is valid, and if so, free it.
Think of the Fortran descriptor like a C++ String object and where you pass the address of the [0]'th entry to a C function...
And then the C function calls free to release the memory. This is what you need to protect against (inter-language domain memory management).
Additional "gotcha" is should the C++ side use the TBB Scalable Memory Allocator the Fortran side may or may not malloc/free the same low-level way that the C++ side does.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
See: https://software.intel.com/en-us/node/506259
up-level: https://software.intel.com/en-us/node/506255
Jim Dempsey
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page