Safe Haskell | None |
---|---|
Language | Haskell2010 |
Codec.Compression.LZ4.Conduit
Contents
Description
TODO: Implement:
- Block checksumming
- Dictionary support
Synopsis
- data Lz4FrameException = Lz4FormatException String
- data BlockSizeID
- data BlockMode
- data ContentChecksum
- data BlockChecksum
- data FrameType
- data FrameInfo = FrameInfo {}
- data Preferences = Preferences {}
- lz4DefaultPreferences :: Preferences
- compress :: (MonadUnliftIO m, MonadResource m) => ConduitT ByteString ByteString m ()
- compressYieldImmediately :: (MonadUnliftIO m, MonadResource m) => ConduitT ByteString ByteString m ()
- compressWithOutBufferSize :: forall m. (MonadUnliftIO m, MonadResource m) => CSize -> ConduitT ByteString ByteString m ()
- decompress :: (MonadUnliftIO m, MonadResource m) => ConduitT ByteString ByteString m ()
- bsChunksOf :: Int -> ByteString -> [ByteString]
- newtype Lz4FrameCompressionContext = Lz4FrameCompressionContext {}
- newtype ScopedLz4FrameCompressionContext = ScopedLz4FrameCompressionContext {}
- newtype ScopedLz4FramePreferencesPtr = ScopedLz4FramePreferencesPtr {}
- newtype Lz4FramePreferencesPtr = Lz4FramePreferencesPtr {}
- newtype Lz4FrameDecompressionContext = Lz4FrameDecompressionContext {}
- lz4fCreatePreferences :: IO Lz4FramePreferencesPtr
- lz4fCreateCompressonContext :: HasCallStack => IO Lz4FrameCompressionContext
- lz4fCreateDecompressionContext :: HasCallStack => IO Lz4FrameDecompressionContext
- withScopedLz4fPreferences :: HasCallStack => (ScopedLz4FramePreferencesPtr -> IO a) -> IO a
- withScopedLz4fCompressionContext :: HasCallStack => (ScopedLz4FrameCompressionContext -> IO a) -> IO a
Documentation
data Lz4FrameException Source #
Constructors
Lz4FormatException String |
Instances
data BlockSizeID Source #
Constructors
LZ4F_default | |
LZ4F_max64KB | |
LZ4F_max256KB | |
LZ4F_max1MB | |
LZ4F_max4MB |
Instances
Constructors
LZ4F_blockLinked | |
LZ4F_blockIndependent |
Instances
Eq BlockMode Source # | |
Ord BlockMode Source # | |
Show BlockMode Source # | |
Storable BlockMode Source # | |
Defined in Codec.Compression.LZ4.CTypes |
data ContentChecksum Source #
Constructors
LZ4F_noContentChecksum | |
LZ4F_contentChecksumEnabled |
Instances
data BlockChecksum Source #
Constructors
LZ4F_noBlockChecksum | |
LZ4F_blockChecksumEnabled |
Instances
Constructors
LZ4F_frame | |
LZ4F_skippableFrame |
Instances
Eq FrameType Source # | |
Ord FrameType Source # | |
Show FrameType Source # | |
Storable FrameType Source # | |
Defined in Codec.Compression.LZ4.CTypes |
Constructors
FrameInfo | |
Fields
|
Instances
Storable FrameInfo Source # | |
Defined in Codec.Compression.LZ4.CTypes |
data Preferences Source #
Constructors
Preferences | |
Fields
|
Instances
Storable Preferences Source # | |
Defined in Codec.Compression.LZ4.CTypes Methods sizeOf :: Preferences -> Int # alignment :: Preferences -> Int # peekElemOff :: Ptr Preferences -> Int -> IO Preferences # pokeElemOff :: Ptr Preferences -> Int -> Preferences -> IO () # peekByteOff :: Ptr b -> Int -> IO Preferences # pokeByteOff :: Ptr b -> Int -> Preferences -> IO () # peek :: Ptr Preferences -> IO Preferences # poke :: Ptr Preferences -> Preferences -> IO () # |
compress :: (MonadUnliftIO m, MonadResource m) => ConduitT ByteString ByteString m () Source #
compressYieldImmediately :: (MonadUnliftIO m, MonadResource m) => ConduitT ByteString ByteString m () Source #
Compresses the incoming stream of ByteStrings with the lz4 frame format.
Yields every LZ4 output as a ByteString as soon as the lz4 frame library produces it.
Note that this does not imply ZL4 frame autoFlush (which affects when the lz4 frame library produces outputs).
compressWithOutBufferSize :: forall m. (MonadUnliftIO m, MonadResource m) => CSize -> ConduitT ByteString ByteString m () Source #
Compresses the incoming stream of ByteStrings with the lz4 frame format.
This function implements two optimisations to reduce unnecessary allocations:
- Incoming ByteStrings are processed in blocks of 16 KB, allowing us to use a single intermediate output buffer through the lifetime of the conduit.
- The
bufferSize
of the output buffer can controlled by the caller via thebufferSize
argument, to reduce the number of smallByteString
s beingyield
ed (especially in the case that the input data compresses very well, e.g. a stream of zeros).
Note that the given bufferSize
is not a hard limit, it can only be
used to *increase* the amount of output buffer we're allowed to use:
The function will choose `max(bufferSize, minBufferSizeNeededByLz4)`
as the eventual output buffer size.
Setting `bufferSize = 0` is the legitimate way to set the output buffer size to be the minimum required to compress 16 KB inputs and is still a fast default.
decompress :: (MonadUnliftIO m, MonadResource m) => ConduitT ByteString ByteString m () Source #
bsChunksOf :: Int -> ByteString -> [ByteString] Source #
Internals
newtype Lz4FrameCompressionContext Source #
Constructors
Lz4FrameCompressionContext | |
Fields |
Instances
newtype ScopedLz4FrameCompressionContext Source #
Constructors
ScopedLz4FrameCompressionContext | |
Instances
newtype ScopedLz4FramePreferencesPtr Source #
Constructors
ScopedLz4FramePreferencesPtr | |
Fields |
Instances
newtype Lz4FramePreferencesPtr Source #
Constructors
Lz4FramePreferencesPtr | |
Instances
newtype Lz4FrameDecompressionContext Source #
Constructors
Lz4FrameDecompressionContext | |
Fields |
Instances
withScopedLz4fPreferences :: HasCallStack => (ScopedLz4FramePreferencesPtr -> IO a) -> IO a Source #
withScopedLz4fCompressionContext :: HasCallStack => (ScopedLz4FrameCompressionContext -> IO a) -> IO a Source #