[GHC] #8250: cgrun072 (optllvm) failing

#8250: cgrun072 (optllvm) failing ------------------------------------+------------------------------------- Reporter: leroux | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: Runtime crash Difficulty: Unknown | Test Case: cgrun072 Blocked By: | Blocking: Related Tickets: 7902 | ------------------------------------+------------------------------------- * Platform: OS X 10.8.4 x86_64 * GHC Version 7.7.20130904 (built with gcc-4.8) To reproduce this: {{{ $ make test TEST=cgrun072 WAY=optllvm }}} Expected output (for failure): {{{ =====> cgrun072(optllvm) 172 of 3749 [0, 0, 2] cd ./codeGen/should_run && '/Users/leroux/Dropbox/src/ghc/ghc- validate/inplace/bin/ghc-stage2' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts -fno-ghci-history -o cgrun072 cgrun072.hs -O -fllvm >cgrun072.comp.stderr 2>&1 cd ./codeGen/should_run && ./cgrun072 cgrun072.run.stdout 2>cgrun072.run.stderr Actual stdout output differs from expected: --- ./codeGen/should_run/cgrun072.stdout 2013-09-04 02:22:32.000000000 -0500 +++ ./codeGen/should_run/cgrun072.run.stdout 2013-09-07 03:27:09.000000000 -0500 @@ -1,3 +1,6 @@ OK -OK +FAIL + Input: 1480294021 +Expected: 2239642456 + Actual: -2055324840 OK *** unexpected failure for cgrun072(optllvm) }}} The failing test case is {{{test_bSwap32}}}. Here are some relevant snippets. bswap and cgrun072 were added in #7902. https://github.com/ghc/testsuite/blob/master/tests/codeGen/should_run/cgrun0...: {{{ bswap32 :: Word32 -> Word32 bswap32 (W32# w#) = W32# (byteSwap32# w#) slowBswap32 :: Word32 -> Word32 slowBswap32 w = (w `shiftR` 24) .|. (w `shiftL` 24) .|. ((w `shiftR` 8) .&. 0xff00) .|. ((w .&. 0xff00) `shiftL` 8) test_bSwap32 = test casesW32 bswap32 slowBswap32 }}} https://github.com/ghc/packages-ghc- prim/blob/master/cbits/bswap.c#L10-L17: {{{ extern StgWord32 hs_bswap32(StgWord32 x); StgWord32 hs_bswap32(StgWord32 x) { return ((x >> 24) | ((x >> 8) & 0xff00) | (x << 24) | ((x & 0xff00) << 8)); } }}} Here are a few things to look at or try. * https://github.com/ghc/packages-ghc-prim/blob/master/cbits/bswap.c * https://github.com/ghc/ghc/tree/master/compiler/llvmGen * Maybe take an object dump and take what's going on. * gdb debugging? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8250 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8250: cgrun072 (optllvm) failing -------------------------------------+------------------------------------ Reporter: leroux | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: cgrun072 | Blocked By: Blocking: | Related Tickets: 7902 -------------------------------------+------------------------------------ Comment (by rwbarton): Thanks for catching this, I can reproduce it on Linux/x86_64 also. There's a similar issue with bswap16 that cgrun072 doesn't catch, because there are no bswap16 test cases with low byte >= 128. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8250#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8250: cgrun072 (optllvm) failing -------------------------------------+------------------------------------ Reporter: leroux | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: cgrun072 | Blocked By: Blocking: | Related Tickets: 7902 -------------------------------------+------------------------------------ Comment (by rwbarton): This is a sign-extension issue: the expected output is `2239642456 = 0x857e3b58`, which treated as a signed 32-bit integer is `2239642456 - 2^32 = -2055324840`. Obviously, `show` on a `Word32` shouldn't be producing output starting with a minus sign! * The NCG generates code for `MO_BSwap W32` that does the byte swap and clears the high 32 bits of the result. (This isn't directly relevant to this test failure, but provides context for the rest.) * The LLVM backend generates LLVM code that does the byte swap and then sign-extends the result to 64 bits, like this: {{{ %ln2uw = trunc i64 %ln2uv to i32 %ln2ux = call ccc i32 (i32)* @llvm.bswap.i32( i32 %ln2uw ) %ln2uy = sext i32 %ln2ux to i64 }}} The reason is that `genCallSimpleCast` does `castVars` before and after the call to `llvm.swap.i32`, and `castVars` produces `LM_Sext` for a widening conversion. That's what's causing the strange test output—the payload of a `Word32#` isn't supposed to have any of the high 32 bits set. * The primop `BSwap32Op` is documented as {{{ primop BSwap32Op "byteSwap32#" Monadic Word# -> Word# {Swap bytes in the lower 32 bits of a word. The higher bytes are undefined. } }}} so both the NCG and LLVM backends are correct, and the test is wrong. It should be doing {{{ bswap32 :: Word32 -> Word32 bswap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#)) }}} and the same for `bswap16`. * The definitions of `byteSwap32` and `byteSwap16` in `GHC.Word` are also wrong for the same reason. They should be {{{ byteSwap32 :: Word32 -> Word32 byteSwap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#)) }}} This doesn't currently make a difference, though, because base is built (by default?) with the NCG, which happens to produce a zero-extended result. An alternative approach would be to redefine the `BSwap32Op` primop to clear the higher bytes of its result. Then the LLVM backend would need to be fixed somehow (looks a little tricky to me) but the cgrun072 test and GHC.Word would be correct as they are. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8250#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8250: cgrun072 (optllvm) failing -------------------------------------+------------------------------------ Reporter: leroux | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: cgrun072 | Blocked By: Blocking: | Related Tickets: 7902 -------------------------------------+------------------------------------ Comment (by rwbarton): A correction to the last bullet point in my previous comment: fixing `GHC.Word.byteSwap{16,32}` actually *does* matter because a user program built with `-O -fllvm` will inline those functions at the Haskell level, and then the LLVM backend will generate the wrong code for the byte-swap primop. {{{ import GHC.Word main = print $ byteSwap32 (0xaabbccdd :: Word32) -- built with ghc -O -fllvm -- expected output: 3721182122 -- actual output: -573785174 }}} The cgrun072 test should test the `GHC.Word.byteSwap*` wrappers, too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8250#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8250: cgrun072 (optllvm) failing -------------------------------------+------------------------------------ Reporter: leroux | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: cgrun072 | Blocked By: Blocking: | Related Tickets: 7902 -------------------------------------+------------------------------------ Changes (by rwbarton): * status: new => patch Comment: The first two patches add more tests to cgrun072. The other two patches fix the use of `byteSwap16/32#` in cgrun072 and in GHC.Word, as described above (treating the description of the byteSwap primops as leaving the higher bytes of the result undefined as correct). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8250#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8250: cgrun072 (optllvm) failing -------------------------------------+------------------------------------ Reporter: leroux | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: cgrun072 | Blocked By: Blocking: | Related Tickets: 7902 -------------------------------------+------------------------------------ Comment (by thoughtpolice): Looks good to me - thanks for the investigation Reid. I'll probably squash these into one patch for `base` and merge them later tonight. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8250#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8250: cgrun072 (optllvm) failing
-------------------------------------+------------------------------------
Reporter: leroux | Owner:
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (LLVM) | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: cgrun072 | Blocked By:
Blocking: | Related Tickets: 7902
-------------------------------------+------------------------------------
Comment (by Austin Seipp

#8250: cgrun072 (optllvm) failing -------------------------------------+------------------------------------ Reporter: leroux | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: cgrun072 | Blocked By: Blocking: | Related Tickets: 7902 -------------------------------------+------------------------------------ Comment (by thoughtpolice): Merged, thanks Reid! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8250#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8250: cgrun072 (optllvm) failing -------------------------------------+------------------------------------ Reporter: leroux | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Runtime crash | Difficulty: Unknown Test Case: cgrun072 | Blocked By: Blocking: | Related Tickets: 7902 -------------------------------------+------------------------------------ Changes (by thoughtpolice): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8250#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC