[GHC] #9494: Probable data corruption with GHCi 7.8.* and Zlib

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Incorrect Blocked By: | result at runtime Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- The following program causes Zlib data corruption errors when run from inside GHCi. It launches two threads which then concurrently read a file, compress it, and immediately decompress it. You need libraries `zlib`, `SHA`, and `async`. {{{ module Main where import qualified Codec.Compression.Zlib as Zlib import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Internal as BI import Control.Exception (bracket) import Control.Concurrent import Control.Monad import Control.Exception ( evaluate) import Data.Digest.Pure.SHA ( sha1) -- from the 'SHA' package import Control.Concurrent.Async ( mapConcurrently) import System.Mem ( performGC ) import Debug.Trace test :: Int -> IO String test _ = do tid <- myThreadId -- testdata is: dd if=/dev/urandom of=/tmp/testdata bs=100k count=100 -- Could also be replaced by: (BL.take (10^7) "/dev/urandom") dat <- BL.readFile "/tmp/testdata" let cbuf = Zlib.compress $ traceChunks tid $ dat s <- evaluate $ sha1 $ Zlib.decompress $ cbuf return $ show s where -- We used this to check whether buffers were reused by different threads, but that -- doesn't seem to be the case. Removing the call to traceChunks, however, makes it -- harder to reproduce possibly because of scheduler effects. In a much larger program -- it could be reproduced more easily without the trace, but in this small example -- tracing seems to cause the right amount of nondeterminism. traceChunks tid bs = BL.fromChunks $ zipWith (\n x -> trace (show tid ++ ":" ++ showBS x) x) [1..] $ BL.toChunks bs showBS (BI.PS ptr off len) = show ptr main = do r <- withGCThread $ mapConcurrently (test) ([1..2] :: [Int]) putStrLn $ show $ r where -- Regularly forcing the GC makes the test-case more reproducible. withGCThread io = bracket (forkIO $ forever $ performGC >> threadDelay 1000) killThread (const io) }}} The output should be something like: {{{ ... ThreadId 51:0x00000001091ee010 ThreadId 49:0x00000001091a7010 ... ThreadId 49:0x000000010986f010 zlib-test-case.hs: user error (Codec.Compression.Zlib: incorrect data check) }}} You'll get different Zlib errors, depending on where it detects the inconsistency. Sometimes Zlib doesn't throw an error, but the checksums are different. So far we've only been able to reproduce this using GHCi 7.8.3 on both Linux (NixOS) and Mac. We haven't been able to trigger it with a compiled executable, nor with GHCi 7.6.3. It '''was''' reproducable with HEAD from Jan 30 (I had that lying around somewhere). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Incorrect | Blocked By: result at runtime | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by basvandijk): * cc: basvandijk (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: aseipp Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Incorrect | Blocked By: result at runtime | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by nominolo): * owner: => aseipp * priority: normal => high Comment: Austin, could you please try to reproduce this? It's a pretty scary bug and until we know the cause it should be high priority to figure out what else it may affect. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: aseipp Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Incorrect | Blocked By: result at runtime | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by rwbarton): The zlib library internally uses a bunch of unsafe functions (`unsafePerformIO`, `unsafeForeignPtrToPtr`) so this is also quite possibly just a bug in zlib. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: aseipp Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Incorrect | Blocked By: result at runtime | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by MikolajKonarski): I reproduced this on GHC 7.8.3, Ubuntu 12.04.5 (the first of many different errors in consecutive runs): {{{ ThreadId 46:0x00007f05a6351010 *** Exception: Codec.Compression.Zlib: invalid stored block lengths }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

The zlib library internally uses a bunch of unsafe functions (`unsafePerformIO`, `unsafeForeignPtrToPtr`) so this is also quite
#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: aseipp Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Incorrect | Blocked By: result at runtime | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by nominolo): Replying to [comment:3 rwbarton]: possibly just a bug in zlib. (See `Codec/Compression/Zlib/Stream.hsc`, it's quite scary.) Yes, it's possible. I looked through that module, but could find any use of the Really Scary `inlinePerformIO`. The scariest functions seem to be `push{Input,Output}Buffer`. Unless we know what really goes wrong, it's possible that other libraries have the same problem and may break in subtle ways on 7.8 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: aseipp Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Incorrect | Blocked By: result at runtime | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by rwbarton): Well the error from zlib is not that scary either: it just means that the zlib API is being used incorrectly. Given that - there is no strong evidence of a compiler bug here - the zlib source is largely incomprehensible I suggest you submit a bug report to the zlib package also. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: aseipp Type: bug | Status: infoneeded Priority: high | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Incorrect | Blocked By: result at runtime | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => infoneeded Comment: Did this indeed turn out to be a bug in `zlib`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: duncan (added) * owner: aseipp => * priority: high => normal Comment: duncan: I can not find the zlib bugtracker. Can you have a look at this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9494: Probable data corruption with GHCi 7.8.* and Zlib -------------------------------------+------------------------------------- Reporter: nominolo | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by NeilMitchell): * status: infoneeded => closed * resolution: => duplicate Comment: This is almost certainly a duplicate of https://github.com/haskell/zlib/issues/7, which lives on the right bug tracker. I've added a link on the zlib bug to this test case, so after it is considered solved the test case can be checked. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9494#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC