[GHC] #14361: GHC HEAD miscompiles `text-containers`

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.3 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: -------------------------------------+------------------------------------- When compiling and running `text-containers`'s test-suite, the test-cases involving lookup functions (e.g. `member :: Key -> TextSet -> Bool`) fail indeterministically. ''more details to follow'' -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by hvr: Old description:
When compiling and running `text-containers`'s test-suite, the test-cases involving lookup functions (e.g. `member :: Key -> TextSet -> Bool`) fail indeterministically.
''more details to follow''
New description:
When compiling and running `text-containers`'s test-suite, the test-cases
involving lookup functions (e.g. `member :: Key -> TextSet -> Bool`) fail
indeterministically.
NB: The code in question works perfectly for GHC 7.10.3/8.0.2/8.2.1; and
I've also verified this isn't related to the new `compareByteArray#`
primop; in fact you get the very same failures if you force `text-
containers` to use the memcmp FFI (by editing the respective `if`
conditional in the .cabal file).
Repro instructions (sorry, haven't had time to minimize it yet):
{{{#!sh
# get wip/ghc-T14361 branch of `text-containers`
git clone https://github.com/hvr/text-containers.git -b wip/ghc-T14361
cd text-containers/
# generate cabal.project.local
cat > cabal.project.local <

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by angerman): * cc: angerman (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For better or worse I am able to reproduce this. Hrmph. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Thankfully the failure is independent of GC frequency, which should make debugging easier. I'm going to finish up #14346 before diving into this though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): To make things easier, here's a smaller repro-case which doesn't require building the test-suite of `text-containers`: {{{#!hs {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} module Main where import Control.Monad import qualified Data.List as List import Data.String import qualified Data.TextSet.Unboxed as TS main :: IO () main = do putStrLn "START" forM_ ([ 0 .. 10 ] :: [Int]) $ \_ -> do forM_ (zip [ 1::Int .. ] (List.inits testData)) $ \(j,xs) -> do unless (all (`TS.member` (TS.fromList xs)) xs) $ putStr (show j ++ " ") forM_ (zip [ 1::Int .. ] (List.tails testData)) $ \(j,xs) -> do unless (all (`TS.member` (TS.fromList xs)) xs) $ putStr (show (-j) ++ " ") putStrLn "" putStrLn "DONE" return () testData :: [TS.Key] testData = [ fromString [c] | c <- ['A' .. 'Z'] ] }}} If you have Cabal 2.1+, you can simply use its generated GHC environment file via {{{ # solve & build *only* the library component, and generate .ghc.environment.* file $ cabal new-build lib:text-containers --disable-tests -w ghc-8.3.20171016 # build test program $ ghc-8.3.20171016 --make -Wall -O1 bug-t14361.hs [1 of 1] Compiling Main ( bug-t14361.hs, bug-t14361.o ) Linking bug-t14361 ... # run test program $ ./bug-t14361 START 22 -2 -23 -3 -1 26 -1 -15 11 12 13 -8 7 15 18 -11 19 -2 -1 26 -1 26 -1 DONE }}} If the program was executed correctly the output would have no numbers, i.e. it would look like {{{ START DONE }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I could have sworn I had left a comment here when I looked at this last but alas it seems to be gone. Anyways, I've done a fair amount of digging on this one. I started by looking at differences in the call patterns of `Internal.$wcompareByteArray` in two compilations of the repro: one compiled with `{-# OPTIONS_GHC -fno-strictness #-}` in the `Internal2.hs` (which I'll call the "good" configuration) and one without (the "bad" configuration). Specifically I setup GDB to instrument calls to this function, logging each. This revealed that the bad configuration sometimes enters `$wcompareByteArray` with the `ofs2` and `n2` arguments being zero, where in good configuration they are non-zero. For instance, {{{#!patch --- gdb.good.log 2017-11-03 16:53:05.956764525 -0400 +++ gdb.bad.log 2017-11-03 16:53:27.481174930 -0400 @@ -186,8 +186,7 @@ done fffffffc memcmp a.len=1 a[0]=44 ofs1=0 n1=1 b.len=50 ofs2=4c n2=1 done ffffffff -memcmp a.len=1 a[0]=44 ofs1=0 n1=1 b.len=50 ofs2=4a n2=1 -done 1 +memcmp a.len=1 a[0]=44 ofs1=0 n1=1 b.len=50 ofs2=0 n2=0 memcmp a.len=1 a[0]=44 ofs1=0 n1=1 b.len=50 ofs2=4b n2=1 done 0 memcmp a.len=1 a[0]=45 ofs1=0 n1=1 b.len=50 ofs2=48 n2=1 }}} The (perhaps slightly poorly-named) `memcmp` message is emitted on entering `$wcompareByteArray`. The `done` message is emitted after the `memcmp` call returns. The fact that there is no `done` message in the bad case is the consequence of the implementation of `compareByteArray`, which skips the `memcmp` if `min n1 n2 == 0`. Another thing I have noticed is that the occurrence probability of the bug changes with GC patterns. Interestingly, it doesn't change monotonically with GC frequency; for a given value of `+RTS -A` I reproducibly get the same set of numbers on stdout. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I should also note that the problem appears to be an interaction between the strictness signature of `Internal2.cmpBA2OfsLen` and one of the call- sites in `Data.TextSet.Unboxed.lookupIndexNear`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Some facts: * Allocating all `ByteArray#`s as pinned makes no difference. * Marking `TextArray.Unboxed.indexOfsLen'` as `NOINLINE` makes the problem vanish * Removing the `assert`s in `lookupIndexNear` makes no difference -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers`
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 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 Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by bgamari):
One thing that I've noticed while looking at the Core here I noticed what
I believe is a slight performance papercut in our Core: In the Core we
essentially have this:
{{{#!hs
data IdxOfsLen = IdxOfsLen !Int !Int !Int
}}}
Inside of `lookupIndexNear` we end up with a join point:
{{{#!hs
$j_sjcd [Dmd=

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Another microoptimization that might be interesting to investigate is to try being a bit more clever when generating code for things like (where the type of `expr` is an enumeration), {{{ case expr of A -> SomeCaf B -> SomeCaf' C -> SomeCaf'' ... }}} Currently we branch on the tag of `expr` to one of a set of a continuations, all of which simply load the result and return. One could eliminate the branches by instead loading the continuation from a table and returning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Alright, the problem was overzealous CBE due to a bug. See Phab:D4152. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Crumbs. From Phab:D4152: {{{ Previously CBE computed equality by taking the lists of middle nodes of the blocks being compared and zipping them together. It would then map over this list with the equality relation, and accumulate the result. However, this is completely wrong: Consider what will happen when we compare a block with no middle nodes with one with one or more. The result of zip will be empty and consequently the pass may conclude that the two are indeed equivalent (if their last nodes also match). }}} That's truly terrible! Well caught. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

It seems like it would be better to either only pass the constructor and extract the needed values out of it inside the join point, or to only pass
#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): the unboxed arguments, and construct the constructor when needed. It's indeed not clear which is best. It's a conscious choice though; see `Note [Case binders and join points]` in `Simplify.hs`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers`
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: (none)
Type: bug | Status: patch
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 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 Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14361: GHC HEAD miscompiles `text-containers`
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: (none)
Type: bug | Status: patch
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 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 Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14361: GHC HEAD miscompiles `text-containers` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: fixed | 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 bgamari): * status: merge => closed * resolution: => fixed Comment: Whoops, this doesn't affect 8.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14361#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC