hosc-0.20: Haskell Open Sound Control
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Osc.Coding.Byte

Description

Byte-level coding utility functions. Plain forms are big-endian, little-endian forms have _le suffix.

Synopsis

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 1.0 == L.pack [63, 128, 0, 0]

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.

read_word32 :: Handle -> IO Word32 Source #

Type-specialised reader for decode.

Io/Int

Io/Float

Io/Ascii

read_pstr :: Handle -> IO ByteString Source #

Read u8 length prefixed Ascii string (pascal string).

Util

bundleHeader_strict :: ByteString Source #

Bundle header as a (strict) ByteString.

S.C.length bundleHeader_strict == 8

bundleHeader :: ByteString Source #

Bundle header as a lazy ByteString.

L.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]