{- | Byte-level coding utility functions.
Plain forms are big-endian, little-endian forms have @_le@ suffix.
-}
module Sound.Osc.Coding.Byte where

import Data.Bits {- base -}
import Data.Int {- base -}
import Data.Word {- base -}
import System.IO {- base -}

import qualified GHC.ByteOrder {- base -}

import qualified Data.Binary as Binary {- binary -}
import qualified Data.Binary.Get as Binary.Get {- binary -}
import qualified Data.Binary.Put as Binary.Put {- binary -}

import qualified Data.ByteString as ByteString {- bytestring -}
import qualified Data.ByteString.Char8 as ByteString.Char8 {- bytestring -}
import qualified Data.ByteString.Internal as ByteString.Internal {- bytestring -}
import qualified Data.ByteString.Lazy as ByteString.Lazy {- bytestring -}
import qualified Data.ByteString.Lazy.Char8 as ByteString.Lazy.Char8 {- bytestring -}
import qualified Data.ByteString.Unsafe as ByteString.Unsafe {- bytestring -}

import qualified Sound.Osc.Coding.Convert as Convert {- hosc -}

-- * Encode

-- | Type specialised 'Binary.encode' (big-endian).
encode_int8 :: Int8 -> ByteString.Lazy.ByteString
encode_int8 :: Int8 -> ByteString
encode_int8 = Int8 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode

{- | Type specialised 'Binary.encode' (big-endian).

>>> encode_int16 0x0102 == ByteString.Lazy.pack [0x01,0x02]
True
-}
encode_int16 :: Int16 -> ByteString.Lazy.ByteString
encode_int16 :: Int16 -> ByteString
encode_int16 = Int16 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode

{- | Little-endian.

>>> encode_int16_le 0x0102 == ByteString.Lazy.pack [0x02,0x01]
True
-}
encode_int16_le :: Int16 -> ByteString.Lazy.ByteString
encode_int16_le :: Int16 -> ByteString
encode_int16_le = Put -> ByteString
Binary.Put.runPut (Put -> ByteString) -> (Int16 -> Put) -> Int16 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Put
Binary.Put.putInt16le

-- | Encode a signed 64-bit integer (big-endian).
encode_int64 :: Int64 -> ByteString.Lazy.ByteString
encode_int64 :: Int64 -> ByteString
encode_int64 = Int64 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode

-- | Type specialised 'Binary.encode' (big-endian).
encode_word8 :: Word8 -> ByteString.Lazy.ByteString
encode_word8 :: Word8 -> ByteString
encode_word8 = Word8 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode

{- | Type specialised 'Binary.encode' (big-endian).

>>> encode_word16 0x0102 == ByteString.Lazy.pack [0x01,0x02]
True
-}
encode_word16 :: Word16 -> ByteString.Lazy.ByteString
encode_word16 :: Word16 -> ByteString
encode_word16 = Word16 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode

{- | Little-endian.

>>> encode_word16_le 0x0102 == ByteString.Lazy.pack [0x02,0x01]
True
-}
encode_word16_le :: Word16 -> ByteString.Lazy.ByteString
encode_word16_le :: Word16 -> ByteString
encode_word16_le = Put -> ByteString
Binary.Put.runPut (Put -> ByteString) -> (Word16 -> Put) -> Word16 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Put
Binary.Put.putWord16le

-- | Type specialised 'Binary.encode'.
encode_word32 :: Word32 -> ByteString.Lazy.ByteString
encode_word32 :: Word32 -> ByteString
encode_word32 = Word32 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode

-- | Little-endian variant of 'encode_word32'.
encode_word32_le :: Word32 -> ByteString.Lazy.ByteString
encode_word32_le :: Word32 -> ByteString
encode_word32_le = Put -> ByteString
Binary.Put.runPut (Put -> ByteString) -> (Word32 -> Put) -> Word32 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Put
Binary.Put.putWord32le

-- | Encode an unsigned 64-bit integer.
encode_word64 :: Word64 -> ByteString.Lazy.ByteString
encode_word64 :: Word64 -> ByteString
encode_word64 = Word64 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode

-- * Encode/Int

