module Codec.Compression.Lzma
(
compress
, decompress
, compressWith
, decompressWith
, CompressStream(..)
, compressIO
, compressST
, DecompressStream(..)
, decompressIO
, decompressST
, LzmaRet(..)
, defaultCompressParams
, CompressParams
, compressIntegrityCheck
, compressLevel
, compressLevelExtreme
, IntegrityCheck(..)
, CompressionLevel(..)
, defaultDecompressParams
, DecompressParams
, decompressTellNoCheck
, decompressTellUnsupportedCheck
, decompressTellAnyCheck
, decompressConcatenated
, decompressAutoDecoder
, decompressMemLimit
) where
import Control.Exception
import Control.Monad
import Control.Monad.ST (stToIO)
import Control.Monad.ST.Lazy (ST, runST, strictToLazyST)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Lazy.Internal as BSL
import LibLzma
decompress :: BSL.ByteString -> BSL.ByteString
decompress = decompressWith defaultDecompressParams
decompressWith :: DecompressParams -> BSL.ByteString -> BSL.ByteString
decompressWith parms input = runST (decompress' input)
where
decompress' :: BSL.ByteString -> ST s BSL.ByteString
decompress' ibs0 = loop ibs0 =<< decompressST parms
where
loop BSL.Empty (DecompressStreamEnd rest)
| BS.null rest = return BSL.Empty
| otherwise = fail "Codec.Compression.Lzma.decompressWith: trailing data"
loop (BSL.Chunk _ _) (DecompressStreamEnd _) =
fail "Codec.Compression.Lzma.decompressWith: trailing data"
loop _ (DecompressStreamError e) =
fail ("Codec.Compression.Lzma.decompressWith: decoding error " ++ show e)
loop BSL.Empty (DecompressInputRequired supply) =
loop BSL.Empty =<< supply BS.empty
loop (BSL.Chunk c bs') (DecompressInputRequired supply) =
loop bs' =<< supply c
loop ibs (DecompressOutputAvailable oc next) = do
obs <- loop ibs =<< next
return (BSL.chunk oc obs)
compress :: BSL.ByteString -> BSL.ByteString
compress = compressWith defaultCompressParams
compressWith :: CompressParams -> BSL.ByteString -> BSL.ByteString
compressWith parms input = runST (compress' input)
where
compress' :: BSL.ByteString -> ST s BSL.ByteString
compress' ibs0 = loop ibs0 =<< compressST parms
where
loop BSL.Empty CompressStreamEnd =
return BSL.Empty
loop (BSL.Chunk _ _) CompressStreamEnd =
fail "Codec.Compression.Lzma.compressWith: the impossible happened"
loop BSL.Empty (CompressInputRequired _ supply) =
loop BSL.Empty =<< supply BS.empty
loop (BSL.Chunk c bs') (CompressInputRequired _ supply) =
loop bs' =<< supply c
loop ibs (CompressOutputAvailable oc next) = do
obs <- loop ibs =<< next
return (BSL.chunk oc obs)
data CompressStream m =
CompressInputRequired (m (CompressStream m))
(ByteString -> m (CompressStream m))
| CompressOutputAvailable !ByteString (m (CompressStream m))
| CompressStreamEnd
compressIO :: CompressParams -> IO (CompressStream IO)
compressIO parms = (stToIO $ newEncodeLzmaStream parms) >>= either throwIO go
where
bUFSIZ = 32752
go :: LzmaStream -> IO (CompressStream IO)
go ls = return inputRequired
where
inputRequired = CompressInputRequired goFlush (withChunk goFinish goInput)
goInput :: ByteString -> IO (CompressStream IO)
goInput chunk = do
(rc, used, obuf) <- stToIO $ runLzmaStream ls chunk LzmaRun bUFSIZ
let chunk' = BS.drop used chunk
case rc of
LzmaRetOK
| BS.null obuf -> do
unless (used > 0) $
fail "compressIO: input chunk not consumed"
withChunk (return inputRequired) goInput chunk'
| otherwise -> return (CompressOutputAvailable obuf
(withChunk (return inputRequired) goInput chunk'))
_ -> throwIO rc
goFlush, goFinish :: IO (CompressStream IO)
goFlush = goSync LzmaSyncFlush (return inputRequired)
goFinish = goSync LzmaFinish (return CompressStreamEnd)
goSync :: LzmaAction -> IO (CompressStream IO) -> IO (CompressStream IO)
goSync LzmaRun _ = fail "goSync called with invalid argument"
goSync action next = goSync'
where
goSync' = do
(rc, 0, obuf) <- stToIO $ runLzmaStream ls BS.empty action bUFSIZ
case rc of
LzmaRetOK
| BS.null obuf -> fail ("compressIO: empty output chunk during " ++ show action)
| otherwise -> return (CompressOutputAvailable obuf goSync')
LzmaRetStreamEnd
| BS.null obuf -> next
| otherwise -> return (CompressOutputAvailable obuf next)
_ -> throwIO rc
compressST :: CompressParams -> ST s (CompressStream (ST s))
compressST parms = strictToLazyST (newEncodeLzmaStream parms) >>= either throw go
where
bUFSIZ = 32752
go ls = return inputRequired
where
inputRequired = CompressInputRequired goFlush (withChunk goFinish goInput)
goInput :: ByteString -> ST s (CompressStream (ST s))
goInput chunk = do
(rc, used, obuf) <- strictToLazyST $ runLzmaStream ls chunk LzmaRun bUFSIZ
let chunk' = BS.drop used chunk
case rc of
LzmaRetOK
| BS.null obuf -> do
unless (used > 0) $
fail "compressST: input chunk not consumed"
withChunk (return inputRequired) goInput chunk'
| otherwise -> return (CompressOutputAvailable obuf
(withChunk (return inputRequired) goInput chunk'))
_ -> throw rc
goFlush, goFinish :: ST s (CompressStream (ST s))
goFlush = goSync LzmaSyncFlush (return inputRequired)
goFinish = goSync LzmaFinish (return CompressStreamEnd)
goSync :: LzmaAction -> ST s (CompressStream (ST s)) -> ST s (CompressStream (ST s))
goSync LzmaRun _ = fail "compressST: goSync called with invalid argument"
goSync action next = goSync'
where
goSync' = do
(rc, 0, obuf) <- strictToLazyST $ runLzmaStream ls BS.empty action bUFSIZ
case rc of
LzmaRetOK
| BS.null obuf -> fail ("compressIO: empty output chunk during " ++ show action)
| otherwise -> return (CompressOutputAvailable obuf goSync')
LzmaRetStreamEnd
| BS.null obuf -> next
| otherwise -> return (CompressOutputAvailable obuf next)
_ -> throw rc
data DecompressStream m =
DecompressInputRequired (ByteString -> m (DecompressStream m))
| DecompressOutputAvailable !ByteString (m (DecompressStream m))
| DecompressStreamEnd ByteString
| DecompressStreamError !LzmaRet
decompressIO :: DecompressParams -> IO (DecompressStream IO)
decompressIO parms = stToIO (newDecodeLzmaStream parms) >>= either (return . DecompressStreamError) go
where
bUFSIZ = 32752
go :: LzmaStream -> IO (DecompressStream IO)
go ls = return inputRequired
where
inputRequired = DecompressInputRequired goInput
goInput :: ByteString -> IO (DecompressStream IO)
goInput chunk
| BS.null chunk = goFinish
| otherwise = do
(rc, used, obuf) <- stToIO $ runLzmaStream ls chunk LzmaRun bUFSIZ
let chunk' = BS.drop used chunk
case rc of
LzmaRetOK
| BS.null obuf -> do
unless (used > 0) $
fail "decompressIO: input chunk not consumed"
withChunk (return inputRequired) goInput chunk'
| otherwise -> return (DecompressOutputAvailable obuf
(withChunk goDrain goInput chunk'))
LzmaRetStreamEnd
| BS.null obuf -> return (DecompressStreamEnd chunk')
| otherwise -> return (DecompressOutputAvailable obuf
(return (DecompressStreamEnd chunk')))
_ -> return (DecompressStreamError rc)
goDrain, goFinish :: IO (DecompressStream IO)
goDrain = goSync LzmaRun (return inputRequired)
goFinish = goSync LzmaFinish (return $ DecompressStreamError LzmaRetOK)
goSync :: LzmaAction -> IO (DecompressStream IO) -> IO (DecompressStream IO)
goSync action next = goSync'
where
goSync' = do
(rc, 0, obuf) <- stToIO $ runLzmaStream ls BS.empty action bUFSIZ
case rc of
LzmaRetOK
| BS.null obuf -> next
| otherwise -> return (DecompressOutputAvailable obuf goSync')
LzmaRetStreamEnd
| BS.null obuf -> eof0
| otherwise -> return (DecompressOutputAvailable obuf eof0)
_ -> return (DecompressStreamError rc)
eof0 = return $ DecompressStreamEnd BS.empty
decompressST :: DecompressParams -> ST s (DecompressStream (ST s))
decompressST parms = strictToLazyST (newDecodeLzmaStream parms) >>= either (return . DecompressStreamError) go
where
bUFSIZ = 32752
go :: LzmaStream -> ST s (DecompressStream (ST s))
go ls = return inputRequired
where
inputRequired = DecompressInputRequired goInput
goInput :: ByteString -> ST s (DecompressStream (ST s))
goInput chunk
| BS.null chunk = goFinish
| otherwise = do
(rc, used, obuf) <- strictToLazyST $ runLzmaStream ls chunk LzmaRun bUFSIZ
let chunk' = BS.drop used chunk
case rc of
LzmaRetOK
| BS.null obuf -> do
unless (used > 0) $
fail "decompressST: input chunk not consumed"
withChunk (return inputRequired) goInput chunk'
| otherwise -> return (DecompressOutputAvailable obuf
(withChunk goDrain goInput chunk'))
LzmaRetStreamEnd
| BS.null obuf -> return (DecompressStreamEnd chunk')
| otherwise -> return (DecompressOutputAvailable obuf
(return (DecompressStreamEnd chunk')))
_ -> return (DecompressStreamError rc)
goDrain, goFinish :: ST s (DecompressStream (ST s))
goDrain = goSync LzmaRun (return inputRequired)
goFinish = goSync LzmaFinish (return $ DecompressStreamError LzmaRetOK)
goSync :: LzmaAction -> ST s (DecompressStream (ST s)) -> ST s (DecompressStream (ST s))
goSync action next = goSync'
where
goSync' = do
(rc, 0, obuf) <- strictToLazyST $ runLzmaStream ls BS.empty action bUFSIZ
case rc of
LzmaRetOK
| BS.null obuf -> next
| otherwise -> return (DecompressOutputAvailable obuf goSync')
LzmaRetStreamEnd
| BS.null obuf -> eof0
| otherwise -> return (DecompressOutputAvailable obuf eof0)
_ -> return (DecompressStreamError rc)
eof0 = return $ DecompressStreamEnd BS.empty
withChunk :: t -> (ByteString -> t) -> ByteString -> t
withChunk emptyChunk nemptyChunk chunk
| BS.null chunk = emptyChunk
| otherwise = nemptyChunk chunk