ChatGPT has suggested wrapping a couple of C functions including fmemopen
(on POSIX) and fread
:
// Function to open a memory buffer as a file and read it
FILE *open_memory_buffer(const char *buffer, size_t size) {
return fmemopen((void *)buffer, size, "rb");
}
// Function to read from the memory buffer
void read_from_memory_buffer(FILE *stream, void *outbuf, size_t size) {
fread(outbuf, 1, size, stream);
}
// Function to close the memory buffer
void close_memory_buffer(FILE *stream) {
fclose(stream);
}
In Fortran these would become:
function open_memory_buffer(buffer,size) bind(c)
integer(c_size_t), value :: size
character(kind=c_char) :: buffer(size)
type(c_ptr) :: open_memory_buffer
end function
subroutine read_from_memory_buffer(stream,outbuf,size) bind(c)
type(c_ptr), value :: stream
type(*) :: outbuf
integer(c_size_t), value :: size
end subroutine
subroutine close_memory_buffer(stream) bind(c)
type(c_ptr), value :: stream
end subroutine
I thought that maybe I can just copy the same stream idea using a Fortran deferred-length string pointer as the stream. Here is what I’ve come up with (not thoroughly tested yet!):
// sread.c
#include <string.h>
#include <ISO_Fortran_binding.h>
// Read from a string stream
//
// subroutine sread(buffer,size,count,stream,ierr) bind(c)
// type(*), intent(out) :: buffer
// integer(c_int), value :: size, count
// character(kind=c_char), pointer :: stream(:)
// integer(c_int), intent(out) :: ierr
//
void sread(
void *restrict buffer,
int size,
int count,
CFI_cdesc_t *restrict stream,
int *ierr)
{
*ierr = 0;
const size_t nbytes = size * count;
const size_t remaining = stream->elem_len - nbytes;
if (remaining < 0) {
*ierr = -1;
return;
}
memcpy(buffer, stream->base_addr, nbytes);
CFI_CDESC_T(0) tmp;
int istat;
// tmp => stream(nbytes+1:)
istat = CFI_establish(
(CFI_cdesc_t *) &tmp,
stream->base_addr + nbytes,
CFI_attribute_pointer,
stream->type,
remaining,
stream->rank,
NULL);
if (istat != CFI_SUCCESS) {
*ierr = -2;
return;
}
// stream => tmp
istat = CFI_setpointer(stream, (CFI_cdesc_t *) &tmp, NULL);
if (istat != CFI_SUCCESS) {
*ierr = -3;
return;
}
}
I’m not sure if the pointer association this way is completely legal. It’s also not clear what is supposed to happen when the stream is consumed; I’m guessing it should be a zero-length string (and not point one element over the last element as the convention for C++ iterators). The following works in GCC however,
! test_stream.f90
program test_stream
use, intrinsic :: iso_c_binding
implicit none
interface
subroutine sread(buffer,size,count,stream,ierr) bind(c)
import c_int, c_char
type(*) :: buffer
integer(c_int), value :: size, count
character(len=:,kind=c_char), pointer, intent(inout) :: stream
integer(c_int), intent(out) :: ierr
end subroutine
end interface
character(len=12,kind=c_char), target :: data
character(len=:,kind=c_char), pointer :: stream
integer :: ierr
character(len=5) :: p1, p2
integer(c_int16_t) :: pad
data = "Hello, World"
stream => data
! Read
call sread(p1,5,1,stream,ierr)
call sread(pad,2,1,stream,ierr)
call sread(p2,5,1,stream,ierr)
print *, p1
print *, pad, transfer(', ',pad)
print *, p2
end program
Results of GCC:
$ gcc-14 -Wall -c sread.c
$ gfortran -Wall test_stream.f90 sread.o
$ ./a.out
Hello
8236 8236
World
Results of Intel compilers:
$ icc -std=c11 -diag-disable=10441 -Wall -c sread.c
$ ifort test_stream.f90 sread.o
$ ./a.out
forrtl: severe (174): SIGSEGV, segmentation fault occurred
Image PC Routine Line Source
a.out 0000000104AB0564 for__signal_handl Unknown Unknown
libsystem_platfor 00007FF814993DFD _sigtramp Unknown Unknown
a.out 0000000104B118C1 __intel_avx_rep_m Unknown Unknown
a.out 0000000104A88FA1 sread Unknown Unknown
a.out 0000000104A88D99 MAIN__ Unknown Unknown
a.out 0000000104A88C2E main Unknown Unknown
The runtime failure occurs at the point I call CFI_setpointer
. The Intel Fortran documentation on CFI_setpointer
implies that it isn’t legal to have a data pointer object as the source. But according to the F2023 interpretation document (section 18.5.5.9, paragraph 2) it is legal:
- source, shall be a null pointer or the address of a C descriptor for an allocated allocatable object, a data pointer object, or a nonallocatable nonpointer data object that is not an assumed-size array. (emphasis added)
I’m guessing this is an amendment made in the F2023 standard.