{-# LINE 1 "Codec/Compression/Zlib/Stream.hsc" #-}
{-# LANGUAGE CPP, ForeignFunctionInterface, DeriveDataTypeable #-}

{-# LINE 3 "Codec/Compression/Zlib/Stream.hsc" #-}
{-# LANGUAGE DeriveGeneric #-}

{-# LINE 5 "Codec/Compression/Zlib/Stream.hsc" #-}

{-# LINE 6 "Codec/Compression/Zlib/Stream.hsc" #-}
{-# LANGUAGE CApiFFI #-}

{-# LINE 8 "Codec/Compression/Zlib/Stream.hsc" #-}
-----------------------------------------------------------------------------
-- |
-- Copyright   :  (c) 2006-2015 Duncan Coutts
-- License     :  BSD-style
--
-- Maintainer  :  duncan@community.haskell.org
--
-- Zlib wrapper layer
--
-----------------------------------------------------------------------------
module Codec.Compression.Zlib.Stream (

  -- * The Zlib state monad
  Stream,
  State,
  mkState,
  runStream,
  unsafeLiftIO,
  finalise,

  -- * Initialisation
  deflateInit, 
  inflateInit,

  -- ** Initialisation parameters
  Format(..),
    gzipFormat,
    zlibFormat,
    rawFormat,
    gzipOrZlibFormat,
    formatSupportsDictionary,
  CompressionLevel(..),
    defaultCompression,
    noCompression,
    bestSpeed,
    bestCompression,
    compressionLevel,
  Method(..),
    deflateMethod,
  WindowBits(..),
    defaultWindowBits,
    windowBits,
  MemoryLevel(..),
    defaultMemoryLevel,
    minMemoryLevel,
    maxMemoryLevel,
    memoryLevel,
  CompressionStrategy(..),
    defaultStrategy,
    filteredStrategy,
    huffmanOnlyStrategy,

  -- * The buisness
  deflate,
  inflate,
  Status(..),
  Flush(..),
  ErrorCode(..),
  -- ** Special operations
  inflateReset,

  -- * Buffer management
  -- ** Input buffer
  pushInputBuffer,
  inputBufferEmpty,
  popRemainingInputBuffer,

  -- ** Output buffer
  pushOutputBuffer,
  popOutputBuffer,
  outputBufferBytesAvailable,
  outputBufferSpaceRemaining,
  outputBufferFull,

  -- ** Dictionary
  deflateSetDictionary,
  inflateSetDictionary,

  -- ** Dictionary hashes
  DictionaryHash,
  dictionaryHash,
  zeroDictionaryHash,


{-# LINE 97 "Codec/Compression/Zlib/Stream.hsc" #-}

  ) where

-- Note we don't use the MIN_VERSION_* macros here for compatability with
-- old Cabal versions that come with old GHC, that didn't provide these
-- macros for .hsc files. So we use __GLASGOW_HASKELL__ as a proxy.

import Foreign
         ( Word8, Ptr, nullPtr, plusPtr, peekByteOff, pokeByteOff
         , ForeignPtr, FinalizerPtr, mallocForeignPtrBytes, addForeignPtrFinalizer
         , withForeignPtr, touchForeignPtr, minusPtr )

{-# LINE 109 "Codec/Compression/Zlib/Stream.hsc" #-}
import Foreign.ForeignPtr.Unsafe ( unsafeForeignPtrToPtr )
import System.IO.Unsafe          ( unsafePerformIO )

{-# LINE 114 "Codec/Compression/Zlib/Stream.hsc" #-}

{-# LINE 115 "Codec/Compression/Zlib/Stream.hsc" #-}
import Foreign
         ( finalizeForeignPtr )

{-# LINE 118 "Codec/Compression/Zlib/Stream.hsc" #-}
import Foreign.C
import Data.ByteString.Internal (nullForeignPtr)
import qualified Data.ByteString.Unsafe as B
import Data.ByteString (ByteString)

{-# LINE 125 "Codec/Compression/Zlib/Stream.hsc" #-}
import Control.Monad (ap,liftM)

{-# LINE 127 "Codec/Compression/Zlib/Stream.hsc" #-}
import qualified Control.Monad.Fail as Fail

{-# LINE 129 "Codec/Compression/Zlib/Stream.hsc" #-}

{-# LINE 130 "Codec/Compression/Zlib/Stream.hsc" #-}

{-# LINE 131 "Codec/Compression/Zlib/Stream.hsc" #-}
import Control.Monad.ST.Strict

{-# LINE 135 "Codec/Compression/Zlib/Stream.hsc" #-}
import Control.Monad.ST.Unsafe

{-# LINE 139 "Codec/Compression/Zlib/Stream.hsc" #-}
import Control.Exception (assert)
import Data.Typeable (Typeable)

{-# LINE 142 "Codec/Compression/Zlib/Stream.hsc" #-}
import GHC.Generics (Generic)

{-# LINE 144 "Codec/Compression/Zlib/Stream.hsc" #-}

{-# LINE 147 "Codec/Compression/Zlib/Stream.hsc" #-}

import Prelude hiding (length)




pushInputBuffer :: ForeignPtr Word8 -> Int -> Int -> Stream ()
pushInputBuffer :: ForeignPtr Word8 -> Int -> Int -> Stream ()
pushInputBuffer ForeignPtr Word8
inBuf' Int
offset Int
length = do

  -- must not push a new input buffer if the last one is not used up
  Int
inAvail <- Stream Int
getInAvail
  Bool -> Stream () -> Stream ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
inAvail Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Stream () -> Stream ()) -> Stream () -> Stream ()
forall a b. (a -> b) -> a -> b
$ () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

  -- Now that we're setting a new input buffer, we can be sure that zlib no
  -- longer has a reference to the old one. Therefore this is the last point
  -- at which the old buffer had to be retained. It's safe to release now.
  ForeignPtr Word8
inBuf <- Stream (ForeignPtr Word8)
getInBuf 
  IO () -> Stream ()
forall a. IO a -> Stream a
unsafeLiftIO (IO () -> Stream ()) -> IO () -> Stream ()
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr Word8
inBuf    

  -- now set the available input buffer ptr and length
  ForeignPtr Word8 -> Stream ()
setInBuf   ForeignPtr Word8
inBuf'
  Int -> Stream ()
setInAvail Int
length
  Ptr Word8 -> Stream ()
setInNext  (ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
inBuf' Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
offset)
  -- Note the 'unsafe'. We are passing the raw ptr inside inBuf' to zlib.
  -- To make this safe we need to hold on to the ForeignPtr for at least as
  -- long as zlib is using the underlying raw ptr.


inputBufferEmpty :: Stream Bool
inputBufferEmpty :: Stream Bool
inputBufferEmpty = Stream Int
getInAvail Stream Int -> (Int -> Stream Bool) -> Stream Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Stream Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Stream Bool) -> (Int -> Bool) -> Int -> Stream Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0)


popRemainingInputBuffer :: Stream (ForeignPtr Word8, Int, Int)
popRemainingInputBuffer :: Stream (ForeignPtr Word8, Int, Int)
popRemainingInputBuffer = do

  ForeignPtr Word8
inBuf    <- Stream (ForeignPtr Word8)
getInBuf
  Ptr Word8
inNext   <- Stream (Ptr Word8)
getInNext
  Int
inAvail  <- Stream Int
getInAvail

  -- there really should be something to pop, otherwise it's silly
  Bool -> Stream () -> Stream ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
inAvail Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (Stream () -> Stream ()) -> Stream () -> Stream ()
forall a b. (a -> b) -> a -> b
$ () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  Int -> Stream ()
setInAvail Int
0

  (ForeignPtr Word8, Int, Int) -> Stream (ForeignPtr Word8, Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, Ptr Word8
inNext Ptr Word8 -> Ptr Word8 -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
inBuf, Int
inAvail)


pushOutputBuffer :: ForeignPtr Word8 -> Int -> Int -> Stream ()
pushOutputBuffer :: ForeignPtr Word8 -> Int -> Int -> Stream ()
pushOutputBuffer ForeignPtr Word8
outBuf' Int
offset Int
length = do

  --must not push a new buffer if there is still data in the old one
  Int
outAvail <- Stream Int
getOutAvail
  Bool -> Stream () -> Stream ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
outAvail Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Stream () -> Stream ()) -> Stream () -> Stream ()
forall a b. (a -> b) -> a -> b
$ () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  -- Note that there may still be free space in the output buffer, that's ok,
  -- you might not want to bother completely filling the output buffer say if
  -- there's only a few free bytes left.

  ForeignPtr Word8
outBuf <- Stream (ForeignPtr Word8)
getOutBuf
  IO () -> Stream ()
forall a. IO a -> Stream a
unsafeLiftIO (IO () -> Stream ()) -> IO () -> Stream ()
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr Word8
outBuf

  -- now set the available input buffer ptr and length
  ForeignPtr Word8 -> Stream ()
setOutBuf  ForeignPtr Word8
outBuf'
  Int -> Stream ()
setOutFree Int
length
  Ptr Word8 -> Stream ()
setOutNext (ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
outBuf' Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
offset)

  Int -> Stream ()
setOutOffset Int
offset
  Int -> Stream ()
setOutAvail  Int
0


-- get that part of the output buffer that is currently full
-- (might be 0, use outputBufferBytesAvailable to check)
-- this may leave some space remaining in the buffer, use
-- outputBufferSpaceRemaining to check.
popOutputBuffer :: Stream (ForeignPtr Word8, Int, Int)
popOutputBuffer :: Stream (ForeignPtr Word8, Int, Int)
popOutputBuffer = do

  ForeignPtr Word8
outBuf    <- Stream (ForeignPtr Word8)
getOutBuf
  Int
outOffset <- Stream Int
getOutOffset
  Int
outAvail  <- Stream Int
getOutAvail

  -- there really should be something to pop, otherwise it's silly
  Bool -> Stream () -> Stream ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
outAvail Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (Stream () -> Stream ()) -> Stream () -> Stream ()
forall a b. (a -> b) -> a -> b
$ () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

  Int -> Stream ()
setOutOffset (Int
outOffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
outAvail)
  Int -> Stream ()
setOutAvail  Int
0

  (ForeignPtr Word8, Int, Int) -> Stream (ForeignPtr Word8, Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
outBuf, Int
outOffset, Int
outAvail)


-- this is the number of bytes available in the output buffer
outputBufferBytesAvailable :: Stream Int
outputBufferBytesAvailable :: Stream Int
outputBufferBytesAvailable = Stream Int
getOutAvail


-- you needen't get all the output immediately, you can continue until
-- there is no more output space available, this tells you that amount
outputBufferSpaceRemaining :: Stream Int
outputBufferSpaceRemaining :: Stream Int
outputBufferSpaceRemaining = Stream Int
getOutFree


-- you only need to supply a new buffer when there is no more output buffer
-- space remaining
outputBufferFull :: Stream Bool
outputBufferFull :: Stream Bool
outputBufferFull = (Int -> Bool) -> Stream Int -> Stream Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0) Stream Int
outputBufferSpaceRemaining


-- you can only run this when the output buffer is not empty
-- you can run it when the input buffer is empty but it doesn't do anything
-- after running deflate either the output buffer will be full
-- or the input buffer will be empty (or both)
deflate :: Flush -> Stream Status
deflate :: Flush -> Stream Status
deflate Flush
flush = do

  Int
outFree <- Stream Int
getOutFree

  -- deflate needs free space in the output buffer
  Bool -> Stream () -> Stream ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
outFree Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (Stream () -> Stream ()) -> Stream () -> Stream ()
forall a b. (a -> b) -> a -> b
$ () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

  Status
result <- Flush -> Stream Status
deflate_ Flush
flush
  Int
outFree' <- Stream Int
getOutFree
    
  -- number of bytes of extra output there is available as a result of
  -- the call to deflate:
  let outExtra :: Int
outExtra = Int
outFree Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
outFree'
  
  Int
outAvail <- Stream Int
getOutAvail
  Int -> Stream ()
setOutAvail (Int
outAvail Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
outExtra)
  Status -> Stream Status
forall (m :: * -> *) a. Monad m => a -> m a
return Status
result


inflate :: Flush -> Stream Status
inflate :: Flush -> Stream Status
inflate Flush
flush = do

  Int
outFree <- Stream Int
getOutFree

  -- inflate needs free space in the output buffer
  Bool -> Stream () -> Stream ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
outFree Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (Stream () -> Stream ()) -> Stream () -> Stream ()
forall a b. (a -> b) -> a -> b
$ () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

  Status
result <- Flush -> Stream Status
inflate_ Flush
flush
  Int
outFree' <- Stream Int
getOutFree

  -- number of bytes of extra output there is available as a result of
  -- the call to inflate:
  let outExtra :: Int
outExtra = Int
outFree Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
outFree'

  Int
outAvail <- Stream Int
getOutAvail
  Int -> Stream ()
setOutAvail (Int
outAvail Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
outExtra)
  Status -> Stream Status
forall (m :: * -> *) a. Monad m => a -> m a
return Status
result


inflateReset :: Stream ()
inflateReset :: Stream ()
inflateReset = do

  Int
outAvail <- Stream Int
getOutAvail
  Int
inAvail  <- Stream Int
getInAvail
  -- At the point where this is used, all the output should have been consumed
  -- and any trailing input should be extracted and resupplied explicitly, not
  -- just left.
  Bool -> Stream () -> Stream ()
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
outAvail Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Int
inAvail Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Stream () -> Stream ()) -> Stream () -> Stream ()
forall a b. (a -> b) -> a -> b
$ () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

  CInt
err <- (StreamState -> IO CInt) -> Stream CInt
forall a. (StreamState -> IO a) -> Stream a
withStreamState ((StreamState -> IO CInt) -> Stream CInt)
-> (StreamState -> IO CInt) -> Stream CInt
forall a b. (a -> b) -> a -> b
$ \StreamState
zstream ->
    StreamState -> IO CInt
c_inflateReset StreamState
zstream
  CInt -> Stream ()
failIfError CInt
err



deflateSetDictionary :: ByteString -> Stream Status
deflateSetDictionary :: ByteString -> Stream Status
deflateSetDictionary ByteString
dict = do
  CInt
err <- (StreamState -> IO CInt) -> Stream CInt
forall a. (StreamState -> IO a) -> Stream a
withStreamState ((StreamState -> IO CInt) -> Stream CInt)
-> (StreamState -> IO CInt) -> Stream CInt
forall a b. (a -> b) -> a -> b
$ \StreamState
zstream ->
           ByteString -> (CStringLen -> IO CInt) -> IO CInt
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
dict ((CStringLen -> IO CInt) -> IO CInt)
-> (CStringLen -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
             StreamState -> Ptr CChar -> CUInt -> IO CInt
c_deflateSetDictionary StreamState
zstream Ptr CChar
ptr (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
  CInt -> Stream Status
toStatus CInt
err

inflateSetDictionary :: ByteString -> Stream Status
inflateSetDictionary :: ByteString -> Stream Status
inflateSetDictionary ByteString
dict = do
  CInt
err <- (StreamState -> IO CInt) -> Stream CInt
forall a. (StreamState -> IO a) -> Stream a
withStreamState ((StreamState -> IO CInt) -> Stream CInt)
-> (StreamState -> IO CInt) -> Stream CInt
forall a b. (a -> b) -> a -> b
$ \StreamState
zstream -> do
           ByteString -> (CStringLen -> IO CInt) -> IO CInt
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
dict ((CStringLen -> IO CInt) -> IO CInt)
-> (CStringLen -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
             StreamState -> Ptr CChar -> CUInt -> IO CInt
c_inflateSetDictionary StreamState
zstream Ptr CChar
ptr (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
  CInt -> Stream Status
toStatus CInt
err

-- | A hash of a custom compression dictionary. These hashes are used by
-- zlib as dictionary identifiers.
-- (The particular hash function used is Adler32.)
--
newtype DictionaryHash = DictHash CULong
  deriving (DictionaryHash -> DictionaryHash -> Bool
(DictionaryHash -> DictionaryHash -> Bool)
-> (DictionaryHash -> DictionaryHash -> Bool) -> Eq DictionaryHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DictionaryHash -> DictionaryHash -> Bool
$c/= :: DictionaryHash -> DictionaryHash -> Bool
== :: DictionaryHash -> DictionaryHash -> Bool
$c== :: DictionaryHash -> DictionaryHash -> Bool
Eq, Eq DictionaryHash
Eq DictionaryHash
-> (DictionaryHash -> DictionaryHash -> Ordering)
-> (DictionaryHash -> DictionaryHash -> Bool)
-> (DictionaryHash -> DictionaryHash -> Bool)
-> (DictionaryHash -> DictionaryHash -> Bool)
-> (DictionaryHash -> DictionaryHash -> Bool)
-> (DictionaryHash -> DictionaryHash -> DictionaryHash)
-> (DictionaryHash -> DictionaryHash -> DictionaryHash)
-> Ord DictionaryHash
DictionaryHash -> DictionaryHash -> Bool
DictionaryHash -> DictionaryHash -> Ordering
DictionaryHash -> DictionaryHash -> DictionaryHash
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
min :: DictionaryHash -> DictionaryHash -> DictionaryHash
$cmin :: DictionaryHash -> DictionaryHash -> DictionaryHash
max :: DictionaryHash -> DictionaryHash -> DictionaryHash
$cmax :: DictionaryHash -> DictionaryHash -> DictionaryHash
>= :: DictionaryHash -> DictionaryHash -> Bool
$c>= :: DictionaryHash -> DictionaryHash -> Bool
> :: DictionaryHash -> DictionaryHash -> Bool
$c> :: DictionaryHash -> DictionaryHash -> Bool
<= :: DictionaryHash -> DictionaryHash -> Bool
$c<= :: DictionaryHash -> DictionaryHash -> Bool
< :: DictionaryHash -> DictionaryHash -> Bool
$c< :: DictionaryHash -> DictionaryHash -> Bool
compare :: DictionaryHash -> DictionaryHash -> Ordering
$ccompare :: DictionaryHash -> DictionaryHash -> Ordering
$cp1Ord :: Eq DictionaryHash
Ord, ReadPrec [DictionaryHash]
ReadPrec DictionaryHash
Int -> ReadS DictionaryHash
ReadS [DictionaryHash]
(Int -> ReadS DictionaryHash)
-> ReadS [DictionaryHash]
-> ReadPrec DictionaryHash
-> ReadPrec [DictionaryHash]
-> Read DictionaryHash
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DictionaryHash]
$creadListPrec :: ReadPrec [DictionaryHash]
readPrec :: ReadPrec DictionaryHash
$creadPrec :: ReadPrec DictionaryHash
readList :: ReadS [DictionaryHash]
$creadList :: ReadS [DictionaryHash]
readsPrec :: Int -> ReadS DictionaryHash
$creadsPrec :: Int -> ReadS DictionaryHash
Read, Int -> DictionaryHash -> ShowS
[DictionaryHash] -> ShowS
DictionaryHash -> String
(Int -> DictionaryHash -> ShowS)
-> (DictionaryHash -> String)
-> ([DictionaryHash] -> ShowS)
-> Show DictionaryHash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DictionaryHash] -> ShowS
$cshowList :: [DictionaryHash] -> ShowS
show :: DictionaryHash -> String
$cshow :: DictionaryHash -> String
showsPrec :: Int -> DictionaryHash -> ShowS
$cshowsPrec :: Int -> DictionaryHash -> ShowS
Show)

-- | Update a running 'DictionaryHash'. You can generate a 'DictionaryHash'
-- from one or more 'ByteString's by starting from 'zeroDictionaryHash', e.g.
--
-- > dictionaryHash zeroDictionaryHash :: ByteString -> DictionaryHash
--
-- or
--
-- > foldl' dictionaryHash zeroDictionaryHash :: [ByteString] -> DictionaryHash
--
dictionaryHash :: DictionaryHash -> ByteString -> DictionaryHash
dictionaryHash :: DictionaryHash -> ByteString -> DictionaryHash
dictionaryHash (DictHash CULong
adler) ByteString
dict =
  IO DictionaryHash -> DictionaryHash
forall a. IO a -> a
unsafePerformIO (IO DictionaryHash -> DictionaryHash)
-> IO DictionaryHash -> DictionaryHash
forall a b. (a -> b) -> a -> b
$
    ByteString
-> (CStringLen -> IO DictionaryHash) -> IO DictionaryHash
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
dict ((CStringLen -> IO DictionaryHash) -> IO DictionaryHash)
-> (CStringLen -> IO DictionaryHash) -> IO DictionaryHash
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
      (CULong -> DictionaryHash) -> IO CULong -> IO DictionaryHash
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CULong -> DictionaryHash
DictHash (IO CULong -> IO DictionaryHash) -> IO CULong -> IO DictionaryHash
forall a b. (a -> b) -> a -> b
$ CULong -> Ptr CChar -> CUInt -> IO CULong
c_adler32 CULong
adler Ptr CChar
ptr (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)

-- | A zero 'DictionaryHash' to use as the initial value with 'dictionaryHash'.
--
zeroDictionaryHash :: DictionaryHash
zeroDictionaryHash :: DictionaryHash
zeroDictionaryHash = CULong -> DictionaryHash
DictHash CULong
0

----------------------------
-- Stream monad
--

newtype Stream a = Z {
    Stream a
-> ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
unZ :: ForeignPtr StreamState
        -> ForeignPtr Word8
        -> ForeignPtr Word8
        -> Int -> Int
        -> IO (ForeignPtr Word8
              ,ForeignPtr Word8
              ,Int, Int, a)
  }

instance Functor Stream where
  fmap :: (a -> b) -> Stream a -> Stream b
fmap   = (a -> b) -> Stream a -> Stream b
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM

instance Applicative Stream where
  pure :: a -> Stream a
pure   = a -> Stream a
forall a. a -> Stream a
returnZ
  <*> :: Stream (a -> b) -> Stream a -> Stream b
(<*>)  = Stream (a -> b) -> Stream a -> Stream b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
  *> :: Stream a -> Stream b -> Stream b
(*>)   = Stream a -> Stream b -> Stream b
forall a b. Stream a -> Stream b -> Stream b
thenZ_

instance Monad Stream where
  >>= :: Stream a -> (a -> Stream b) -> Stream b
(>>=)  = Stream a -> (a -> Stream b) -> Stream b
forall a b. Stream a -> (a -> Stream b) -> Stream b
thenZ
--  m >>= f = (m `thenZ` \a -> consistencyCheck `thenZ_` returnZ a) `thenZ` f
  >> :: Stream a -> Stream b -> Stream b
(>>)   = Stream a -> Stream b -> Stream b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)


{-# LINE 383 "Codec/Compression/Zlib/Stream.hsc" #-}


{-# LINE 389 "Codec/Compression/Zlib/Stream.hsc" #-}


{-# LINE 391 "Codec/Compression/Zlib/Stream.hsc" #-}
instance Fail.MonadFail Stream where
  fail   = (finalise >>) . failZ

{-# LINE 394 "Codec/Compression/Zlib/Stream.hsc" #-}

returnZ :: a -> Stream a
returnZ :: a -> Stream a
returnZ a
a = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
 -> Stream a)
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_ ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength ->
                  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, a
a)
{-# INLINE returnZ #-}

thenZ :: Stream a -> (a -> Stream b) -> Stream b
thenZ :: Stream a -> (a -> Stream b) -> Stream b
thenZ (Z ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
m) a -> Stream b
f =
  (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b))
-> Stream b
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b))
 -> Stream b)
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b))
-> Stream b
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength ->
    ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
m ForeignPtr StreamState
stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
-> ((ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b))
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      \(ForeignPtr Word8
inBuf', ForeignPtr Word8
outBuf', Int
outOffset', Int
outLength', a
a) ->
        Stream b
-> ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b)
forall a.
Stream a
-> ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
unZ (a -> Stream b
f a
a) ForeignPtr StreamState
stream ForeignPtr Word8
inBuf' ForeignPtr Word8
outBuf' Int
outOffset' Int
outLength'
{-# INLINE thenZ #-}

thenZ_ :: Stream a -> Stream b -> Stream b
thenZ_ :: Stream a -> Stream b -> Stream b
thenZ_ (Z ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
m) Stream b
f =
  (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b))
-> Stream b
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b))
 -> Stream b)
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b))
-> Stream b
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength ->
    ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
m ForeignPtr StreamState
stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
-> ((ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b))
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      \(ForeignPtr Word8
inBuf', ForeignPtr Word8
outBuf', Int
outOffset', Int
outLength', a
_) ->
        Stream b
-> ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, b)
forall a.
Stream a
-> ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
unZ Stream b
f ForeignPtr StreamState
stream ForeignPtr Word8
inBuf' ForeignPtr Word8
outBuf' Int
outOffset' Int
outLength'
{-# INLINE thenZ_ #-}

failZ :: String -> Stream a
failZ :: String -> Stream a
failZ String
msg = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z (\ForeignPtr StreamState
_ ForeignPtr Word8
_ ForeignPtr Word8
_ Int
_ Int
_ -> String -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Codec.Compression.Zlib: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg))

data State s = State !(ForeignPtr StreamState)
                     !(ForeignPtr Word8)
                     !(ForeignPtr Word8)
      {-# UNPACK #-} !Int
      {-# UNPACK #-} !Int

mkState :: ST s (State s)
mkState :: ST s (State s)
mkState = IO (State s) -> ST s (State s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (State s) -> ST s (State s)) -> IO (State s) -> ST s (State s)
forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr StreamState
stream <- Int -> IO (ForeignPtr StreamState)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
112)
{-# LINE 428 "Codec/Compression/Zlib/Stream.hsc" #-}
  withForeignPtr stream $ \ptr -> do
    (\hsc_ptr -> pokeByteOff hsc_ptr 48)       ptr nullPtr
{-# LINE 430 "Codec/Compression/Zlib/Stream.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 64)    ptr nullPtr
{-# LINE 431 "Codec/Compression/Zlib/Stream.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 72)     ptr nullPtr
{-# LINE 432 "Codec/Compression/Zlib/Stream.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 80)    ptr nullPtr
{-# LINE 433 "Codec/Compression/Zlib/Stream.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 0)   ptr nullPtr
{-# LINE 434 "Codec/Compression/Zlib/Stream.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 24)  ptr nullPtr
{-# LINE 435 "Codec/Compression/Zlib/Stream.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 8)  ptr (0 :: CUInt)
{-# LINE 436 "Codec/Compression/Zlib/Stream.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 32) ptr (0 :: CUInt)
{-# LINE 437 "Codec/Compression/Zlib/Stream.hsc" #-}
  return (State stream nullForeignPtr nullForeignPtr 0 0)

runStream :: Stream a -> State s -> ST s (a, State s)
runStream :: Stream a -> State s -> ST s (a, State s)
runStream (Z ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
m) (State ForeignPtr StreamState
stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength) =
  IO (a, State s) -> ST s (a, State s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (a, State s) -> ST s (a, State s))
-> IO (a, State s) -> ST s (a, State s)
forall a b. (a -> b) -> a -> b
$
    ForeignPtr StreamState
-> ForeignPtr Word8
-> ForeignPtr Word8
-> Int
-> Int
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
m ForeignPtr StreamState
stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
-> ((ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
    -> IO (a, State s))
-> IO (a, State s)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      \(ForeignPtr Word8
inBuf', ForeignPtr Word8
outBuf', Int
outOffset', Int
outLength', a
a) ->
        (a, State s) -> IO (a, State s)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, ForeignPtr StreamState
-> ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> Int -> State s
forall s.
ForeignPtr StreamState
-> ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> Int -> State s
State ForeignPtr StreamState
stream ForeignPtr Word8
inBuf' ForeignPtr Word8
outBuf' Int
outOffset' Int
outLength')

-- This is marked as unsafe because runStream uses unsafeIOToST so anything
-- lifted here can end up being unsafePerformIO'd.
unsafeLiftIO :: IO a -> Stream a
unsafeLiftIO :: IO a -> Stream a
unsafeLiftIO IO a
m = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
 -> Stream a)
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength -> do
  a
a <- IO a
m
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, a
a)

getStreamState :: Stream (ForeignPtr StreamState)
getStreamState :: Stream (ForeignPtr StreamState)
getStreamState = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO
      (ForeignPtr Word8, ForeignPtr Word8, Int, Int,
       ForeignPtr StreamState))
-> Stream (ForeignPtr StreamState)
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO
       (ForeignPtr Word8, ForeignPtr Word8, Int, Int,
        ForeignPtr StreamState))
 -> Stream (ForeignPtr StreamState))
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO
         (ForeignPtr Word8, ForeignPtr Word8, Int, Int,
          ForeignPtr StreamState))
-> Stream (ForeignPtr StreamState)
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int,
 ForeignPtr StreamState)
-> IO
     (ForeignPtr Word8, ForeignPtr Word8, Int, Int,
      ForeignPtr StreamState)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, ForeignPtr StreamState
stream)

getInBuf :: Stream (ForeignPtr Word8)
getInBuf :: Stream (ForeignPtr Word8)
getInBuf = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO
      (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8))
-> Stream (ForeignPtr Word8)
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO
       (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8))
 -> Stream (ForeignPtr Word8))
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO
         (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8))
-> Stream (ForeignPtr Word8)
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8)
-> IO
     (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, ForeignPtr Word8
inBuf)

getOutBuf :: Stream (ForeignPtr Word8)
getOutBuf :: Stream (ForeignPtr Word8)
getOutBuf = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO
      (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8))
-> Stream (ForeignPtr Word8)
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO
       (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8))
 -> Stream (ForeignPtr Word8))
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO
         (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8))
-> Stream (ForeignPtr Word8)
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8)
-> IO
     (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ForeignPtr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, ForeignPtr Word8
outBuf)

getOutOffset :: Stream Int
getOutOffset :: Stream Int
getOutOffset = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int))
-> Stream Int
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int))
 -> Stream Int)
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int))
-> Stream Int
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int)
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, Int
outOffset)

