home *** CD-ROM | disk | FTP | other *** search
/ Liren Large Software Subsidy 9 / 09.iso / e / e032 / 3.ddi / FILES / UTILITIE.PAK / BINARYFI.M next >
Encoding:
Text File  |  1992-07-29  |  17.8 KB  |  583 lines

  1. (* :Title: Binary File Operations *)
  2.  
  3. (* :Context: Utilities`BinaryFiles` *)
  4.  
  5. (* :Author: John M. Novak *)
  6.  
  7. (* :Summary: Allows opening, reading, and writing of files
  8.     containing binary data.  *)
  9.  
  10. (* :Package Version: 1.0 *)
  11.  
  12. (* :Mathematica Version: 2.0 *)
  13.  
  14. (* :History:
  15.     V. 1.0, Sept. 1991, by John M. Novak
  16. *)
  17.  
  18. (* :Keywords:
  19.     files, binary, read, write, open
  20. *)
  21.  
  22. (* :Sources:
  23.     IEEE,  "IEEE Recommended Practice for Code and Format
  24.         Conventions", IEEE Std. 728-1982, pp.50-51
  25.         (Floating Point Representations)
  26. *)
  27.  
  28. (* :Limitation:
  29.     Integers are read MSB first - this may cause problems on
  30.     systems that store integers LSB first.
  31. *)
  32.  
  33. (* :Discussion:
  34.     Allows opening a file for binary I/O (really just the
  35.     standard Open*, but with certain options set for writes so
  36.     no bad bytes get written.
  37.     
  38.     Allows writing a byte or list of bytes (or nested lists
  39.     of bytes) to a file;  a byte is an Integer, between 0 and
  40.     255.  The write is accomplished by turning the list of
  41.     bytes into a string, and using WriteString to dump it to
  42.     a file.  Note that this requires the capabilities in 2.0
  43.     of allowing any character (ASCII 0 - 255) to be in a
  44.     string...  The writing function (WriteBinary) will
  45.     automatically convert input to the form described using
  46.     converstion utility ToBytes (included).  
  47.     
  48.     ToBytes generates a (nested) list of the binary representations
  49.     of the leaves of an expression handed it.  The raw types
  50.     can be Strings, Reals, or Integers.  They will be converted
  51.     to one of the types named below.  Do not use the Signed
  52.     types;  negative numbers will automatically be generated in
  53.     the signed type, positive numbers are the same in both forms.
  54.     Type casting can also be performed (converting a Real to an
  55.     Int32 for output, for instance.)  The binary representation
  56.     is a list of bytes, as described above.
  57.     
  58.     Allows reading binary data from a number of standard data
  59.     types.  These types are:
  60.     Int8, SignedInt8, Int16, SignedInt16, Int32, SignedInt32,
  61.     Single, Double, and CString. Byte is also allowed.  The
  62.     IntN correspond to N-bit integers.  Signed ints are two's-
  63.     complement.  Single and Double are single and double precision
  64.     ieee floating point types, respectively.  CString
  65.     is a null-terminated string of arbitrary length.  The Read
  66.     functions and ToBytes have an option ByteOrder, which can be
  67.     set to LeastSignificantByteFirst or MostSignificantByteFirst.
  68.     The form of the function is like Read - a structure can be
  69.     given with types, which are replaced by values read in
  70.     (replaced in the order of evaluation, not necessarily a
  71.     left-to-right order.)  Note one modification to this -
  72.     the structure is held, not evaluated as in Read.  This
  73.     allows, for instance, the structure Double + Double to be
  74.     read, and two reads will occur; also, numbers can be mixed
  75.     in (so you might say, ReadBinary[file,LongInt * 256], or
  76.     somesuch.) This allows greater flexibility in reads.
  77.     EndOfFile is returned much as in Read.
  78.     Also, ReadListBinary is available, working much as ReadList.
  79.     Note that only option the binary read operations allow is
  80.     BigEndian.
  81.     
  82.     Note that CloseBinary was not implemented; Close works just
  83.     fine.
  84. *)
  85.  
  86. BeginPackage["Utilities`BinaryFiles`"]
  87.  
  88. OpenReadBinary::usage =
  89. "OpenReadBinary[\"filename\"] opens the named file for
  90. reading; it returns an InputStream object with which
  91. ReadBinary can be used.";
  92.  
  93. OpenAppendBinary::usage =
  94. "OpenAppendBinary[\"filename\"] opens the named file for
  95. appending; it returns an OutputStream object with which
  96. WriteBinary can be used.";
  97.  
  98. OpenWriteBinary::usage =
  99. "OpenWriteBinary[\"filename\"] opens the named file for
  100. writing; it returns an OutputStream object with which
  101. WriteBinary can be used.";
  102.  
  103. WriteBinary::usage =
  104. "WriteBinary[stream,data] converts the data to binary
  105. format via the function specified in the ByteConversion
  106. option.  The data is then written in binary form to the
  107. stream. WriteBinary[\"filename\",data]
  108. opens the named file before writing to it;  the file is
  109. left open after the write.";
  110.  
  111. ByteConversion::usage =
  112. "ByteConversion is an option for WriteBinary;  specifies
  113. function to convert data to binary form (list of integers
  114. between 0 and 255). The default is ToBytes.
  115. If your data is in the form of integers between 0 and 255,
  116. you may wish to use the function (# &) instead.";
  117.  
  118. ToBytes::usage =
  119. "ToBytes[expr] maps to the leaves of expr and converts
  120. them to list of integers representing their binary form.
  121. This works best on lists and arrays of numerical data.
  122. Options are available controlling what binary type each
  123. object is to be converted to.  Objects handled
  124. are Real, Integer, and String.  Options controlling
  125. conversion of these types are RealConvert, IntegerConvert,
  126. and StringConvert.  ToBytes[expr,type] forces conversion of
  127. the leaves of expr to the named type, overriding the above
  128. options.  Note that in the binary form of integers, negative
  129. numbers are automatically converted to the signed representation
  130. of the named type.";
  131.  
  132. RealConvert::usage =
  133. "RealConvert is an option for ToBytes.  It gives the
  134. type of byte form to convert Reals to.
  135. The default is Double.";
  136.  
  137. IntegerConvert::usage =
  138. "IntegerConvert is an option for ToBytes.  It gives the
  139. type of byte form to convert Integers to.
  140. The default is Int16.";
  141.  
  142. StringConvert::usage =
  143. "StringConvert is an option for ToBytes.  It gives the
  144. type of byte form to convert Strings to.
  145. The default is CString.";
  146.  
  147. ReadBinary::usage =
  148. "ReadBinary[stream, type] reads the binary type from the stream.
  149. ReadBinary[stream,{type1,type2,...,typen}] reads a list of
  150. binary types.  More complex structures can be used as well.
  151. ReadBinary[\"filename\",type] opens the file for reading;
  152. the file is left open after the read.";
  153.  
  154. ReadListBinary::usage =
  155. "ReadListBinary[\"filename\",type] reads a list of the binary
  156. types from the file, until the end of the file is reached.
  157. ReadListBinary[\"filename\",type,{n}] reads n elements of
  158. the named type. Type can be a list of binary types, or more
  159. complex structures (as in ReadBinary.)  ReadListBinary[stream,
  160. type] reads from the current point in an open stream to the
  161. end of the stream.";
  162.  
  163. ByteOrder::usage =
  164. "ByteOrder is an option for ReadBinary, ReadListBinary, and
  165. ToBytes; it specifies whether integers should be dealt with in
  166. most significant byte first form or other form.  Default is 
  167. MostSignificantByteFirst. You may wish to change this on machines
  168. with an Intel processor, or other least signficant byte first
  169. architecture to LeastSignificantByteFirst.";
  170.  
  171. MostSignificantByteFirst::usage =
  172. "Value for ByteOrder option.";
  173.  
  174. LeastSignificantByteFirst::usage =
  175. "Value for ByteOrder option.";
  176.  
  177. SignedByte::usage =
  178. "A binary type for use with ReadBinary.  Takes integer value
  179. between -128 to 127, inclusive.";
  180.  
  181. Int8::usage =
  182. "Int8 is binary type for use with ReadBinary.  Same as Byte -
  183. takes value between 0 to 255, inclusive.";
  184.  
  185. SignedInt8::usage =
  186. "SignedInt8 is a binary type for use with ReadBinary.
  187.  Same as SignedByte.";
  188.  
  189. Int16::usage =
  190. "Int16 is a binary type for use with ReadBinary.  Unsigned 16 bit
  191. integer.";
  192.  
  193. SignedInt16::usage =
  194. "SignedInt16 is a binary type for use with ReadBinary.  16 bit signed
  195. integer.";
  196.  
  197. Int32::usage =
  198. "Int32 is a binary type for use with ReadBinary.  Unsigned 32 bit
  199. integer.";
  200.  
  201. SignedInt32::usage =
  202. "SignedInt32 is a binary type for use with ReadBinary.  32 bit signed
  203. integer.";
  204.  
  205. Single::usage =
  206. "A binary type for use with ReadBinary.  Single precision
  207. floating point in IEEE format: 4 bytes long.";
  208.  
  209. Double::usage =
  210. "A binary type for use with ReadBinary.  Double precision
  211. floating point in IEEE format: 8 bytes long.";
  212.  
  213. CString::usage =
  214. "A binary type for use with ReadBinary.  Null terminated
  215. string of characters, ASCII values between 1 and 255
  216. inclusive.";
  217.  
  218. Begin["`Private`"]
  219.  
  220. OpenReadBinary[filename_String] := OpenRead[filename]
  221.  
  222. OpenAppendBinary[filename_String] :=
  223.     OpenAppend[filename,PageWidth->Infinity,
  224.             FormatType->OutputForm,PageHeight->Infinity,
  225.             TotalHeight->Infinity,TotalWidth->Infinity]
  226.  
  227. OpenWriteBinary[filename_String] :=
  228.     OpenWrite[filename,PageWidth->Infinity,
  229.             FormatType->OutputForm,PageHeight->Infinity,
  230.             TotalHeight->Infinity,TotalWidth->Infinity]
  231.  
  232. (* Rules for WriteBinary *)
  233.  
  234. Options[WriteBinary] =
  235.     {ByteConversion -> ToBytes};
  236.  
  237. (* This rule will open a file for a binary write if the
  238.     file is not already open. *)
  239.  
  240. WriteBinary[filename_String,rest___] :=
  241.         WriteBinary[OpenWriteBinary[filename],rest]
  242.  
  243. WriteBinary[stream_OutputStream,towrite_,opts___] :=
  244.     Module[{func},
  245.         {func} = {ByteConversion}/.{opts}/.Options[WriteBinary];
  246.         writebinary[stream,func[towrite]]
  247.     ]
  248.  
  249. (* for speed, these simpler patterns can be written directly,
  250.     instead of using the rule that follows this rule. See
  251.     that rule for more info... *)
  252.  
  253. writebinary[stream_,bytes:(_Integer | {__Integer})] :=
  254.     WriteString[stream,FromCharacterCode[bytes]]
  255.  
  256. (* this writes any structure of bytes, after flattening it out.
  257.     this allows a conversion to be run on the elements before
  258.     writing. Note the implicit assumption that the integers
  259.     passed in are between 0 and 255, without explicitly
  260.     checking them.  I made the (not necessarily well founded)
  261.     assumption that some might want to write the result of
  262.     FromCharacterCode being applied to other integers... 
  263.     Note that OpenWriteBinary should have been used before
  264.     WriteBinary, to make certain the correct options to Open
  265.     have been used. *)
  266.  
  267. writebinary[stream_,bytes___] :=
  268.     With[{flat = Flatten[{bytes}]},
  269.         WriteString[stream,FromCharacterCode[flat]]/;
  270.             MatchQ[flat,{___Integer}]
  271.     ]
  272.  
  273. (* The following is the ToBytes conversion utility, with
  274.     associated functions.  ToBytes is used with WriteBinary,
  275.     above. *)
  276.  
  277. ToBytes::noconv =
  278. "Unable to convert `1` to byte form.";
  279.  
  280. ToBytes::cast =
  281. "Warning: converting object of type `1` to type `2`.";
  282.  
  283. Options[ToBytes] =
  284.     {ByteOrder -> MostSignificantByteFirst,
  285.     IntegerConvert -> Int16,
  286.     RealConvert -> Double,
  287.     StringConvert -> CString};
  288.  
  289. ToBytes[expr_,type_Symbol:None,opts___] :=
  290.     Module[{itype, rtype, stype, endian},
  291.         {itype, rtype, stype, endian} = {IntegerConvert,
  292.                 RealConvert, StringConvert,ByteOrder}/.
  293.             {opts}/.Options[ToBytes];
  294.         endian = If[endian === LeastSignificantByteFirst, False, True];
  295.         If[type =!= None,
  296.             itype = rtype = stype = type
  297.         ];
  298.         If[!AtomQ[expr],
  299.             Map[tobytes[#, itype, rtype, stype, endian]&,
  300.                 expr,
  301.                 {-1}
  302.             ],
  303.             tobytes[expr, itype, rtype, stype, endian]
  304.         ]
  305.     ]
  306.  
  307. (* coversions *)
  308.  
  309. tobytes[num_Real,_,Single,_,_] :=
  310.     Module[{frac, exp},
  311.         {frac, exp} = RealDigits[num,2];
  312.         Map[bitstointeger, Partition[Join[
  313.                 If[Negative[num],
  314.                     {1},
  315.                     {0}
  316.                 ],
  317.                 exp = IntegerDigits[exp + 126,2];
  318.                 If[Length[exp] < 8,
  319.                     Join[zeropad[8 - Length[exp]],exp],
  320.                     exp
  321.                 ],
  322.                 frac = Drop[frac,1];
  323.                 If[Length[frac] < 23,
  324.                     Join[frac, zeropad[23 - Length[frac]]],
  325.                     Take[frac,23]
  326.                 ]],8]
  327.         ]/; -127 <= exp <= 128
  328.     ]
  329.  
  330. tobytes[num_Real,_,Double,_,_] :=
  331.     Module[{frac, exp},
  332.         {frac, exp} = RealDigits[num,2];
  333.         Map[bitstointeger, Partition[Join[
  334.                 If[Negative[num],
  335.                     {1},
  336.                     {0}
  337.                 ],
  338.                 exp = IntegerDigits[exp + 1022,2];
  339.                 If[Length[exp] < 11,
  340.                     Join[zeropad[11 - Length[exp]],exp],
  341.                     exp
  342.                 ],
  343.                 frac = Drop[frac,1];
  344.                 If[Length[frac] < 52,
  345.                     Join[frac, zeropad[52 - Length[frac]]],
  346.                     Take[frac,52]
  347.                 ]],8]
  348.         ]/; -1023 <= exp <= 1024
  349.     ]
  350.  
  351. tobytes[num_Real,_,type:(Int | Int16 | Int32),_,end_] :=
  352.     (Message[ToBytes::cast, Real, type];
  353.     tobytes[Round[num],type,Null,Null,end])
  354.  
  355. tobytes[num_Real,_,type:(CString),_,_] :=
  356.     (Message[ToBytes::cast, Real, type];
  357.     tobytes[ToString[num],Null,Null,type,Null])
  358.  
  359. tobytes[num_Integer,Byte,_,_,_] :=
  360.     Mod[num,256]
  361.  
  362. tobytes[num_Integer,Int16,_,_,True] :=
  363.     {Quotient[#,256], Mod[#,256]}&[Mod[num, 65536]]
  364.  
  365. tobytes[num_Integer,Int32,_,_,True] :=
  366.     {Quotient[#,16777216],
  367.     Quotient[Mod[#,16777216],65536],
  368.     Mod[Quotient[#,65536],256],
  369.     Mod[#,256]}&[Mod[num, 4294967296]]
  370.  
  371. tobytes[num_Integer,type:(Int16 | Int32),_,_,False] :=
  372.     Reverse[tobytes[num,type,Null,Null,True]]
  373.  
  374. tobytes[num_Integer,type:(Single | Double),_,_,_] :=
  375.     (Message[ToBytes::cast, Integer, type];
  376.     tobytes[N[num],Null,type,Null,Null])
  377.  
  378. tobytes[num_Integer,type:(CString),_,_,_] :=
  379.     (Message[ToBytes::cast, Integer, type];
  380.     tobytes[ToString[num],Null,Null,type,Null])
  381.  
  382. tobytes[str_String,_,_,CString,_] :=
  383.     ToCharacterCode[str<>"\000"]
  384.  
  385. tobytes[str_String,_,_,type_,end_] :=
  386.     (Message[ToBytes::cast, String, type];
  387.     tobytes[ToExpression[str], type, type, Null, end])
  388.  
  389. tobytes[anything_, ___] :=
  390.     (Message[ToBytes::noconv,anything];
  391.     anything)
  392.  
  393. (* ToBytes utility functions; bitstointeger takes a list of
  394.     ones and zeros, assumes they are bits, and converts it
  395.     to the integer represented.  zeropad takes an integer n,
  396.     and creates a list of zeros of length n. *)
  397.  
  398. bitstointeger[bits_] :=
  399.     ToExpression["2^^" <>
  400.         StringJoin[Map[ToString,bits]]
  401.     ]
  402.  
  403. zeropad[n_] := Table[0,{n}]
  404.  
  405. (* Following are the ReadBinary functions. *)
  406.  
  407. Attributes[ReadBinary] := {HoldRest}
  408.  
  409. ReadBinary::nonnormal =
  410.     "Warning: Binary value `1` was not in the normalized
  411.     floating point format;  value may not be correct.";
  412.  
  413. ReadBinary::incstring =
  414.     "Warning: encountered end of file before end of string;
  415.     string may be incomplete."
  416.  
  417. Options[ReadBinary] =
  418.     {ByteOrder -> MostSignificantByteFirst};
  419.  
  420. ReadBinary[filename_String,args__] :=
  421.     Module[{stream},
  422.         stream = OpenRead[filename];
  423.         ReadBinary[stream,args];
  424.     ]
  425.  
  426. ReadBinary[stream_InputStream,pat_,
  427.         opts:((_Rule | _RuleDelayed)...)] :=
  428.     Module[{endian},
  429.         {endian} = {ByteOrder}/.{opts}/.Options[ReadBinary];
  430.         endian = If[endian === LeastSignificantByteFirst, False, True];
  431.         If[Read[stream,Byte] =!= EndOfFile,
  432.             SetStreamPosition[stream,StreamPosition[stream] - 1];
  433.                 ReleaseHold[Hold[pat]/.
  434.                     (n:(Byte | Int8 | Int16 | Int32 | Single |
  435.                         Double | SignedByte | SignedInt8 |
  436.                         SignedInt16 | SignedInt32 | CString) :>
  437.                     readbinary[stream,n,TrueQ[endian]])
  438.                 ],
  439.             EndOfFile]
  440.     ]
  441.  
  442. readbinary[stream_,pat_,endian_] :=
  443.     With[{out = rb[stream,pat,endian]},
  444.         If[FreeQ[out,EndOfFile],
  445.             out,
  446.             EndOfFile]
  447.     ]
  448.  
  449. (* :Implementation Note:
  450.     For many (most) of these types of input, I used a hard-coded
  451.     form, rather than more elegant or concise code, for reasons
  452.     of efficiency.  (e.g., Read[stream,{Byte,Byte,...Byte}] rather
  453.     than Read[stream,Table[Byte,{n}]], or explicitly scaling
  454.     each byte of the input, rather than doing them all together
  455.     with a Fold construct or such-like.)
  456. *)
  457.  
  458. rb[stream_InputStream,Byte,_] :=
  459.     Read[stream,Byte]
  460.  
  461. rb[stream_InputStream,SignedByte,_] :=
  462.     (# - Quotient[#,128] 256)&[Read[stream,Byte]]
  463.  
  464. rb[stream_InputStream,Int8,_] :=
  465.     Read[stream,Byte]
  466.  
  467. rb[stream_InputStream,SignedInt8,_] :=
  468.     (# - Quotient[#,128] 256)&[Read[stream,Byte]]
  469.  
  470. rb[stream_InputStream,Int16,True] :=
  471.     (256 #1 + #2)& @@ Read[stream,{Byte,Byte}]
  472.  
  473. rb[stream_InputStream,Int16,False] :=
  474.     (256 #2 + #1)& @@ Read[stream,{Byte,Byte}]
  475.  
  476. rb[stream_InputStream,SignedInt16,True] :=
  477.     (256 #1 + #2 - Quotient[#1,128] 65536)& @@
  478.         Read[stream,{Byte,Byte}]
  479.  
  480. rb[stream_InputStream,SignedInt16,False] :=
  481.     (256 #2 + #1 - Quotient[#2,128] 65536)& @@
  482.         Read[stream,{Byte,Byte}]
  483.  
  484. rb[stream_InputStream,Int32,True] :=
  485.     (256^3 #1 + 256^2 #2 + 256 #3 + #4)& @@
  486.             Read[stream,{Byte,Byte,Byte,Byte}]
  487.  
  488. rb[stream_InputStream,Int32,False] :=
  489.     (256^3 #4 + 256^2 #3 + 256 #2 + #1)& @@
  490.             Read[stream,{Byte,Byte,Byte,Byte}]
  491.  
  492. rb[stream_InputStream,SignedInt32,True] :=
  493.     (256^3 #1 + 256^2 #2 + 256 #3 + #4 - Quotient[#1,128] 256^4)& @@
  494.             Read[stream,{Byte,Byte,Byte,Byte}]
  495.  
  496. rb[stream_InputStream,SignedInt32,False] :=
  497.     (256^3 #4 + 256^2 #3 + 256 #2 + #1 - Quotient[#4,128] 256^4)& @@
  498.             Read[stream,{Byte,Byte,Byte,Byte}]
  499.  
  500. rb[stream_InputStream,Single,_] :=
  501.     floatvalue @@ {Quotient[#1,128],
  502.                 (Mod[#1,128])*2 + Quotient[#2,128],
  503.                 ((Mod[#2,128])*256^2 + #3*256 + #4)/(2^23) + 1}& @@
  504.             Read[stream,{Byte,Byte,Byte,Byte}]
  505.  
  506. floatvalue[s_,0,1] := 0
  507.  
  508. floatvalue[s_,0,f_] :=
  509.     (Message[ReadBinary::nonnormal,f - 1];f - 1)
  510.  
  511. floatvalue[s_,255,1] := (-1)^s Infinity
  512.  
  513. floatvalue[s_,255,_] := Indeterminate
  514.  
  515. floatvalue[s_,e_,f_] := N[(-1)^s * 2^(e - 127) * f]
  516.  
  517. rb[stream_InputStream,Double,_] :=
  518.     doublevalue @@ {Quotient[#1,128],
  519.                 (Mod[#1,128])*2^4 + Quotient[#2,16],
  520.                 ((Mod[#2,16])*256^6 + #3*256^5 + #4*256^4 +
  521.                     #5*256^3 + #6*256^2 + #7*256 + #8)/(2^52) +
  522.                     1}& @@
  523.             Read[stream,{Byte,Byte,Byte,Byte,Byte,Byte,Byte,Byte}]
  524.  
  525. doublevalue[s_,0,1] := 0
  526.  
  527. doublevalue[s_,0,f_] :=
  528.     (Message[ReadBinary::nonnormal,f - 1];f - 1)
  529.  
  530. doublevalue[s_,2047,1] := (-1)^s Infinity
  531.  
  532. doublevalue[s_,2047,_] := Indeterminate
  533.  
  534. doublevalue[s_,e_,f_] := N[(-1)^s * 2^(e - 1023) * f]
  535.  
  536. rb[stream_InputStream,CString,_] :=
  537.     Module[{tmp,out = ""},
  538.         tmp = Read[stream,Byte];
  539.         If[tmp === EndOfFile,Return[EndOfFile]];
  540.         While[tmp =!= 0,
  541.             If[tmp === EndOfFile,
  542.                 Message[ReadBinary::incstring];Break[]
  543.             ];
  544.             out <> FromCharacterCode[tmp];
  545.             tmp = Read[stream,Byte]
  546.         ];
  547.         out
  548.     ]
  549.  
  550. Attributes[ReadListBinary] := {HoldRest}
  551.  
  552. ReadListBinary[filename_String,args__] :=
  553.     Module[{stream,out},
  554.         stream = OpenRead[filename];
  555.         If[Head[stream] =!= InputStream,
  556.             Abort[]];
  557.         out = ReadListBinary[stream,args];
  558.         Close[stream];
  559.         out
  560.     ]
  561.  
  562. ReadListBinary[stream_InputStream,pat_,
  563.         n:(_Integer | Infinity):Infinity,
  564.         opts:((_Rule | _RuleDelayed)...)] :=
  565.     Module[{cnt = 0,tmp,out = {}},
  566.         While[(tmp = ReadBinary[stream,pat,opts]) =!= EndOfFile &&
  567.                 cnt < n,
  568.             AppendTo[out,tmp];
  569.             cnt ++
  570.         ];
  571.         out
  572.     ]/;(!FreeQ[pat,Byte | Int8 | Int16 | Int32 | Single |
  573.                         Double | SignedByte | SignedInt8 |
  574.                         SignedInt16 | SignedInt32 | CString,
  575.                     Infinity] ||
  576.         MatchQ[pat, Byte | Int8 | Int16 | Int32 | Single |
  577.                         Double | SignedByte | SignedInt8 |
  578.                         SignedInt16 | SignedInt32 | CString])
  579.  
  580. End[]
  581.  
  582. EndPackage[]
  583.