module Sound.OSC.Coding.Byte where
import Data.Binary
import Data.Bits
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 Data.Int
import Sound.OSC.Coding.Cast
import Sound.OSC.Type
encode_i8 :: Int -> L.ByteString
encode_i8 n = encode (fromIntegral n :: Int8)
encode_u8 :: Int -> L.ByteString
encode_u8 n = encode (fromIntegral n :: Word8)
encode_i16 :: Int -> L.ByteString
encode_i16 n = encode (fromIntegral n :: Int16)
encode_i32 :: Int -> L.ByteString
encode_i32 n = encode (fromIntegral n :: Int32)
encode_u32 :: Int -> L.ByteString
encode_u32 n = encode (fromIntegral n :: Word32)
encode_i64 :: Int64 -> L.ByteString
encode_i64 = encode
encode_u64 :: Word64 -> L.ByteString
encode_u64 = encode
encode_f32 :: Float -> L.ByteString
encode_f32 = encode . f32_w32
encode_f64 :: Double -> L.ByteString
encode_f64 = encode . f64_w64
encode_str :: ASCII -> L.ByteString
encode_str = L.pack . S.unpack
decode_u8 :: L.ByteString -> Int
decode_u8 = fromIntegral . L.head
decode_i8 :: L.ByteString -> Int
decode_i8 b = fromIntegral (decode b :: Int8)
decode_i16 :: L.ByteString -> Int
decode_i16 b = fromIntegral (decode b :: Int16)
decode_i32 :: L.ByteString -> Int
decode_i32 b = fromIntegral (decode b :: Int32)
decode_u32 :: L.ByteString -> Int
decode_u32 b = fromIntegral (decode b :: Word32)
decode_i64 :: L.ByteString -> Int64
decode_i64 = decode
decode_u64 :: L.ByteString -> Word64
decode_u64 = decode
decode_f32 :: L.ByteString -> Float
decode_f32 b = w32_f32 (decode b :: Word32)
decode_f64 :: L.ByteString -> Double
decode_f64 b = w64_f64 (decode b :: Word64)
decode_str :: L.ByteString -> ASCII
decode_str = S.C.pack . L.C.unpack
bundleHeader_strict :: S.C.ByteString
bundleHeader_strict = S.C.pack "#bundle\0"
bundleHeader :: L.ByteString
bundleHeader = L.C.fromChunks [bundleHeader_strict]
align :: (Num i,Bits i) => i -> i
align n = ((n + 3) .&. complement 3) n