{-# LINE 1 "src/Codec/Lz4/Foreign.chs" #-}
module Codec.Lz4.Foreign (
lZ4VersionNumber
, lZ4VersionString
, lZ4CompressDefault
, lZ4DecompressSafe
, lZ4CompressBound
, lZ4FIsError
, lZ4FGetErrorName
, lZ4FGetVersion
, lZ4FCreateCompressionContext
, lZ4FFreeCompressionContext
, lZ4FHeaderSizeMax
, lZ4FCompressBegin
, lZ4FCompressBound
, lZ4FCompressUpdate
, lZ4FCompressEnd
, lZ4FCreateDecompressionContext
, lZ4FFreeDecompressionContext
, lZ4FDecompress
, lZ4MaxInputSize
, lZ4CompressHC
, lZ4HCClevelMax
, LZ4FErrorCode
, LzCtx
, LzCtxPtr
, LzDecompressionCtx
, LzDecompressionCtxPtr
) where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.ForeignPtr as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified System.IO.Unsafe as C2HSImp
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)
lZ4VersionNumber :: (CInt)
lZ4VersionNumber =
C2HSImp.unsafePerformIO $
lZ4VersionNumber'_ >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 43 "src/Codec/Lz4/Foreign.chs" #-}
lZ4VersionString :: (String)
lZ4VersionString =
C2HSImp.unsafePerformIO $
lZ4VersionString'_ >>= \res ->
C2HSImp.peekCString res >>= \res' ->
return (res')
{-# LINE 45 "src/Codec/Lz4/Foreign.chs" #-}
lZ4CompressDefault :: (CString) -> (CString) -> (CInt) -> (CInt) -> IO ((CInt))
lZ4CompressDefault a1 a2 a3 a4 =
(flip ($)) a1 $ \a1' ->
(flip ($)) a2 $ \a2' ->
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
lZ4CompressDefault'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 47 "src/Codec/Lz4/Foreign.chs" #-}
lZ4DecompressSafe :: (CString) -> (CString) -> (CInt) -> (CInt) -> IO ((CInt))
lZ4DecompressSafe a1 a2 a3 a4 =
(flip ($)) a1 $ \a1' ->
(flip ($)) a2 $ \a2' ->
let {a3' = fromIntegral a3} in
let {a4' = fromIntegral a4} in
lZ4DecompressSafe'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 48 "src/Codec/Lz4/Foreign.chs" #-}
lZ4CompressBound :: (CInt) -> (CInt)
lZ4CompressBound a1 =
C2HSImp.unsafePerformIO $
let {a1' = fromIntegral a1} in
lZ4CompressBound'_ a1' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 50 "src/Codec/Lz4/Foreign.chs" #-}
type LZ4FErrorCode = CSize
{-# LINE 53 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FIsError :: (LZ4FErrorCode) -> (Bool)
lZ4FIsError a1 =
C2HSImp.unsafePerformIO $
let {a1' = id a1} in
lZ4FIsError'_ a1' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 55 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FGetErrorName :: (LZ4FErrorCode) -> (String)
lZ4FGetErrorName a1 =
C2HSImp.unsafePerformIO $
let {a1' = id a1} in
lZ4FGetErrorName'_ a1' >>= \res ->
C2HSImp.peekCString res >>= \res' ->
return (res')
{-# LINE 56 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FGetVersion :: (CUInt)
lZ4FGetVersion =
C2HSImp.unsafePerformIO $
lZ4FGetVersion'_ >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 58 "src/Codec/Lz4/Foreign.chs" #-}
data LzCtx
type LzCtxPtr = C2HSImp.ForeignPtr (LzCtx)
{-# LINE 62 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FCreateCompressionContext :: (CUInt) -> IO ((LZ4FErrorCode), (Ptr LzCtx))
lZ4FCreateCompressionContext a2 =
alloca $ \a1' ->
let {a2' = fromIntegral a2} in
lZ4FCreateCompressionContext'_ a1' a2' >>= \res ->
let {res' = id res} in
peek a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 64 "src/Codec/Lz4/Foreign.chs" #-}
data LzPreferences
type LzPreferencesPtr = C2HSImp.Ptr (LzPreferences)
{-# LINE 68 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FHeaderSizeMax :: Integral a => a
lZ4FHeaderSizeMax = 19
{-# LINE 71 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FCompressBegin :: (LzCtxPtr) -> (Ptr a) -> (CSize) -> (LzPreferencesPtr) -> IO ((CSize))
lZ4FCompressBegin :: LzCtxPtr
-> Ptr a -> LZ4FErrorCode -> LzPreferencesPtr -> IO LZ4FErrorCode
lZ4FCompressBegin a1 :: LzCtxPtr
a1 a2 :: Ptr a
a2 a3 :: LZ4FErrorCode
a3 a4 :: LzPreferencesPtr
a4 =
LzCtxPtr -> (Ptr LzCtx -> IO LZ4FErrorCode) -> IO LZ4FErrorCode
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
C2HSImp.withForeignPtr LzCtxPtr
a1 ((Ptr LzCtx -> IO LZ4FErrorCode) -> IO LZ4FErrorCode)
-> (Ptr LzCtx -> IO LZ4FErrorCode) -> IO LZ4FErrorCode
forall a b. (a -> b) -> a -> b
$ \a1' :: Ptr LzCtx
a1' ->
let {a2' :: Ptr b
a2' = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
a2} in
let {a3' :: CULong
a3' = LZ4FErrorCode -> CULong
forall a b. Coercible a b => a -> b
coerce LZ4FErrorCode
a3} in
let {a4' :: LzPreferencesPtr
a4' = LzPreferencesPtr -> LzPreferencesPtr
forall a. a -> a
id LzPreferencesPtr
a4} in
Ptr LzCtx -> Ptr () -> CULong -> LzPreferencesPtr -> IO CULong
lZ4FCompressBegin'_ Ptr LzCtx
a1' Ptr ()
forall b. Ptr b
a2' CULong
a3' LzPreferencesPtr
a4' IO CULong -> (CULong -> IO LZ4FErrorCode) -> IO LZ4FErrorCode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \res :: CULong
res ->
let {res' :: LZ4FErrorCode
res' = CULong -> LZ4FErrorCode
forall a b. Coercible a b => a -> b
coerce CULong
res} in
LZ4FErrorCode -> IO LZ4FErrorCode
forall (m :: * -> *) a. Monad m => a -> m a
return (LZ4FErrorCode
res')
{-# LINE 73 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FCompressBound :: (CSize) -> (LzPreferencesPtr) -> (CSize)
lZ4FCompressBound a1 a2 =
C2HSImp.unsafePerformIO $
let {a1' = coerce a1} in
let {a2' = id a2} in
lZ4FCompressBound'_ a1' a2' >>= \res ->
let {res' = coerce res} in
return (res')
{-# LINE 75 "src/Codec/Lz4/Foreign.chs" #-}
data LzCompressOptions
type LzCompressOptionsPtr = C2HSImp.Ptr (LzCompressOptions)
{-# LINE 79 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FCompressUpdate :: (LzCtxPtr) -> (Ptr a) -> (CSize) -> (Ptr b) -> (CSize) -> (LzCompressOptionsPtr) -> IO ((CSize))
lZ4FCompressUpdate a1 a2 a3 a4 a5 a6 =
C2HSImp.withForeignPtr a1 $ \a1' ->
let {a2' = castPtr a2} in
let {a3' = coerce a3} in
let {a4' = castPtr a4} in
let {a5' = coerce a5} in
let {a6' = id a6} in
lZ4FCompressUpdate'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = coerce res} in
return (res')
{-# LINE 89 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FCompressEnd :: (LzCtxPtr) -> (Ptr a) -> (CSize) -> (LzCompressOptionsPtr) -> IO ((CSize))
lZ4FCompressEnd a1 a2 a3 a4 =
C2HSImp.withForeignPtr a1 $ \a1' ->
let {a2' = castPtr a2} in
let {a3' = coerce a3} in
let {a4' = id a4} in
lZ4FCompressEnd'_ a1' a2' a3' a4' >>= \res ->
let {res' = coerce res} in
return (res')
{-# LINE 92 "src/Codec/Lz4/Foreign.chs" #-}
data LzDecompressionCtx
type LzDecompressionCtxPtr = C2HSImp.ForeignPtr (LzDecompressionCtx)
{-# LINE 96 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FCreateDecompressionContext :: (CUInt) -> IO ((LZ4FErrorCode), (Ptr LzDecompressionCtx))
lZ4FCreateDecompressionContext a2 =
alloca $ \a1' ->
let {a2' = fromIntegral a2} in
lZ4FCreateDecompressionContext'_ a1' a2' >>= \res ->
let {res' = id res} in
peek a1'>>= \a1'' ->
return (res', a1'')
{-# LINE 98 "src/Codec/Lz4/Foreign.chs" #-}
data LzDecompressOptions
type LzDecompressOptionsPtr = C2HSImp.Ptr (LzDecompressOptions)
{-# LINE 102 "src/Codec/Lz4/Foreign.chs" #-}
lZ4FDecompress :: (LzDecompressionCtxPtr) -> (Ptr a) -> (Ptr CSize) -> (Ptr b) -> (Ptr CSize) -> (LzDecompressOptionsPtr) -> IO ((CSize))
lZ4FDecompress a1 a2 a3 a4 a5 a6 =
C2HSImp.withForeignPtr a1 $ \a1' ->
let {a2' = castPtr a2} in
let {a3' = castPtr a3} in
let {a4' = castPtr a4} in
let {a5' = castPtr a5} in
let {a6' = id a6} in
lZ4FDecompress'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = coerce res} in
return (res')
{-# LINE 112 "src/Codec/Lz4/Foreign.chs" #-}
lZ4MaxInputSize :: Integral a => a
lZ4MaxInputSize = 0x7e000000
{-# LINE 116 "src/Codec/Lz4/Foreign.chs" #-}
lZ4CompressHC :: (CString) -> (CString) -> (CInt) -> (CInt) -> (CInt) -> IO ((CInt))
lZ4CompressHC :: Ptr CChar -> Ptr CChar -> CInt -> CInt -> CInt -> IO CInt
lZ4CompressHC a1 :: Ptr CChar
a1 a2 :: Ptr CChar
a2 a3 :: CInt
a3 a4 :: CInt
a4 a5 :: CInt
a5 =
(((Ptr CChar -> IO CInt) -> Ptr CChar -> IO CInt)
-> Ptr CChar -> (Ptr CChar -> IO CInt) -> IO CInt
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Ptr CChar -> IO CInt) -> Ptr CChar -> IO CInt
forall a b. (a -> b) -> a -> b
($)) Ptr CChar
a1 ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \a1' :: Ptr CChar
a1' ->
(((Ptr CChar -> IO CInt) -> Ptr CChar -> IO CInt)
-> Ptr CChar -> (Ptr CChar -> IO CInt) -> IO CInt
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Ptr CChar -> IO CInt) -> Ptr CChar -> IO CInt
forall a b. (a -> b) -> a -> b
($)) Ptr CChar
a2 ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \a2' :: Ptr CChar
a2' ->
let {a3' :: CInt
a3' = CInt -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
a3} in
let {a4' = fromIntegral a4} in
let {a5' = fromIntegral a5} in
lZ4CompressHC'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' :: CInt
res' = CInt -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
res} in
CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt
res')
{-# LINE 119 "src/Codec/Lz4/Foreign.chs" #-}
lZ4HCClevelMax :: Integral a => a
lZ4HCClevelMax = 12
{-# LINE 123 "src/Codec/Lz4/Foreign.chs" #-}
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4_versionNumber"
lZ4VersionNumber'_ :: (IO C2HSImp.CInt)
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4_versionString"
lZ4VersionString'_ :: (IO (C2HSImp.Ptr C2HSImp.CChar))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4_compress_default"
lZ4CompressDefault'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4_decompress_safe"
lZ4DecompressSafe'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4_compressBound"
lZ4CompressBound'_ :: (C2HSImp.CInt -> (IO C2HSImp.CInt))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_isError"
lZ4FIsError'_ :: (LZ4FErrorCode -> (IO C2HSImp.CUInt))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_getErrorName"
lZ4FGetErrorName'_ :: (LZ4FErrorCode -> (IO (C2HSImp.Ptr C2HSImp.CChar)))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_getVersion"
lZ4FGetVersion'_ :: (IO C2HSImp.CUInt)
foreign import ccall "Codec/Lz4/Foreign.chs.h &LZ4F_freeCompressionContext"
lZ4FFreeCompressionContext :: C2HSImp.FinalizerPtr ()
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_createCompressionContext"
lZ4FCreateCompressionContext'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr (LzCtx))) -> (C2HSImp.CUInt -> (IO LZ4FErrorCode)))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_compressBegin"
lZ4FCompressBegin'_ :: ((C2HSImp.Ptr (LzCtx)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((LzPreferencesPtr) -> (IO C2HSImp.CULong)))))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_compressBound"
lZ4FCompressBound'_ :: (C2HSImp.CULong -> ((LzPreferencesPtr) -> (IO C2HSImp.CULong)))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_compressUpdate"
lZ4FCompressUpdate'_ :: ((C2HSImp.Ptr (LzCtx)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((LzCompressOptionsPtr) -> (IO C2HSImp.CULong)))))))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_compressEnd"
lZ4FCompressEnd'_ :: ((C2HSImp.Ptr (LzCtx)) -> ((C2HSImp.Ptr ()) -> (C2HSImp.CULong -> ((LzCompressOptionsPtr) -> (IO C2HSImp.CULong)))))
foreign import ccall "Codec/Lz4/Foreign.chs.h &LZ4F_freeDecompressionContext"
lZ4FFreeDecompressionContext :: C2HSImp.FinalizerPtr ()
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_createDecompressionContext"
lZ4FCreateDecompressionContext'_ :: ((C2HSImp.Ptr (C2HSImp.Ptr (LzDecompressionCtx))) -> (C2HSImp.CUInt -> (IO LZ4FErrorCode)))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4F_decompress"
lZ4FDecompress'_ :: ((C2HSImp.Ptr (LzDecompressionCtx)) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr C2HSImp.CULong) -> ((LzDecompressOptionsPtr) -> (IO C2HSImp.CULong)))))))
foreign import ccall safe "Codec/Lz4/Foreign.chs.h LZ4_compress_HC"
lZ4CompressHC'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (C2HSImp.CInt -> (C2HSImp.CInt -> (IO C2HSImp.CInt))))))