getOutAvail :: Stream Int
getOutAvail :: Stream Int
getOutAvail = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int))
-> Stream Int
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int))
 -> Stream Int)
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int))
-> Stream Int
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
outLength -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int)
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, Int
outLength)

setInBuf :: ForeignPtr Word8 -> Stream ()
setInBuf :: ForeignPtr Word8 -> Stream ()
setInBuf ForeignPtr Word8
inBuf = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
-> Stream ()
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
 -> Stream ())
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
-> Stream ()
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
_ ForeignPtr Word8
outBuf Int
outOffset Int
outLength -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ())
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ())
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, ())

setOutBuf :: ForeignPtr Word8 -> Stream ()
setOutBuf :: ForeignPtr Word8 -> Stream ()
setOutBuf ForeignPtr Word8
outBuf = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
-> Stream ()
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
 -> Stream ())
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
-> Stream ()
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
inBuf ForeignPtr Word8
_ Int
outOffset Int
outLength -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ())
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ())
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, ())

setOutOffset :: Int -> Stream ()
setOutOffset :: Int -> Stream ()
setOutOffset Int
outOffset = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
-> Stream ()
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
 -> Stream ())
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
-> Stream ()
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
_ Int
outLength -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ())
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ())
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, ())

setOutAvail :: Int -> Stream ()
setOutAvail :: Int -> Stream ()
setOutAvail Int
outLength = (ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
-> Stream ()
forall a.
(ForeignPtr StreamState
 -> ForeignPtr Word8
 -> ForeignPtr Word8
 -> Int
 -> Int
 -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, a))
