C file pointers and Fortran file units

A lot of C libraries use filepointers (FILE *) for their input and output routines.
When writing C wrappers for these libraries, it is possible to use the type c_ptr for
the filepointer object and create interfaces to fopen and fclose.

In principle, this works fine. However, the consequence is that filehandling has to be done
in the way it is done in C, not the way it is usually done in fortran (open, close, integer value
for the file unit.) and there may be two different way to handle files in the same program or library.

See below, as an example, a program that uses a Fortran binding to the graphics library GDlib I am currently working on:

So it would be nice if there exists a (portable) way to link Fortran file units to File pointers an vice versa.

program test_fortran_gd
  use iso_c_binding,  only: c_ptr, c_int, c_null_char
  use fortran_libgd
  implicit none

  type(c_ptr)   :: im

 ! file pointer 
  type (c_ptr)  :: pngout,

  integer(c_int):: black
  integer(c_int):: closestatus
  im = gdImageCreate(64_c_int, 64_c_int)
  black = gdImageColorAllocate(im, 0_c_int, 0_c_int, 0_c_int)

! gd_fopen ist just a wrapper for C's fopen
  pngout = gd_fopen("test_black.png"//c_null_char, "wb"//c_null_char)

  call gdImagePng(im, pngout)

! close file
  closestatus = gd_fclose(pngout)
  call gdImageDestroy(im);
     
end program test_fortran_gd

The Sun/Oracle Compiler has (had ?) the function getfilep available, that took the unit number of a file as an argument and returned the address of the file pointer. However, this seem to be a proprietary vendor extension (and pre-2003 Fortran).
So I would be interested, whether there are more portable approaches.

1 Like

You’re assuming that Fortran I/O units always correspond to a C file pointer. I know of multiple compilers where that is not true. What you ask will never be portable, and more important, the Fortran library maintains state about the I/O unit that would be bypassed if you interacted with the underlying file API directly, leading to other problems.

4 Likes

Thank you very much for the information.

For mostly historical perspective, you might want to look for information about the fortran posix interface. This was an excellent step forward towards fortran portability with POSIX compliant operating systems. Among such features as command line arguments and environment variable access, it also included interface routines to POSIX i/o and file system functions. However, for reasons that I never understood, even now in hindsight, it was not popular among fortran programmers at the time, although it was fairly widely supported by vendors.

This f77 interface was published in the early 1990s. About 15 years later, f2003 included the fortran-C interop functionality, which replaced some, but not all, of the functionality of this standard interface. Progress along these lines has been frustratingly slow over the decades.

1003.9-1992 - IEEE Standard for InformationTechnology - POSIX(R) FORTRAN 77 Language Interfaces - Part 1: Binding for System Application Program Interface (API) | IEEE Standard | IEEE Xplore

1 Like

DEC Fortran (and Compaq and Intel) supported the POSIX interface, but almost nobody used it. It didn’t help that the POSIX Fortran interface never progressed beyond F77.

2 Likes

Interesting topic. I think in general it would be advised to do all of the I/O on either the C or the Fortran side, for the reasons discussed here.
I think one reasonable way to mix reading and writing between C and Fortran is to

  • Use file name + the C file pointer to inform the Fortran program
  • only use stream access in the Fortran side
  • Interface to C stdlib’s “fseek” and “ftell” functions to sync the file position in C after it’s been manipulated by Fortran

Here’s a simple example. I have a text.txt file that contains 1234567890.
C main program (test_file.c):

#include <stdio.h>

// Interface to fortran function
void fortran_file_info(FILE* filePtr);

int main() {

   FILE* myFile = fopen("text.txt","r");

   // Pass to Fortran, inquire state
   fortran_file_info(myFile);

   // Read two characters
   char str[2];
   fscanf(myFile,"%2s",str);
   printf("read string: %s \n",str);

   // Test state again
   fortran_file_info(myFile);

   // Close file
   fclose(myFile);

}

Fortran manipulation routine:

subroutine fortran_file_info(filePtr) bind(C,name="fortran_file_info")
   use iso_c_binding
   implicit none
   type(c_ptr), intent(in), value :: filePtr

   logical :: OK
   integer, save :: funit
   character(len=2) :: twoChar

   ! Interface to C file routines
   interface
       integer(c_long) function ftell(filePtr) bind(C)
          import c_ptr,c_long
          type(c_ptr), intent(in), value :: filePtr
       end function ftell
   end interface

   ! Get file details
   inquire(file="text.txt",opened=OK)

   print *, 'is file opened in fortran? ',OK,' how about C? ',ftell(filePtr)>=0_c_long,' at ',ftell(filePtr),' bytes position '

   ! Read if open in C
   if (ftell(filePtr)>0_c_long) then
      if (.not.OK) open(file="text.txt",newunit=funit,access='stream')

      ! C->Fortran indexing: read two characters   
      read(funit,pos=ftell(filePtr)+1) twoChar

      print *, 'fortran read 2 characters: ',twoChar

   endif

end subroutine fortran_file_info

The program prints out:

 is file opened in fortran?  F  how about C?  T  at                     0  bytes position 
read string: 12 
 is file opened in fortran?  F  how about C?  T  at                     2  bytes position 
 fortran read 2 characters: 34

So, Fortran can position the file at the current C location using stream access. The updated location after all Fortran manipulation could be passed back to C by a call to fseek.

1 Like

My advice is simpler - choose one language for your I/O and call it from the other. Maybe your test program works with the compilers you are using, but I would not want to promise it works everywhere.

2 Likes

I totally agree! Still fun to see how easy it was to manage something such language-specific as I/O between the two languages.