Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Byte-level coding utility functions.
Plain forms are big-endian, little-endian forms have _le
suffix.
Synopsis
- encode_int8 :: Int8 -> ByteString
- encode_int16 :: Int16 -> ByteString
- encode_int16_le :: Int16 -> ByteString
- encode_int64 :: Int64 -> ByteString
- encode_word8 :: Word8 -> ByteString
- encode_word16 :: Word16 -> ByteString
- encode_word16_le :: Word16 -> ByteString
- encode_word32 :: Word32 -> ByteString
- encode_word32_le :: Word32 -> ByteString
- encode_word64 :: Word64 -> ByteString
- encode_i8 :: Int -> ByteString
- encode_u8 :: Int -> ByteString
- encode_u16 :: Int -> ByteString
- encode_u16_le :: Int -> ByteString
- encode_i16 :: Int -> ByteString
- encode_i32 :: Int -> ByteString
- encode_u32 :: Int -> ByteString
- encode_u32_le :: Int -> ByteString
- encode_f32 :: Float -> ByteString
- encode_f32_le :: Float -> ByteString
- encode_f64 :: Double -> ByteString
- encode_f64_le :: Double -> ByteString
- encode_ascii :: ByteString -> ByteString
- decode_word16 :: ByteString -> Word16
- decode_word16_le :: ByteString -> Word16
- decode_int16 :: ByteString -> Int16
- decode_word32 :: ByteString -> Word32
- decode_word32_le :: ByteString -> Word32
- decode_int64 :: ByteString -> Int64
- decode_word64 :: ByteString -> Word64
- decode_u8 :: ByteString -> Int
- decode_i8 :: ByteString -> Int
- decode_u16 :: ByteString -> Int
- decode_u16_le :: ByteString -> Int
- decode_i16 :: ByteString -> Int
- decode_i16_le :: ByteString -> Int
- decode_i32 :: ByteString -> Int
- decode_i32_le :: ByteString -> Int
- decode_u32 :: ByteString -> Int
- decode_u32_le :: ByteString -> Int
- decode_f32 :: ByteString -> Float
- decode_f32_le :: ByteString -> Float
- decode_f64 :: ByteString -> Double
- decode_ascii :: ByteString -> ByteString
- read_decode :: (ByteString -> t) -> Int -> Handle -> IO t
- read_word32 :: Handle -> IO Word32
- read_word32_le :: Handle -> IO Word32
- write_word32 :: Handle -> Word32 -> IO ()
- write_word32_le :: Handle -> Word32 -> IO ()
- read_i8 :: Handle -> IO Int
- read_i16 :: Handle -> IO Int
- read_i32 :: Handle -> IO Int
- read_i32_le :: Handle -> IO Int
- read_u32 :: Handle -> IO Int
- read_u32_le :: Handle -> IO Int
- write_u32 :: Handle -> Int -> IO ()
- write_u32_le :: Handle -> Int -> IO ()
- read_f32 :: Handle -> IO Float
- read_f32_le :: Handle -> IO Float
- read_pstr :: Handle -> IO ByteString
- bundleHeader_strict :: ByteString
- bundleHeader :: ByteString
- align :: (Num i, Bits i) => i -> i
- isLittleEndian :: Bool
- byteStringSwap32BitWords :: ByteString -> ByteString
- byteString32BitNetworkOrder :: ByteString -> ByteString
Encode
encode_int8 :: Int8 -> ByteString Source #
Type specialised encode
(big-endian).
encode_int16 :: Int16 -> ByteString Source #
Type specialised encode
(big-endian).
>>>
encode_int16 0x0102 == ByteString.Lazy.pack [0x01,0x02]
True
encode_int16_le :: Int16 -> ByteString Source #
Little-endian.
>>>
encode_int16_le 0x0102 == ByteString.Lazy.pack [0x02,0x01]
True
encode_int64 :: Int64 -> ByteString Source #
Encode a signed 64-bit integer (big-endian).
encode_word8 :: Word8 -> ByteString Source #
Type specialised encode
(big-endian).
encode_word16 :: Word16 -> ByteString Source #
Type specialised encode
(big-endian).
>>>
encode_word16 0x0102 == ByteString.Lazy.pack [0x01,0x02]
True
encode_word16_le :: Word16 -> ByteString Source #
Little-endian.
>>>
encode_word16_le 0x0102 == ByteString.Lazy.pack [0x02,0x01]
True
encode_word32 :: Word32 -> ByteString Source #
Type specialised encode
.
encode_word32_le :: Word32 -> ByteString Source #
Little-endian variant of encode_word32
.
encode_word64 :: Word64 -> ByteString Source #
Encode an unsigned 64-bit integer.
Encode/Int
encode_i8 :: Int -> ByteString Source #
Encode a signed 8-bit integer.
encode_u8 :: Int -> ByteString Source #
Encode an un-signed 8-bit integer.
encode_u16 :: Int -> ByteString Source #
Encode an un-signed 16-bit integer.
>>>
encode_u16 0x0102 == ByteString.Lazy.pack [1,2]
True
encode_u16_le :: Int -> ByteString Source #
Little-endian.
>>>
encode_u16_le 0x0102 == ByteString.Lazy.pack [2,1]
True
encode_i16 :: Int -> ByteString Source #
Encode a signed 16-bit integer.
encode_i32 :: Int -> ByteString Source #
Encode a signed 32-bit integer.
encode_u32 :: Int -> ByteString Source #
Encode an unsigned 32-bit integer.
>>>
ByteString.Lazy.unpack (encode_u32 0x01020304)
[1,2,3,4]
encode_u32_le :: Int -> ByteString Source #
Little-endian.
>>>
ByteString.Lazy.unpack (encode_u32_le 0x01020304)
[4,3,2,1]
Encode/Float
encode_f32 :: Float -> ByteString Source #
Encode a 32-bit IEEE floating point number.
>>>
ByteString.Lazy.unpack (encode_f32 3.141)
[64,73,6,37]
encode_f32_le :: Float -> ByteString Source #
Little-endian variant of encode_f32
.
>>>
ByteString.Lazy.unpack (encode_f32_le 3.141)
[37,6,73,64]
encode_f64 :: Double -> ByteString Source #
Encode a 64-bit IEEE floating point number.
>>>
ByteString.Lazy.unpack (encode_f64 3.141)
[64,9,32,196,155,165,227,84]
encode_f64_le :: Double -> ByteString Source #
Little-endian variant of encode_f64
.
>>>
ByteString.Lazy.unpack (encode_f64_le 3.141)
[84,227,165,155,196,32,9,64]
Encode/Ascii
encode_ascii :: ByteString -> ByteString Source #
Encode an Ascii string (Ascii at Datum is an alias for a Char8 Bytetring).
Decode
decode_word16 :: ByteString -> Word16 Source #
Type specialised decode
.
decode_word16_le :: ByteString -> Word16 Source #
Little-endian variant of decode_word16
.
decode_int16 :: ByteString -> Int16 Source #
Type specialised decode
.
decode_word32 :: ByteString -> Word32 Source #
Type specialised decode
.
decode_word32_le :: ByteString -> Word32 Source #
Little-endian variant of decode_word32
.
decode_int64 :: ByteString -> Int64 Source #
Type specialised decode
.
decode_word64 :: ByteString -> Word64 Source #
Type specialised decode
.
Decode/Int
decode_u8 :: ByteString -> Int Source #
Decode an un-signed 8-bit integer.
decode_i8 :: ByteString -> Int Source #
Decode a signed 8-bit integer.
decode_u16 :: ByteString -> Int Source #
Decode an unsigned 8-bit integer.
decode_u16_le :: ByteString -> Int Source #
Little-endian variant of decode_u16
.
decode_i16 :: ByteString -> Int Source #
Decode a signed 16-bit integer.
decode_i16_le :: ByteString -> Int Source #
Little-endian variant of decode_i16
.
decode_i32 :: ByteString -> Int Source #
Decode a signed 32-bit integer.
>>>
decode_i32 (ByteString.Lazy.pack [0x00,0x00,0x03,0xe7]) == 0x03e7
True
decode_i32_le :: ByteString -> Int Source #
Little-endian variant of decode_i32
.
>>>
decode_i32_le (ByteString.Lazy.pack [0xe7,0x03,0x00,0x00]) == 0x03e7
True
decode_u32 :: ByteString -> Int Source #
Decode an unsigned 32-bit integer.
>>>
decode_u32 (ByteString.Lazy.pack [1,2,3,4]) == 0x01020304
True
decode_u32_le :: ByteString -> Int Source #
Little-endian variant of decode_u32.
>>>
decode_u32_le (ByteString.Lazy.pack [1,2,3,4]) == 0x04030201
True
Decode/Float
decode_f32 :: ByteString -> Float Source #
Decode a 32-bit IEEE floating point number.
>>>
decode_f32 (ByteString.Lazy.pack [64,73,6,37])
3.141
decode_f32_le :: ByteString -> Float Source #
Little-endian variant of decode_f32
.
decode_f64 :: ByteString -> Double Source #
Decode a 64-bit IEEE floating point number.
Decode/Ascii
decode_ascii :: ByteString -> ByteString Source #
Decode an Ascii string, inverse of encode_ascii
.
IO
read_decode :: (ByteString -> t) -> Int -> Handle -> IO t Source #
Read n bytes from h and run f.
write_word32 :: Handle -> Word32 -> IO () Source #
hPut
of encode_word32
.
write_word32_le :: Handle -> Word32 -> IO () Source #
hPut
of encode_word32_le
.
Io/Int
read_i32_le :: Handle -> IO Int Source #
decode_i32_le
of hGet
.
read_u32_le :: Handle -> IO Int Source #
decode_u32_le
of hGet
.
write_u32_le :: Handle -> Int -> IO () Source #
hPut
of encode_u32_le
.
Io/Float
read_f32_le :: Handle -> IO Float Source #
decode_f32_le
of hGet
.
Io/Ascii
Util
bundleHeader_strict :: ByteString Source #
Bundle header as a (strict) ByteString
.
>>>
ByteString.Char8.length bundleHeader_strict
8
bundleHeader :: ByteString Source #
Bundle header as a lazy ByteString.
>>>
ByteString.Lazy.length bundleHeader
8
align :: (Num i, Bits i) => i -> i Source #
The number of bytes required to align an Osc value to the next 4-byte boundary.
>>>
map align [0::Int .. 7]
[0,3,2,1,0,3,2,1]
>>>
map align [512::Int .. 519]
[0,3,2,1,0,3,2,1]
ByteString
isLittleEndian :: Bool Source #
Is machine little endian?
byteStringSwap32BitWords :: ByteString -> ByteString Source #
Byte-swap byte string in four-byte segments.
byteString32BitNetworkOrder :: ByteString -> ByteString Source #
If target is little-endian, swap bytes to be in network order, else identity.