-> Stream a
Z ((ForeignPtr StreamState
  -> ForeignPtr Word8
  -> ForeignPtr Word8
  -> Int
  -> Int
  -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
 -> Stream ())
-> (ForeignPtr StreamState
    -> ForeignPtr Word8
    -> ForeignPtr Word8
    -> Int
    -> Int
    -> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ()))
-> Stream ()
forall a b. (a -> b) -> a -> b
$ \ForeignPtr StreamState
_stream ForeignPtr Word8
inBuf ForeignPtr Word8
outBuf Int
outOffset Int
_ -> do
  (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ())
-> IO (ForeignPtr Word8, ForeignPtr Word8, Int, Int, ())
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8
inBuf, ForeignPtr Word8
outBuf, Int
outOffset, Int
outLength, ())

----------------------------
-- Debug stuff
--


{-# LINE 532 "Codec/Compression/Zlib/Stream.hsc" #-}


----------------------------
-- zlib wrapper layer
--

data Status =
    Ok
  | StreamEnd
  | Error ErrorCode String

data ErrorCode =
    NeedDict DictionaryHash
  | FileError
  | StreamError
  | DataError
  | MemoryError
  | BufferError -- ^ No progress was possible or there was not enough room in
                --   the output buffer when 'Finish' is used. Note that
                --   'BuferError' is not fatal, and 'inflate' can be called
                --   again with more input and more output space to continue.
  | VersionError
  | Unexpected

toStatus :: CInt -> Stream Status
toStatus :: CInt -> Stream Status
toStatus CInt
errno = case CInt
errno of
  (CInt
0)            -> Status -> Stream Status
forall (m :: * -> *) a. Monad m => a -> m a
return Status
Ok
{-# LINE 559 "Codec/Compression/Zlib/Stream.hsc" #-}
  (1)    -> return StreamEnd
{-# LINE 560 "Codec/Compression/Zlib/Stream.hsc" #-}
  (2)     -> do
{-# LINE 561 "Codec/Compression/Zlib/Stream.hsc" #-}
    adler <- withStreamPtr ((\hsc_ptr -> peekByteOff hsc_ptr 96))
{-# LINE 562 "Codec/Compression/Zlib/Stream.hsc" #-}
    err (NeedDict (DictHash adler))  "custom dictionary needed"
  (-5)     -> ErrorCode -> String -> Stream Status
err ErrorCode
BufferError  String
"buffer error"
{-# LINE 564 "Codec/Compression/Zlib/Stream.hsc" #-}
  (-1)         -> err FileError    "file error"
{-# LINE 565 "Codec/Compression/Zlib/Stream.hsc" #-}
  (-2)  -> err StreamError  "stream error"
{-# LINE 566 "Codec/Compression/Zlib/Stream.hsc" #-}
  (-3)    -> err DataError    "data error"
{-# LINE 567 "Codec/Compression/Zlib/Stream.hsc" #-}
  (-4)     -> err MemoryError  "insufficient memory"
{-# LINE 568 "Codec/Compression/Zlib/Stream.hsc" #-}
  (-6) -> err VersionError "incompatible zlib version"
{-# LINE 569 "Codec/Compression/Zlib/Stream.hsc" #-}
  other                      -> return $ Error Unexpected
                                  ("unexpected zlib status: " ++ show other)
 where
   err :: ErrorCode -> String -> Stream Status
err ErrorCode
errCode String
altMsg = (String -> Status) -> Stream String -> Stream Status
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (ErrorCode -> String -> Status
Error ErrorCode
errCode) (Stream String -> Stream Status) -> Stream String -> Stream Status
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
msgPtr <- (Ptr StreamState -> IO (Ptr CChar)) -> Stream (Ptr CChar)
forall a. (Ptr StreamState -> IO a) -> Stream a
withStreamPtr ((\Ptr StreamState
hsc_ptr -> Ptr StreamState -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr StreamState
hsc_ptr Int
48))
{-# LINE 574 "Codec/Compression/Zlib/Stream.hsc" #-}
    if msgPtr /= nullPtr
     then unsafeLiftIO (peekCAString msgPtr)
     else return altMsg

failIfError :: CInt -> Stream ()
failIfError :: CInt -> Stream ()
failIfError CInt
errno = CInt -> Stream Status
toStatus CInt
errno Stream Status -> (Status -> Stream ()) -> Stream ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Status
status -> case Status
status of
  (Error ErrorCode
_ String
msg) -> String -> Stream ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
msg
  Status
_             -> () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


data Flush =
    NoFlush
  | SyncFlush
  | FullFlush
  | Finish
--  | Block -- only available in zlib 1.2 and later, uncomment if you need it.

fromFlush :: Flush -> CInt
fromFlush :: Flush -> CInt
fromFlush Flush
NoFlush   = CInt
0
{-# LINE 593 "Codec/Compression/Zlib/Stream.hsc" #-}
fromFlush SyncFlush = 2
{-# LINE 594 "Codec/Compression/Zlib/Stream.hsc" #-}
fromFlush FullFlush = 3
{-# LINE 595 "Codec/Compression/Zlib/Stream.hsc" #-}
fromFlush Finish    = 4
{-# LINE 596 "Codec/Compression/Zlib/Stream.hsc" #-}
--  fromFlush Block     = #{const Z_BLOCK}


-- | The format used for compression or decompression. There are three
-- variations.
--
data Format = GZip | Zlib | Raw | GZipOrZlib
  deriving (Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c== :: Format -> Format -> Bool
Eq, Eq Format
Eq Format
-> (Format -> Format -> Ordering)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Format)
-> (Format -> Format -> Format)
-> Ord Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
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
min :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmax :: Format -> Format -> Format
>= :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c< :: Format -> Format -> Bool
compare :: Format -> Format -> Ordering
$ccompare :: Format -> Format -> Ordering
$cp1Ord :: Eq Format
Ord, Int -> Format
Format -> Int
Format -> [Format]
Format -> Format
Format -> Format -> [Format]
Format -> Format -> Format -> [Format]
(Format -> Format)
-> (Format -> Format)
-> (Int -> Format)
-> (Format -> Int)
-> (Format -> [Format])
-> (Format -> Format -> [Format])
-> (Format -> Format -> [Format])
-> (Format -> Format -> Format -> [Format])
-> Enum Format
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Format -> Format -> Format -> [Format]
$cenumFromThenTo :: Format -> Format -> Format -> [Format]
enumFromTo :: Format -> Format -> [Format]
$cenumFromTo :: Format -> Format -> [Format]
enumFromThen :: Format -> Format -> [Format]
$cenumFromThen :: Format -> Format -> [Format]
enumFrom :: Format -> [Format]
$cenumFrom :: Format -> [Format]
fromEnum :: Format -> Int
$cfromEnum :: Format -> Int
toEnum :: Int -> Format
$ctoEnum :: Int -> Format
pred :: Format -> Format
$cpred :: Format -> Format
succ :: Format -> Format
$csucc :: Format -> Format
Enum, Format
Format -> Format -> Bounded Format
forall a. a -> a -> Bounded a
maxBound :: Format
$cmaxBound :: Format
minBound :: Format
$cminBound :: Format
Bounded, Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
(Int -> Format -> ShowS)
-> (Format -> String) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Format] -> ShowS
$cshowList :: [Format] -> ShowS
show :: Format -> String
$cshow :: Format -> String
showsPrec :: Int -> Format -> ShowS
$cshowsPrec :: Int -> Format -> ShowS
Show, Typeable

{-# LINE 605 "Codec/Compression/Zlib/Stream.hsc" #-}
              , (forall x. Format -> Rep Format x)
-> (forall x. Rep Format x -> Format) -> Generic Format
forall x. Rep Format x -> Format
forall x. Format -> Rep Format x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Format x -> Format
$cfrom :: forall x. Format -> Rep Format x
Generic

{-# LINE 607 "Codec/Compression/Zlib/Stream.hsc" #-}
           )

{-# DEPRECATED GZip       "Use gzipFormat. Format constructors will be hidden in version 0.7"       #-}
{-# DEPRECATED Zlib       "Use zlibFormat. Format constructors will be hidden in version 0.7"       #-}
{-# DEPRECATED Raw        "Use rawFormat. Format constructors will be hidden in version 0.7"        #-}
{-# DEPRECATED GZipOrZlib "Use gzipOrZlibFormat. Format constructors will be hidden in version 0.7" #-}

-- | The gzip format uses a header with a checksum and some optional meta-data
-- about the compressed file. It is intended primarily for compressing
-- individual files but is also sometimes used for network protocols such as
-- HTTP. The format is described in detail in RFC #1952
-- <http://www.ietf.org/rfc/rfc1952.txt>
--
gzipFormat :: Format
gzipFormat :: Format
gzipFormat = Format
GZip

-- | The zlib format uses a minimal header with a checksum but no other
-- meta-data. It is especially designed for use in network protocols. The
-- format is described in detail in RFC #1950
-- <http://www.ietf.org/rfc/rfc1950.txt>
--
zlibFormat :: Format
zlibFormat :: Format
zlibFormat = Format
Zlib

-- | The \'raw\' format is just the compressed data stream without any
-- additional header, meta-data or data-integrity checksum. The format is
-- described in detail in RFC #1951 <http://www.ietf.org/rfc/rfc1951.txt>
--
rawFormat :: Format
rawFormat :: Format
rawFormat = Format
Raw

-- | This is not a format as such. It enabled zlib or gzip decoding with
-- automatic header detection. This only makes sense for decompression.
--
gzipOrZlibFormat :: Format
gzipOrZlibFormat :: Format
gzipOrZlibFormat = Format
GZipOrZlib

formatSupportsDictionary :: Format -> Bool
formatSupportsDictionary :: Format -> Bool
formatSupportsDictionary Format
Zlib = Bool
True
formatSupportsDictionary Format
Raw  = Bool
True
formatSupportsDictionary Format
_    = Bool
False

-- | The compression method
--
data Method = Deflated
  deriving (Method -> Method -> Bool
(Method -> Method -> Bool)
-> (Method -> Method -> Bool) -> Eq Method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Method -> Method -> Bool
$c/= :: Method -> Method -> Bool
== :: Method -> Method -> Bool
$c== :: Method -> Method -> Bool
Eq, Eq Method
Eq Method
-> (Method -> Method -> Ordering)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Method)
-> (Method -> Method -> Method)
-> Ord Method
Method -> Method -> Bool
Method -> Method -> Ordering
Method -> Method -> Method
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
min :: Method -> Method -> Method
$cmin :: Method -> Method -> Method
max :: Method -> Method -> Method
$cmax :: Method -> Method -> Method
>= :: Method -> Method -> Bool
$c>= :: Method -> Method -> Bool
> :: Method -> Method -> Bool
$c> :: Method -> Method -> Bool
<= :: Method -> Method -> Bool
$c<= :: Method -> Method -> Bool
< :: Method -> Method -> Bool
$c< :: Method -> Method -> Bool
compare :: Method -> Method -> Ordering
$ccompare :: Method -> Method -> Ordering
$cp1Ord :: Eq Method
Ord, Int -> Method
Method -> Int
Method -> [Method]
Method -> Method
Method -> Method -> [Method]
Method -> Method -> Method -> [Method]
(Method -> Method)
-> (Method -> Method)
-> (Int -> Method)
-> (Method -> Int)
-> (Method -> [Method])
-> (Method -> Method -> [Method])
-> (Method -> Method -> [Method])
-> (Method -> Method -> Method -> [Method])
-> Enum Method
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Method -> Method -> Method -> [Method]
$cenumFromThenTo :: Method -> Method -> Method -> [Method]
enumFromTo :: Method -> Method -> [Method]
$cenumFromTo :: Method -> Method -> [Method]
enumFromThen :: Method -> Method -> [Method]
$cenumFromThen :: Method -> Method -> [Method]
enumFrom :: Method -> [Method]
$cenumFrom :: Method -> [Method]
fromEnum :: Method -> Int
$cfromEnum :: Method -> Int
toEnum :: Int -> Method
$ctoEnum :: Int -> Method
pred :: Method -> Method
$cpred :: Method -> Method
succ :: Method -> Method
$csucc :: Method -> Method
Enum, Method
Method -> Method -> Bounded Method
forall a. a -> a -> Bounded a
maxBound :: Method
$cmaxBound :: Method
minBound :: Method
$cminBound :: Method
Bounded, Int -> Method -> ShowS
[Method] -> ShowS
Method -> String
(Int -> Method -> ShowS)
-> (Method -> String) -> ([Method] -> ShowS) -> Show Method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Method] -> ShowS
$cshowList :: [Method] -> ShowS
show :: Method -> String
$cshow :: Method -> String
showsPrec :: Int -> Method -> ShowS
$cshowsPrec :: Int -> Method -> ShowS
Show, Typeable

{-# LINE 654 "Codec/Compression/Zlib/Stream.hsc" #-}
              , (forall x. Method -> Rep Method x)
-> (forall x. Rep Method x -> Method) -> Generic Method
forall x. Rep Method x -> Method
forall x. Method -> Rep Method x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Method x -> Method
$cfrom :: forall x. Method -> Rep Method x
Generic

{-# LINE 656 "Codec/Compression/Zlib/Stream.hsc" #-}
           )

{-# DEPRECATED Deflated "Use deflateMethod. Method constructors will be hidden in version 0.7" #-}

-- | \'Deflate\' is the only method supported in this version of zlib.
-- Indeed it is likely to be the only method that ever will be supported.
--
deflateMethod :: Method
deflateMethod :: Method
deflateMethod = Method
Deflated

fromMethod :: Method -> CInt
fromMethod :: Method -> CInt
fromMethod Method
Deflated = CInt
8
{-# LINE 668 "Codec/Compression/Zlib/Stream.hsc" #-}


-- | The compression level parameter controls the amount of compression. This
-- is a trade-off between the amount of compression and the time required to do
-- the compression.
--
data CompressionLevel = 
    DefaultCompression
  | NoCompression
  | BestSpeed
  | BestCompression
  | CompressionLevel Int
  deriving (CompressionLevel -> CompressionLevel -> Bool
(CompressionLevel -> CompressionLevel -> Bool)
-> (CompressionLevel -> CompressionLevel -> Bool)
-> Eq CompressionLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompressionLevel -> CompressionLevel -> Bool
$c/= :: CompressionLevel -> CompressionLevel -> Bool
== :: CompressionLevel -> CompressionLevel -> Bool
$c== :: CompressionLevel -> CompressionLevel -> Bool
Eq, Int -> CompressionLevel -> ShowS
[CompressionLevel] -> ShowS
CompressionLevel -> String
(Int -> CompressionLevel -> ShowS)
-> (CompressionLevel -> String)
-> ([CompressionLevel] -> ShowS)
-> Show CompressionLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompressionLevel] -> ShowS
$cshowList :: [CompressionLevel] -> ShowS
show :: CompressionLevel -> String
$cshow :: CompressionLevel -> String
showsPrec :: Int -> CompressionLevel -> ShowS
$cshowsPrec :: Int -> CompressionLevel -> ShowS
Show, Typeable

{-# LINE 682 "Codec/Compression/Zlib/Stream.hsc" #-}
              , (forall x. CompressionLevel -> Rep CompressionLevel x)
-> (forall x. Rep CompressionLevel x -> CompressionLevel)
-> Generic CompressionLevel
forall x. Rep CompressionLevel x -> CompressionLevel
forall x. CompressionLevel -> Rep CompressionLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompressionLevel x -> CompressionLevel
$cfrom :: forall x. CompressionLevel -> Rep CompressionLevel x
Generic

{-# LINE 684 "Codec/Compression/Zlib/Stream.hsc" #-}
           )

{-# DEPRECATED DefaultCompression "Use defaultCompression. CompressionLevel constructors will be hidden in version 0.7" #-}
{-# DEPRECATED NoCompression      "Use noCompression. CompressionLevel constructors will be hidden in version 0.7"      #-}
{-# DEPRECATED BestSpeed          "Use bestSpeed. CompressionLevel constructors will be hidden in version 0.7"          #-}
{-# DEPRECATED BestCompression    "Use bestCompression. CompressionLevel constructors will be hidden in version 0.7"    #-}
--FIXME: cannot deprecate constructor named the same as the type
{- DEPRECATED CompressionLevel   "Use compressionLevel. CompressionLevel constructors will be hidden in version 0.7"   -}

-- | The default compression level is 6 (that is, biased towards higher
-- compression at expense of speed).
defaultCompression :: CompressionLevel
defaultCompression :: CompressionLevel
defaultCompression = CompressionLevel
DefaultCompression

-- | No compression, just a block copy.
noCompression :: CompressionLevel
noCompression :: CompressionLevel
noCompression = Int -> CompressionLevel
CompressionLevel Int
0

-- | The fastest compression method (less compression)
bestSpeed :: CompressionLevel
bestSpeed :: CompressionLevel
bestSpeed = Int -> CompressionLevel
CompressionLevel Int
1

-- | The slowest compression method (best compression).
bestCompression :: CompressionLevel
bestCompression :: CompressionLevel
bestCompression = Int -> CompressionLevel
CompressionLevel Int
9

-- | A specific compression level between 0 and 9.
compressionLevel :: Int -> CompressionLevel
compressionLevel :: Int -> CompressionLevel
compressionLevel Int
n
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
9 = Int -> CompressionLevel
CompressionLevel Int
n
  | Bool
otherwise        = String -> CompressionLevel
forall a. (?callStack::CallStack) => String -> a
error String
"CompressionLevel must be in the range 0..9"

fromCompressionLevel :: CompressionLevel -> CInt
fromCompressionLevel :: CompressionLevel -> CInt
fromCompressionLevel CompressionLevel
DefaultCompression   = -CInt
1
fromCompressionLevel CompressionLevel
NoCompression        = CInt
0
fromCompressionLevel CompressionLevel
BestSpeed            = CInt
1
fromCompressionLevel CompressionLevel
BestCompression      = CInt
9
fromCompressionLevel (CompressionLevel Int
n)
           | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
9 = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n
           | Bool
otherwise        = String -> CInt
forall a. (?callStack::CallStack) => String -> a
error String
"CompressLevel must be in the range 1..9"


-- | This specifies the size of the compression window. Larger values of this
-- parameter result in better compression at the expense of higher memory
-- usage.
--
-- The compression window size is the value of the the window bits raised to
-- the power 2. The window bits must be in the range @9..15@ which corresponds
-- to compression window sizes of 512b to 32Kb. The default is 15 which is also
-- the maximum size.
--
-- The total amount of memory used depends on the window bits and the
-- 'MemoryLevel'. See the 'MemoryLevel' for the details.
--
data WindowBits = WindowBits Int
                | DefaultWindowBits -- This constructor must be last to make
                                    -- the Ord instance work. The Ord instance
                                    -- is used by the tests.
                                    -- It makse sense because the default value
                                    -- is is also the max value at 15.
  deriving (WindowBits -> WindowBits -> Bool
(WindowBits -> WindowBits -> Bool)
-> (WindowBits -> WindowBits -> Bool) -> Eq WindowBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowBits -> WindowBits -> Bool
$c/= :: WindowBits -> WindowBits -> Bool
== :: WindowBits -> WindowBits -> Bool
$c== :: WindowBits -> WindowBits -> Bool
Eq, Eq WindowBits
Eq WindowBits
-> (WindowBits -> WindowBits -> Ordering)
-> (WindowBits -> WindowBits -> Bool)
-> (WindowBits -> WindowBits -> Bool)
-> (WindowBits -> WindowBits -> Bool)
-> (WindowBits -> WindowBits -> Bool)
-> (WindowBits -> WindowBits -> WindowBits)
-> (WindowBits -> WindowBits -> WindowBits)
-> Ord WindowBits
WindowBits -> WindowBits -> Bool
WindowBits -> WindowBits -> Ordering
WindowBits -> WindowBits -> WindowBits
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
min :: WindowBits -> WindowBits -> WindowBits
$cmin :: WindowBits -> WindowBits -> WindowBits
max :: WindowBits -> WindowBits -> WindowBits
$cmax :: WindowBits -> WindowBits -> WindowBits
>= :: WindowBits -> WindowBits -> Bool
$c>= :: WindowBits -> WindowBits -> Bool
> :: WindowBits -> WindowBits -> Bool
$c> :: WindowBits -> WindowBits -> Bool
<= :: WindowBits -> WindowBits -> Bool
$c<= :: WindowBits -> WindowBits -> Bool
< :: WindowBits -> WindowBits -> Bool
$c< :: WindowBits -> WindowBits -> Bool
compare :: WindowBits -> WindowBits -> Ordering
$ccompare :: WindowBits -> WindowBits -> Ordering
$cp1Ord :: Eq WindowBits
Ord, Int -> WindowBits -> ShowS
[WindowBits] -> ShowS
WindowBits -> String
(Int -> WindowBits -> ShowS)
-> (WindowBits -> String)
-> ([WindowBits] -> ShowS)
-> Show WindowBits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowBits] -> ShowS
$cshowList :: [WindowBits] -> ShowS
show :: WindowBits -> String
$cshow :: WindowBits -> String
showsPrec :: Int -> WindowBits -> ShowS
$cshowsPrec :: Int -> WindowBits -> ShowS
Show, Typeable

{-# LINE 746 "Codec/Compression/Zlib/Stream.hsc" #-}
              , (forall x. WindowBits -> Rep WindowBits x)
-> (forall x. Rep WindowBits x -> WindowBits) -> Generic WindowBits
forall x. Rep WindowBits x -> WindowBits
forall x. WindowBits -> Rep WindowBits x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowBits x -> WindowBits
$cfrom :: forall x. WindowBits -> Rep WindowBits x
Generic

{-# LINE 748 "Codec/Compression/Zlib/Stream.hsc" #-}
           )

{-# DEPRECATED DefaultWindowBits  "Use defaultWindowBits. WindowBits constructors will be hidden in version 0.7" #-}
--FIXME: cannot deprecate constructor named the same as the type
{- DEPRECATED WindowBits         "Use windowBits. WindowBits constructors will be hidden in version 0.7"        -}

-- | The default 'WindowBits' is 15 which is also the maximum size.
--
defaultWindowBits :: WindowBits
defaultWindowBits :: WindowBits
defaultWindowBits = Int -> WindowBits
WindowBits Int
15

-- | A specific compression window size, specified in bits in the range @9..15@
--
windowBits :: Int -> WindowBits
windowBits :: Int -> WindowBits
windowBits Int
n
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
9 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
15 = Int -> WindowBits
WindowBits Int
n
  | Bool
otherwise         = String -> WindowBits
forall a. (?callStack::CallStack) => String -> a
error String
"WindowBits must be in the range 9..15"

fromWindowBits :: Format -> WindowBits-> CInt
fromWindowBits :: Format -> WindowBits -> CInt
fromWindowBits Format
format WindowBits
bits = (Format -> CInt -> CInt
forall a. Num a => Format -> a -> a
formatModifier Format
format) (WindowBits -> CInt
forall p. Num p => WindowBits -> p
checkWindowBits WindowBits
bits)
  where checkWindowBits :: WindowBits -> p
checkWindowBits WindowBits
DefaultWindowBits = p
15
        checkWindowBits (WindowBits Int
n)
          | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
9 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
15 = Int -> p
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n
          | Bool
otherwise         = String -> p
forall a. (?callStack::CallStack) => String -> a
error String
"WindowBits must be in the range 9..15"
        formatModifier :: Format -> a -> a
formatModifier Format
Zlib       = a -> a
forall a. a -> a
id
        formatModifier Format
GZip       = (a -> a -> a
forall a. Num a => a -> a -> a
+a
16)
        formatModifier Format
GZipOrZlib = (a -> a -> a
forall a. Num a => a -> a -> a
+a
32)
        formatModifier Format
Raw        = a -> a
forall a. Num a => a -> a
negate


-- | The 'MemoryLevel' parameter specifies how much memory should be allocated
-- for the internal compression state. It is a tradoff between memory usage,
-- compression ratio and compression speed. Using more memory allows faster
-- compression and a better compression ratio.
--
-- The total amount of memory used for compression depends on the 'WindowBits'
-- and the 'MemoryLevel'. For decompression it depends only on the
-- 'WindowBits'. The totals are given by the functions:
--
-- > compressTotal windowBits memLevel = 4 * 2^windowBits + 512 * 2^memLevel
-- > decompressTotal windowBits = 2^windowBits
--
-- For example, for compression with the default @windowBits = 15@ and
-- @memLevel = 8@ uses @256Kb@. So for example a network server with 100
-- concurrent compressed streams would use @25Mb@. The memory per stream can be
-- halved (at the cost of somewhat degraded and slower compressionby) by
-- reducing the @windowBits@ and @memLevel@ by one.
--
-- Decompression takes less memory, the default @windowBits = 15@ corresponds
-- to just @32Kb@.
--
data MemoryLevel =
    DefaultMemoryLevel
  | MinMemoryLevel
  | MaxMemoryLevel
  | MemoryLevel Int
  deriving (MemoryLevel -> MemoryLevel -> Bool
(MemoryLevel -> MemoryLevel -> Bool)
-> (MemoryLevel -> MemoryLevel -> Bool) -> Eq MemoryLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryLevel -> MemoryLevel -> Bool
$c/= :: MemoryLevel -> MemoryLevel -> Bool
== :: MemoryLevel -> MemoryLevel -> Bool
$c== :: MemoryLevel -> MemoryLevel -> Bool
Eq, Int -> MemoryLevel -> ShowS
[MemoryLevel] -> ShowS
MemoryLevel -> String
(Int -> MemoryLevel -> ShowS)
-> (MemoryLevel -> String)
-> ([MemoryLevel] -> ShowS)
-> Show MemoryLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MemoryLevel] -> ShowS
$cshowList :: [MemoryLevel] -> ShowS
show :: MemoryLevel -> String
$cshow :: MemoryLevel -> String
showsPrec :: Int -> MemoryLevel -> ShowS
$cshowsPrec :: Int -> MemoryLevel -> ShowS
Show, Typeable

{-# LINE 806 "Codec/Compression/Zlib/Stream.hsc" #-}
              , (forall x. MemoryLevel -> Rep MemoryLevel x)
-> (forall x. Rep MemoryLevel x -> MemoryLevel)
-> Generic MemoryLevel
forall x. Rep MemoryLevel x -> MemoryLevel
forall x. MemoryLevel -> Rep MemoryLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MemoryLevel x -> MemoryLevel
$cfrom :: forall x. MemoryLevel -> Rep MemoryLevel x
Generic

{-# LINE 808 "Codec/Compression/Zlib/Stream.hsc" #-}
           )

{-# DEPRECATED DefaultMemoryLevel "Use defaultMemoryLevel. MemoryLevel constructors will be hidden in version 0.7" #-}
{-# DEPRECATED MinMemoryLevel     "Use minMemoryLevel. MemoryLevel constructors will be hidden in version 0.7"     #-}
{-# DEPRECATED MaxMemoryLevel     "Use maxMemoryLevel. MemoryLevel constructors will be hidden in version 0.7"     #-}
--FIXME: cannot deprecate constructor named the same as the type
{- DEPRECATED MemoryLevel        "Use memoryLevel. MemoryLevel constructors will be hidden in version 0.7"        -}

-- | The default memory level. (Equivalent to @'memoryLevel' 8@)
--
defaultMemoryLevel :: MemoryLevel
defaultMemoryLevel :: MemoryLevel
defaultMemoryLevel = Int -> MemoryLevel
MemoryLevel Int
8

-- | Use minimum memory. This is slow and reduces the compression ratio.
-- (Equivalent to @'memoryLevel' 1@)
--
minMemoryLevel :: MemoryLevel
minMemoryLevel :: MemoryLevel
minMemoryLevel = Int -> MemoryLevel
MemoryLevel Int
1

-- | Use maximum memory for optimal compression speed.
-- (Equivalent to @'memoryLevel' 9@)
--
maxMemoryLevel :: MemoryLevel
maxMemoryLevel :: MemoryLevel
maxMemoryLevel = Int -> MemoryLevel
MemoryLevel Int
9

-- | A specific level in the range @1..9@
--
memoryLevel :: Int -> MemoryLevel
memoryLevel :: Int -> MemoryLevel
memoryLevel Int
n
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
9 = Int -> MemoryLevel
MemoryLevel Int
n
  | Bool
otherwise        = String -> MemoryLevel
forall a. (?callStack::CallStack) => String -> a
error String
"MemoryLevel must be in the range 1..9"

fromMemoryLevel :: MemoryLevel -> CInt
fromMemoryLevel :: MemoryLevel -> CInt
fromMemoryLevel MemoryLevel
DefaultMemoryLevel = CInt
8
fromMemoryLevel MemoryLevel
MinMemoryLevel     = CInt
1
fromMemoryLevel MemoryLevel
MaxMemoryLevel     = CInt
9
fromMemoryLevel (MemoryLevel Int
n)
         | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
9 = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n
         | Bool
otherwise        = String -> CInt
forall a. (?callStack::CallStack) => String -> a
error String
"MemoryLevel must be in the range 1..9"


-- | The strategy parameter is used to tune the compression algorithm.
--
-- The strategy parameter only affects the compression ratio but not the
-- correctness of the compressed output even if it is not set appropriately.
--
data CompressionStrategy =
    DefaultStrategy
  | Filtered
  | HuffmanOnly
  deriving (CompressionStrategy -> CompressionStrategy -> Bool
(CompressionStrategy -> CompressionStrategy -> Bool)
-> (CompressionStrategy -> CompressionStrategy -> Bool)
-> Eq CompressionStrategy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompressionStrategy -> CompressionStrategy -> Bool
$c/= :: CompressionStrategy -> CompressionStrategy -> Bool
== :: CompressionStrategy -> CompressionStrategy -> Bool
$c== :: CompressionStrategy -> CompressionStrategy -> Bool
Eq, Eq CompressionStrategy
Eq CompressionStrategy
-> (CompressionStrategy -> CompressionStrategy -> Ordering)
-> (CompressionStrategy -> CompressionStrategy -> Bool)
-> (CompressionStrategy -> CompressionStrategy -> Bool)
-> (CompressionStrategy -> CompressionStrategy -> Bool)
-> (CompressionStrategy -> CompressionStrategy -> Bool)
-> (CompressionStrategy
    -> CompressionStrategy -> CompressionStrategy)
-> (CompressionStrategy
    -> CompressionStrategy -> CompressionStrategy)
-> Ord CompressionStrategy
CompressionStrategy -> CompressionStrategy -> Bool
CompressionStrategy -> CompressionStrategy -> Ordering
CompressionStrategy -> CompressionStrategy -> CompressionStrategy
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
min :: CompressionStrategy -> CompressionStrategy -> CompressionStrategy
$cmin :: CompressionStrategy -> CompressionStrategy -> CompressionStrategy
max :: CompressionStrategy -> CompressionStrategy -> CompressionStrategy
$cmax :: CompressionStrategy -> CompressionStrategy -> CompressionStrategy
>= :: CompressionStrategy -> CompressionStrategy -> Bool
$c>= :: CompressionStrategy -> CompressionStrategy -> Bool
> :: CompressionStrategy -> CompressionStrategy -> Bool
$c> :: CompressionStrategy -> CompressionStrategy -> Bool
<= :: CompressionStrategy -> CompressionStrategy -> Bool
$c<= :: CompressionStrategy -> CompressionStrategy -> Bool
< :: CompressionStrategy -> CompressionStrategy -> Bool
$c< :: CompressionStrategy -> CompressionStrategy -> Bool
compare :: CompressionStrategy -> CompressionStrategy -> Ordering
$ccompare :: CompressionStrategy -> CompressionStrategy -> Ordering
$cp1Ord :: Eq CompressionStrategy
Ord, Int -> CompressionStrategy
CompressionStrategy -> Int
CompressionStrategy -> [CompressionStrategy]
CompressionStrategy -> CompressionStrategy
CompressionStrategy -> CompressionStrategy -> [CompressionStrategy]
CompressionStrategy
-> CompressionStrategy
-> CompressionStrategy
-> [CompressionStrategy]
(CompressionStrategy -> CompressionStrategy)
-> (CompressionStrategy -> CompressionStrategy)
-> (Int -> CompressionStrategy)
-> (CompressionStrategy -> Int)
-> (CompressionStrategy -> [CompressionStrategy])
-> (CompressionStrategy
    -> CompressionStrategy -> [CompressionStrategy])
-> (CompressionStrategy
    -> CompressionStrategy -> [CompressionStrategy])
-> (CompressionStrategy
    -> CompressionStrategy
    -> CompressionStrategy
    -> [CompressionStrategy])
-> Enum CompressionStrategy
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CompressionStrategy
-> CompressionStrategy
-> CompressionStrategy
-> [CompressionStrategy]
$cenumFromThenTo :: CompressionStrategy
-> CompressionStrategy
-> CompressionStrategy
-> [CompressionStrategy]
enumFromTo :: CompressionStrategy -> CompressionStrategy -> [CompressionStrategy]
$cenumFromTo :: CompressionStrategy -> CompressionStrategy -> [CompressionStrategy]
enumFromThen :: CompressionStrategy -> CompressionStrategy -> [CompressionStrategy]
$cenumFromThen :: CompressionStrategy -> CompressionStrategy -> [CompressionStrategy]
enumFrom :: CompressionStrategy -> [CompressionStrategy]
$cenumFrom :: CompressionStrategy -> [CompressionStrategy]
fromEnum :: CompressionStrategy -> Int
$cfromEnum :: CompressionStrategy -> Int
toEnum :: Int -> CompressionStrategy
$ctoEnum :: Int -> CompressionStrategy
pred :: CompressionStrategy -> CompressionStrategy
$cpred :: CompressionStrategy -> CompressionStrategy
succ :: CompressionStrategy -> CompressionStrategy
$csucc :: CompressionStrategy -> CompressionStrategy
Enum, CompressionStrategy
CompressionStrategy
-> CompressionStrategy -> Bounded CompressionStrategy
forall a. a -> a -> Bounded a
maxBound :: CompressionStrategy
$cmaxBound :: CompressionStrategy
minBound :: CompressionStrategy
$cminBound :: CompressionStrategy
Bounded, Int -> CompressionStrategy -> ShowS
[CompressionStrategy] -> ShowS
CompressionStrategy -> String
(Int -> CompressionStrategy -> ShowS)
-> (CompressionStrategy -> String)
-> ([CompressionStrategy] -> ShowS)
-> Show CompressionStrategy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompressionStrategy] -> ShowS
$cshowList :: [CompressionStrategy] -> ShowS
show :: CompressionStrategy -> String
$cshow :: CompressionStrategy -> String
showsPrec :: Int -> CompressionStrategy -> ShowS
$cshowsPrec :: Int -> CompressionStrategy -> ShowS
Show, Typeable

{-# LINE 860 "Codec/Compression/Zlib/Stream.hsc" #-}
              , (forall x. CompressionStrategy -> Rep CompressionStrategy x)
-> (forall x. Rep CompressionStrategy x -> CompressionStrategy)
-> Generic CompressionStrategy
forall x. Rep CompressionStrategy x -> CompressionStrategy
forall x. CompressionStrategy -> Rep CompressionStrategy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompressionStrategy x -> CompressionStrategy
$cfrom :: forall x. CompressionStrategy -> Rep CompressionStrategy x
Generic

{-# LINE 862 "Codec/Compression/Zlib/Stream.hsc" #-}
           )

{-
-- -- only available in zlib 1.2 and later, uncomment if you need it.
  | RLE             -- ^ Use 'RLE' to limit match distances to one (run-length
                    --   encoding). 'RLE' is designed to be almost as fast as
                    --   'HuffmanOnly', but give better compression for PNG
                    --   image data.
  | Fixed           -- ^ 'Fixed' prevents the use of dynamic Huffman codes,
                    --   allowing for a simpler decoder for special applications.
-}

{-# DEPRECATED DefaultStrategy "Use defaultStrategy. CompressionStrategy constructors will be hidden in version 0.7"     #-}
{-# DEPRECATED Filtered        "Use filteredStrategy. CompressionStrategy constructors will be hidden in version 0.7"    #-}
{-# DEPRECATED HuffmanOnly     "Use huffmanOnlyStrategy. CompressionStrategy constructors will be hidden in version 0.7" #-}

-- | Use this default compression strategy for normal data.
--
defaultStrategy :: CompressionStrategy
defaultStrategy :: CompressionStrategy
defaultStrategy = CompressionStrategy
DefaultStrategy

-- | Use the filtered compression strategy for data produced by a filter (or
-- predictor). Filtered data consists mostly of small values with a somewhat
-- random distribution. In this case, the compression algorithm is tuned to
-- compress them better. The effect of this strategy is to force more Huffman
-- coding and less string matching; it is somewhat intermediate between
-- 'defaultCompressionStrategy' and 'huffmanOnlyCompressionStrategy'.
--
filteredStrategy :: CompressionStrategy
filteredStrategy :: CompressionStrategy
filteredStrategy = CompressionStrategy
Filtered

-- | Use the Huffman-only compression strategy to force Huffman encoding only
-- (no string match).
--
huffmanOnlyStrategy :: CompressionStrategy
huffmanOnlyStrategy :: CompressionStrategy
huffmanOnlyStrategy = CompressionStrategy
HuffmanOnly


fromCompressionStrategy :: CompressionStrategy -> CInt
fromCompressionStrategy :: CompressionStrategy -> CInt
fromCompressionStrategy CompressionStrategy
DefaultStrategy = CInt
0
{-# LINE 902 "Codec/Compression/Zlib/Stream.hsc" #-}
fromCompressionStrategy Filtered        = 1
{-# LINE 903 "Codec/Compression/Zlib/Stream.hsc" #-}
fromCompressionStrategy HuffmanOnly     = 2
{-# LINE 904 "Codec/Compression/Zlib/Stream.hsc" #-}
--fromCompressionStrategy RLE             = #{const Z_RLE}
--fromCompressionStrategy Fixed           = #{const Z_FIXED}


withStreamPtr :: (Ptr StreamState -> IO a) -> Stream a
withStreamPtr :: (Ptr StreamState -> IO a) -> Stream a
withStreamPtr Ptr StreamState -> IO a
f = do
  ForeignPtr StreamState
stream <- Stream (ForeignPtr StreamState)
getStreamState
  IO a -> Stream a
forall a. IO a -> Stream a
unsafeLiftIO (ForeignPtr StreamState -> (Ptr StreamState -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr StreamState
stream Ptr StreamState -> IO a
f)

withStreamState :: (StreamState -> IO a) -> Stream a
withStreamState :: (StreamState -> IO a) -> Stream a
withStreamState StreamState -> IO a
f = do
  ForeignPtr StreamState
stream <- Stream (ForeignPtr StreamState)
getStreamState
  IO a -> Stream a
forall a. IO a -> Stream a
unsafeLiftIO (ForeignPtr StreamState -> (Ptr StreamState -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr StreamState
stream (StreamState -> IO a
f (StreamState -> IO a)
-> (Ptr StreamState -> StreamState) -> Ptr StreamState -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr StreamState -> StreamState
StreamState))

setInAvail :: Int -> Stream ()
setInAvail :: Int -> Stream ()
setInAvail Int
val = (Ptr StreamState -> IO ()) -> Stream ()
forall a. (Ptr StreamState -> IO a) -> Stream a
withStreamPtr ((Ptr StreamState -> IO ()) -> Stream ())
-> (Ptr StreamState -> IO ()) -> Stream ()
forall a b. (a -> b) -> a -> b
$ \Ptr StreamState
ptr ->
  (\Ptr StreamState
hsc_ptr -> Ptr StreamState -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr StreamState
hsc_ptr Int
8) Ptr StreamState
ptr (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
val :: CUInt)
{-# LINE 921 "Codec/Compression/Zlib/Stream.hsc" #-}

getInAvail :: Stream Int
getInAvail :: Stream Int
getInAvail = (CUInt -> Int) -> Stream CUInt -> Stream Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: CUInt -> Int) (Stream CUInt -> Stream Int) -> Stream CUInt -> Stream Int
forall a b. (a -> b) -> a -> b
$
  (Ptr StreamState -> IO CUInt) -> Stream CUInt
forall a. (Ptr StreamState -> IO a) -> Stream a
withStreamPtr ((\Ptr StreamState
hsc_ptr -> Ptr StreamState -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr StreamState
hsc_ptr Int
8))
{-# LINE 925 "Codec/Compression/Zlib/Stream.hsc" #-}

setInNext :: Ptr Word8 -> Stream ()
setInNext :: Ptr Word8 -> Stream ()
setInNext Ptr Word8
val = (Ptr StreamState -> IO ()) -> Stream ()
forall a. (Ptr StreamState -> IO a) -> Stream a
withStreamPtr (\Ptr StreamState
ptr -> (\Ptr StreamState
hsc_ptr -> Ptr StreamState -> Int -> Ptr Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr StreamState
hsc_ptr Int
0) Ptr StreamState
ptr Ptr Word8
val)
{-# LINE 928 "Codec/Compression/Zlib/Stream.hsc" #-}

getInNext :: Stream (Ptr Word8)
getInNext :: Stream (Ptr Word8)
getInNext = (Ptr StreamState -> IO (Ptr Word8)) -> Stream (Ptr Word8)
forall a. (Ptr StreamState -> IO a) -> Stream a
withStreamPtr ((\Ptr StreamState
hsc_ptr -> Ptr StreamState -> Int -> IO (Ptr Word8)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr StreamState
hsc_ptr Int
0))
{-# LINE 931 "Codec/Compression/Zlib/Stream.hsc" #-}

setOutFree :: Int -> Stream ()
setOutFree :: Int -> Stream ()
setOutFree Int
val = (Ptr StreamState -> IO ()) -> Stream ()
forall a. (Ptr StreamState -> IO a) -> Stream a
withStreamPtr ((Ptr StreamState -> IO ()) -> Stream ())
-> (Ptr StreamState -> IO ()) -> Stream ()
forall a b. (a -> b) -> a -> b
$ \Ptr StreamState
ptr ->
  (\Ptr StreamState
hsc_ptr -> Ptr StreamState -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr StreamState
hsc_ptr Int
32) Ptr StreamState
ptr (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
val :: CUInt)
{-# LINE 935 "Codec/Compression/Zlib/Stream.hsc" #-}

getOutFree :: Stream Int
getOutFree :: Stream Int
getOutFree = (CUInt -> Int) -> Stream CUInt -> Stream Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: CUInt -> Int) (Stream CUInt -> Stream Int) -> Stream CUInt -> Stream Int
forall a b. (a -> b) -> a -> b
$
  (Ptr StreamState -> IO CUInt) -> Stream CUInt
forall a. (Ptr StreamState -> IO a) -> Stream a
withStreamPtr ((\Ptr StreamState
hsc_ptr -> Ptr StreamState -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr StreamState
hsc_ptr Int
32))
{-# LINE 939 "Codec/Compression/Zlib/Stream.hsc" #-}

setOutNext  :: Ptr Word8 -> Stream ()
setOutNext :: Ptr Word8 -> Stream ()
setOutNext Ptr Word8
val = (Ptr StreamState -> IO ()) -> Stream ()
forall a. (Ptr StreamState -> IO a) -> Stream a
withStreamPtr (\Ptr StreamState
ptr -> (\Ptr StreamState
hsc_ptr -> Ptr StreamState -> Int -> Ptr Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr StreamState
hsc_ptr Int
24) Ptr StreamState
ptr Ptr Word8
val)
{-# LINE 942 "Codec/Compression/Zlib/Stream.hsc" #-}


{-# LINE 947 "Codec/Compression/Zlib/Stream.hsc" #-}

inflateInit :: Format -> WindowBits -> Stream ()
inflateInit :: Format -> WindowBits -> Stream ()
inflateInit Format
format WindowBits
bits = do
  Format -> Stream ()
checkFormatSupported Format
format
  CInt
err <- (StreamState -> IO CInt) -> Stream CInt
forall a. (StreamState -> IO a) -> Stream a
withStreamState ((StreamState -> IO CInt) -> Stream CInt)
-> (StreamState -> IO CInt) -> Stream CInt
forall a b. (a -> b) -> a -> b
$ \StreamState
zstream ->
    StreamState -> CInt -> IO CInt
c_inflateInit2 StreamState
zstream (CInt -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Format -> WindowBits -> CInt
fromWindowBits Format
format WindowBits
bits))
  CInt -> Stream ()
failIfError CInt
err
  Stream (ForeignPtr StreamState)
getStreamState Stream (ForeignPtr StreamState)
-> (ForeignPtr StreamState -> Stream ()) -> Stream ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> Stream ()
forall a. IO a -> Stream a
unsafeLiftIO (IO () -> Stream ())
-> (ForeignPtr StreamState -> IO ())
-> ForeignPtr StreamState
-> Stream ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FinalizerPtr StreamState -> ForeignPtr StreamState -> IO ()
forall a. FinalizerPtr a -> ForeignPtr a -> IO ()
addForeignPtrFinalizer FinalizerPtr StreamState
c_inflateEnd

deflateInit :: Format
            -> CompressionLevel
            -> Method
            -> WindowBits
            -> MemoryLevel
            -> CompressionStrategy
            -> Stream ()
deflateInit :: Format
-> CompressionLevel
-> Method
-> WindowBits
-> MemoryLevel
-> CompressionStrategy
-> Stream ()
deflateInit Format
format CompressionLevel
compLevel Method
method WindowBits
bits MemoryLevel
memLevel CompressionStrategy
strategy = do
  Format -> Stream ()
checkFormatSupported Format
format
  CInt
err <- (StreamState -> IO CInt) -> Stream CInt
forall a. (StreamState -> IO a) -> Stream a
withStreamState ((StreamState -> IO CInt) -> Stream CInt)
-> (StreamState -> IO CInt) -> Stream CInt
forall a b. (a -> b) -> a -> b
$ \StreamState
zstream ->
    StreamState -> CInt -> CInt -> CInt -> CInt -> CInt -> IO CInt
c_deflateInit2 StreamState
zstream
                  (CompressionLevel -> CInt
fromCompressionLevel CompressionLevel
compLevel)
                  (Method -> CInt
fromMethod Method
method)
                  (Format -> WindowBits -> CInt
fromWindowBits Format
format WindowBits
bits)
                  (MemoryLevel -> CInt
fromMemoryLevel MemoryLevel
memLevel)
                  (CompressionStrategy -> CInt
fromCompressionStrategy CompressionStrategy
strategy)
  CInt -> Stream ()
failIfError CInt
err
  Stream (ForeignPtr StreamState)
getStreamState Stream (ForeignPtr StreamState)
-> (ForeignPtr StreamState -> Stream ()) -> Stream ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> Stream ()
forall a. IO a -> Stream a
unsafeLiftIO (IO () -> Stream ())
-> (ForeignPtr StreamState -> IO ())
-> ForeignPtr StreamState
-> Stream ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FinalizerPtr StreamState -> ForeignPtr StreamState -> IO ()
forall a. FinalizerPtr a -> ForeignPtr a -> IO ()
addForeignPtrFinalizer FinalizerPtr StreamState
c_deflateEnd

inflate_ :: Flush -> Stream Status
inflate_ :: Flush -> Stream Status
inflate_ Flush
flush = do
  CInt
err <- (StreamState -> IO CInt) -> Stream CInt
forall a. (StreamState -> IO a) -> Stream a
withStreamState ((StreamState -> IO CInt) -> Stream CInt)
-> (StreamState -> IO CInt) -> Stream CInt
forall a b. (a -> b) -> a -> b
$ \StreamState
zstream ->
    StreamState -> CInt -> IO CInt
c_inflate StreamState
zstream (Flush -> CInt
fromFlush Flush
flush)
  CInt -> Stream Status
toStatus CInt
err

deflate_ :: Flush -> Stream Status
deflate_ :: Flush -> Stream Status
deflate_ Flush
flush = do
  CInt
err <- (StreamState -> IO CInt) -> Stream CInt
forall a. (StreamState -> IO a) -> Stream a
withStreamState ((StreamState -> IO CInt) -> Stream CInt)
-> (StreamState -> IO CInt) -> Stream CInt
forall a b. (a -> b) -> a -> b
$ \StreamState
zstream ->
    StreamState -> CInt -> IO CInt
c_deflate StreamState
zstream (Flush -> CInt
fromFlush Flush
flush)
  CInt -> Stream Status
toStatus CInt
err

-- | This never needs to be used as the stream's resources will be released
-- automatically when no longer needed, however this can be used to release
-- them early. Only use this when you can guarantee that the stream will no
-- longer be needed, for example if an error occurs or if the stream ends.
--
finalise :: Stream ()

{-# LINE 994 "Codec/Compression/Zlib/Stream.hsc" #-}
--TODO: finalizeForeignPtr is ghc-only
finalise :: Stream ()
finalise = Stream (ForeignPtr StreamState)
getStreamState Stream (ForeignPtr StreamState)
-> (ForeignPtr StreamState -> Stream ()) -> Stream ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO () -> Stream ()
forall a. IO a -> Stream a
unsafeLiftIO (IO () -> Stream ())
-> (ForeignPtr StreamState -> IO ())
-> ForeignPtr StreamState
-> Stream ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr StreamState -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr

{-# LINE 999 "Codec/Compression/Zlib/Stream.hsc" #-}

checkFormatSupported :: Format -> Stream ()
checkFormatSupported :: Format -> Stream ()
checkFormatSupported Format
format = do
  String
version <- IO String -> Stream String
forall a. IO a -> Stream a
unsafeLiftIO (Ptr CChar -> IO String
peekCAString (Ptr CChar -> IO String) -> IO (Ptr CChar) -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Ptr CChar)
c_zlibVersion)
  case String
version of
    (Char
'1':Char
'.':Char
'1':Char
'.':String
_)
       | Format
format Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
GZip
      Bool -> Bool -> Bool
|| Format
format Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Format
GZipOrZlib
      -> String -> Stream ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Stream ()) -> String -> Stream ()
forall a b. (a -> b) -> a -> b
$ String
"version 1.1.x of the zlib C library does not support the"
             String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" 'gzip' format via the in-memory api, only the 'raw' and "
             String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" 'zlib' formats."
    String
_ -> () -> Stream ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

----------------------
-- The foreign imports

newtype StreamState = StreamState (Ptr StreamState)

-- inflateInit2 and deflateInit2 are actually defined as macros in zlib.h
-- They are defined in terms of inflateInit2_ and deflateInit2_ passing two
-- additional arguments used to detect compatability problems. They pass the
-- version of zlib as a char * and the size of the z_stream struct.
-- If we compile via C then we can avoid this hassle however thats not really
-- kosher since the Haskell FFI is defined at the C ABI level, not the C
-- language level. There is no requirement to compile via C and pick up C
-- headers. So it's much better if we can make it work properly and that'd
-- also allow compiling via ghc's ncg which is a good thing since the C
-- backend is not going to be around forever.
--
-- So we define c_inflateInit2 and c_deflateInit2 here as wrappers around
-- their _ counterparts and pass the extra args.
--
-- As of GHC 7.6, we can import macros directly using the CApiFFI extension.
-- This avoids the need for the hsc2hs #{const_str} construct, which means
-- hsc2hs can run in cross-compilation mode.

#ifdef NON_BLOCKING_FFI
#define SAFTY safe
#else
#define SAFTY unsafe
#endif


{-# LINE 1042 "Codec/Compression/Zlib/Stream.hsc" #-}
foreign import capi unsafe "zlib.h inflateInit2"
  c_inflateInit2 :: StreamState -> CInt -> IO CInt
 
foreign import capi unsafe "zlib.h deflateInit2"
  c_deflateInit2 :: StreamState
                 -> CInt -> CInt -> CInt -> CInt -> CInt -> IO CInt

{-# LINE 1069 "Codec/Compression/Zlib/Stream.hsc" #-}

foreign import ccall SAFTY "zlib.h inflate"
  c_inflate :: StreamState -> CInt -> IO CInt

foreign import ccall unsafe "zlib.h &inflateEnd"
  c_inflateEnd :: FinalizerPtr StreamState

foreign import ccall unsafe "zlib.h inflateReset"
  c_inflateReset :: StreamState -> IO CInt

foreign import ccall unsafe "zlib.h deflateSetDictionary"
  c_deflateSetDictionary :: StreamState
                         -> Ptr CChar
                         -> CUInt
                         -> IO CInt

foreign import ccall unsafe "zlib.h inflateSetDictionary"
  c_inflateSetDictionary :: StreamState
                         -> Ptr CChar
                         -> CUInt
                         -> IO CInt

foreign import ccall SAFTY "zlib.h deflate"
  c_deflate :: StreamState -> CInt -> IO CInt

foreign import ccall unsafe "zlib.h &deflateEnd"
  c_deflateEnd :: FinalizerPtr StreamState

foreign import ccall unsafe "zlib.h zlibVersion"
  c_zlibVersion :: IO CString

foreign import ccall unsafe "zlib.h adler32"
  c_adler32 :: CULong
            -> Ptr CChar
            -> CUInt
            -> IO CULong