Skip to content

gzip decompression stops early without error #37

@dimbleby

Description

@dimbleby

Originally raised against pipes-zlib as k0001/pipes-zlib#16, but the following program displays the same fault without pipes being involved:

#!/usr/bin/env stack
{- stack
   --resolver lts-7.23
   runghc
   --package streaming-commons
   --package turtle
 -}

{-# LANGUAGE OverloadedStrings #-}

import qualified Codec.Compression.GZip as GZip
import Control.Exception (throwIO)
import qualified Data.ByteString.Lazy as L
import Control.Monad (foldM)
import Data.Streaming.Zlib
import Data.Text (unpack)

import Turtle

decompress :: L.ByteString -> IO L.ByteString
decompress gzipped = do
    inf <- initInflate $ WindowBits 31
    ungzipped <- foldM (go' inf) id $ L.toChunks gzipped
    final <- finishInflate inf
    return $ L.fromChunks $ ungzipped [final]
  where
    go' inf front bs = feedInflate inf bs >>= go front
    go front x = do
        y <- x
        case y of
            PRDone -> return front
            PRNext z -> go (front . (:) z) x
            PRError e -> throwIO e

main = do
    fn <- options "GZip decompression test script" (argPath "file" "file to decompress")

    -- lazy IO solution, works!
    -- fmap GZip.decompress (L.readFile . unpack . format fp $ fn) >>= L.putStr

    -- Streaming solution, stops early without error!
    gzipped <- L.readFile . unpack . format fp $ fn
    decompress gzipped >>= L.putStr

... where my decompress is based on decompressRaw, and the test input file that reproduces the problem is, per the original issue, available here.

Metadata

Metadata

Assignees

No one assigned

    Labels

    No labels
    No labels

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions