Read/Write Binary files with F90-95

I am trying to read/write a binary file in Linux. I am converting code from an older Microsoft FORTRAN '95. I can’t seem to correctly read/write the binary source file, named: CLTAPE. You’ll see the gfortran compile statement in the comments.


This is the hex representation of the first 64 bytes of my CLTAPE file:

           1     |     3      |      1     | 4294967278
   0  01 00 00 00 03 00 00 00   01 00 00 00 ee ff ff ff        ................  
  10  04 00 00 00 01 00 00 00   e8 03 00 00 01 00 00 00  ................  
  20  00 00 00 00 00 00 00 00   30 30 30 30 30 31 20 20  ........000001    
  30  0d 00 00 00 02 00 00 00   d0 07 00 00 15 04 00 00  ................  

and my code:

C TAPERD_test.FOR, 22MAR21 JOM
C Compile in Linux with this stmt:
C $ gfortran -std=legacy -o taperd_test *.FOR

  PROGRAM taperd_test  

  INTEGER*4 ibufno,indxbg, irecf, irecl

  OPEN (UNIT=2, FILE='CLTAPE', STATUS='OLD',
 +     ACCESS='SEQUENTIAL',   
 +     RECL= 4, 
 +     FORM='UNFORMATTED')

  READ (UNIT=2, IOSTAT=istat) 
 +  ibufno, indxbg, irecf, irecl
 
  WRITE (*,'(A8,I4,A9,I4)') 'IBUFNO=',ibufno,'INDXBG=',indxbg 
  WRITE (*,'(A7,I2,A7,I6)') 'IRECF=',irecf,  'IRECL=', irecl
  END

Execution Results:

$ ./taperd_test
IBUFNO=**** INDXBG=****
IRECF= 1 IRECL= 0


I think I should be hoping to see:

IBUFNO= 1 INDXBG= 3
IRECF= 1 IRECL= 4294967278


I have tried different record lengths: 8, 64, 1024
and a few other unit numbers to no avail.

Any suggestions as to why the output does not correspond to what I am expecting?

thanks for reading…

p.s. - those are just my remarks above the hex code: 1 | 3 | 1 | 4294967278


edited 23Mar2021

This is the solution, and the code that worked:

  PROGRAM taperd_test  ! TAPERD test for CLTAPE; IBM 360 APT
       !  Compiled with: $ gfortran -o taperd_test *.FOR

  OPEN (UNIT=2, FILE='CLTAPE', STATUS='OLD',
 +     ACCESS='STREAM',
 +     FORM='UNFORMATTED')

  READ (UNIT=2, IOSTAT=istat) 
 +  ibufno, indxbg, irecf, irecl
 
  WRITE (*,'(A8,I4,A9,I4)') 'IBUFNO=',ibufno,'INDXBG=',indxbg 
  WRITE (*,'(A7,I2,A7,I6)') 'IRECF=',irecf,'IRECL=',irecl

  END

and the results:

$ ./taperd_test
IBUFNO= 1 INDXBG= 3
IRECF= 1 IRECL= -18

thanks guys…

@jomyer,

Welcome to this forum.

Do you happen to have the older code? If yes, have you tried that code as-is with either gfortran (with -std=legacy) and/or the free Intel oneAPI IFORT “Classic” compiler?

Note the fpscomp compiler option with Intel oneAPI free compiler: that may be of interest to you to look into for this I/O need.

1 Like

Welcome to the Discourse!
Concerning the write side, you may be interested by this post demonstrating writing a binary file in modern Fortran:
https://fortran-lang.discourse.group/t/how-to-write-bytes-in-a-binary-file/763/7

The following page was very useful:
http://fortranwiki.org/fortran/show/Stream+Input+Output

1 Like

@jomyer, can you tell us what the contents should be? I have some experience reading binary/unformatted files the hard way and I do not quite recognise the numbers.

Also, MicroSoft FORTRAN '95 - what compiler was that? I do not recognise that one either :wink:

1 Like

Hi @jomyer, welcome to the Discourse!

One issue you may be facing is that the value 4294967278 is above the maximum signed 32bit integer of 2147483647, so you will need a larger integer kind to hold it.

I have the following program which compiles and runs with gfortran:

program test
use iso_fortran_env, only: int32, int64
implicit none

integer(int32) :: fh, ibufno, indxbg, irecf
integer(int64) :: irecl

open(newunit=fh, file='CLTAPE', access='stream')

write(fh) 1_int32, 3_int32, 1_int32 
write(fh) 4294967278_int64

close(fh)

open(newunit=fh, file='CLTAPE', access='stream')
read(fh) ibufno, indxbg, irecf, irecl
close(fh)

write(*,'(A10,I4,A10,I4)') 'IBUFNO=',ibufno,'INDXBG=',indxbg 
write(*,'(A10,I4,A10,I10)') 'IRECF=',irecf,  'IRECL=', irecl

end program test
~/test/binio$ ./a.out
   IBUFNO=   1   INDXBG=   3
    IRECF=   1    IRECL=4294967278
~/test/binio$ hexdump -C CLTAPE 
00000000  01 00 00 00 03 00 00 00  01 00 00 00 ee ff ff ff  |................|
00000010  00 00 00 00                                       |....|
00000014

2 Likes

Yes, I still have the older code. The time and date routines were definitely unusable. And I was getting so many warnings that I used ‘-std=legacy’ to get rid of them. But that option did not affect this code so I pulled it out for simplicity.

As for the oneAPI IFORT “Classic” compiler - thanks for that link. Do you think that it will not matter if I am not using an Intel chip?

I don’t know much about hardware, but I am running on a Raspberry Pi 4B, 4 core, with a ARM A72 64bit chip. Not sure how important that is to a specific compiler.

ARM chips have a very different architecture, relative to x86/x86-64. So you need a compiler compiled for ARM architecture.

1 Like

Microsoft sold FORTRAN 95 in a box as a separate software, in a box like Windows NT came in. That is what I recall, anyway.

The contents are: a CLFILE - Cutter Location file - from IBM 360 APT - the ANS X3.37 Numerical Control Programming language (from which FORTRAN derived, btw). I am making a noble attempt to convert postprocessor code to Linux. Here is a screen shot of my editor showing a rendition of the binary:

I get stuck just reading the first 4 bytes.

I tried to upload the file CLTAPE, but got the message, ‘not authorized’.

The number size occurred to me, and I tried the statement UNSIGNED INT with some variation, but got syntax errors. I don’t have any documentation with me. So, I’m going by memory somewhat. I am glad you did elaborate on that. I am not familiar with the more modern syntax (as my code suggests). But I figured, those are the 4 bytes, so why shouldn’t the number be valid? And also, perhaps the number was negative. If so, that is beyond where I want to go at the moment. It represents the last record in the file, so I thought I’d worry about the beginning of the file first. It all worked in Windows.

Ok, that’s different. Something I need to look into.

Yeah, I’d like to find an older equivalent syntax to keep it consistent with the older code. This syntax I have seen but am unfamiliar with. There maybe something going on with that last record identifier ‘irecl’ that eludes me for now.

thanks for the awesome reply…

Yes, I saw the ACCESS=stream syntax somewhere, but it did not appear in the FORTRAN 90 documentaion: https://wg5-fortran.org/N001-N1100/N692.pdf

So I figured that was not going to be valid. I’ll have to check. But if I need a different compiler…or computer hardware…

It seems “Stream” was introduced in Fortran 2003. If you use gfortran it’s OK, gfortran is supporting Fortran 2003, and most of Fortran 2008:

1 Like

@jomyer ,

Is it possible for you to try to get a working version of your old code first on a Windows machine (x64/x86 arch)? Given what you write about some version of Microsoft Fortran previously in use with this code, this may be the better approach to wrap your hands around the code. Toward this, you can use either Intel oneAPI IFORT compiler (with possible use of compiler options that provide some compatibility with certain Microsoft Fortran PowerStation aspects) and/or gfortran?

Once you get a working version going on Windows, you can consider porting your code with better and current knowledge of this code to ARM 64-bit architecture - gfortran will likely be of considerable help with this - IFORT will not work on ARM unless I’m mistaken.

1 Like

Yeah, I started off with working code for Windows, from back in '95. I had to hack it up a bit to get it to compile in gfortran.

That CLTAPE file is a hex dump? That is my source file full of lots of good stuff, meticulously stored in binary. Maybe you could call it a hex dump. I dunno. I know there are 4 byte chunks; some 4 byte chunks get split into two 2-byte chunks; some chunks get filled with characters over a larger array. How to deal with it - gotta be able to READ it first, then refigure out the structure of the CLFILE.

I got my test to work. I’ll post that momentarily…

[quote="
0xffffffee+18 = 0x100000000 = 0b100000000000000000000000000000000
Therefore 0xffffffee represents -18 in two’s complement.
[/quote]

yes, I knew it was called the two’s complement. But I never understood any explanation of it.

Is this the same as taking the largest representable number (like ff ff ff ff in this case) and subtracting from it for it’s representation of a negative?

I’m pleased to see that my note on stream-I/O is useful - I only posted it to the Fortran Wiki about a month ago. The gfortran compiler supports stream I/O fully, but if you have the misfortune to be forced to use an older compiler then don’t use ACCESS=‘SEQUENTIAL’ as it always writes (or expects to read) extra stuff such as byte counts at the start of each record. The only way is to use ACCESS=‘DIRECT’ and choose a suitable record length. These records will not be messed up with extra stuff. But stream I/O, if you can use it, is much better.

1 Like

ok, the ‘stream’ suggestion is the approach that I took.

To use ACCESS=‘STREAM’, I had to throw out the RECL=4 specifier, and also throw out the ACCESS=‘SEQUENTIAL’ specifier, which is mostly the only commentary that I could find on the subject.

Since they could not be both ‘STREAM’ and ‘SEQUENTIAL’, what’s a mother to do? You try this:

  OPEN (UNIT=2, FILE='CLTAPE', STATUS='OLD',
 +     ACCESS='STREAM',
 +     FORM='UNFORMATTED')

And you get this:

$ ./taperd_test
IBUFNO= 1 INDXBG= 3
IRECF= 1 IRECL= -18

And the icing: since IRECL was so large, I thought it might be negative? By calculating in my head, I had actually thought it might be -17. I don’t know what that represents at the moment, but I’m pretty sure I’ve handled it in my code already (a while back).

Thank you so much. I’m on my way again…

As you say, ACCESS=‘SEQUENTIAL’ must be totally a different concept than just reading files sequentially.

You’ll see that I used:

  OPEN (UNIT=2, FILE='CLTAPE', STATUS='OLD',
 +     ACCESS='STREAM',
 +     FORM='UNFORMATTED')

largely with efficacy. So far, I’m gonna see how that works.

thanks…

Well access=‘sequential’ does indeed read a file sequentially, but only works if the records were written by another Fortran program using the same compiler on the same o/s and hardware. Then the byte counts and record terminators will be what it expects.

1 Like

https://en.wikipedia.org/wiki/Two’s_complement

The two’s complement of an N-bit number is defined as its complement with respect to 2^N ; the sum of a number and its two’s complement is 2^N .

0xffffffee+18 = 0x100000000 = 0b100000000000000000000000000000000
Therefore 0xffffffee represents -18 in two’s complement.

1 Like