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 = Binary.encode
encode_int16 :: Int16 -> L.ByteString
encode_int16 = Binary.encode
encode_int16_le :: Int16 -> L.ByteString
encode_int16_le = Put.runPut . Put.putInt16le
encode_int64 :: Int64 -> L.ByteString
encode_int64 = Binary.encode
encode_word8 :: Word8 -> L.ByteString
encode_word8 = Binary.encode
encode_word16 :: Word16 -> L.ByteString
encode_word16 = Binary.encode
encode_word16_le :: Word16 -> L.ByteString
encode_word16_le = Put.runPut . Put.putWord16le
encode_word32 :: Word32 -> L.ByteString
encode_word32 = Binary.encode
encode_word32_le :: Word32 -> L.ByteString
encode_word32_le = Put.runPut . Put.putWord32le
encode_word64 :: Word64 -> L.ByteString
encode_word64 = Binary.encode
encode_i8 :: Int -> L.ByteString
encode_i8 = encode_int8 . int_to_int8
encode_u8 :: Int -> L.ByteString
encode_u8 = encode_word8 . int_to_word8
encode_u16 :: Int -> L.ByteString
encode_u16 = encode_word16 . int_to_word16
encode_u16_le :: Int -> L.ByteString
encode_u16_le = encode_word16_le . int_to_word16
encode_i16 :: Int -> L.ByteString
encode_i16 = Binary.encode . int_to_int16
encode_i32 :: Int -> L.ByteString
encode_i32 = Binary.encode . int_to_int32
encode_u32 :: Int -> L.ByteString
encode_u32 = encode_word32 . int_to_word32
encode_u32_le :: Int -> L.ByteString
encode_u32_le = encode_word32_le . int_to_word32
encode_f32 :: Float -> L.ByteString
encode_f32 = Binary.encode . Cast.f32_w32
encode_f32_le :: Float -> L.ByteString
encode_f32_le = Put.runPut . Put.putWord32le . Cast.f32_w32
encode_f64 :: Double -> L.ByteString
encode_f64 = Binary.encode . Cast.f64_w64
encode_f64_le :: Double -> L.ByteString
encode_f64_le = Put.runPut . Put.putWord64le . Cast.f64_w64
encode_ascii :: S.C.ByteString -> L.ByteString
encode_ascii = L.pack . S.unpack
decode_word16 :: L.ByteString -> Word16
decode_word16 = Binary.decode
decode_word16_le :: L.ByteString -> Word16
decode_word16_le = Get.runGet Get.getWord16le
decode_int16 :: L.ByteString -> Int16
decode_int16 = Binary.decode
decode_word32 :: L.ByteString -> Word32
decode_word32 = Binary.decode
decode_word32_le :: L.ByteString -> Word32
decode_word32_le = Get.runGet Get.getWord32le
decode_int64 :: L.ByteString -> Int64
decode_int64 = Binary.decode
decode_word64 :: L.ByteString -> Word64
decode_word64 = Binary.decode
decode_u8 :: L.ByteString -> Int
decode_u8 = word8_to_int . L.head
decode_i8 :: L.ByteString -> Int
decode_i8 = int8_to_int . Binary.decode
decode_u16 :: L.ByteString -> Int
decode_u16 = word16_to_int . decode_word16
decode_u16_le :: L.ByteString -> Int
decode_u16_le = word16_to_int . decode_word16_le
decode_i16 :: L.ByteString -> Int
decode_i16 = int16_to_int . decode_int16
decode_i16_le :: L.ByteString -> Int
decode_i16_le = decode_i16 . L.reverse
decode_i32 :: L.ByteString -> Int
decode_i32 = int32_to_int . Binary.decode
decode_i32_le :: L.ByteString -> Int
decode_i32_le = decode_i32 . L.reverse
decode_u32 :: L.ByteString -> Int
decode_u32 = word32_to_int . decode_word32
decode_u32_le :: L.ByteString -> Int
decode_u32_le = word32_to_int . decode_word32_le
decode_f32 :: L.ByteString -> Float
decode_f32 = Cast.w32_f32 . decode_word32
decode_f32_le :: L.ByteString -> Float
decode_f32_le = Cast.w32_f32 . decode_word32_le
decode_f64 :: L.ByteString -> Double
decode_f64 b = Cast.w64_f64 (Binary.decode b :: Word64)
decode_ascii :: L.ByteString -> S.C.ByteString
{-# INLINE decode_ascii #-}
decode_ascii = S.C.pack . L.C.unpack
read_decode :: (L.ByteString -> t) -> Int -> Handle -> IO t
read_decode f n = fmap f . flip L.hGet n
read_word32 :: Handle -> IO Word32
read_word32 = read_decode Binary.decode 4
read_word32_le :: Handle -> IO Word32
read_word32_le = read_decode decode_word32_le 4
write_word32 :: Handle -> Word32 -> IO ()
write_word32 h = L.hPut h . encode_word32
write_word32_le :: Handle -> Word32 -> IO ()
write_word32_le h = L.hPut h . encode_word32_le
read_i8 :: Handle -> IO Int
read_i8 = read_decode decode_i8 1
read_i16 :: Handle -> IO Int
read_i16 = read_decode decode_i16 2
read_i32 :: Handle -> IO Int
read_i32 = read_decode decode_i32 4
read_i32_le :: Handle -> IO Int
read_i32_le = read_decode decode_i32_le 4
read_u32 :: Handle -> IO Int
read_u32 = read_decode decode_u32 4
read_u32_le :: Handle -> IO Int
read_u32_le = read_decode decode_u32_le 4
write_u32 :: Handle -> Int -> IO ()
write_u32 h = L.hPut h . encode_u32
write_u32_le :: Handle -> Int -> IO ()
write_u32_le h = L.hPut h . encode_u32_le
read_f32 :: Handle -> IO Float
read_f32 = read_decode decode_f32 4
read_f32_le :: Handle -> IO Float
read_f32_le = read_decode decode_f32_le 4
read_pstr :: Handle -> IO S.C.ByteString
read_pstr h = do
n <- fmap decode_u8 (L.hGet h 1)
fmap decode_ascii (L.hGet h n)
bundleHeader_strict :: S.C.ByteString
bundleHeader_strict = S.C.pack "#bundle\0"
bundleHeader :: L.ByteString
{-# INLINE bundleHeader #-}
bundleHeader = L.C.fromChunks [bundleHeader_strict]
align :: (Num i,Bits i) => i -> i
{-# INLINE align #-}
align n = ((n + 3) .&. complement 3) - n