pipes-zlib-0.4.4.1/0000755000370400037040000000000012775536202012515 5ustar00kk00000000000000pipes-zlib-0.4.4.1/pipes-zlib.cabal0000644000370400037040000000356512775536202015570 0ustar00kk00000000000000name: pipes-zlib version: 0.4.4.1 license: BSD3 license-file: LICENSE Copyright: Copyright (c) Paolo Capriotti 2012, Renzo Carbonara 2013-2016 author: Renzo Carbonara, Paolo Capriotti maintainer: renzocarbonaraλgmail.com stability: Experimental homepage: https://github.com/k0001/pipes-zlib bug-reports: https://github.com/k0001/pipes-zlib/issues category: Pipes, Compression build-type: Simple synopsis: Zlib and GZip compression and decompression for Pipes streams description: Zlib and GZip compression and decompression for Pipes streams cabal-version: >=1.10 extra-source-files: README.md PEOPLE changelog.md source-repository head type: git location: git://github.com/k0001/pipes-zlib.git library hs-source-dirs: src exposed-modules: Pipes.Zlib Pipes.GZip build-depends: base >= 4.5 && < 5.0 , transformers >= 0.2 && < 0.6 , pipes >= 4.0 && < 4.3 , bytestring >= 0.9.2.1 , streaming-commons >= 0.1.15 && < 0.2 ghc-options: -Wall -O2 default-language: Haskell2010 test-suite test type: exitcode-stdio-1.0 hs-source-dirs: test main-is: Main.hs build-depends: base , pipes-zlib , pipes , bytestring , HUnit , QuickCheck , quickcheck-instances , tasty , tasty-quickcheck , tasty-hunit ghc-options: -threaded -rtsopts -with-rtsopts=-N default-language: Haskell2010 source-repository head type: git location: https://github.com/githubuser/twio pipes-zlib-0.4.4.1/test/0000755000370400037040000000000012775536202013474 5ustar00kk00000000000000pipes-zlib-0.4.4.1/test/Main.hs0000644000370400037040000000524412775536202014721 0ustar00kk00000000000000{-# LANGUAGE OverloadedStrings #-} import Control.Arrow import qualified Data.ByteString.Char8 as B8 import Data.List import Data.Ord import Test.Tasty import Test.Tasty.QuickCheck as QC import Test.QuickCheck.Instances () import Test.Tasty.HUnit import qualified Pipes as P import qualified Pipes.Prelude as P import qualified Pipes.Zlib as PZ import qualified Pipes.GZip as PGZ main = defaultMain tests -------------------------------------------------------------------------------- tests :: TestTree tests = testGroup "Tests" [properties, unitTests] properties :: TestTree properties = testGroup "Properties" [qcProps] qcProps = testGroup "(checked by QuickCheck)" [ QC.testProperty "id == decompress . compress" $ \bs -> QC.ioProperty $ do let pc = PZ.compress PZ.defaultCompression PZ.defaultWindowBits (P.yield bs) pd = PZ.decompress PZ.defaultWindowBits pc bs' <- B8.concat <$> P.toListM pd return (bs QC.=== bs') , QC.testProperty "id == decompress' . compress" $ \bs bsl -> QC.ioProperty $ do let pc = PZ.compress PZ.defaultCompression PZ.defaultWindowBits (P.yield bs) pd = PZ.decompress' PZ.defaultWindowBits (pc >> P.yield bsl) (bs', elr) <- first B8.concat <$> P.toListM' pd case elr of Left pl -> do bsl' <- B8.concat <$> P.toListM pl return $ (bs QC.=== bs') QC..&&. (bsl QC.=== bsl') Right () -> do return $ (bs QC.=== bs') QC..&&. (bsl QC.=== B8.empty) ] unitTests = testGroup "Unit tests" [ testCase "Zlib compression default" $ do let pc = PZ.compress PZ.defaultCompression PZ.defaultWindowBits (P.yield bsUncompressed) bs <- B8.concat <$> P.toListM pc bs @?= bsCompressedZlibDefault , testCase "Zlib decompression default" $ do let pd = PZ.decompress PZ.defaultWindowBits (P.yield bsCompressedZlibDefault) bs <- B8.concat <$> P.toListM pd bs @?= bsUncompressed , testCase "GZip compression default" $ do let pd = PGZ.compress PGZ.defaultCompression (P.yield bsUncompressed) bs <- B8.concat <$> P.toListM pd bs @?= bsCompressedGZipDefault , testCase "GZip decompression default" $ do let pd = PGZ.decompress (P.yield bsCompressedGZipDefault) bs <- B8.concat <$> P.toListM pd bs @?= bsUncompressed ] bsUncompressed :: B8.ByteString bsUncompressed = "foo" bsCompressedZlibDefault :: B8.ByteString bsCompressedZlibDefault = "x\156K\203\207\a\NUL\STX\130\SOHE" bsCompressedGZipDefault :: B8.ByteString bsCompressedGZipDefault = "\US\139\b\NUL\NUL\NUL\NUL\NUL\NUL\ETXK\203\207\a\NUL!es\140\ETX\NUL\NUL\NUL" pipes-zlib-0.4.4.1/Setup.hs0000644000370400037040000000005612775536202014152 0ustar00kk00000000000000import Distribution.Simple main = defaultMain pipes-zlib-0.4.4.1/LICENSE0000644000370400037040000000310412775536202013520 0ustar00kk00000000000000Copyright (c) 2012 Paolo Capriotti Copyright (c) 2013-2016 Renzo Carbonara All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of nor the names of other contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. pipes-zlib-0.4.4.1/README.md0000644000370400037040000000060612775536202013776 0ustar00kk00000000000000# pipes-zlib Utilities to deal with zlib compressed streams the **pipes** and libraries. Check the source or rendered Haddocks for extensive documentation. This code is licensed under the terms of the so called **3-clause BSD license**. Read the file named ``LICENSE`` found in this same directory for details. See the ``PEOPLE`` file to learn about the people involved in this effort. pipes-zlib-0.4.4.1/changelog.md0000644000370400037040000000230412775536202014765 0ustar00kk00000000000000# Version 0.4.4.1 * Bump upper bound dependency on `pipes`. # Version 0.4.4 * Depend on `streaming-commons` instead of `zlib` and `zlib-bindings`, as the latter are deprecated. * Add `Pipes.Zlib.decompress'` and `Pipes.GZip.decompress'`. * Bump upper bound dependency on `transformers`. * Add tests. # Version 0.4.3 * Fix usage of the `Producer'` type synonym (#14). # Version 0.4.2.1 * Fix “Codec.Compression.Zlib: premature end of compressed stream” (#13) # Version 0.4.2 * Added the `Pipes/GZip.hs` file that was missing in 0.4.1. # Version 0.4.1 * Added `Pipes.GZip` module. # Version 0.4.0.1 * Bump upper bound dependency on `transformers`. # Version 0.4.0 * Backwards incompatible API. `compress` and `decompress` are now functions of `Producer'`s as they need to perform actions at the beginning and end of input. (Issue #3) # Version 0.3.1 * Dependency upper bounds. # Version 0.3.0 * Upgraded to work with pipes-4.0.0, creating a new backwards incompatible API. * Generalize base `IO` monad to `MonadIO`. # Version 0.2.0.0 * New backwards incompatible API. * Based on pipes-3.3 and zlib-bindings. # Up to version 0.1.0 * Based on pipes-core and zlib-bindings. pipes-zlib-0.4.4.1/PEOPLE0000644000370400037040000000036112775536202013424 0ustar00kk00000000000000The following people have participated in creating this library, either by directly contributing code or by providing thoughtful input in discussions about the library design. Renzo Carbonara Paolo Capriotti Oliver Charles Gabriel Gonzalez pipes-zlib-0.4.4.1/src/0000755000370400037040000000000012775536202013304 5ustar00kk00000000000000pipes-zlib-0.4.4.1/src/Pipes/0000755000370400037040000000000012775536202014364 5ustar00kk00000000000000pipes-zlib-0.4.4.1/src/Pipes/Zlib.hs0000644000370400037040000001136212775536202015623 0ustar00kk00000000000000{-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} -- | This module exports utilities to compress and decompress @pipes@ streams -- using the zlib compression codec. -- -- If you want to compress or decompress GZip streams, use the "Pipes.GZip" -- module instead. module Pipes.Zlib ( -- * Streams decompress , decompress' , compress -- * Compression levels , CompressionLevel , defaultCompression , noCompression , bestSpeed , bestCompression , compressionLevel -- * Window size -- $ccz-re-export , Z.defaultWindowBits , windowBits ) where import Data.Streaming.Zlib as Z import Control.Exception (throwIO) import Control.Monad (unless) import qualified Data.ByteString as B import Pipes -------------------------------------------------------------------------------- -- | Decompress bytes flowing from a 'Producer'. -- -- See the "Codec.Compression.Zlib" module for details about 'Z.WindowBits'. -- -- @ -- 'decompress' :: 'MonadIO' m -- => 'Z.WindowBits' -- => 'Producer' 'B.ByteString' m r -- -> 'Producer' 'B.ByteString' m r -- @ decompress :: MonadIO m => Z.WindowBits -> Proxy x' x () B.ByteString m r -- ^ Compressed stream -> Proxy x' x () B.ByteString m r -- ^ Decompressed stream decompress wbits p0 = do inf <- liftIO $ Z.initInflate wbits r <- for p0 $ \bs -> do popper <- liftIO (Z.feedInflate inf bs) fromPopper popper bs <- liftIO $ Z.finishInflate inf unless (B.null bs) (yield bs) return r {-# INLINABLE decompress #-} -- | Decompress bytes flowing from a 'Producer', returning any leftover input -- that follows the compressed stream. decompress' :: MonadIO m => Z.WindowBits -> Producer B.ByteString m r -- ^ Compressed stream -> Producer B.ByteString m (Either (Producer B.ByteString m r) r) -- ^ Decompressed stream, ending with either leftovers or a result decompress' wbits p0 = go p0 =<< liftIO (Z.initInflate wbits) where flush inf = do bs <- liftIO $ Z.flushInflate inf unless (B.null bs) (yield bs) go p inf = do res <- lift (next p) case res of Left r -> return $ Right r Right (bs, p') -> do fromPopper =<< liftIO (Z.feedInflate inf bs) flush inf leftover <- liftIO $ Z.getUnusedInflate inf if B.null leftover then go p' inf else return $ Left (yield leftover >> p') {-# INLINABLE decompress' #-} -- | Compress bytes flowing from a 'Producer'. -- -- See the "Codec.Compression.Zlib" module for details about -- 'Z.CompressionLevel' and 'Z.WindowBits'. -- -- @ -- 'compress' :: 'MonadIO' m -- => 'Z.CompressionLevel' -- -> 'Z.WindowBits' -- -> 'Producer' 'B.ByteString' m r -- -> 'Producer' 'B.ByteString' m r -- @ compress :: MonadIO m => CompressionLevel -> Z.WindowBits -> Proxy x' x () B.ByteString m r -- ^ Decompressed stream -> Proxy x' x () B.ByteString m r -- ^ Compressed stream compress (CompressionLevel clevel) wbits p0 = do def <- liftIO $ Z.initDeflate clevel wbits r <- for p0 $ \bs -> do popper <- liftIO (Z.feedDeflate def bs) fromPopper popper fromPopper $ Z.finishDeflate def return r {-# INLINABLE compress #-} -------------------------------------------------------------------------------- -- $ccz-re-export -- -- The following are re-exported from "Codec.Compression.Zlib" for your -- convenience. -------------------------------------------------------------------------------- -- Compression Levels -- | How hard should we try to compress? newtype CompressionLevel = CompressionLevel Int deriving (Show, Read, Eq, Ord) defaultCompression, noCompression, bestSpeed, bestCompression :: CompressionLevel defaultCompression = CompressionLevel (-1) noCompression = CompressionLevel 0 bestSpeed = CompressionLevel 1 bestCompression = CompressionLevel 9 -- | A specific compression level between 0 and 9. compressionLevel :: Int -> CompressionLevel compressionLevel n | n >= 0 && n <= 9 = CompressionLevel n | otherwise = error "CompressionLevel must be in the range 0..9" windowBits :: Int -> WindowBits windowBits = WindowBits -------------------------------------------------------------------------------- -- Internal stuff -- | Produce values from the given 'Z.Popper' until exhausted. fromPopper :: MonadIO m => Z.Popper -> Producer' B.ByteString m () fromPopper pop = loop where loop = do mbs <- liftIO pop case mbs of PRDone -> return () PRError e -> liftIO $ throwIO e PRNext bs -> yield bs >> loop {-# INLINABLE fromPopper #-} pipes-zlib-0.4.4.1/src/Pipes/GZip.hs0000644000370400037040000000405312775536202015573 0ustar00kk00000000000000{-# LANGUAGE RankNTypes #-} -- | This module exports utilities to compress and decompress GZip @pipes@ -- streams. module Pipes.GZip ( -- * Streams decompress , decompress' , compress -- * Compression level , Pipes.Zlib.CompressionLevel , Pipes.Zlib.defaultCompression , Pipes.Zlib.noCompression , Pipes.Zlib.bestSpeed , Pipes.Zlib.bestCompression , Pipes.Zlib.compressionLevel ) where import qualified Data.Streaming.Zlib as Zlib import qualified Data.ByteString as B import Pipes import qualified Pipes.Zlib -------------------------------------------------------------------------------- -- | Decompress bytes flowing from a 'Producer'. -- -- @ -- 'decompress' :: 'MonadIO' m -- => 'Producer' 'B.ByteString' m r -- -> 'Producer' 'B.ByteString' m r -- @ decompress :: MonadIO m => Proxy x' x () B.ByteString m r -- ^ Compressed stream -> Proxy x' x () B.ByteString m r -- ^ Decompressed stream decompress = Pipes.Zlib.decompress gzWindowBits {-# INLINABLE decompress #-} -- | Decompress bytes flowing from a 'Producer', returning any leftover input -- that follows the compressed stream. decompress' :: MonadIO m => Producer B.ByteString m r -- ^ Compressed stream -> Producer B.ByteString m (Either (Producer B.ByteString m r) r) -- ^ Decompressed stream, returning either a 'Producer' of the leftover input -- or the return value from the input 'Producer'. decompress' = Pipes.Zlib.decompress' gzWindowBits {-# INLINABLE decompress' #-} -- | Compress bytes flowing from a 'Producer'. -- -- @ -- 'compress' :: 'MonadIO' m -- => 'ZC.CompressionLevel' -- -> 'Producer' 'B.ByteString' m r -- -> 'Producer' 'B.ByteString' m r -- @ compress :: MonadIO m => Pipes.Zlib.CompressionLevel -> Proxy x' x () B.ByteString m r -- ^ Decompressed stream -> Proxy x' x () B.ByteString m r -- ^ Compressed stream compress clevel = Pipes.Zlib.compress clevel gzWindowBits {-# INLINABLE compress #-} gzWindowBits :: Zlib.WindowBits gzWindowBits = Zlib.WindowBits 31