home *** CD-ROM | disk | FTP | other *** search
- (* :Title: Binary File Operations *)
-
- (* :Context: Utilities`BinaryFiles` *)
-
- (* :Author: John M. Novak *)
-
- (* :Summary: Allows opening, reading, and writing of files
- containing binary data. *)
-
- (* :Package Version: 1.0 *)
-
- (* :Mathematica Version: 2.0 *)
-
- (* :History:
- V. 1.0, Sept. 1991, by John M. Novak
- *)
-
- (* :Keywords:
- files, binary, read, write, open
- *)
-
- (* :Sources:
- IEEE, "IEEE Recommended Practice for Code and Format
- Conventions", IEEE Std. 728-1982, pp.50-51
- (Floating Point Representations)
- *)
-
- (* :Limitation:
- Integers are read MSB first - this may cause problems on
- systems that store integers LSB first.
- *)
-
- (* :Discussion:
- Allows opening a file for binary I/O (really just the
- standard Open*, but with certain options set for writes so
- no bad bytes get written.
-
- Allows writing a byte or list of bytes (or nested lists
- of bytes) to a file; a byte is an Integer, between 0 and
- 255. The write is accomplished by turning the list of
- bytes into a string, and using WriteString to dump it to
- a file. Note that this requires the capabilities in 2.0
- of allowing any character (ASCII 0 - 255) to be in a
- string... The writing function (WriteBinary) will
- automatically convert input to the form described using
- converstion utility ToBytes (included).
-
- ToBytes generates a (nested) list of the binary representations
- of the leaves of an expression handed it. The raw types
- can be Strings, Reals, or Integers. They will be converted
- to one of the types named below. Do not use the Signed
- types; negative numbers will automatically be generated in
- the signed type, positive numbers are the same in both forms.
- Type casting can also be performed (converting a Real to an
- Int32 for output, for instance.) The binary representation
- is a list of bytes, as described above.
-
- Allows reading binary data from a number of standard data
- types. These types are:
- Int8, SignedInt8, Int16, SignedInt16, Int32, SignedInt32,
- Single, Double, and CString. Byte is also allowed. The
- IntN correspond to N-bit integers. Signed ints are two's-
- complement. Single and Double are single and double precision
- ieee floating point types, respectively. CString
- is a null-terminated string of arbitrary length. The Read
- functions and ToBytes have an option ByteOrder, which can be
- set to LeastSignificantByteFirst or MostSignificantByteFirst.
- The form of the function is like Read - a structure can be
- given with types, which are replaced by values read in
- (replaced in the order of evaluation, not necessarily a
- left-to-right order.) Note one modification to this -
- the structure is held, not evaluated as in Read. This
- allows, for instance, the structure Double + Double to be
- read, and two reads will occur; also, numbers can be mixed
- in (so you might say, ReadBinary[file,LongInt * 256], or
- somesuch.) This allows greater flexibility in reads.
- EndOfFile is returned much as in Read.
- Also, ReadListBinary is available, working much as ReadList.
- Note that only option the binary read operations allow is
- BigEndian.
-
- Note that CloseBinary was not implemented; Close works just
- fine.
- *)
-
- BeginPackage["Utilities`BinaryFiles`"]
-
- OpenReadBinary::usage =
- "OpenReadBinary[\"filename\"] opens the named file for
- reading; it returns an InputStream object with which
- ReadBinary can be used.";
-
- OpenAppendBinary::usage =
- "OpenAppendBinary[\"filename\"] opens the named file for
- appending; it returns an OutputStream object with which
- WriteBinary can be used.";
-
- OpenWriteBinary::usage =
- "OpenWriteBinary[\"filename\"] opens the named file for
- writing; it returns an OutputStream object with which
- WriteBinary can be used.";
-
- WriteBinary::usage =
- "WriteBinary[stream,data] converts the data to binary
- format via the function specified in the ByteConversion
- option. The data is then written in binary form to the
- stream. WriteBinary[\"filename\",data]
- opens the named file before writing to it; the file is
- left open after the write.";
-
- ByteConversion::usage =
- "ByteConversion is an option for WriteBinary; specifies
- function to convert data to binary form (list of integers
- between 0 and 255). The default is ToBytes.
- If your data is in the form of integers between 0 and 255,
- you may wish to use the function (# &) instead.";
-
- ToBytes::usage =
- "ToBytes[expr] maps to the leaves of expr and converts
- them to list of integers representing their binary form.
- This works best on lists and arrays of numerical data.
- Options are available controlling what binary type each
- object is to be converted to. Objects handled
- are Real, Integer, and String. Options controlling
- conversion of these types are RealConvert, IntegerConvert,
- and StringConvert. ToBytes[expr,type] forces conversion of
- the leaves of expr to the named type, overriding the above
- options. Note that in the binary form of integers, negative
- numbers are automatically converted to the signed representation
- of the named type.";
-
- RealConvert::usage =
- "RealConvert is an option for ToBytes. It gives the
- type of byte form to convert Reals to.
- The default is Double.";
-
- IntegerConvert::usage =
- "IntegerConvert is an option for ToBytes. It gives the
- type of byte form to convert Integers to.
- The default is Int16.";
-
- StringConvert::usage =
- "StringConvert is an option for ToBytes. It gives the
- type of byte form to convert Strings to.
- The default is CString.";
-
- ReadBinary::usage =
- "ReadBinary[stream, type] reads the binary type from the stream.
- ReadBinary[stream,{type1,type2,...,typen}] reads a list of
- binary types. More complex structures can be used as well.
- ReadBinary[\"filename\",type] opens the file for reading;
- the file is left open after the read.";
-
- ReadListBinary::usage =
- "ReadListBinary[\"filename\",type] reads a list of the binary
- types from the file, until the end of the file is reached.
- ReadListBinary[\"filename\",type,{n}] reads n elements of
- the named type. Type can be a list of binary types, or more
- complex structures (as in ReadBinary.) ReadListBinary[stream,
- type] reads from the current point in an open stream to the
- end of the stream.";
-
- ByteOrder::usage =
- "ByteOrder is an option for ReadBinary, ReadListBinary, and
- ToBytes; it specifies whether integers should be dealt with in
- most significant byte first form or other form. Default is
- MostSignificantByteFirst. You may wish to change this on machines
- with an Intel processor, or other least signficant byte first
- architecture to LeastSignificantByteFirst.";
-
- MostSignificantByteFirst::usage =
- "Value for ByteOrder option.";
-
- LeastSignificantByteFirst::usage =
- "Value for ByteOrder option.";
-
- SignedByte::usage =
- "A binary type for use with ReadBinary. Takes integer value
- between -128 to 127, inclusive.";
-
- Int8::usage =
- "Int8 is binary type for use with ReadBinary. Same as Byte -
- takes value between 0 to 255, inclusive.";
-
- SignedInt8::usage =
- "SignedInt8 is a binary type for use with ReadBinary.
- Same as SignedByte.";
-
- Int16::usage =
- "Int16 is a binary type for use with ReadBinary. Unsigned 16 bit
- integer.";
-
- SignedInt16::usage =
- "SignedInt16 is a binary type for use with ReadBinary. 16 bit signed
- integer.";
-
- Int32::usage =
- "Int32 is a binary type for use with ReadBinary. Unsigned 32 bit
- integer.";
-
- SignedInt32::usage =
- "SignedInt32 is a binary type for use with ReadBinary. 32 bit signed
- integer.";
-
- Single::usage =
- "A binary type for use with ReadBinary. Single precision
- floating point in IEEE format: 4 bytes long.";
-
- Double::usage =
- "A binary type for use with ReadBinary. Double precision
- floating point in IEEE format: 8 bytes long.";
-
- CString::usage =
- "A binary type for use with ReadBinary. Null terminated
- string of characters, ASCII values between 1 and 255
- inclusive.";
-
- Begin["`Private`"]
-
- OpenReadBinary[filename_String] := OpenRead[filename]
-
- OpenAppendBinary[filename_String] :=
- OpenAppend[filename,PageWidth->Infinity,
- FormatType->OutputForm,PageHeight->Infinity,
- TotalHeight->Infinity,TotalWidth->Infinity]
-
- OpenWriteBinary[filename_String] :=
- OpenWrite[filename,PageWidth->Infinity,
- FormatType->OutputForm,PageHeight->Infinity,
- TotalHeight->Infinity,TotalWidth->Infinity]
-
- (* Rules for WriteBinary *)
-
- Options[WriteBinary] =
- {ByteConversion -> ToBytes};
-
- (* This rule will open a file for a binary write if the
- file is not already open. *)
-
- WriteBinary[filename_String,rest___] :=
- WriteBinary[OpenWriteBinary[filename],rest]
-
- WriteBinary[stream_OutputStream,towrite_,opts___] :=
- Module[{func},
- {func} = {ByteConversion}/.{opts}/.Options[WriteBinary];
- writebinary[stream,func[towrite]]
- ]
-
- (* for speed, these simpler patterns can be written directly,
- instead of using the rule that follows this rule. See
- that rule for more info... *)
-
- writebinary[stream_,bytes:(_Integer | {__Integer})] :=
- WriteString[stream,FromCharacterCode[bytes]]
-
- (* this writes any structure of bytes, after flattening it out.
- this allows a conversion to be run on the elements before
- writing. Note the implicit assumption that the integers
- passed in are between 0 and 255, without explicitly
- checking them. I made the (not necessarily well founded)
- assumption that some might want to write the result of
- FromCharacterCode being applied to other integers...
- Note that OpenWriteBinary should have been used before
- WriteBinary, to make certain the correct options to Open
- have been used. *)
-
- writebinary[stream_,bytes___] :=
- With[{flat = Flatten[{bytes}]},
- WriteString[stream,FromCharacterCode[flat]]/;
- MatchQ[flat,{___Integer}]
- ]
-
- (* The following is the ToBytes conversion utility, with
- associated functions. ToBytes is used with WriteBinary,
- above. *)
-
- ToBytes::noconv =
- "Unable to convert `1` to byte form.";
-
- ToBytes::cast =
- "Warning: converting object of type `1` to type `2`.";
-
- Options[ToBytes] =
- {ByteOrder -> MostSignificantByteFirst,
- IntegerConvert -> Int16,
- RealConvert -> Double,
- StringConvert -> CString};
-
- ToBytes[expr_,type_Symbol:None,opts___] :=
- Module[{itype, rtype, stype, endian},
- {itype, rtype, stype, endian} = {IntegerConvert,
- RealConvert, StringConvert,ByteOrder}/.
- {opts}/.Options[ToBytes];
- endian = If[endian === LeastSignificantByteFirst, False, True];
- If[type =!= None,
- itype = rtype = stype = type
- ];
- If[!AtomQ[expr],
- Map[tobytes[#, itype, rtype, stype, endian]&,
- expr,
- {-1}
- ],
- tobytes[expr, itype, rtype, stype, endian]
- ]
- ]
-
- (* coversions *)
-
- tobytes[num_Real,_,Single,_,_] :=
- Module[{frac, exp},
- {frac, exp} = RealDigits[num,2];
- Map[bitstointeger, Partition[Join[
- If[Negative[num],
- {1},
- {0}
- ],
- exp = IntegerDigits[exp + 126,2];
- If[Length[exp] < 8,
- Join[zeropad[8 - Length[exp]],exp],
- exp
- ],
- frac = Drop[frac,1];
- If[Length[frac] < 23,
- Join[frac, zeropad[23 - Length[frac]]],
- Take[frac,23]
- ]],8]
- ]/; -127 <= exp <= 128
- ]
-
- tobytes[num_Real,_,Double,_,_] :=
- Module[{frac, exp},
- {frac, exp} = RealDigits[num,2];
- Map[bitstointeger, Partition[Join[
- If[Negative[num],
- {1},
- {0}
- ],
- exp = IntegerDigits[exp + 1022,2];
- If[Length[exp] < 11,
- Join[zeropad[11 - Length[exp]],exp],
- exp
- ],
- frac = Drop[frac,1];
- If[Length[frac] < 52,
- Join[frac, zeropad[52 - Length[frac]]],
- Take[frac,52]
- ]],8]
- ]/; -1023 <= exp <= 1024
- ]
-
- tobytes[num_Real,_,type:(Int | Int16 | Int32),_,end_] :=
- (Message[ToBytes::cast, Real, type];
- tobytes[Round[num],type,Null,Null,end])
-
- tobytes[num_Real,_,type:(CString),_,_] :=
- (Message[ToBytes::cast, Real, type];
- tobytes[ToString[num],Null,Null,type,Null])
-
- tobytes[num_Integer,Byte,_,_,_] :=
- Mod[num,256]
-
- tobytes[num_Integer,Int16,_,_,True] :=
- {Quotient[#,256], Mod[#,256]}&[Mod[num, 65536]]
-
- tobytes[num_Integer,Int32,_,_,True] :=
- {Quotient[#,16777216],
- Quotient[Mod[#,16777216],65536],
- Mod[Quotient[#,65536],256],
- Mod[#,256]}&[Mod[num, 4294967296]]
-
- tobytes[num_Integer,type:(Int16 | Int32),_,_,False] :=
- Reverse[tobytes[num,type,Null,Null,True]]
-
- tobytes[num_Integer,type:(Single | Double),_,_,_] :=
- (Message[ToBytes::cast, Integer, type];
- tobytes[N[num],Null,type,Null,Null])
-
- tobytes[num_Integer,type:(CString),_,_,_] :=
- (Message[ToBytes::cast, Integer, type];
- tobytes[ToString[num],Null,Null,type,Null])
-
- tobytes[str_String,_,_,CString,_] :=
- ToCharacterCode[str<>"\000"]
-
- tobytes[str_String,_,_,type_,end_] :=
- (Message[ToBytes::cast, String, type];
- tobytes[ToExpression[str], type, type, Null, end])
-
- tobytes[anything_, ___] :=
- (Message[ToBytes::noconv,anything];
- anything)
-
- (* ToBytes utility functions; bitstointeger takes a list of
- ones and zeros, assumes they are bits, and converts it
- to the integer represented. zeropad takes an integer n,
- and creates a list of zeros of length n. *)
-
- bitstointeger[bits_] :=
- ToExpression["2^^" <>
- StringJoin[Map[ToString,bits]]
- ]
-
- zeropad[n_] := Table[0,{n}]
-
- (* Following are the ReadBinary functions. *)
-
- Attributes[ReadBinary] := {HoldRest}
-
- ReadBinary::nonnormal =
- "Warning: Binary value `1` was not in the normalized
- floating point format; value may not be correct.";
-
- ReadBinary::incstring =
- "Warning: encountered end of file before end of string;
- string may be incomplete."
-
- Options[ReadBinary] =
- {ByteOrder -> MostSignificantByteFirst};
-
- ReadBinary[filename_String,args__] :=
- Module[{stream},
- stream = OpenRead[filename];
- ReadBinary[stream,args];
- ]
-
- ReadBinary[stream_InputStream,pat_,
- opts:((_Rule | _RuleDelayed)...)] :=
- Module[{endian},
- {endian} = {ByteOrder}/.{opts}/.Options[ReadBinary];
- endian = If[endian === LeastSignificantByteFirst, False, True];
- If[Read[stream,Byte] =!= EndOfFile,
- SetStreamPosition[stream,StreamPosition[stream] - 1];
- ReleaseHold[Hold[pat]/.
- (n:(Byte | Int8 | Int16 | Int32 | Single |
- Double | SignedByte | SignedInt8 |
- SignedInt16 | SignedInt32 | CString) :>
- readbinary[stream,n,TrueQ[endian]])
- ],
- EndOfFile]
- ]
-
- readbinary[stream_,pat_,endian_] :=
- With[{out = rb[stream,pat,endian]},
- If[FreeQ[out,EndOfFile],
- out,
- EndOfFile]
- ]
-
- (* :Implementation Note:
- For many (most) of these types of input, I used a hard-coded
- form, rather than more elegant or concise code, for reasons
- of efficiency. (e.g., Read[stream,{Byte,Byte,...Byte}] rather
- than Read[stream,Table[Byte,{n}]], or explicitly scaling
- each byte of the input, rather than doing them all together
- with a Fold construct or such-like.)
- *)
-
- rb[stream_InputStream,Byte,_] :=
- Read[stream,Byte]
-
- rb[stream_InputStream,SignedByte,_] :=
- (# - Quotient[#,128] 256)&[Read[stream,Byte]]
-
- rb[stream_InputStream,Int8,_] :=
- Read[stream,Byte]
-
- rb[stream_InputStream,SignedInt8,_] :=
- (# - Quotient[#,128] 256)&[Read[stream,Byte]]
-
- rb[stream_InputStream,Int16,True] :=
- (256 #1 + #2)& @@ Read[stream,{Byte,Byte}]
-
- rb[stream_InputStream,Int16,False] :=
- (256 #2 + #1)& @@ Read[stream,{Byte,Byte}]
-
- rb[stream_InputStream,SignedInt16,True] :=
- (256 #1 + #2 - Quotient[#1,128] 65536)& @@
- Read[stream,{Byte,Byte}]
-
- rb[stream_InputStream,SignedInt16,False] :=
- (256 #2 + #1 - Quotient[#2,128] 65536)& @@
- Read[stream,{Byte,Byte}]
-
- rb[stream_InputStream,Int32,True] :=
- (256^3 #1 + 256^2 #2 + 256 #3 + #4)& @@
- Read[stream,{Byte,Byte,Byte,Byte}]
-
- rb[stream_InputStream,Int32,False] :=
- (256^3 #4 + 256^2 #3 + 256 #2 + #1)& @@
- Read[stream,{Byte,Byte,Byte,Byte}]
-
- rb[stream_InputStream,SignedInt32,True] :=
- (256^3 #1 + 256^2 #2 + 256 #3 + #4 - Quotient[#1,128] 256^4)& @@
- Read[stream,{Byte,Byte,Byte,Byte}]
-
- rb[stream_InputStream,SignedInt32,False] :=
- (256^3 #4 + 256^2 #3 + 256 #2 + #1 - Quotient[#4,128] 256^4)& @@
- Read[stream,{Byte,Byte,Byte,Byte}]
-
- rb[stream_InputStream,Single,_] :=
- floatvalue @@ {Quotient[#1,128],
- (Mod[#1,128])*2 + Quotient[#2,128],
- ((Mod[#2,128])*256^2 + #3*256 + #4)/(2^23) + 1}& @@
- Read[stream,{Byte,Byte,Byte,Byte}]
-
- floatvalue[s_,0,1] := 0
-
- floatvalue[s_,0,f_] :=
- (Message[ReadBinary::nonnormal,f - 1];f - 1)
-
- floatvalue[s_,255,1] := (-1)^s Infinity
-
- floatvalue[s_,255,_] := Indeterminate
-
- floatvalue[s_,e_,f_] := N[(-1)^s * 2^(e - 127) * f]
-
- rb[stream_InputStream,Double,_] :=
- doublevalue @@ {Quotient[#1,128],
- (Mod[#1,128])*2^4 + Quotient[#2,16],
- ((Mod[#2,16])*256^6 + #3*256^5 + #4*256^4 +
- #5*256^3 + #6*256^2 + #7*256 + #8)/(2^52) +
- 1}& @@
- Read[stream,{Byte,Byte,Byte,Byte,Byte,Byte,Byte,Byte}]
-
- doublevalue[s_,0,1] := 0
-
- doublevalue[s_,0,f_] :=
- (Message[ReadBinary::nonnormal,f - 1];f - 1)
-
- doublevalue[s_,2047,1] := (-1)^s Infinity
-
- doublevalue[s_,2047,_] := Indeterminate
-
- doublevalue[s_,e_,f_] := N[(-1)^s * 2^(e - 1023) * f]
-
- rb[stream_InputStream,CString,_] :=
- Module[{tmp,out = ""},
- tmp = Read[stream,Byte];
- If[tmp === EndOfFile,Return[EndOfFile]];
- While[tmp =!= 0,
- If[tmp === EndOfFile,
- Message[ReadBinary::incstring];Break[]
- ];
- out <> FromCharacterCode[tmp];
- tmp = Read[stream,Byte]
- ];
- out
- ]
-
- Attributes[ReadListBinary] := {HoldRest}
-
- ReadListBinary[filename_String,args__] :=
- Module[{stream,out},
- stream = OpenRead[filename];
- If[Head[stream] =!= InputStream,
- Abort[]];
- out = ReadListBinary[stream,args];
- Close[stream];
- out
- ]
-
- ReadListBinary[stream_InputStream,pat_,
- n:(_Integer | Infinity):Infinity,
- opts:((_Rule | _RuleDelayed)...)] :=
- Module[{cnt = 0,tmp,out = {}},
- While[(tmp = ReadBinary[stream,pat,opts]) =!= EndOfFile &&
- cnt < n,
- AppendTo[out,tmp];
- cnt ++
- ];
- out
- ]/;(!FreeQ[pat,Byte | Int8 | Int16 | Int32 | Single |
- Double | SignedByte | SignedInt8 |
- SignedInt16 | SignedInt32 | CString,
- Infinity] ||
- MatchQ[pat, Byte | Int8 | Int16 | Int32 | Single |
- Double | SignedByte | SignedInt8 |
- SignedInt16 | SignedInt32 | CString])
-
- End[]
-
- EndPackage[]
-