module Sound.OSC.Coding.Byte where
import Data.Bits
import Data.Int
import Data.Word
import System.IO
import qualified Data.Binary as Binary
import qualified Data.Binary.Get as Get
import qualified Data.Binary.Put as Put
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as S.C
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as L.C
import qualified Sound.OSC.Coding.Cast as Cast
import Sound.OSC.Coding.Convert
encode_int8 :: Int8 -> L.ByteString
encode_int8 :: Int8 -> ByteString
encode_int8 = Int8 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode
encode_int16 :: Int16 -> L.ByteString
encode_int16 :: Int16 -> ByteString
encode_int16 = Int16 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode
encode_int16_le :: Int16 -> L.ByteString
encode_int16_le :: Int16 -> ByteString
encode_int16_le = Put -> ByteString
Put.runPut (Put -> ByteString) -> (Int16 -> Put) -> Int16 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Put
Put.putInt16le
encode_int64 :: Int64 -> L.ByteString
encode_int64 :: Int64 -> ByteString
encode_int64 = Int64 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode
encode_word8 :: Word8 -> L.ByteString
encode_word8 :: Word8 -> ByteString
encode_word8 = Word8 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode
encode_word16 :: Word16 -> L.ByteString
encode_word16 :: Word16 -> ByteString
encode_word16 = Word16 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode
encode_word16_le :: Word16 -> L.ByteString
encode_word16_le :: Word16 -> ByteString
encode_word16_le = Put -> ByteString
Put.runPut (Put -> ByteString) -> (Word16 -> Put) -> Word16 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Put
Put.putWord16le
encode_word32 :: Word32 -> L.ByteString
encode_word32 :: Word32 -> ByteString
encode_word32 = Word32 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode
encode_word32_le :: Word32 -> L.ByteString
encode_word32_le :: Word32 -> ByteString
encode_word32_le = Put -> ByteString
Put.runPut (Put -> ByteString) -> (Word32 -> Put) -> Word32 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Put
Put.putWord32le
encode_word64 :: Word64 -> L.ByteString
encode_word64 :: Word64 -> ByteString
encode_word64 = Word64 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode
encode_i8 :: Int -> L.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
int_to_int8
encode_u8 :: Int -> L.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
int_to_word8
encode_u16 :: Int -> L.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
int_to_word16
encode_u16_le :: Int -> L.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
int_to_word16
encode_i16 :: Int -> L.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
int_to_int16
encode_i32 :: Int -> L.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
int_to_int32
encode_u32 :: Int -> L.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
int_to_word32
encode_u32_le :: Int -> L.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
int_to_word32
encode_f32 :: Float -> L.ByteString
encode_f32 :: Float -> ByteString
encode_f32 = Word32 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode (Word32 -> ByteString) -> (Float -> Word32) -> Float -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Word32
Cast.f32_w32
encode_f32_le :: Float -> L.ByteString
encode_f32_le :: Float -> ByteString
encode_f32_le = Put -> ByteString
Put.runPut (Put -> ByteString) -> (Float -> Put) -> Float -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Put
Put.putWord32le (Word32 -> Put) -> (Float -> Word32) -> Float -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Word32
Cast.f32_w32
encode_f64 :: Double -> L.ByteString
encode_f64 :: Double -> ByteString
encode_f64 = Word64 -> ByteString
forall a. Binary a => a -> ByteString
Binary.encode (Word64 -> ByteString)
-> (Double -> Word64) -> Double -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Word64
Cast.f64_w64
encode_f64_le :: Double -> L.ByteString
encode_f64_le :: Double -> ByteString
encode_f64_le = Put -> ByteString
Put.runPut (Put -> ByteString) -> (Double -> Put) -> Double -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Put
Put.putWord64le (Word64 -> Put) -> (Double -> Word64) -> Double -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Word64
Cast.f64_w64
encode_ascii :: S.C.ByteString -> L.ByteString
encode_ascii :: ByteString -> ByteString
encode_ascii = [Word8] -> ByteString
L.pack ([Word8] -> ByteString)
-> (ByteString -> [Word8]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
S.unpack
decode_word16 :: L.ByteString -> Word16
decode_word16 :: ByteString -> Word16
decode_word16 = ByteString -> Word16
forall a. Binary a => ByteString -> a
Binary.decode
decode_word16_le :: L.ByteString -> Word16
decode_word16_le :: ByteString -> Word16
decode_word16_le = Get Word16 -> ByteString -> Word16
forall a. Get a -> ByteString -> a
Get.runGet Get Word16
Get.getWord16le
decode_int16 :: L.ByteString -> Int16
decode_int16 :: ByteString -> Int16
decode_int16 = ByteString -> Int16
forall a. Binary a => ByteString -> a
Binary.decode
decode_word32 :: L.ByteString -> Word32
decode_word32 :: ByteString -> Word32
decode_word32 = ByteString -> Word32
forall a. Binary a => ByteString -> a
Binary.decode
decode_word32_le :: L.ByteString -> Word32
decode_word32_le :: ByteString -> Word32
decode_word32_le = Get Word32 -> ByteString -> Word32
forall a. Get a -> ByteString -> a
Get.runGet Get Word32
Get.getWord32le
decode_int64 :: L.ByteString -> Int64
decode_int64 :: ByteString -> Int64
decode_int64 = ByteString -> Int64
forall a. Binary a => ByteString -> a
Binary.decode
decode_word64 :: L.ByteString -> Word64
decode_word64 :: ByteString -> Word64
decode_word64 = ByteString -> Word64
forall a. Binary a => ByteString -> a
Binary.decode
decode_u8 :: L.ByteString -> Int
decode_u8 :: ByteString -> Int
decode_u8 = Word8 -> Int
word8_to_int (Word8 -> Int) -> (ByteString -> Word8) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word8
L.head
decode_i8 :: L.ByteString -> Int
decode_i8 :: ByteString -> Int
decode_i8 = Int8 -> Int
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_u16 :: L.ByteString -> Int
decode_u16 :: ByteString -> Int
decode_u16 = Word16 -> Int
word16_to_int (Word16 -> Int) -> (ByteString -> Word16) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word16
decode_word16
decode_u16_le :: L.ByteString -> Int
decode_u16_le :: ByteString -> Int
decode_u16_le = Word16 -> Int
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_i16 :: L.ByteString -> Int
decode_i16 :: ByteString -> Int
decode_i16 = Int16 -> Int
int16_to_int (Int16 -> Int) -> (ByteString -> Int16) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Int16
decode_int16
decode_i16_le :: L.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
L.reverse
decode_i32 :: L.ByteString -> Int
decode_i32 :: ByteString -> Int
decode_i32 = Int32 -> Int
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
decode_i32_le :: L.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
L.reverse
decode_u32 :: L.ByteString -> Int
decode_u32 :: ByteString -> Int
decode_u32 = Word32 -> Int
word32_to_int (Word32 -> Int) -> (ByteString -> Word32) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word32
decode_word32
decode_u32_le :: L.ByteString -> Int
decode_u32_le :: ByteString -> Int
decode_u32_le = Word32 -> Int
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_f32 :: L.ByteString -> Float
decode_f32 :: ByteString -> Float
decode_f32 = Word32 -> Float
Cast.w32_f32 (Word32 -> Float) -> (ByteString -> Word32) -> ByteString -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word32
decode_word32
decode_f32_le :: L.ByteString -> Float
decode_f32_le :: ByteString -> Float
decode_f32_le = Word32 -> Float
Cast.w32_f32 (Word32 -> Float) -> (ByteString -> Word32) -> ByteString -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Word32
decode_word32_le
decode_f64 :: L.ByteString -> Double
decode_f64 :: ByteString -> Double
decode_f64 ByteString
b = Word64 -> Double
Cast.w64_f64 (ByteString -> Word64
forall a. Binary a => ByteString -> a
Binary.decode ByteString
b :: Word64)
decode_ascii :: L.ByteString -> S.C.ByteString
{-# INLINE decode_ascii #-}
decode_ascii :: ByteString -> ByteString
decode_ascii = String -> ByteString
S.C.pack (String -> ByteString)
-> (ByteString -> String) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
L.C.unpack
read_decode :: (L.ByteString -> t) -> Int -> Handle -> IO t
read_decode :: (ByteString -> t) -> Int -> Handle -> IO t
read_decode ByteString -> t
f Int
n = (ByteString -> t) -> IO ByteString -> IO t
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
L.hGet Int
n
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_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
write_word32 :: Handle -> Word32 -> IO ()
write_word32 :: Handle -> Word32 -> IO ()
write_word32 Handle
h = Handle -> ByteString -> IO ()
L.hPut Handle
h (ByteString -> IO ()) -> (Word32 -> ByteString) -> Word32 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ByteString
encode_word32
write_word32_le :: Handle -> Word32 -> IO ()
write_word32_le :: Handle -> Word32 -> IO ()
write_word32_le Handle
h = Handle -> ByteString -> IO ()
L.hPut Handle
h (ByteString -> IO ()) -> (Word32 -> ByteString) -> Word32 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ByteString
encode_word32_le
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
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
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
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
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
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
write_u32 :: Handle -> Int -> IO ()
write_u32 :: Handle -> Int -> IO ()
write_u32 Handle
h = Handle -> ByteString -> IO ()
L.hPut Handle
h (ByteString -> IO ()) -> (Int -> ByteString) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString
encode_u32
write_u32_le :: Handle -> Int -> IO ()
write_u32_le :: Handle -> Int -> IO ()
write_u32_le Handle
h = Handle -> ByteString -> IO ()
L.hPut Handle
h (ByteString -> IO ()) -> (Int -> ByteString) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString
encode_u32_le
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
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
read_pstr :: Handle -> IO S.C.ByteString
read_pstr :: Handle -> IO ByteString
read_pstr Handle
h = do
Int
n <- (ByteString -> Int) -> IO ByteString -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Int
decode_u8 (Handle -> Int -> IO ByteString
L.hGet Handle
h Int
1)
(ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
decode_ascii (Handle -> Int -> IO ByteString
L.hGet Handle
h Int
n)
bundleHeader_strict :: S.C.ByteString
= String -> ByteString
S.C.pack String
"#bundle\0"
bundleHeader :: L.ByteString
{-# INLINE bundleHeader #-}
= [ByteString] -> ByteString
L.C.fromChunks [ByteString
bundleHeader_strict]
align :: (Num i,Bits i) => i -> i
{-# INLINE align #-}
align :: 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