{-# LANGUAGE Rank2Types #-}
module Codec.Compression.Zlib.Lens
(
gzipped,
zlibbed,
deflated,
compressed,
Format,
gzip,
zlib,
deflate,
zlibbed',
gzipped',
deflated',
compressed',
Params,
defaultParams,
levelC,
methodC,
windowBitsC,
windowBitsD,
memoryLevelC,
strategyC,
bufferSizeC,
bufferSizeD,
dictionary,
CompressionLevel,
defaultCompression,
noCompression,
bestSpeed,
bestCompression,
compressionLevel,
Method,
deflateMethod,
WindowBits,
defaultWindowBits,
windowBits,
MemoryLevel,
defaultMemoryLevel,
minMemoryLevel,
maxMemoryLevel,
memoryLevel,
CompressionStrategy,
defaultStrategy,
filteredStrategy,
huffmanOnlyStrategy
) where
import Control.Applicative
import Codec.Compression.Zlib.Internal
import Control.Lens
import qualified Data.ByteString as S (ByteString)
import qualified Data.ByteString.Lazy as L (ByteString)
zlib :: Format
zlib = zlibFormat
{-# INLINE zlib #-}
gzip :: Format
gzip = gzipFormat
{-# INLINE gzip #-}
deflate :: Format
deflate = rawFormat
{-# INLINE deflate #-}
gzipped :: Iso' L.ByteString L.ByteString
gzipped = compressed gzip
{-# INLINE gzipped #-}
zlibbed :: Iso' L.ByteString L.ByteString
zlibbed = compressed zlib
{-# INLINE zlibbed #-}
deflated :: Iso' L.ByteString L.ByteString
deflated = compressed deflate
{-# INLINE deflated #-}
compressed :: Format -> Iso' L.ByteString L.ByteString
compressed fmt = compressed' fmt defaultParams
{-# INLINE compressed #-}
gzipped' :: Params -> Iso' L.ByteString L.ByteString
gzipped' = compressed' gzip
{-# INLINE gzipped' #-}
zlibbed' :: Params -> Iso' L.ByteString L.ByteString
zlibbed' = compressed' zlib
{-# INLINE zlibbed' #-}
deflated' :: Params -> Iso' L.ByteString L.ByteString
deflated' = compressed' deflate
{-# INLINE deflated' #-}
compressed' :: Format -> Params -> Iso' L.ByteString L.ByteString
compressed' fmt (Params c d) = iso (compress fmt c) (decompress fmt d)
{-# INLINE compressed' #-}
data Params = Params !CompressParams !DecompressParams
defaultParams :: Params
defaultParams = Params defaultCompressParams defaultDecompressParams
{-# INLINE defaultParams #-}
levelC :: Lens' Params CompressionLevel
levelC = \ f (Params c d) -> (\l -> Params (c {compressLevel = l}) d) <$> f (compressLevel c)
{-# INLINE levelC #-}
methodC :: Lens' Params Method
methodC = \ f (Params c d) -> (\m -> Params (c {compressMethod = m}) d) <$> f (compressMethod c)
{-# INLINE methodC #-}
windowBitsC :: Lens' Params WindowBits
windowBitsC = \ f (Params c d) -> (\wb -> Params (c {compressWindowBits = wb}) d) <$> f (compressWindowBits c)
{-# INLINE windowBitsC #-}
windowBitsD :: Lens' Params WindowBits
windowBitsD = \ f (Params c d) -> (\wb -> Params c (d {decompressWindowBits = wb})) <$> f (decompressWindowBits d)
{-# INLINE windowBitsD #-}
memoryLevelC :: Lens' Params MemoryLevel
memoryLevelC = \ f (Params c d) -> (\ml -> Params (c {compressMemoryLevel = ml}) d) <$> f (compressMemoryLevel c)
{-# INLINE memoryLevelC #-}
strategyC :: Lens' Params CompressionStrategy
strategyC = \ f (Params c d) -> (\s -> Params (c {compressStrategy = s}) d) <$> f (compressStrategy c)
{-# INLINE strategyC #-}
bufferSizeC :: Lens' Params Int
bufferSizeC = \ f (Params c d) -> (\bs -> Params (c {compressBufferSize = bs}) d) <$> f (compressBufferSize c)
{-# INLINE bufferSizeC #-}
bufferSizeD :: Lens' Params Int
bufferSizeD = \ f (Params c d) -> (\bs -> Params c (d {decompressBufferSize = bs})) <$> f (decompressBufferSize d)
{-# INLINE bufferSizeD #-}
dictionary :: Lens' Params (Maybe S.ByteString)
dictionary = \f (Params c d) -> (\mbs -> Params (c {compressDictionary = mbs}) (d {decompressDictionary = mbs})) <$> f (compressDictionary c <|> decompressDictionary d)
{-# INLINE dictionary #-}