[GHC] #10521: Wrong results in strict Word8 storage on x64

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: | Owner: VincentBerthoux2 | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: Incorrect result Architecture: x86_64 | at runtime (amd64) | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The following snippet produce two different results in function of the compiler platform used: {{{#!hs import Data.Word( Word8 ) -- removing the bang patterns on V definition makes -- the problem go away. data V = V !Word8 !Word8 deriving Show toV :: Float -> V toV d = V (truncate $ d * coeff) (fromIntegral $ exponent d + 128) where coeff = significand d * 255.9999 / d main :: IO () main = print $ map toV [ 3.56158e-2, 0.7415215, 0.5383201, 0.1289829, 0.45520145 ] }}} On GHC 7.10.1 x86 (under windows and Linux) the output is: {{{ [V 145 124,V 189 128,V 137 128,V 132 126,V 233 127] }}} On GHC 7.10.1 x64 (under windows and Linux), the (invalid) output is: {{{ [V 0 124,V 0 128,V 0 128,V 0 126,V 0 127] }}} The bug appear at the following optimisation levels: - {{{-O1}}} - {{{-O2}}} - {{{-O3}}} the results are the same at {{{-O0}}} This bug was discovered in a bug report in the library JuicyPixels [https://github.com/Twinside/Juicy.Pixels/issues/98]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by VincentBerthoux2): * priority: normal => high * milestone: => 7.10.2 Old description:
The following snippet produce two different results in function of the compiler platform used:
{{{#!hs import Data.Word( Word8 )
-- removing the bang patterns on V definition makes -- the problem go away. data V = V !Word8 !Word8 deriving Show
toV :: Float -> V toV d = V (truncate $ d * coeff) (fromIntegral $ exponent d + 128) where coeff = significand d * 255.9999 / d
main :: IO () main = print $ map toV [ 3.56158e-2, 0.7415215, 0.5383201, 0.1289829, 0.45520145 ] }}}
On GHC 7.10.1 x86 (under windows and Linux) the output is: {{{ [V 145 124,V 189 128,V 137 128,V 132 126,V 233 127] }}}
On GHC 7.10.1 x64 (under windows and Linux), the (invalid) output is: {{{ [V 0 124,V 0 128,V 0 128,V 0 126,V 0 127] }}}
The bug appear at the following optimisation levels:
- {{{-O1}}} - {{{-O2}}} - {{{-O3}}}
the results are the same at {{{-O0}}}
This bug was discovered in a bug report in the library JuicyPixels [https://github.com/Twinside/Juicy.Pixels/issues/98].
New description: The following snippet produce two different results in function of the compiler platform used: {{{#!hs import Data.Word( Word8 ) -- removing the bang patterns on V definition makes -- the problem go away. data V = V !Word8 !Word8 deriving Show toV :: Float -> V toV d = V (truncate $ d * coeff) (fromIntegral $ exponent d + 128) where coeff = significand d * 255.9999 / d main :: IO () main = print $ map toV [ 3.56158e-2, 0.7415215, 0.5383201, 0.1289829, 0.45520145 ] }}} On GHC 7.10.1 x86 (under windows and Linux) the output is: {{{ [V 145 124,V 189 128,V 137 128,V 132 126,V 233 127] }}} On GHC 7.10.1 x64 (under windows and Linux), the (invalid) output is: {{{ [V 0 124,V 0 128,V 0 128,V 0 126,V 0 127] }}} The bug appear at the following optimisation levels: - {{{-O1}}} - {{{-O2}}} - {{{-O3}}} the results are the same at {{{-O0}}} This bug was discovered in a bug report in the library JuicyPixels [https://github.com/Twinside/Juicy.Pixels/issues/98]. The same problem has been seen with GHC 7.10.2 RC1 -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by VincentBerthoux2): * priority: high => normal * milestone: 7.10.2 => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * priority: normal => highest * milestone: => 7.10.2 Comment: Regression relative to 7.8, investigating... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I suggest generating removing just one bang (which apparently is enough to provoke the difference) and compare output of `-ddump-simpl` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I reduced the test case further to {{{ import Data.Word( Word8 ) toV :: Float -> Word8 toV d = let coeff = significand d * 255.9999 / d a = truncate $ d * coeff b = exponent d in a `seq` (b `seq` a) -- just b `seq` a is not enough to reproduce the bug main :: IO () main = print $ map toV [ 3.56158e-2, 0.7415215, 0.5383201, 0.1289829, 0.45520145 ] }}} It's looking like an issue in the backend where it doesn't understand that F1 and D1 are the same physical register (%xmm1) on x86_64. Possibly an old issue that was uncovered by 7.10's new implementation of `significand :: Float -> Float` going through Double. Specifically for the (correct) Core {{{ Main.main14 = \ (d_aC5 [OS=ProbOneShot] :: Float) -> case d_aC5 of _ [Occ=Dead] { GHC.Types.F# x_a22N -> case GHC.Prim.decodeFloat_Int# x_a22N of _ [Occ=Dead] { (# ipv_a1Gg, ipv1_a1Gh #) -> case integer-gmp-1.0.0.0:GHC.Integer.Type.encodeDoubleInteger (integer-gmp-1.0.0.0:GHC.Integer.Type.smallInteger ipv_a1Gg) (-24) of wild1_a1Gj { __DEFAULT -> case GHC.Float.$w$cexponent1 x_a22N of _ [Occ=Dead] { __DEFAULT -> case GHC.Prim.divideFloat# (GHC.Prim.timesFloat# (GHC.Prim.double2Float# wild1_a1Gj) (__float 255.9999)) x_a22N of wild2_a234 { __DEFAULT -> GHC.Word.W8# (GHC.Prim.narrow8Word# (GHC.Prim.int2Word# (GHC.Prim.float2Int# (GHC.Prim.timesFloat# x_a22N wild2_a234)))) } } } } } }}} we generate Cmm like {{{ ... c3MY: I64[Sp] = c3N2; R3 = (-24); R2 = R1; call GHC.Integer.Type.encodeDoubleInteger_info(R3, R2) returns to c3N2, args: 8, res: 8, upd: 8; c3N2: I64[Sp - 8] = c3N6; F1 = F32[Sp + 8]; F64[Sp] = D1; Sp = Sp - 8; call GHC.Float.$w$cexponent1_info(F1) returns to c3N6, args: 8, res: 8, upd: 8; ... }}} The assignment to F1 is to set up the arguments for `$w$cexponent1` from `x_a22N` which has been saved on the stack, and the read from D1 is to save the return value `wild1_a1Gj` from `encodeDoubleInteger`. Technically the program became incorrect in the "Sink assignments" pass when the read from D1 was moved past the store to F1, but maybe it just doesn't make sense to cater to the possibility of multiple STG global registers being aliases of one another. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): The commit that merged F1 and D1 was e2f6bbd3a27685bc667655fdb093734cb565b4cf which is in 7.8 but not 7.6. Here is a reproducer for 7.8 too: {{{ {-# LANGUAGE MagicHash #-} import GHC.Exts f :: Float# -> Float# f x = x {-# NOINLINE f #-} g :: Double# -> Double# g x = x {-# NOINLINE g #-} h :: Float -> Float h (F# x) = let a = F# (f x) b = D# (g (2.0##)) in a `seq` (b `seq` a) main = print (h 1.0) -- with ghc -O, prints 0.0 }}} Not sure yet whether it is better to revert (parts of) that commit or to try to account for STG global registers overlapping in the cmmSink pass and wherever else it might be necessary. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Reid you are a marvel, thank you. My instinct is to "account for registers" overlapping. After all, if Cmm optimisations don't know that two registers are the same, all manner of bad things can happen, perhaps not limited to `CmmSink`. Is this just the Eq instance for `CmmReg`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: rwbarton Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * owner: => rwbarton Comment: In fact I did try just changing GlobalReg's Eq instance (and Ord instance) to treat `FloatReg i` and `DoubleReg i` as the same, and that did fix this issue. Doing this properly will require a bit more refactoring than that, since whether these registers overlap depends on the DynFlags, but it looks like it will be nothing too serious. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: rwbarton Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D993 -------------------------------------+------------------------------------- Changes (by rwbarton): * differential: => Phab:D993 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: rwbarton Type: bug | Status: patch Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D993 -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64
-------------------------------------+-------------------------------------
Reporter: VincentBerthoux2 | Owner: rwbarton
Type: bug | Status: patch
Priority: highest | Milestone: 7.10.2
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: x86_64
Type of failure: Incorrect result | (amd64)
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:D993
-------------------------------------+-------------------------------------
Comment (by Reid Barton

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: rwbarton Type: bug | Status: merge Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D993 -------------------------------------+------------------------------------- Changes (by rwbarton): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10521: Wrong results in strict Word8 storage on x64 -------------------------------------+------------------------------------- Reporter: VincentBerthoux2 | Owner: rwbarton Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D993 -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-7.10`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10521#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC