module Codec.Compression.Utils where import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as BS import Data.ByteString.Base (LazyByteString(LPS)) import Data.Word (Word8) genericSplitAtExactly :: Integral a => a -> [b] -> Maybe ([b], [b]) genericSplitAtExactly 0 xs = return ([], xs) genericSplitAtExactly (n+1) (x:xs) = do (ys, zs) <- genericSplitAtExactly n xs return (x:ys, zs) genericSplitAtExactly _ _ = Nothing genericSplitAtExactlyBS :: Integral a => a -> ByteString -> Maybe (ByteString, ByteString) genericSplitAtExactlyBS i bs = let i' = fromIntegral i in if i' > BS.length bs then Nothing else Just (BS.splitAt i' bs) headTail :: ByteString -> Maybe (Word8, ByteString) headTail bs = if BS.null bs then Nothing else Just (BS.head bs, BS.tail bs) -- XXX The real append is too strict myAppend :: ByteString -> ByteString -> ByteString myAppend (LPS xs) (LPS ys) = LPS (xs ++ ys)