Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Reading a binary with mixed bytes without FORM='BINARY' 2

Status
Not open for further replies.

GerritGroot

Technical User
Nov 3, 2006
291
ES
Hi all,

I've got a problem reading a binary file in Fortran90.

In essence, it may be solved if someone knows how to add
two 2 byte numbers to make a 4 byte one. This would also prevent me
from having to open and close the file again and again.

My compiler doesn't support FORM='BINARY' so I can't use that

The file (extension *.stl) contains triangular surface elements and
their normals. It has the following structure:


# of bytes description
80 Any text such as the creator's name
4 int equal to the number of facets in file
4 float normal x ! FACET 1
4 float normal y
4 float normal z
4 float vertex1 x
4 float vertex1 y
4 float vertex1 z
4 float vertex2 x
4 float vertex2 y
4 float vertex2 z
4 float vertex3 x
4 float vertex3 y
4 float vertex3 z
2 unused (padding to make 50-bytes) ! HERE'S ACTUALLY THE PROBLEM
4 float normal x ! FACET 2
4 float normal y
4 float normal z
4 float vertex1 x
4 float vertex1 y
4 float vertex1 z
4 float vertex2 x
4 float vertex2 y
4 float vertex2 z
4 float vertex3 x
4 float vertex3 y
4 float vertex3 z
2 unused (padding to make 50-bytes)
4 float normal x ! FACET 3
AND SO ON...


I tried something like this:

Code:
PROGRAM HowToDoThis
IMPLICIT NONE

! An included file defines:
INTEGER, PARAMETER :: I1B=SELECTED_INT_KIND(2)
INTEGER, PARAMETER :: I2B=SELECTED_INT_KIND(4)
INTEGER, PARAMETER :: I4B=SELECTED_INT_KIND(9)
INTEGER, PARAMETER :: I8B=SELECTED_INT_KIND(18)
INTEGER, PARAMETER :: R1B=SELECTED_REAL_KIND(r=2)
INTEGER, PARAMETER :: R2B=SELECTED_REAL_KIND(r=4)
INTEGER, PARAMETER :: R4B=SELECTED_REAL_KIND(r=9)
INTEGER, PARAMETER :: R8B=SELECTED_REAL_KIND(r=18)

! Next, I define:
CHARACTER(LEN=80) :: header
INTEGER(KIND=I4B) :: ntri
INTEGER(KIND=I2B) :: padding
REAL(KIND=R4B), DIMENSION(3) :: n,x1,x2,x3


OPEN(UNIT=1,FILE='input.stl',STATUS='OLD',ACCESS='DIRECT',FORM='UNFORMATTED',RECL=80)
READ(1,REC=1)header
CLOSE(1,STATUS='KEEP')
! So far it works fine, but then...


OPEN(UNIT=1,FILE='input.stl',STATUS='OLD',ACCESS='DIRECT',FORM='UNFORMATTED',RECL=4)
! I start with 21, supposing I have to pass 80 bytes from the header, so 20*4 bytes
READ(1,REC=21)ntri
CLOSE(1,STATUS='KEEP')


OPEN(UNIT=1,FILE='input.stl',STATUS='OLD',ACCESS='DIRECT',FORM='UNFORMATTED',RECL=4)
! In fact, the program already breaks down here, although I don't know why
READ(1,REC=22)( n(i),i=1,3,1)
READ(1,REC=25)(x1(i),i=1,3,1)
READ(1,REC=28)(x2(i),i=1,3,1)
READ(1,REC=31)(x2(i),i=1,3,1)
CLOSE(1,STATUS='KEEP')


! Then I'll read the two byte integer
OPEN(UNIT=1,FILE='input.stl',STATUS='OLD',ACCESS='DIRECT',FORM='UNFORMATTED',RECL=2)
READ(1,REC=67)padding
CLOSE(1,STATUS='KEEP')