-- | Encode a signed 8-bit integer.
encode_i8 :: Int -> ByteString.Lazy.ByteString
encode_i8 :: Int -> ByteString
encode_i8 = Int8 -> ByteString
encode_int8 (Int8 -> ByteString) -> (Int -> Int8) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int8
Convert.int_to_int8

-- | Encode an un-signed 8-bit integer.
encode_u8 :: Int -> ByteString.Lazy.ByteString
encode_u8 :: Int -> ByteString
encode_u8 = Word8 -> ByteString
encode_word8 (Word8 -> ByteString) -> (Int -> Word8) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word8
Convert.int_to_word8

{- | Encode an un-signed 16-bit integer.

>>> encode_u16 0x0102 == ByteString.Lazy.pack [1,2]
True
-}
encode_u16 :: Int -> ByteString.Lazy.ByteString
encode_u16 :: Int -> ByteString
encode_u16 = Word16 -> ByteString
encode_word16 (Word16 -> ByteString) -> (Int -> Word16) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word16
Convert.int_to_word16

{- | Little-endian.

>>> encode_u16_le 0x0102 == ByteString.Lazy.pack [2,1]
True
-}
encode_u16_le :: Int -> ByteString.Lazy.ByteString
encode_u16_le :: Int -> ByteString
encode_u16_le = Word16 -> ByteString
encode_word16_le (Word16 -> ByteString) -> (Int -> Word16) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word16
Convert.int_to_word16

-- | Encode a signed 16-bit integer.
encode_i16 :: Int -> ByteString.Lazy.ByteString
encode_i16 :: Int -> ByteString
encode_i16 = Int16 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode (Int16 -> ByteString) -> (Int -> Int16) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int16
Convert.int_to_int16

-- | Encode a signed 32-bit integer.
encode_i32 :: Int -> ByteString.Lazy.ByteString
encode_i32 :: Int -> ByteString
encode_i32 = Int32 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode (Int32 -> ByteString) -> (Int -> Int32) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32
Convert.int_to_int32

{- | Encode an unsigned 32-bit integer.

>>> ByteString.Lazy.unpack (encode_u32 0x01020304)
[1,2,3,4]
-}
encode_u32 :: Int -> ByteString.Lazy.ByteString
encode_u32 :: Int -> ByteString
encode_u32 = Word32 -> ByteString
encode_word32 (Word32 -> ByteString) -> (Int -> Word32) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word32
Convert.int_to_word32

{- | Little-endian.

>>> ByteString.Lazy.unpack (encode_u32_le 0x01020304)
[4,3,2,1]
-}
encode_u32_le :: Int -> ByteString.Lazy.ByteString
encode_u32_le :: Int -> ByteString
encode_u32_le = Word32 -> ByteString
encode_word32_le (Word32 -> ByteString) -> (Int -> Word32) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word32
Convert.int_to_word32

-- * Encode/Float

{- | Encode a 32-bit IEEE floating point number.

>>> ByteString.Lazy.unpack (encode_f32 3.141)
[64,73,6,37]
-}
encode_f32 :: Float -> ByteString.Lazy.ByteString
encode_f32 :: Float -> ByteString
encode_f32 = Put -> ByteString
Binary.Put.runPut (Put -> ByteString) -> (Float -> Put) -> Float -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Put
Binary.Put.putFloatbe

{- | Little-endian variant of 'encode_f32'.

>>> ByteString.Lazy.unpack (encode_f32_le 3.141)
[37,6,73,64]
-}
encode_f32_le :: Float -> ByteString.Lazy.ByteString
encode_f32_le :: Float -> ByteString
encode_f32_le = Put -> ByteString
Binary.Put.runPut (Put -> ByteString) -> (Float -> Put) -> Float -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Put
Binary.Put.putFloatle

{- | 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 :: Double -> ByteString.Lazy.ByteString
encode_f64 :: Double -> ByteString
encode_f64 = Put -> ByteString
Binary.Put.runPut (Put -> ByteString) -> (Double -> Put) -> Double -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Put
Binary.Put.putDoublebe

{- | Little-endian variant of 'encode_f64'.

>>> ByteString.Lazy.unpack (encode_f64_le 3.141)
[84,227,165,155,196,32,9,64]
-}
encode_f64_le :: Double -> ByteString.Lazy.ByteString
encode_f64_le :: Double -> ByteString
encode_f64_le = Put -> ByteString
Binary.Put.runPut (Put -> ByteString) -> (Double -> Put) -> Double -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Put
Binary.Put.putDoublele

-- * Encode/Ascii

-- | Encode an Ascii string (Ascii at Datum is an alias for a Char8 Bytetring).
encode_ascii :: ByteString.Char8.ByteString -> ByteString.Lazy.ByteString
encode_ascii :: ByteString -> ByteString
encode_ascii = [Word8] -> ByteString
ByteString.Lazy.pack ([Word8] -> ByteString)
-> (ByteString -> [Word8]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
ByteString.unpack

-- * Decode

-- | Type specialised 'Binary.decode'.
decode_word16 :: ByteString.Lazy.ByteString -> Word16
decode_word16 :: ByteString -> Word16
decode_word16 = ByteString -> Word16
forall a. Binary a => ByteString -> a
Binary.decode

-- | Little-endian variant of 'decode_word16'.
decode_word16_le :: ByteString.Lazy.ByteString -> Word16
decode_word16_le :: ByteString -> Word16
decode_word16_le = Get Word16 -> ByteString -> Word16
forall a. Get a -> ByteString -> a
Binary.Get.runGet Get Word16
Binary.Get.getWord16le

-- | Type specialised 'Binary.decode'.
decode_int16 :: ByteString.Lazy.ByteString -> Int16
decode_int16 :: ByteString -> Int16
decode_int16 = ByteString -> Int16
forall a. Binary a => ByteString -> a
Binary.decode

-- | Type specialised 'Binary.decode'.
decode_word32 :: ByteString.Lazy.ByteString -> Word32
decode_word32 :: ByteString -> Word32
decode_word32 = ByteString -> Word32
forall a. Binary a => ByteString -> a
Binary.decode

-- | Little-endian variant of 'decode_word32'.
decode_word32_le :: ByteString.Lazy.ByteString -> Word32
decode_word32_le :: ByteString -> Word32
decode_word32_le = Get Word32 -> ByteString -> Word32
forall a. Get a -> ByteString -> a
Binary.Get.runGet Get Word32
Binary.Get.getWord32le

-- | Type specialised 'Binary.decode'.
decode_int64 :: ByteString.Lazy.ByteString -> Int64
decode_int64 :: ByteString -> Int64
decode_int64 = ByteString -> Int64
forall a. Binary a => ByteString -> a
Binary.decode

-- | Type specialised 'Binary.decode'.
decode_word64 :: ByteString.Lazy.ByteString -> Word64
decode_word64 :: ByteString -> Word64
decode_word64 = ByteString -> Word64
forall a. Binary a => ByteString -> a
Binary.decode

-- * Decode/Int

-- | Decode an un-signed 8-bit integer.
decode_u8 :: ByteString.Lazy.ByteString -> Int
decode_u8 :: ByteString -> Int
decode_u8 = Word8 -> Int
Convert.word8_to_int (Word8 -> Int) -> (ByteString -> Word8) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => ByteString -> Word8
ByteString -> Word8
ByteString.Lazy.head

-- | Decode a signed 8-bit integer.
decode_i8 :: ByteString.Lazy.ByteString -> Int
decode_i8 :: ByteString -> Int
decode_i8 = Int8 -> Int
Convert.int8_to_int (Int8 -> Int) -> (ByteString -> Int8) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Int8
forall a. Binary a => ByteString -> a
Binary.decode

-- | Decode an unsigned 8-bit integer.
decode_u16 :: ByteString.Lazy.ByteString -> Int
decode_u16 :: ByteString -> Int
decode_u16 = Word16 -> Int
Convert.word16_to_int (Word16 -> Int) -> (ByteString -> Word16) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word16
decode_word16

-- | Little-endian variant of 'decode_u16'.
decode_u16_le :: ByteString.Lazy.ByteString -> Int
decode_u16_le :: ByteString -> Int
decode_u16_le = Word16 -> Int
Convert.word16_to_int (Word16 -> Int) -> (ByteString -> Word16) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word16
decode_word16_le

-- | Decode a signed 16-bit integer.
decode_i16 :: ByteString.Lazy.ByteString -> Int
decode_i16 :: ByteString -> Int
decode_i16 = Int16 -> Int
Convert.int16_to_int (Int16 -> Int) -> (ByteString -> Int16) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Int16
decode_int16

-- | Little-endian variant of 'decode_i16'.
decode_i16_le :: ByteString.Lazy.ByteString -> Int
decode_i16_le :: ByteString -> Int
decode_i16_le = ByteString -> Int
decode_i16 (ByteString -> Int)
-> (ByteString -> ByteString) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
ByteString.Lazy.reverse

{- | Decode a signed 32-bit integer.

>>> decode_i32 (ByteString.Lazy.pack [0x00,0x00,0x03,0xe7]) == 0x03e7
True
-}
decode_i32 :: ByteString.Lazy.ByteString -> Int
decode_i32 :: ByteString -> Int
decode_i32 = Int32 -> Int
Convert.int32_to_int (Int32 -> Int) -> (ByteString -> Int32) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Int32
forall a. Binary a => ByteString -> a
Binary.decode

{- | Little-endian variant of 'decode_i32'.

>>> decode_i32_le (ByteString.Lazy.pack [0xe7,0x03,0x00,0x00]) == 0x03e7
True
-}
decode_i32_le :: ByteString.Lazy.ByteString -> Int
decode_i32_le :: ByteString -> Int
decode_i32_le = ByteString -> Int
decode_i32 (ByteString -> Int)
-> (ByteString -> ByteString) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
ByteString.Lazy.reverse

{- | Decode an unsigned 32-bit integer.

>>> decode_u32 (ByteString.Lazy.pack [1,2,3,4]) == 0x01020304
True
-}
decode_u32 :: ByteString.Lazy.ByteString -> Int
decode_u32 :: ByteString -> Int
decode_u32 = Word32 -> Int
Convert.word32_to_int (Word32 -> Int) -> (ByteString -> Word32) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word32
decode_word32

{- | Little-endian variant of decode_u32.

>>> decode_u32_le (ByteString.Lazy.pack [1,2,3,4]) == 0x04030201
True
-}
decode_u32_le :: ByteString.Lazy.ByteString -> Int
decode_u32_le :: ByteString -> Int
decode_u32_le = Word32 -> Int
Convert.word32_to_int (Word32 -> Int) -> (ByteString -> Word32) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word32
decode_word32_le

-- * Decode/Float

{- | Decode a 32-bit IEEE floating point number.

>>> decode_f32 (ByteString.Lazy.pack [64,73,6,37])
3.141
-}
decode_f32 :: ByteString.Lazy.ByteString -> Float
decode_f32 :: ByteString -> Float
decode_f32 = Get Float -> ByteString -> Float
forall a. Get a -> ByteString -> a
Binary.Get.runGet Get Float
Binary.Get.getFloatbe

-- | Little-endian variant of 'decode_f32'.
decode_f32_le :: ByteString.Lazy.ByteString -> Float
decode_f32_le :: ByteString -> Float
decode_f32_le = Get Float -> ByteString -> Float
forall a. Get a -> ByteString -> a
Binary.Get.runGet Get Float
Binary.Get.getFloatle

-- | Decode a 64-bit IEEE floating point number.
decode_f64 :: ByteString.Lazy.ByteString -> Double
decode_f64 :: ByteString -> Double
decode_f64 = Get Double -> ByteString -> Double
forall a. Get a -> ByteString -> a
Binary.Get.runGet Get Double
Binary.Get.getDoublebe

-- * Decode/Ascii

-- | Decode an Ascii string, inverse of 'encode_ascii'.
decode_ascii :: ByteString.Lazy.ByteString -> ByteString.Char8.ByteString
{-# INLINE decode_ascii #-}
decode_ascii :: ByteString -> ByteString
decode_ascii = String -> ByteString
ByteString.Char8.pack (String -> ByteString)
-> (ByteString -> String) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
ByteString.Lazy.Char8.unpack

-- * IO

-- | Read /n/ bytes from /h/ and run /f/.
read_decode :: (ByteString.Lazy.ByteString -> t) -> Int -> Handle -> IO t
read_decode :: forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> t
f Int
n = (ByteString -> t) -> IO ByteString -> IO t
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> t
f (IO ByteString -> IO t)
-> (Handle -> IO ByteString) -> Handle -> IO t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Handle -> Int -> IO ByteString) -> Int -> Handle -> IO ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip Handle -> Int -> IO ByteString
ByteString.Lazy.hGet Int
n

-- | Type-specialised reader for 'Binary.decode'.
read_word32 :: Handle -> IO Word32
read_word32 :: Handle -> IO Word32
read_word32 = (ByteString -> Word32) -> Int -> Handle -> IO Word32
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Word32
forall a. Binary a => ByteString -> a
Binary.decode Int
4

-- | 'read_decode' of 'decode_word32_le'.
read_word32_le :: Handle -> IO Word32
read_word32_le :: Handle -> IO Word32
read_word32_le = (ByteString -> Word32) -> Int -> Handle -> IO Word32
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Word32
decode_word32_le Int
4

-- | 'ByteString.Lazy.hPut' of 'encode_word32'.
write_word32 :: Handle -> Word32 -> IO ()
write_word32 :: Handle -> Word32 -> IO ()
write_word32 Handle
h = Handle -> ByteString -> IO ()
ByteString.Lazy.hPut Handle
h (ByteString -> IO ()) -> (Word32 -> ByteString) -> Word32 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ByteString
encode_word32

-- | 'ByteString.Lazy.hPut' of 'encode_word32_le'.
write_word32_le :: Handle -> Word32 -> IO ()
write_word32_le :: Handle -> Word32 -> IO ()
write_word32_le Handle
h = Handle -> ByteString -> IO ()
ByteString.Lazy.hPut Handle
h (ByteString -> IO ()) -> (Word32 -> ByteString) -> Word32 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ByteString
encode_word32_le

-- * Io/Int

-- | 'decode_i8' of 'ByteString.Lazy.hGet'.
read_i8 :: Handle -> IO Int
read_i8 :: Handle -> IO Int
read_i8 = (ByteString -> Int) -> Int -> Handle -> IO Int
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Int
decode_i8 Int
1

-- | 'decode_i16' of 'ByteString.Lazy.hGet'.
read_i16 :: Handle -> IO Int
read_i16 :: Handle -> IO Int
read_i16 = (ByteString -> Int) -> Int -> Handle -> IO Int
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Int
decode_i16 Int
2

-- | 'decode_i32' of 'ByteString.Lazy.hGet'.
read_i32 :: Handle -> IO Int
read_i32 :: Handle -> IO Int
read_i32 = (ByteString -> Int) -> Int -> Handle -> IO Int
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Int
decode_i32 Int
4

-- | 'decode_i32_le' of 'ByteString.Lazy.hGet'.
read_i32_le :: Handle -> IO Int
read_i32_le :: Handle -> IO Int
read_i32_le = (ByteString -> Int) -> Int -> Handle -> IO Int
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Int
decode_i32_le Int
4

-- | 'decode_u32' of 'ByteString.Lazy.hGet'.
read_u32 :: Handle -> IO Int
read_u32 :: Handle -> IO Int
read_u32 = (ByteString -> Int) -> Int -> Handle -> IO Int
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Int
decode_u32 Int
4

-- | 'decode_u32_le' of 'ByteString.Lazy.hGet'.
read_u32_le :: Handle -> IO Int
read_u32_le :: Handle -> IO Int
read_u32_le = (ByteString -> Int) -> Int -> Handle -> IO Int
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Int
decode_u32_le Int
4

-- | 'ByteString.Lazy.hPut' of 'encode_u32'.
write_u32 :: Handle -> Int -> IO ()
write_u32 :: Handle -> Int -> IO ()
write_u32 Handle
h = Handle -> ByteString -> IO ()
ByteString.Lazy.hPut Handle
h (ByteString -> IO ()) -> (Int -> ByteString) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString
encode_u32

-- | 'ByteString.Lazy.hPut' of 'encode_u32_le'.
write_u32_le :: Handle -> Int -> IO ()
write_u32_le :: Handle -> Int -> IO ()
write_u32_le Handle
h = Handle -> ByteString -> IO ()
ByteString.Lazy.hPut Handle
h (ByteString -> IO ()) -> (Int -> ByteString) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString
encode_u32_le

-- * Io/Float

-- | 'decode_f32' of 'ByteString.Lazy.hGet'.
read_f32 :: Handle -> IO Float
read_f32 :: Handle -> IO Float
read_f32 = (ByteString -> Float) -> Int -> Handle -> IO Float
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Float
decode_f32 Int
4

-- | 'decode_f32_le' of 'ByteString.Lazy.hGet'.
read_f32_le :: Handle -> IO Float
read_f32_le :: Handle -> IO Float
read_f32_le = (ByteString -> Float) -> Int -> Handle -> IO Float
forall t. (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> Float
decode_f32_le Int
4

-- * Io/Ascii

-- | Read u8 length prefixed Ascii string (pascal string).
read_pstr :: Handle -> IO ByteString.Char8.ByteString
read_pstr :: Handle -> IO ByteString
read_pstr Handle
h = do
  Int
n <- (ByteString -> Int) -> IO ByteString -> IO Int
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Int
decode_u8 (Handle -> Int -> IO ByteString
ByteString.Lazy.hGet Handle
h Int
1)
  (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
decode_ascii (Handle -> Int -> IO ByteString
ByteString.Lazy.hGet Handle
h Int
n)

-- * Util

{- | Bundle header as a (strict) 'ByteString.Char8.ByteString'.

>>> ByteString.Char8.length bundleHeader_strict
8
-}
bundleHeader_strict :: ByteString.Char8.ByteString
bundleHeader_strict :: ByteString
bundleHeader_strict = String -> ByteString
ByteString.Char8.pack String
"#bundle\0"

{- | Bundle header as a lazy ByteString.

>>> ByteString.Lazy.length bundleHeader
8
-}
bundleHeader :: ByteString.Lazy.ByteString
{-# INLINE bundleHeader #-}
bundleHeader :: ByteString
bundleHeader = [ByteString] -> ByteString
ByteString.Lazy.Char8.fromChunks [ByteString
bundleHeader_strict]

{- | 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]
-}
align :: (Num i, Bits i) => i -> i
{-# INLINE align #-}
align :: forall i. (Num i, Bits i) => i -> i
align i
n = ((i
n i -> i -> i
forall a. Num a => a -> a -> a
+ i
3) i -> i -> i
forall a. Bits a => a -> a -> a
.&. i -> i
forall a. Bits a => a -> a
complement i
3) i -> i -> i
forall a. Num a => a -> a -> a
- i
n

-- * ByteString

-- | Is machine little endian?
isLittleEndian :: Bool
isLittleEndian :: Bool
isLittleEndian = ByteOrder
GHC.ByteOrder.targetByteOrder ByteOrder -> ByteOrder -> Bool
forall a. Eq a => a -> a -> Bool
== ByteOrder
GHC.ByteOrder.LittleEndian

-- | Byte-swap byte string in four-byte segments.
byteStringSwap32BitWords :: ByteString.ByteString -> ByteString.ByteString
byteStringSwap32BitWords :: ByteString -> ByteString
byteStringSwap32BitWords ByteString
xs =
  Int -> [Word8] -> ByteString
ByteString.Internal.unsafePackLenBytes
    (ByteString -> Int
ByteString.length ByteString
xs Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4)
    [ ByteString -> Int -> Word8
ByteString.Unsafe.unsafeIndex ByteString
xs (Int -> Word8) -> Int -> Word8
forall a b. (a -> b) -> a -> b
$ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
j
    | Int
i <- [Int
0 .. ByteString -> Int
ByteString.length ByteString
xs Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
    , Int
j <- [Int
3, Int
2, Int
1, Int
0]
    ]

-- | If target is little-endian, swap bytes to be in network order, else identity.
byteString32BitNetworkOrder :: ByteString.ByteString -> ByteString.ByteString
byteString32BitNetworkOrder :: ByteString -> ByteString
byteString32BitNetworkOrder ByteString
x = if Bool
isLittleEndian then ByteString -> ByteString
byteStringSwap32BitWords ByteString
x else ByteString
x