[GHC] #12433: GHCi produces incorrect results when evaluating with compiled code

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: ghci, dynamic | Operating System: Linux linking, compiled code | Architecture: x86_64 | Type of failure: Incorrect result (amd64) | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When GHCi evaluates in non-interpreted mode, it sometimes produces incorrect results. The following example---extracted from a much larger program---illustrates the problem: {{{#!hs import Lex num = 100000 txt1 = "aaa,aaa" main :: IO () main = print $ sum $ map (length . haskellLex) $ replicate num txt1 }}} This program lexes the same string 100000 times, and prints the total number of tokens. Since we are lexing the same string, we'd expect to always get the same result, but due to this bug, this is not the case! We repeat the process 100000 times so that we can encounter the bug somewhat reliably---the problem does not occur every time. To reproduce the problem, we need to load `Lex` in compiled form, not interpreted and with some optimizations: {{{ ghc -c -O1 -dynamic Lex.hs }}} The source code for the "lexer" is as follows: {{{#!haskell module Lex (haskellLex) where cclass :: Char -> Int cclass c = case c of 'a' -> 10 ',' -> 11 'A' -> 0 'B' -> 0 'C' -> 0 'D' -> 0 'E' -> 0 'F' -> 0 haskellLex :: String -> [()] haskellLex [] = [] haskellLex (i:is) = case cclass i of 10 -> haskellLex62 is 11 -> () : haskellLex is haskellLex62 :: String -> [()] haskellLex62 [] = [()] haskellLex62 (i:is) = case cclass i of 0 -> [()] 1 -> [()] 2 -> [()] 3 -> [()] 4 -> [()] 10 -> haskellLex62 is 11 -> () : haskellLex (i:is) x -> error ("[GHC BUG] cclass returned: " ++ show (i,x) }}} This is a minimized version from a full lexer. As odd as it looks, removing pretty much anything seems to cause the bug to go away. This is what happens when we run the program: {{{ runhaskell test.hs test.hs: [GHC BUG] cclass returned: (',',-556) CallStack (from HasCallStack): error, called at Lex.hs:36:12 in main:Lex }}} The problem is that after many evaluations, the function `cclass` returned `-556` for character `,`, when it should have returned `11`. I've been able to reproduce this on two Linux machines, both running 64-bit Ubuntu (16.04). The issue does not seem to happen on Mac OS. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by diatchki): * Attachment "bug.tar.gz" added. Source code and a `Makefile` to reproduce the bug -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * priority: normal => highest Comment: I can even reproduce it without ghci. Just compile `Lex.hs` with `-O` and `test.hs` without; both still `-dynamic`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ekmett): * cc: ekmett (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): The problem is in PIC code generation for jump tables (CmmSwitch). Here is the problematic part of `haskellLex62`: {{{ call $wcclass_r2lE_info(R2) returns to c2s5, args: 8, res: 8, upd: 8; c2s5: _s2mn::I64 = I64[Sp + 8]; _s2mo::I64 = R1; if (%MO_S_Ge_W64(R1, 12)) goto c2sB; else goto u2t1; u2t1: if (%MO_S_Lt_W64(_s2mo::I64, 0)) goto c2sB; else goto u2t2; u2t2: switch [0 .. 11] _s2mo::I64 { case 0, 1, 2, 3, 4 : goto u2t7; case 10 : goto c2sT; case 11 : goto c2sV; default: goto c2sB; } c2sV: Hp = Hp + 48; if (Hp > HpLim) goto c2sY; else goto c2sX; c2sY: HpAlloc = 48; R1 = _s2mo::I64; call stg_gc_unbx_r1(R1) returns to c2s5, args: 8, res: 8, upd: 8; c2sX: I64[Hp - 40] = sat_s2mp_info; P64[Hp - 24] = P64[Sp + 24]; I64[Hp - 16] = :_con_info; P64[Hp - 8] = GHC.Tuple.()_closure+1; P64[Hp] = Hp - 40; R1 = Hp - 14; Sp = Sp + 32; call (P64[Sp])(R1) args: 8, res: 0, upd: 8; }}} Observe that `c2s5` is the continuation for the call to `$wcclass_r2lE`, but it can also be returned to from the garbage collector after a failed heap check. The variable `_s2mo` is initialized at `c2s5` and then still live in the failed heap check block `c2sY`. However, the assembly generated for the switch looks like {{{ _c2s5: movq 8(%rbp),%rax movq %rbx,%rcx ; %rcx is _s2mo, set to R1 = %rbx cmpq $18,%rbx jge _c2sB _u2t1: testq %rcx,%rcx jl _c2sB _u2t2: leaq _n2tK(%rip),%rbx movslq (%rbx,%rcx,8),%rcx addq %rcx,%rbx jmp *%rbx ;; then a big jump table named _n2tK; in the case of 11, it jumps to _c2sV _c2sY: movq $48,904(%r13) movq %rcx,%rbx jmp *stg_gc_unbx_r1@gotpcrel(%rip) _c2sV: addq $48,%r12 cmpq 856(%r13),%r12 ja _c2sY }}} In the failed heap check code at `_c2sY`, ghc thinks that `_s2mo` is still in `%rcx`. But actually it was clobbered by the jump table calculation at `_u2t2`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): So, if the heap check should happen to fail, the R1 that is passed to `stg_gc_unbx_r1` is not actually the value returned by `$wcclass`, but rather some other value (the offset from the jump table start to the branch that was taken). Then when the GC finishes and returns to `c2s5`, it looks as though `$wcclass` returned that value, which causes the error you saw. I haven't looked at the code yet to determine who is at fault--maybe liveness calculation does not flow through `switch` statements properly, or maybe the NCG is clobbering registers that it isn't entitled to clobber. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I think it's `genSwitch` that is at fault here. It calculates the operand adjusted for the start of the jump table with `getSomeReg`, but that doesn't mean it is entitled to clobber the returned `reg` later, after `-- HACK: On x86_64 binutils<2.17 is only able to generate...`. Here is a single-module reproducer that does not involve the GC. It should be compiled with `-dynamic` (or `-fPIC`) and `-O`. {{{#!hs f :: Int -> IO () f p = case p of 0 -> return () 1 -> return () 2 -> return () 3 -> return () 4 -> return () 10 -> return () 11 -> return () _ -> print p {-# NOINLINE f #-} main = f 8 }}} I had to use a value that falls into the default case, as GHC creates an unfolding for a scrutinee that has been successfully matched against a numeric literal and then I couldn't find any way to get the generated code to refer to the original scrutinee. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Looks like it never got mentioned here, but this was going to be fixed by #11758, but the patch there caused problems on Windows and had to be reverted. It's probably an easy enough fix here if we just ignore ticket #11758. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * milestone: => 8.0.2 Comment: Can we fix this in 8.0.2? Reid, it looks as if you know what is going on.. I'll milestone it for 8.0.2 so we don't forget. Thanks Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): rwbarton, any word on this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code
-------------------------------------+-------------------------------------
Reporter: diatchki | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 8.0.2
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: ghci, dynamic
| linking, compiled code
Operating System: Linux | Architecture: x86_64
Type of failure: Incorrect result | (amd64)
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: simonmar Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * owner: => simonmar Comment: I think I see the problem: `genSwitch` is assuming that it can modify the register it got from evaluating the scrutinee, but it has no right to do that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: simonmar Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2529 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * differential: => Phab:D2529 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code
-------------------------------------+-------------------------------------
Reporter: diatchki | Owner: simonmar
Type: bug | Status: new
Priority: highest | Milestone: 8.0.2
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: ghci, dynamic
| linking, compiled code
Operating System: Linux | Architecture: x86_64
Type of failure: Incorrect result | (amd64)
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2529
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Marlow

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: simonmar Type: bug | Status: merge Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2529 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12433: GHCi produces incorrect results when evaluating with compiled code -------------------------------------+------------------------------------- Reporter: diatchki | Owner: simonmar Type: bug | Status: closed Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: ghci, dynamic | linking, compiled code Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2529 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as a0472f8dd29037412c61cbd42537863ad18b74f0. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12433#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC