Copyright | (c) 2016-present Facebook Inc. All rights reserved. |
---|---|
License | BSD3 |
Maintainer | bryano@fb.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Low-level bindings to the native zstd compression library. These bindings make almost no effort to provide any additional safety or ease of use above that of the C library. Unless you have highly specialized needs, you should use the streaming or base APIs instead.
To correctly use the functions in this module, you must read the
API documentation in the zstd library's zstd.h
include file. It
would also be wise to search elsewhere in this package for uses of
the functions you are interested in.
Synopsis
- compress :: Ptr dst -> CSize -> Ptr src -> CSize -> CInt -> IO CSize
- compressBound :: CSize -> IO CSize
- maxCLevel :: Int
- decompress :: Ptr dst -> CSize -> Ptr src -> CSize -> IO CSize
- getDecompressedSize :: Ptr src -> CSize -> IO CULLong
- data CCtx
- createCCtx :: IO (Ptr CCtx)
- freeCCtx :: Ptr CCtx -> IO ()
- p_freeCCtx :: FunPtr (Ptr CCtx -> IO ())
- compressCCtx :: Ptr CCtx -> Ptr dst -> CSize -> Ptr src -> CSize -> CInt -> IO CSize
- data DCtx
- createDCtx :: IO (Ptr DCtx)
- freeDCtx :: Ptr DCtx -> IO ()
- p_freeDCtx :: FunPtr (Ptr DCtx -> IO ())
- decompressDCtx :: Ptr DCtx -> Ptr dst -> CSize -> Ptr src -> CSize -> IO CSize
- isError :: CSize -> Bool
- getErrorName :: CSize -> String
- checkError :: IO CSize -> IO (Either String CSize)
- checkAlloc :: String -> IO (Ptr a) -> IO (Ptr a)
- data CStream
- data DStream
- data Buffer io = Buffer {}
- data In
- data Out
- cstreamInSize :: CSize
- cstreamOutSize :: CSize
- createCStream :: IO (Ptr CStream)
- freeCStream :: Ptr CStream -> IO ()
- p_freeCStream :: FunPtr (Ptr CStream -> IO ())
- initCStream :: Ptr CStream -> CInt -> IO CSize
- compressStream :: Ptr CStream -> Ptr (Buffer Out) -> Ptr (Buffer In) -> IO CSize
- endStream :: Ptr CStream -> Ptr (Buffer Out) -> IO CSize
- dstreamInSize :: CSize
- dstreamOutSize :: CSize
- createDStream :: IO (Ptr DStream)
- initDStream :: Ptr DStream -> IO CSize
- decompressStream :: Ptr DStream -> Ptr (Buffer Out) -> Ptr (Buffer In) -> IO CSize
- freeDStream :: Ptr DStream -> IO ()
- p_freeDStream :: FunPtr (Ptr DStream -> IO ())
- trainFromBuffer :: Ptr dict -> CSize -> Ptr samples -> Ptr CSize -> CUInt -> IO CSize
- getDictID :: Ptr dict -> CSize -> IO CUInt
- compressUsingDict :: Ptr CCtx -> Ptr dst -> CSize -> Ptr src -> CSize -> Ptr dict -> CSize -> CInt -> IO CSize
- decompressUsingDict :: Ptr DCtx -> Ptr dst -> CSize -> Ptr src -> CSize -> Ptr dict -> CSize -> IO CSize
- data CDict
- createCDict :: Ptr dict -> CSize -> CInt -> IO (Ptr CDict)
- freeCDict :: Ptr CDict -> IO ()
- p_freeCDict :: FunPtr (Ptr CDict -> IO ())
- compressUsingCDict :: Ptr CCtx -> Ptr dst -> CSize -> Ptr src -> CSize -> Ptr CDict -> IO CSize
- data DDict
- createDDict :: Ptr dict -> CSize -> IO (Ptr DDict)
- freeDDict :: Ptr DDict -> IO ()
- p_freeDDict :: FunPtr (Ptr DDict -> IO ())
- decompressUsingDDict :: Ptr DCtx -> Ptr dst -> CSize -> Ptr src -> CSize -> Ptr DDict -> IO CSize
- c_maxCLevel :: CInt
One-shot functions
:: Ptr dst | Destination buffer. |
-> CSize | Capacity of destination buffer. |
-> Ptr src | Source buffer. |
-> CSize | Size of source buffer. |
-> CInt | Compression level. |
-> IO CSize |
Compress bytes from source buffer into destination buffer. The destination buffer must be already allocated.
Returns the number of bytes written into destination buffer, or an
error code if it fails (which can be tested using isError
).
Compute the maximum compressed size of given source buffer.
:: Ptr dst | Destination buffer. |
-> CSize | Capacity of destination buffer. |
-> Ptr src | Source buffer. |
-> CSize | Size of compressed input. This must be exact, so for example supplying the size of a buffer that is larger than the compressed input will cause a failure. |
-> IO CSize |
Decompress a buffer. The destination buffer must be already allocated.
Returns the number of bytes written into destination buffer, or an
error code if it fails (which can be tested using isError
).
getDecompressedSize :: Ptr src -> CSize -> IO CULLong Source #
Returns the decompressed size of a compressed payload if known, 0 otherwise.
To discover precisely why a result is 0, follow up with
getFrameParams
.
Cheaper operations using contexts
Compression
p_freeCCtx :: FunPtr (Ptr CCtx -> IO ()) Source #
Free a compression context. For use by a finalizer.
:: Ptr CCtx | Compression context. |
-> Ptr dst | Destination buffer. |
-> CSize | Capacity of destination buffer. |
-> Ptr src | Source buffer. |
-> CSize | Size of source buffer. |
-> CInt | Compression level. |
-> IO CSize |
Compress bytes from source buffer into destination buffer. The destination buffer must be already allocated.
Returns the number of bytes written into destination buffer, or an
error code if it fails (which can be tested using isError
).
Decompression
p_freeDCtx :: FunPtr (Ptr DCtx -> IO ()) Source #
Free a decompression context. For use by a finalizer.
:: Ptr DCtx | Decompression context. |
-> Ptr dst | Destination buffer. |
-> CSize | Capacity of destination buffer. |
-> Ptr src | Source buffer. |
-> CSize | Size of compressed input. This must be exact, so for example supplying the size of a buffer that is larger than the compressed input will cause a failure. |
-> IO CSize |
Decompress a buffer. The destination buffer must be already allocated.
Returns the number of bytes written into destination buffer, or an
error code if it fails (which can be tested using isError
).
Result and error checks
getErrorName :: CSize -> String Source #
Gives the description associated with an error code.
checkError :: IO CSize -> IO (Either String CSize) Source #
Check whether a CSize
has an error encoded in it (yuck!), and
report success or failure more safely.
checkAlloc :: String -> IO (Ptr a) -> IO (Ptr a) Source #
Check that an allocating operation is successful. If it fails,
throw an IOError
.
Streaming operations
Streaming types
A streaming buffer type. The type parameter statically indicates whether the buffer is used to track an input or output buffer.
Buffer | |
|
Instances
Storable (Buffer io) Source # | |
Defined in Codec.Compression.Zstd.FFI.Types |
Streaming compression
cstreamInSize :: CSize Source #
Recommended size for input buffer.
cstreamOutSize :: CSize Source #
Recommended size for output buffer.
createCStream :: IO (Ptr CStream) Source #
Create a streaming compression context. This must be freed using
freeCStream
, or if using a finalizer, with p_freeCStream
.
p_freeCStream :: FunPtr (Ptr CStream -> IO ()) Source #
Free a CStream
value. For use by a finalizer.
Begin a new compression operation.
compressStream :: Ptr CStream -> Ptr (Buffer Out) -> Ptr (Buffer In) -> IO CSize Source #
Consume part or all of an input.
endStream :: Ptr CStream -> Ptr (Buffer Out) -> IO CSize Source #
End a compression stream. This performs a flush and writes a frame epilogue.
Streaming decompression
dstreamInSize :: CSize Source #
Recommended size for input buffer.
dstreamOutSize :: CSize Source #
Recommended size for output buffer.
createDStream :: IO (Ptr DStream) Source #
Create a streaming decompression context. This must be freed using
freeDStream
, or if using a finalizer, with p_freeDStream
.
decompressStream :: Ptr DStream -> Ptr (Buffer Out) -> Ptr (Buffer In) -> IO CSize Source #
Consume part or all of an input.
p_freeDStream :: FunPtr (Ptr DStream -> IO ()) Source #
Free a CStream
value. For use by a finalizer.
Dictionary-based compression
:: Ptr dict | Preallocated dictionary buffer. |
-> CSize | Capacity of dictionary buffer. |
-> Ptr samples | Concatenated samples. |
-> Ptr CSize | Array of sizes of samples. |
-> CUInt | Number of samples. |
-> IO CSize |
Train a dictionary from a collection of samples. Returns the number size of the resulting dictionary.
Return the identifier for the given dictionary, or zero if not a valid dictionary.
:: Ptr CCtx | Compression context. |
-> Ptr dst | Destination buffer. |
-> CSize | Capacity of destination buffer. |
-> Ptr src | Source buffer. |
-> CSize | Size of source buffer. |
-> Ptr dict | Dictionary. |
-> CSize | Size of dictionary. |
-> CInt | Compression level. |
-> IO CSize |
Compress bytes from source buffer into destination buffer, using a prebuilt dictionary. The destination buffer must be already allocated.
Returns the number of bytes written into destination buffer, or an
error code if it fails (which can be tested using isError
).
:: Ptr DCtx | Decompression context. |
-> Ptr dst | Destination buffer. |
-> CSize | Capacity of destination buffer. |
-> Ptr src | Source buffer. |
-> CSize | Size of compressed input. This must be exact, so for example supplying the size of a buffer that is larger than the compressed input will cause a failure. |
-> Ptr dict | Dictionary. |
-> CSize | Size of dictionary. |
-> IO CSize |
Decompress a buffer, using a prebuilt dictionary. The destination buffer must be already allocated.
Returns the number of bytes written into destination buffer, or an
error code if it fails (which can be tested using isError
).
Pre-digested dictionaries
Compression
Allocate a pre-digested dictionary.
:: Ptr CCtx | Compression context. |
-> Ptr dst | Destination buffer. |
-> CSize | Capacity of destination buffer. |
-> Ptr src | Source buffer. |
-> CSize | Size of source buffer. |
-> Ptr CDict | Dictionary. |
-> IO CSize |
Compress bytes from source buffer into destination buffer, using a pre-built, pre-digested dictionary. The destination buffer must be already allocated.
Returns the number of bytes written into destination buffer, or an
error code if it fails (which can be tested using isError
).
Decompression
Allocate a pre-digested dictionary.
:: Ptr DCtx | Decompression context. |
-> Ptr dst | Destination buffer. |
-> CSize | Capacity of destination buffer. |
-> Ptr src | Source buffer. |
-> CSize | Size of compressed input. This must be exact, so for example supplying the size of a buffer that is larger than the compressed input will cause a failure. |
-> Ptr DDict | Dictionary. |
-> IO CSize |
Decompress a buffer, using a pre-built, pre-digested dictionary. The destination buffer must be already allocated.
Returns the number of bytes written into destination buffer, or an
error code if it fails (which can be tested using isError
).
Low-level code
c_maxCLevel :: CInt Source #
Returns the maximum compression level supported by the library.