{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Data.Conduit.Zlib (
compress, decompress, gzip, ungzip,
compressFlush, decompressFlush,
multiple,
WindowBits (..), defaultWindowBits
) where
import Data.Streaming.Zlib
import Data.Conduit
import Data.ByteString (ByteString)
import qualified Data.ByteString as S
import Control.Monad (unless, liftM)
import Control.Monad.Trans.Class (lift, MonadTrans)
import Control.Monad.Primitive (PrimMonad, unsafePrimToPrim)
import Control.Monad.Trans.Resource (MonadThrow, throwM)
import Data.Function (fix)
gzip :: (MonadThrow m, PrimMonad m) => ConduitT ByteString ByteString m ()
gzip = compress (-1) (WindowBits 31)
ungzip :: (PrimMonad m, MonadThrow m) => ConduitT ByteString ByteString m ()
ungzip = decompress (WindowBits 31)
unsafeLiftIO :: (PrimMonad m, MonadThrow m) => IO a -> m a
unsafeLiftIO = unsafePrimToPrim
decompress
:: (PrimMonad m, MonadThrow m)
=> WindowBits
-> ConduitT ByteString ByteString m ()
decompress =
helperDecompress (liftM (fmap Chunk) await) yield' leftover
where
yield' Flush = return ()
yield' (Chunk bs) = yield bs
decompressFlush
:: (PrimMonad m, MonadThrow m)
=> WindowBits
-> ConduitT (Flush ByteString) (Flush ByteString) m ()
decompressFlush = helperDecompress await yield (leftover . Chunk)
helperDecompress :: (Monad (t m), PrimMonad m, MonadThrow m, MonadTrans t)
=> t m (Maybe (Flush ByteString))
-> (Flush ByteString -> t m ())
-> (ByteString -> t m ())
-> WindowBits
-> t m ()
helperDecompress await' yield' leftover' config = do
inf <- lift $ unsafeLiftIO $ initInflate config
let
flush = do
chunk <- lift $ unsafeLiftIO $ flushInflate inf
unless (S.null chunk) $ yield' $ Chunk chunk
getUnused = lift $ unsafeLiftIO $ getUnusedInflate inf
unused = do
rem' <- getUnused
unless (S.null rem') $ leftover' rem'
fix $ \feeder -> do
mnext <- await'
case mnext of
Nothing -> do
flush
unused
Just (Chunk x) -> do
popper <- lift $ unsafeLiftIO $ feedInflate inf x
fix $ \pop -> do
mbs <- lift $ unsafeLiftIO popper
case mbs of
PRDone -> do
rem' <- getUnused
if S.null rem'
then feeder
else do
flush
leftover' rem'
PRNext bs -> do
yield' (Chunk bs)
pop
PRError e -> lift $ throwM e
Just Flush -> do
flush
yield' Flush
feeder
compress
:: (PrimMonad m, MonadThrow m)
=> Int
-> WindowBits
-> ConduitT ByteString ByteString m ()
compress =
helperCompress (liftM (fmap Chunk) await) yield'
where
yield' Flush = return ()
yield' (Chunk bs) = yield bs
compressFlush
:: (PrimMonad m, MonadThrow m)
=> Int
-> WindowBits
-> ConduitT (Flush ByteString) (Flush ByteString) m ()
compressFlush = helperCompress await yield
helperCompress :: (Monad (t m), PrimMonad m, MonadThrow m, MonadTrans t)
=> t m (Maybe (Flush ByteString))
-> (Flush ByteString -> t m ())
-> Int
-> WindowBits
-> t m ()
helperCompress await' yield' level config =
await' >>= maybe (return ()) start
where
start input = do
def <- lift $ unsafeLiftIO $ initDeflate level config
push def input
continue def = await' >>= maybe (close def) (push def)
goPopper popper = do
mbs <- lift $ unsafeLiftIO popper
case mbs of
PRDone -> return ()
PRNext bs -> yield' (Chunk bs) >> goPopper popper
PRError e -> lift $ throwM e
push def (Chunk x) = do
popper <- lift $ unsafeLiftIO $ feedDeflate def x
goPopper popper
continue def
push def Flush = do
mchunk <- lift $ unsafeLiftIO $ flushDeflate def
case mchunk of
PRDone -> return ()
PRNext x -> yield' $ Chunk x
PRError e -> lift $ throwM e
yield' Flush
continue def
close def = do
mchunk <- lift $ unsafeLiftIO $ finishDeflate def
case mchunk of
PRDone -> return ()
PRNext chunk -> yield' (Chunk chunk) >> close def
PRError e -> lift $ throwM e
multiple :: Monad m
=> ConduitT ByteString a m ()
-> ConduitT ByteString a m ()
multiple inner =
loop
where
loop = do
mbs <- await
case mbs of
Nothing -> return ()
Just bs
| S.null bs -> loop
| otherwise -> do
leftover bs
inner
loop