module Data.Streaming.Zlib
(
Inflate
, initInflate
, initInflateWithDictionary
, feedInflate
, finishInflate
, flushInflate
, Deflate
, initDeflate
, initDeflateWithDictionary
, feedDeflate
, finishDeflate
, flushDeflate
, WindowBits (..)
, defaultWindowBits
, ZlibException (..)
, Popper
, PopperRes (..)
) where
import Data.Streaming.Zlib.Lowlevel
import Foreign.ForeignPtr
import Foreign.C.Types
import Data.ByteString.Unsafe
import Codec.Compression.Zlib (WindowBits(WindowBits), defaultWindowBits)
import qualified Data.ByteString as S
import Data.ByteString.Lazy.Internal (defaultChunkSize)
import Control.Monad (when)
import Data.Typeable (Typeable)
import Control.Exception (Exception)
type ZStreamPair = (ForeignPtr ZStreamStruct, ForeignPtr CChar)
newtype Inflate = Inflate (ZStreamPair, Maybe S.ByteString)
newtype Deflate = Deflate ZStreamPair
data ZlibException = ZlibException Int
deriving (Show, Typeable)
instance Exception ZlibException
zNeedDict :: CInt
zNeedDict = 2
zBufError :: CInt
zBufError = 5
initInflate :: WindowBits -> IO Inflate
initInflate w = do
zstr <- zstreamNew
inflateInit2 zstr w
fzstr <- newForeignPtr c_free_z_stream_inflate zstr
fbuff <- mallocForeignPtrBytes defaultChunkSize
withForeignPtr fbuff $ \buff ->
c_set_avail_out zstr buff $ fromIntegral defaultChunkSize
return $ Inflate ((fzstr, fbuff), Nothing)
initInflateWithDictionary :: WindowBits -> S.ByteString -> IO Inflate
initInflateWithDictionary w bs = do
zstr <- zstreamNew
inflateInit2 zstr w
fzstr <- newForeignPtr c_free_z_stream_inflate zstr
fbuff <- mallocForeignPtrBytes defaultChunkSize
withForeignPtr fbuff $ \buff ->
c_set_avail_out zstr buff $ fromIntegral defaultChunkSize
return $ Inflate ((fzstr, fbuff), Just bs)
initDeflate :: Int
-> WindowBits -> IO Deflate
initDeflate level w = do
zstr <- zstreamNew
deflateInit2 zstr level w 8 StrategyDefault
fzstr <- newForeignPtr c_free_z_stream_deflate zstr
fbuff <- mallocForeignPtrBytes defaultChunkSize
withForeignPtr fbuff $ \buff ->
c_set_avail_out zstr buff $ fromIntegral defaultChunkSize
return $ Deflate (fzstr, fbuff)
initDeflateWithDictionary :: Int
-> S.ByteString
-> WindowBits -> IO Deflate
initDeflateWithDictionary level bs w = do
zstr <- zstreamNew
deflateInit2 zstr level w 8 StrategyDefault
fzstr <- newForeignPtr c_free_z_stream_deflate zstr
fbuff <- mallocForeignPtrBytes defaultChunkSize
unsafeUseAsCStringLen bs $ \(cstr, len) -> do
c_call_deflate_set_dictionary zstr cstr $ fromIntegral len
withForeignPtr fbuff $ \buff ->
c_set_avail_out zstr buff $ fromIntegral defaultChunkSize
return $ Deflate (fzstr, fbuff)
feedInflate
:: Inflate
-> S.ByteString
-> IO Popper
feedInflate (Inflate ((fzstr, fbuff), inflateDictionary)) bs = do
withForeignPtr fzstr $ \zstr ->
unsafeUseAsCStringLen bs $ \(cstr, len) ->
c_set_avail_in zstr cstr $ fromIntegral len
return $ drain fbuff fzstr (Just bs) inflate False
where
inflate zstr = do
res <- c_call_inflate_noflush zstr
if (res == zNeedDict)
then maybe (return zNeedDict)
(\dict -> (unsafeUseAsCStringLen dict $ \(cstr, len) -> do
c_call_inflate_set_dictionary zstr cstr $ fromIntegral len
c_call_inflate_noflush zstr))
inflateDictionary
else return res
type Popper = IO PopperRes
data PopperRes = PRDone
| PRNext !S.ByteString
| PRError !ZlibException
deriving (Show, Typeable)
keepAlive :: Maybe S.ByteString -> IO a -> IO a
keepAlive Nothing = id
keepAlive (Just bs) = unsafeUseAsCStringLen bs . const
drain :: ForeignPtr CChar
-> ForeignPtr ZStreamStruct
-> Maybe S.ByteString
-> (ZStream' -> IO CInt)
-> Bool
-> Popper
drain fbuff fzstr mbs func isFinish = withForeignPtr fzstr $ \zstr -> keepAlive mbs $ do
res <- func zstr
if res < 0 && res /= zBufError
then return $ PRError $ ZlibException $ fromIntegral res
else do
avail <- c_get_avail_out zstr
let size = defaultChunkSize fromIntegral avail
toOutput = avail == 0 || (isFinish && size /= 0)
if toOutput
then withForeignPtr fbuff $ \buff -> do
bs <- S.packCStringLen (buff, size)
c_set_avail_out zstr buff
$ fromIntegral defaultChunkSize
return $ PRNext bs
else return PRDone
finishInflate :: Inflate -> IO S.ByteString
finishInflate (Inflate ((fzstr, fbuff), _)) =
withForeignPtr fzstr $ \zstr ->
withForeignPtr fbuff $ \buff -> do
avail <- c_get_avail_out zstr
let size = defaultChunkSize fromIntegral avail
bs <- S.packCStringLen (buff, size)
c_set_avail_out zstr buff $ fromIntegral defaultChunkSize
return bs
flushInflate :: Inflate -> IO S.ByteString
flushInflate = finishInflate
feedDeflate :: Deflate -> S.ByteString -> IO Popper
feedDeflate (Deflate (fzstr, fbuff)) bs = do
withForeignPtr fzstr $ \zstr ->
unsafeUseAsCStringLen bs $ \(cstr, len) -> do
c_set_avail_in zstr cstr $ fromIntegral len
return $ drain fbuff fzstr (Just bs) c_call_deflate_noflush False
finishDeflate :: Deflate -> Popper
finishDeflate (Deflate (fzstr, fbuff)) =
drain fbuff fzstr Nothing c_call_deflate_finish True
flushDeflate :: Deflate -> Popper
flushDeflate (Deflate (fzstr, fbuff)) =
drain fbuff fzstr Nothing c_call_deflate_flush True