| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Sound.OSC.Coding.Byte
Description
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
Encode
encode_int8 :: Int8 -> ByteString Source #
Type specialised encode (big-endian).
encode_int16 :: Int16 -> ByteString Source #
Type specialised encode (big-endian).
encode_int16 0x0102 == L.pack [0x01,0x02]
encode_int16_le :: Int16 -> ByteString Source #
Little-endian.
encode_int16_le 0x0102 == L.pack [0x02,0x01]
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 == L.pack [0x01,0x02]
encode_word16_le :: Word16 -> ByteString Source #
Little-endian.
encode_word16_le 0x0102 == L.pack [0x02,0x01]
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 == L.pack [1,2]
encode_u16_le :: Int -> ByteString Source #
Little-endian.
encode_u16_le 0x0102 == L.pack [2,1]
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.
encode_u32 0x01020304 == L.pack [1,2,3,4]
encode_u32_le :: Int -> ByteString Source #
Little-endian.
encode_u32_le 0x01020304 == L.pack [4,3,2,1]
Encode/Float
encode_f32 :: Float -> ByteString Source #
Encode a 32-bit IEEE floating point number.
encode_f32_le :: Float -> ByteString Source #
Little-endian variant of encode_f32.
encode_f64 :: Double -> ByteString Source #
Encode a 64-bit IEEE floating point number.
encode_f64_le :: Double -> ByteString Source #
Little-endian variant of encode_f64.
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 (L.pack [0x00,0x00,0x03,0xe7]) == 0x03e7
decode_i32_le :: ByteString -> Int Source #
Little-endian variant of decode_i32.
decode_i32_le (L.pack [0xe7,0x03,0x00,0x00]) == 0x03e7
decode_u32 :: ByteString -> Int Source #
Decode an unsigned 32-bit integer.
decode_u32 (L.pack [1,2,3,4]) == 0x01020304
decode_u32_le :: ByteString -> Int Source #
Little-endian variant of decode_u32.
decode_u32_le (L.pack [1,2,3,4]) == 0x04030201
Decode/Float
decode_f32 :: ByteString -> Float Source #
Decode a 32-bit IEEE floating point number.
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.
bundleHeader :: ByteString Source #
Bundle header as a lazy ByteString.