{-# LANGUAGE CPP,TypeSynonymInstances #-} module ByteStream where import qualified Data.ByteString.Lazy as BS import Data.Bits(shiftR,(.&.)) import Utils2(Split(..)) import RGB class Bytes a where bytes :: a -> BS.ByteString bytelist :: a -> [Byte] bytelist = BS.unpack . bytes list2bytes :: [a] -> BS.ByteString list2bytes xs = BS.concat (map bytes xs) list2bytelist :: [a] -> [Byte] list2bytelist = BS.unpack . list2bytes class FromBytes a where #if MIN_VERSION_base(4,13,0) fromBytes :: MonadFail m => BS.ByteString -> m a #else fromBytes :: Monad m => BS.ByteString -> m a #endif putBytes x = BS.putStr (bytes x) hPutBytes h = BS.hPut h . bytes writeBytes path = BS.writeFile path . bytes getBytes :: FromBytes a => IO a getBytes = fromBytes =<< BS.getContents hGetBytes h = fromBytes =<< BS.hGetContents h readBytes path = fromBytes =<< BS.readFile path instance Bytes a => Bytes [a] where bytes = list2bytes bytelist = list2bytelist instance (Bytes a,Bytes b,Bytes c) => Bytes (a,b,c) where bytes (x,y,z) = BS.concat [bytes x,bytes y,bytes z] instance Bytes Byte where bytes = BS.singleton bytelist b = [b] list2bytes = BS.pack list2bytelist = id instance Bytes Short where bytes = bytes . be16 -- Big endian! instance Bytes BS.ByteString where bytes = id list2bytes = BS.concat instance FromBytes BS.ByteString where fromBytes = pure instance Bytes Bool where bytes = BS.singleton . toEnum . fromEnum list2bytes = BS.pack . bools2bytes instance Bytes c => Bytes (RGB c) where bytes (RGB r g b) = bytes (r,g,b) instance Split BS.ByteString where isEmpty = BS.null splitAt n = BS.splitAt (fromIntegral n) instance Unpack BS.ByteString where unpack = BS.unpack be32 x = bytes $ reverse (le32 x) be16 x = bytes $ reverse (le16 x) le16 x = take 2 (le x) :: [Byte] le32 x = take 4 (le x) :: [Byte] le n = chr (n .&. 0xff) : le (shiftR n 8) chr x = toEnum (fromIntegral x)