! (Here I'll write some stuff to an ascii file so n,x1,x2 and x3 are not lost but converted to another format)

! And...  ...even though the above doesn't work yet, supposing it will, my problem will
! come here, when I read the second triangular element.
OPEN(UNIT=1,FILE='input.stl',STATUS='OLD',ACCESS='DIRECT',FORM='UNFORMATTED',RECL=4)
READ(1,REC=34.5)( n(i),i=1,3,1)
!...ETC
CLOSE(1,STATUS='KEEP')

END PROGRAM HowToDoThis


There must be a better way to do this, without having to open and close the file
again and again and without having to use REC=34.5 which obviously is never going to work.

Thanks in advance,

Gerrit
 
Does your implementation have the transfer function? It allows you to convert from one type to another.
 
The transfer function? I never heard of that, but it sounds hopeful. I use the gfortran compiler.

Gerrit
 
It is not very well publicised. Similar to illegal equivalences which we used to do in earlier versions of Fortran. Read the whole file as either an array of character or integer*2 and then use transfer to work through it.
 
Thanks, I'll try to find something about the TRANSFER function on the net.
 
Hi GerriGroot

Have you tried to open the file with RECL=2 (after you have read the 80 bytes header) and read two INTEGER*2 integers at a time (until you reach the 2 byte padding) and combine them together (into REAL*4) with an EQUIVALENCE sentence or in the program itself? This makes the program longer and a bit more complicated, but solves your problem as far as I can see.

Best wishes
gullipe
 
Hi GerritGroot again

I make a short program to do this using an EQUIVALENCE sentence, see below. If I find out how to combine the two INTEGER*2 ingegers into a REAL*4 variable by using some build-in functions (instead of EQUIVALENCE), I will let you know.

program test

real*4 rrr
integer*2 in(2)
equivalence (rrr,in)

c Create a file to read:

open(1,file='a.a',form='binary')
rrr = 345.67
write (1) rrr
close(1)

c Read from the file:

open(2,file='a.a',access='direct',form='unformatted',recl=2)

read(2,rec=1) in(1)
read(2,rec=2) in(2)
write(*,*) rrr

close(2)
end
 
You can do that with equivalence under F77 but not under F90/95. The compiler won't let it through.
 
Hi, xwb & Gerritgroot

OK, I did not know this about the EQUIVALENCE in F90/F95. But here is another solution without EQUIVALENCE, namely using COMMON statements and reading the file in a subroutine. This works at least in my old Microsoft F77 compiler.

program test

implicit none
real*4 rrr
real*4 sss
common /aaa/sss

c Create a file to read:

open(1,file='a.a',form='binary')
rrr = 345.67
write (1) rrr
close(1)

c Read from the file:

open(2,file='a.a',access='direct',form='unformatted',recl=2)

call reada
write(*,*) sss

close(2)
end


subroutine reada()

integer*2 i1,i2
common /aaa/i1,i2

read(2,rec=1) i1
read(2,rec=2) i2

return
end
 
I used to abuse common blocks and equivalence like that but you can't do that with the modern compilers.
 
Hi, xwb & GerritGroot

Really, so it is not possible to use COMMON either in this way in F90/F95!! I do not know if GerritGrrot has already solved his problem. Maybe the only way for him is to use an old F77 compiler! ... unless the TRANSFER function solves the problem.
 
You can use it in this way in Fortran 90 but I don't know if the gfortran compiler will moan about it. I used to use Lahey when it was free (6 years ago) and that didn't allow this abuse of common blocks.
 
Hi again,

First of all many thanks for your help. I didn't know about the existence of the transfer function and never imagined that a F77 compiler would accept the trick Gullipe proposes, I'm stunned really.

Using fortran 90 I tried with the intrinsic TRANSFER, the problem is that taking

result=TRANSFER(source,mould)

If the mould has more bits than the source, the last bits of the result will be undefined (according to what I found about TRANSFER).

So, HOW CAN WE MERGE THAN TWO 2 BYTE VARIABLES TO ONE 4 BYTE??

My try out code so far looks like:
(for the moment I use integers only)

first a small and general include 'bytes.inc' defining the KINDS...

Code:
INTEGER, PARAMETER :: I1B=SELECTED_INT_KIND(2)
INTEGER, PARAMETER :: I2B=SELECTED_INT_KIND(4)
INTEGER, PARAMETER :: I4B=SELECTED_INT_KIND(9)
INTEGER, PARAMETER :: I8B=SELECTED_INT_KIND(18)
INTEGER, PARAMETER :: R1B=SELECTED_REAL_KIND(r=2)
INTEGER, PARAMETER :: R2B=SELECTED_REAL_KIND(r=4)
INTEGER, PARAMETER :: R4B=SELECTED_REAL_KIND(r=9)
INTEGER, PARAMETER :: R8B=SELECTED_REAL_KIND(r=18)

...And then...

Code:
PROGRAM Test
IMPLICIT NONE

INCLUDE 'bytes.inc'

INTEGER(KIND=I4B) :: fourbytewritten,fourbyteread,dum1,dum2
INTEGER(KIND=I2B) :: lefttwobyte,righttwobyte


! Write a 4 byte integer
fourbytewritten=1000000009
OPEN(UNIT=1,FILE='data.dat',ACCESS='DIRECT',FORM='UNFORMATTED',STATUS='REPLACE',RECL=4)
WRITE(1,REC=1)fourbytewritten
CLOSE(1,STATUS='KEEP')


! Read two 2 byte integers
OPEN(UNIT=1,FILE='data.dat',ACCESS='DIRECT',FORM='UNFORMATTED',STATUS='OLD',RECL=2)
READ(1,REC=1)lefttwobyte
READ(1,REC=2)righttwobyte
CLOSE(1,STATUS='KEEP')

!Try to merge them

! Read my 2 byte integer in my 4 byte dummy
! The last 16 bits will be undefined

dum1=TRANSFER(righttwobyte,dum1)

! Move the first 16 bits of "dum1" to the last 16 bits of
! "fourbyteread"

CALL MVBITS(dum1,16,16,fourbyteread,0)

! Now I try to add the first 16 bits available in "lefttwobyte"
! to the variable "fourbyteread"
fourbyteread=TRANSFER(lefttwobyte,dum2)

! BUT this does NOT work because the last 16 bits will be
! undefined again in "fourbyteread"

READ(*,*)

END PROGRAM Test

So, how can we maintain the last 16 bits bits in the 4 byte variable when we add the second half of 16 bits coming from the second 2 byte one??

Thanks,

Gerrit
 
Try it this way - replace left and right with an array. As long as it is contiguous it will work
Code:
INTEGER(KIND=I4B) :: fourbytewritten,fourbyteread,dum4
INTEGER(KIND=I2B) :: twobyte(2)

...
! Read two 2 byte integers
OPEN(UNIT=1,FILE='data.dat',ACCESS='DIRECT',FORM='UNFORMATTED',STATUS='OLD',RECL=2)
READ(1,REC=1)twobyte
CLOSE(1,STATUS='KEEP')

!                                  
!                                 ,--- Initialize to keep compiler quiet
fourbyteread = transfer(twobyte, dum4)
print *, fourbyteread
...
 
Hi again

I do not have a TRANFER function in F77, but I looked it up in the Intel Fortran Language Reference manual (for F95). It seems to be, that the first argument must be integer*4, but not integer*2. If I am correct, you must first combine, in a correct way, the two integer*2 integers (that you read) into one integer*4, that becomes the fist argument in the TRANSFER function. I could combine the two integers in F77 in this way:

j1 = i1
j2 = i2
iii = (j1.and.#0000FFFF).or.ishft(j2,16)

Here "i1" is the first integer*2 read and "i2" is the second. "j1" and "j2" are defined as integer*4, and we must first transfer the two two-byte integers (that were read) into two four-byte integers, before we combine these two into one four-byte integer "iii", that goes into the TRANSFER function, with 0.0 in the second argument (or so says the manual):

sss = TRANSFER(iii,0.0)

And out comes the real*4 number in the original file (hopefully). Note that "j1.and.#0000FFFF", is used to clear the last two bytes (16 bits) of "j1", before we combine it with "j2" (with "or" to preserve the bits).
 
Hi xwb & gullipe,

Both methods are quite elegant AND WORK, I pasted the code below for completeness. Many thanks!!!

Gullipe, in your method you're doing some logic using #0000FFFF. First of all, I didn't know logic to integers was applied at binary level per bit. Anyway, this hash # is new to me, I suppose it's being used to give hex values directly as you do.

Does there exist a similar symbol in stead of the hash for binary or any other kind of values??

And does there exist an intrinsic by which means the integer is printed or represented in binary form?

Thanks,

Gerrit

Code:
PROGRAM Test
IMPLICIT NONE

INCLUDE 'bytes.inc'

INTEGER(KIND=I4B) :: fourbytewritten,fourbyteread,j1,j2d,j2
INTEGER(KIND=I2B), DIMENSION(2) :: twobyte
INTEGER(KIND=I2B) :: i1,i2


fourbytewritten=1000000009
OPEN(UNIT=1,FILE='data.dat',ACCESS='DIRECT',FORM='UNFORMATTED',STATUS='REPLACE',RECL=4)
WRITE(1,REC=1)fourbytewritten
CLOSE(1,STATUS='KEEP')


OPEN(UNIT=1,FILE='data.dat',ACCESS='DIRECT',FORM='UNFORMATTED',STATUS='OLD',RECL=2)
READ(1,REC=1)twobyte(1)
READ(1,REC=2)twobyte(2)
CLOSE(1,STATUS='KEEP')


fourbyteread=TRANSFER(twobyte,fourbyteread)
WRITE(*,*) fourbyteread


OPEN(UNIT=1,FILE='data.dat',ACCESS='DIRECT',FORM='UNFORMATTED',STATUS='OLD',RECL=2)
READ(1,REC=1)i1
READ(1,REC=2)i2
CLOSE(1,STATUS='KEEP')


j1=TRANSFER(i1,j1)
j2d=TRANSFER(i2,j2d)
j2=ISHFT(j2d,16)
! CALL MVBITS (j2d, 0, 16, j2, 16) Does the same
fourbytewritten=0
fourbytewritten=((j1.AND.#0000FFFF).OR.j2)
WRITE(*,*) fourbyteread


READ(*,*)

END PROGRAM Test
 
See if your compiler accepts this

Z'0000ffff' for hex
O'77' for octal
B'10101' for binary

Look up BOZ literals.
 
Yes, it does, thanks. So, like that i'd be able to give binary values and convert them to integers.

Do you also know how to do it the other way around?

Imagine that I've got

i=2

And want to be printed 0000000000000010 for example?

Gerrit
 
Hi GerritGroot

1) You asked about this hash #. It is not only for hex values but also for other bases. The following integers (most of which are not base 10) are all assigned a value equal to 3994575:

I = 2#1111001111001111001111
m = 7#45644664
J = +8#17171717
K = #3CF3CF !(default for 16#3CF3CF)
n = +17#2DE110
L = 3994575
index = 36#2DM8F

This is an extension to my old Microsoft Fortran (F77) compiler (version 5.1) and according to the Intel F95 manual, it is also an extension to the F95 standard.

2) Regarding writing an integer as a bit string:

According to the Intel F95 manual (that can be found on the internet), you can do this:

i = 2
write(*,'(B16)') i

This seems to be a standard F95 (my MS F77 compiler does not understand this). The following explanation of the "B editing" is given in the Inter F95 manual:

B Editing:
The B data edit descriptor transfers binary (base 2)values. It takes the following form:
Bw[.m]
The value of m (the minimum number of digits in the constant) must not exceed the value of w (the field width). The m has no effect on input, only output.
The specified I/O list item can be of type integer, real, or logical.

Rules for Input Processing:
On input, the B data edit descriptor transfers w characters from an external field and assigns their binary value to the corresponding I/O list item. The external field must contain only binary digits (0 or 1) or blanks. If the value exceeds the range of the corresponding input list item, an error occurs.

Rules for Output Processing:
On output, the B data edit descriptor transfers the binary value of the corresponding I/O list item, right-justified, to an external field that is w characters long. The field consists of zero or more blanks, followed by an unsigned integer constant (consisting of binary digits) with no leading zeros. A negative value is transferred in internal form.

Format Input Value
B4 1001 9
B1 1 1
B2 0 0

If m is specified, the unsigned integer constant must have at least m digits. If necessary, it is padded with leading zeros. If m is zero, and the output list item has the value zero, the external field is filled with blanks. The following shows output using the B edit descriptor:

Format Value Output
B4 9 1001
B2 0 0
 
This hash is a marvellous solution!

It's good news if it's included in the 95 standard.

Unfortunately, compiling f90, gfortran doesn't swallow that. B'10101' or so does work, however, is not as general as the hash option where you can give 17#5 or strange things as you give in your example.

Thanks,

Gerrit
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top