{-# LANGUAGE CApiFFI #-} module Codec.Lz4.Foreign ( -- * Blocks lZ4VersionNumber , lZ4VersionString , lZ4CompressDefault , lZ4DecompressSafe , lZ4CompressBound -- * Frames , lZ4FIsError , lZ4FGetErrorName , lZ4FGetVersion , lZ4FCreateCompressionContext , lZ4FFreeCompressionContext , lZ4FHeaderSizeMax , lZ4FCompressBegin , lZ4FCompressBound , lZ4FCompressUpdate , lZ4FCompressEnd , lZ4FCreateDecompressionContext , lZ4FDecompress , lZ4MaxInputSize , lZ4CompressHC -- * Macros , lZ4HCClevelMax -- * Types , LZ4FErrorCode , LzCtx , LzCtxPtr , LzDecompressionCtx , LzDecompressionCtxPtr , LzPreferencesPtr , BlockMode (Lz4fBlocklinked) , BlockSize (Lz4fDefault) , ContentChecksum (Lz4fNocontentchecksum) , BlockChecksum (Lz4fNoblockchecksum) , FrameType (Lz4fFrame) ) where import Data.Coerce (coerce) import Foreign.C.String (CString) import Foreign.C.Types (CInt, CUInt, CSize (..)) import Foreign.Marshal.Alloc (alloca) import Foreign.Ptr (castPtr, Ptr) import Foreign.Storable (peek) #include #include #include {# enum LZ4F_blockSizeID_t as BlockSize {underscoreToCase} #} {# enum LZ4F_blockMode_t as BlockMode {underscoreToCase} #} {# enum LZ4F_contentChecksum_t as ContentChecksum {underscoreToCase} #} {# enum LZ4F_blockChecksum_t as BlockChecksum {underscoreToCase} #} {# enum LZ4F_frameType_t as FrameType {underscoreToCase} #} {# fun pure LZ4_versionNumber as ^ {} -> `CInt' #} -- | @since 0.1.1.0 {# fun pure LZ4_versionString as ^ {} -> `String' #} {# fun unsafe LZ4_compress_default as ^ { `CString', `CString', `CInt' , `CInt' } -> `CInt' #} {# fun unsafe LZ4_decompress_safe as ^ { `CString', `CString', `CInt' , `CInt' } -> `CInt' #} {# fun pure LZ4_compressBound as ^ { `CInt' } -> `CInt' #} type LZ4FErrorCode = CSize -- {# type LZ4F_errorCode_t #} {# typedef LZ4F_errorCode_t LZ4FErrorCode #} {# fun pure LZ4F_isError as ^ { `LZ4FErrorCode' } -> `Bool' #} {# fun pure LZ4F_getErrorName as ^ { `LZ4FErrorCode' } -> `String' #} {# fun pure LZ4F_getVersion as ^ {} -> `CUInt' #} data LzCtx {# pointer *LZ4F_cctx as LzCtxPtr foreign finalizer LZ4F_freeCompressionContext as ^ -> LzCtx #} {# fun unsafe LZ4F_createCompressionContext as ^ { alloca- `Ptr LzCtx' peek*, `CUInt' } -> `LZ4FErrorCode' #} data LzPreferences {# pointer *LZ4F_preferences_t as LzPreferencesPtr foreign -> LzPreferences #} lZ4FHeaderSizeMax :: Integral a => a lZ4FHeaderSizeMax = {# const LZ4F_HEADER_SIZE_MAX #} {# fun unsafe LZ4F_compressBegin as ^ { `LzCtxPtr', castPtr `Ptr a', coerce `CSize', `LzPreferencesPtr' } -> `CSize' coerce #} {# fun pure LZ4F_compressBound as ^ { coerce `CSize', `LzPreferencesPtr' } -> `CSize' coerce #} data LzCompressOptions {# pointer *LZ4F_compressOptions_t as LzCompressOptionsPtr -> LzCompressOptions #} {# fun unsafe LZ4F_compressUpdate as ^ { `LzCtxPtr' , castPtr `Ptr a' , coerce `CSize' , castPtr `Ptr b' , coerce `CSize' , `LzCompressOptionsPtr' } -> `CSize' coerce #} {# fun unsafe LZ4F_compressEnd as ^ { `LzCtxPtr', castPtr `Ptr a', coerce `CSize', `LzCompressOptionsPtr' } -> `CSize' coerce #} data LzDecompressionCtx {# pointer *LZ4F_dctx as LzDecompressionCtxPtr foreign finalizer LZ4F_freeDecompressionContext as ^ -> LzDecompressionCtx #} {# fun unsafe LZ4F_createDecompressionContext as ^ { alloca- `Ptr LzDecompressionCtx' peek*, `CUInt' } -> `LZ4FErrorCode' #} data LzDecompressOptions {# pointer *LZ4F_decompressOptions_t as LzDecompressOptionsPtr -> LzDecompressOptions #} {# fun unsafe LZ4F_decompress as ^ { `LzDecompressionCtxPtr' , castPtr `Ptr a' , castPtr `Ptr CSize' , castPtr `Ptr b' , castPtr `Ptr CSize' , `LzDecompressOptionsPtr' } -> `CSize' coerce #} -- | @since 0.1.1.0 lZ4MaxInputSize :: Integral a => a lZ4MaxInputSize = {# const LZ4_MAX_INPUT_SIZE #} {# fun unsafe LZ4_compress_HC as ^ { `CString', `CString', `CInt', `CInt', `CInt' } -> `CInt' #} -- | @since 0.1.1.0 lZ4HCClevelMax :: Integral a => a lZ4HCClevelMax = {# const LZ4HC_CLEVEL_MAX #}