{-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE EmptyDataDecls #-} module Data.Streaming.Zlib.Lowlevel ( ZStreamStruct , ZStream' , zstreamNew , Strategy(..) , deflateInit2 , inflateInit2 , c_free_z_stream_inflate , c_free_z_stream_deflate , c_set_avail_in , c_set_avail_out , c_get_avail_out , c_get_avail_in , c_get_next_in , c_call_inflate_noflush , c_call_deflate_noflush , c_call_deflate_finish , c_call_deflate_flush , c_call_deflate_full_flush , c_call_deflate_set_dictionary , c_call_inflate_set_dictionary ) where import Foreign.C import Foreign.Ptr import Codec.Compression.Zlib (WindowBits (WindowBits)) data ZStreamStruct type ZStream' = Ptr ZStreamStruct data Strategy = StrategyDefault | StrategyFiltered | StrategyHuffman | StrategyRLE | StrategyFixed deriving (Int -> Strategy -> ShowS [Strategy] -> ShowS Strategy -> String (Int -> Strategy -> ShowS) -> (Strategy -> String) -> ([Strategy] -> ShowS) -> Show Strategy forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Strategy -> ShowS showsPrec :: Int -> Strategy -> ShowS $cshow :: Strategy -> String show :: Strategy -> String $cshowList :: [Strategy] -> ShowS showList :: [Strategy] -> ShowS Show,Strategy -> Strategy -> Bool (Strategy -> Strategy -> Bool) -> (Strategy -> Strategy -> Bool) -> Eq Strategy forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Strategy -> Strategy -> Bool == :: Strategy -> Strategy -> Bool $c/= :: Strategy -> Strategy -> Bool /= :: Strategy -> Strategy -> Bool Eq,Eq Strategy Eq Strategy => (Strategy -> Strategy -> Ordering) -> (Strategy -> Strategy -> Bool) -> (Strategy -> Strategy -> Bool) -> (Strategy -> Strategy -> Bool) -> (Strategy -> Strategy -> Bool) -> (Strategy -> Strategy -> Strategy) -> (Strategy -> Strategy -> Strategy) -> Ord Strategy Strategy -> Strategy -> Bool Strategy -> Strategy -> Ordering Strategy -> Strategy -> Strategy forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: Strategy -> Strategy -> Ordering compare :: Strategy -> Strategy -> Ordering $c< :: Strategy -> Strategy -> Bool < :: Strategy -> Strategy -> Bool $c<= :: Strategy -> Strategy -> Bool <= :: Strategy -> Strategy -> Bool $c> :: Strategy -> Strategy -> Bool > :: Strategy -> Strategy -> Bool $c>= :: Strategy -> Strategy -> Bool >= :: Strategy -> Strategy -> Bool $cmax :: Strategy -> Strategy -> Strategy max :: Strategy -> Strategy -> Strategy $cmin :: Strategy -> Strategy -> Strategy min :: Strategy -> Strategy -> Strategy Ord,Int -> Strategy Strategy -> Int Strategy -> [Strategy] Strategy -> Strategy Strategy -> Strategy -> [Strategy] Strategy -> Strategy -> Strategy -> [Strategy] (Strategy -> Strategy) -> (Strategy -> Strategy) -> (Int -> Strategy) -> (Strategy -> Int) -> (Strategy -> [Strategy]) -> (Strategy -> Strategy -> [Strategy]) -> (Strategy -> Strategy -> [Strategy]) -> (Strategy -> Strategy -> Strategy -> [Strategy]) -> Enum Strategy forall a. (a -> a) -> (a -> a) -> (Int -> a) -> (a -> Int) -> (a -> [a]) -> (a -> a -> [a]) -> (a -> a -> [a]) -> (a -> a -> a -> [a]) -> Enum a $csucc :: Strategy -> Strategy succ :: Strategy -> Strategy $cpred :: Strategy -> Strategy pred :: Strategy -> Strategy $ctoEnum :: Int -> Strategy toEnum :: Int -> Strategy $cfromEnum :: Strategy -> Int fromEnum :: Strategy -> Int $cenumFrom :: Strategy -> [Strategy] enumFrom :: Strategy -> [Strategy] $cenumFromThen :: Strategy -> Strategy -> [Strategy] enumFromThen :: Strategy -> Strategy -> [Strategy] $cenumFromTo :: Strategy -> Strategy -> [Strategy] enumFromTo :: Strategy -> Strategy -> [Strategy] $cenumFromThenTo :: Strategy -> Strategy -> Strategy -> [Strategy] enumFromThenTo :: Strategy -> Strategy -> Strategy -> [Strategy] Enum) foreign import ccall unsafe "streaming_commons_create_z_stream" zstreamNew :: IO ZStream' foreign import ccall unsafe "streaming_commons_deflate_init2" c_deflateInit2 :: ZStream' -> CInt -> CInt -> CInt -> CInt -> IO () deflateInit2 :: ZStream' -> Int -> WindowBits -> Int -> Strategy -> IO () deflateInit2 :: ZStream' -> Int -> WindowBits -> Int -> Strategy -> IO () deflateInit2 ZStream' zstream Int level WindowBits windowBits Int memlevel Strategy strategy = ZStream' -> CInt -> CInt -> CInt -> CInt -> IO () c_deflateInit2 ZStream' zstream (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral Int level) (WindowBits -> CInt wbToInt WindowBits windowBits) (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral Int memlevel) (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> CInt) -> Int -> CInt forall a b. (a -> b) -> a -> b $ Strategy -> Int forall a. Enum a => a -> Int fromEnum Strategy strategy) foreign import ccall unsafe "streaming_commons_inflate_init2" c_inflateInit2 :: ZStream' -> CInt -> IO () inflateInit2 :: ZStream' -> WindowBits -> IO () inflateInit2 :: ZStream' -> WindowBits -> IO () inflateInit2 ZStream' zstream WindowBits wb = ZStream' -> CInt -> IO () c_inflateInit2 ZStream' zstream (WindowBits -> CInt wbToInt WindowBits wb) foreign import ccall unsafe "&streaming_commons_free_z_stream_inflate" c_free_z_stream_inflate :: FunPtr (ZStream' -> IO ()) foreign import ccall unsafe "&streaming_commons_free_z_stream_deflate" c_free_z_stream_deflate :: FunPtr (ZStream' -> IO ()) foreign import ccall unsafe "streaming_commons_set_avail_in" c_set_avail_in :: ZStream' -> Ptr CChar -> CUInt -> IO () foreign import ccall unsafe "streaming_commons_set_avail_out" c_set_avail_out :: ZStream' -> Ptr CChar -> CUInt -> IO () foreign import ccall unsafe "streaming_commons_get_avail_out" c_get_avail_out :: ZStream' -> IO CUInt foreign import ccall unsafe "streaming_commons_get_avail_in" c_get_avail_in :: ZStream' -> IO CUInt foreign import ccall unsafe "streaming_commons_get_next_in" c_get_next_in :: ZStream' -> IO (Ptr CChar) foreign import ccall unsafe "streaming_commons_call_inflate_noflush" c_call_inflate_noflush :: ZStream' -> IO CInt foreign import ccall unsafe "streaming_commons_call_deflate_noflush" c_call_deflate_noflush :: ZStream' -> IO CInt foreign import ccall unsafe "streaming_commons_call_deflate_finish" c_call_deflate_finish :: ZStream' -> IO CInt foreign import ccall unsafe "streaming_commons_call_deflate_flush" c_call_deflate_flush :: ZStream' -> IO CInt foreign import ccall unsafe "streaming_commons_call_deflate_full_flush" c_call_deflate_full_flush :: ZStream' -> IO CInt foreign import ccall unsafe "streaming_commons_deflate_set_dictionary" c_call_deflate_set_dictionary :: ZStream' -> Ptr CChar -> CUInt -> IO () foreign import ccall unsafe "streaming_commons_inflate_set_dictionary" c_call_inflate_set_dictionary :: ZStream' -> Ptr CChar -> CUInt -> IO () wbToInt :: WindowBits -> CInt wbToInt :: WindowBits -> CInt wbToInt (WindowBits Int i) = Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegral Int i wbToInt WindowBits _ = CInt 15