module Compression.Level ( CompressionLevel (..) , toCompressor , toFileCompressor ) where #ifdef BROTLI import qualified Codec.Compression.Brotli as Br #endif import qualified Codec.Compression.BZip as BZip import qualified Codec.Compression.GZip as GZip import qualified Codec.Compression.Lzma as Lzma import qualified Codec.Compression.Lzo as Lzo #ifdef SNAPPY import qualified Codec.Compression.Snappy.BSL as Snappy #endif import qualified Codec.Compression.Zlib as Zlib import qualified Codec.Compression.Zstd.Lazy as Zstd import qualified Codec.Lz4 as Lz4 import qualified Codec.Lzip as Lzip import Compression.Type import qualified Data.ByteString.Lazy as BSL data CompressionLevel = Best | Fastest | Default | Custom !Int levelGuard :: (Int, Int) -> Int -> Int levelGuard (min', max') lvl | lvl < min' || lvl > max' = error ("Invalid compression level. Compression must be between " ++ show min' ++ " and " ++ show max') | otherwise = lvl gzipCompression :: Int -> GZip.CompressParams gzipCompression lvl = GZip.defaultCompressParams { GZip.compressLevel = GZip.compressionLevel lvl } zlibCompression :: Int -> Zlib.CompressParams zlibCompression lvl = Zlib.defaultCompressParams { Zlib.compressLevel = Zlib.compressionLevel lvl } lzmaCompression :: Int -> Lzma.CompressParams lzmaCompression lvl = Lzma.defaultCompressParams { Lzma.compressLevel = toEnum lvl } #ifdef BROTLI brotliCompression :: Int -> Br.CompressParams brotliCompression lvl = Br.defaultCompressParams { Br.compressLevel = toEnum lvl } #endif toInt :: Compression -> CompressionLevel -> Int #ifdef SNAPPY toInt Snappy _ = undefined #endif toInt Lzo _ = undefined #ifdef BROTLI toInt Brotli Fastest = fromEnum (minBound :: Br.CompressionLevel) toInt Brotli (Custom i) = levelGuard (0,11) i toInt Brotli _ = fromEnum (maxBound :: Br.CompressionLevel) #endif toInt Zstd Best = Zstd.maxCLevel toInt Zstd Fastest = 1 toInt Zstd (Custom i) = levelGuard (1, Zstd.maxCLevel) i toInt Zstd Default = 3 toInt Lzip Best = fromEnum (maxBound :: Lzip.CompressionLevel) toInt Lzip Fastest = fromEnum (minBound :: Lzip.CompressionLevel) toInt Lzip (Custom i) = levelGuard (0, 9) i toInt Lzip Default = 6 toInt Lzma Best = 9 toInt Lzma Fastest = 0 toInt Lzma (Custom i) = levelGuard (0, 9) i toInt Lzma Default = 6 toInt BZip Best = 9 toInt BZip Fastest = 1 toInt BZip (Custom i) = i toInt BZip Default = 7 toInt GZip Best = 9 toInt GZip Fastest = 0 toInt GZip (Custom i) = i toInt GZip Default = 6 toInt Z Best = 9 toInt Z Fastest = 0 toInt Z (Custom i) = i toInt Z Default = 6 toInt Lz4 Best = Lz4.lZ4HCClevelMax toInt Lz4 Fastest = 0 toInt Lz4 (Custom i) = levelGuard (0, Lz4.lZ4HCClevelMax) i toInt Lz4 Default = 0 -- 1? toInt None _ = error "Internal error." toFileCompressor :: Compression -> CompressionLevel -> FilePath -> IO BSL.ByteString toFileCompressor Lzip lvl = Lzip.compressFileLevel (toEnum $ toInt Lzip lvl) toFileCompressor x lvl = fmap (toCompressor x lvl Nothing) . BSL.readFile toCompressor :: Compression -> CompressionLevel -> Maybe Int -> BSL.ByteString -> BSL.ByteString toCompressor Lzma lvl _ = Lzma.compressWith (lzmaCompression $ toInt Lzma lvl) toCompressor Lzip lvl (Just sz) = flip (Lzip.compressWithSz (toEnum $ toInt Lzip lvl)) sz toCompressor Lzip _ _ = error "Internal error." toCompressor BZip lvl _ = BZip.compressWith (fromIntegral $ toInt BZip lvl) 30 toCompressor GZip lvl _ = GZip.compressWith (gzipCompression $ toInt GZip lvl) toCompressor Z lvl _ = Zlib.compressWith (zlibCompression $ toInt Z lvl) toCompressor Zstd lvl _ = Zstd.compress (toInt Zstd lvl) toCompressor Lz4 lvl _ = Lz4.compressSz (toInt Lz4 lvl) #ifdef BROTLI toCompressor Brotli lvl _ = Br.compressWith (brotliCompression $ toInt Brotli lvl) #endif #ifdef SNAPPY toCompressor Snappy _ _ = Snappy.compress #endif toCompressor Lzo _ _ = Lzo.compressFile toCompressor None _ _ = id