zstd-0.1.0.0: Haskell bindings to the Zstandard compression algorithm

Copyright(c) 2016-present Facebook Inc. All rights reserved.
LicenseBSD3
Maintainerbryano@fb.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Codec.Compression.Zstd.FFI

Contents

Description

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

One-shot functions

compress Source #

Arguments

:: 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).

compressBound Source #

Arguments

:: Ptr src

Source buffer.

-> IO CSize 

Compute the maximum compressed size of given source buffer.

maxCLevel :: Int Source #

The maximum compression level supported by the library.

decompress Source #

Arguments

:: 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

data CCtx Source #

An opaque compression context structure.

createCCtx :: IO (Ptr CCtx) Source #

Allocate a compression context.

freeCCtx :: Ptr CCtx -> IO () Source #

Free a compression context.

p_freeCCtx :: FunPtr (Ptr CCtx -> IO ()) Source #

Free a compression context. For use by a finalizer.

compressCCtx Source #

Arguments

:: 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

data DCtx Source #

An opaque decompression context structure.

createDCtx :: IO (Ptr DCtx) Source #

Allocate a decompression context.

freeDCtx :: Ptr DCtx -> IO () Source #

Free a decompression context.

p_freeDCtx :: FunPtr (Ptr DCtx -> IO ()) Source #

Free a decompression context. For use by a finalizer.

decompressDCtx Source #

Arguments

:: 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

isError :: CSize -> Bool Source #

Indicates whether a return value is an error code.

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

data CStream Source #

A context for streaming compression.

data DStream Source #

A context for streaming decompression.

data Buffer io Source #

A streaming buffer type. The type parameter statically indicates whether the buffer is used to track an input or output buffer.

Constructors

Buffer 

Fields

  • bufPtr :: !(Ptr a)

    Pointer to the start of the buffer. This can be set once by the caller, and read by the streaming function.

  • bufSize :: !CSize

    Size of the buffer (in bytes). This can be set once by the caller, and is read by the streaming function.

  • bufPos :: !CSize

    Current offset into the buffer (in bytes). This must be initially set to zero by the caller, and is updated by the streaming function.

Instances

Storable (Buffer io) Source # 

Methods

sizeOf :: Buffer io -> Int #

alignment :: Buffer io -> Int #

peekElemOff :: Ptr (Buffer io) -> Int -> IO (Buffer io) #

pokeElemOff :: Ptr (Buffer io) -> Int -> Buffer io -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Buffer io) #

pokeByteOff :: Ptr b -> Int -> Buffer io -> IO () #

peek :: Ptr (Buffer io) -> IO (Buffer io) #

poke :: Ptr (Buffer io) -> Buffer io -> IO () #

data In Source #

A tag type to indicate that a Buffer is used for tracking input.

data Out Source #

A tag type to indicate that a Buffer is used for tracking output.

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.

freeCStream :: Ptr CStream -> IO () Source #

Free a CStream value.

p_freeCStream :: FunPtr (Ptr CStream -> IO ()) Source #

Free a CStream value. For use by a finalizer.

initCStream Source #

Arguments

:: Ptr CStream 
-> CInt

Compression level.

-> IO CSize 

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.

initDStream :: Ptr DStream -> IO CSize Source #

Begin a new streaming decompression operation.

decompressStream :: Ptr DStream -> Ptr (Buffer Out) -> Ptr (Buffer In) -> IO CSize Source #

Consume part or all of an input.

freeDStream :: Ptr DStream -> IO () Source #

Free a CStream value.

p_freeDStream :: FunPtr (Ptr DStream -> IO ()) Source #

Free a CStream value. For use by a finalizer.

Dictionary-based compression

trainFromBuffer Source #

Arguments

:: 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.

getDictID Source #

Arguments

:: Ptr dict

Dictionary.

-> CSize

Size of dictionary.

-> IO CUInt 

Return the identifier for the given dictionary, or zero if not a valid dictionary.

compressUsingDict Source #

Arguments

:: 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).

decompressUsingDict Source #

Arguments

:: 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

data CDict Source #

An opaque pre-digested compression dictionary structure.

createCDict Source #

Arguments

:: Ptr dict

Dictionary.

-> CSize

Size of dictionary.

-> CInt

Compression level.

-> IO (Ptr CDict) 

Allocate a pre-digested dictionary.

freeCDict :: Ptr CDict -> IO () Source #

Free a pre-digested dictionary.

p_freeCDict :: FunPtr (Ptr CDict -> IO ()) Source #

Free a pre-digested dictionary.

compressUsingCDict Source #

Arguments

:: 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

data DDict Source #

An opaque pre-digested decompression dictionary structure.

createDDict Source #

Arguments

:: Ptr dict

Dictionary.

-> CSize

Size of dictionary.

-> IO (Ptr DDict) 

Allocate a pre-digested dictionary.

freeDDict :: Ptr DDict -> IO () Source #

Free a pre-digested dictionary.

p_freeDDict :: FunPtr (Ptr DDict -> IO ()) Source #

Free a pre-digested dictionary.

decompressUsingDDict Source #

Arguments

:: 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.