[GHC] #8103: Segfault when passing unboxed Float# and Double# across modules

#8103: Segfault when passing unboxed Float# and Double# across modules -----------------------------+---------------------------------- Reporter: jstolarek | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Operating System: Linux Architecture: x86 | Type of failure: Runtime crash Difficulty: Unknown | Test Case: Blocked By: | Blocking: 6135 Related Tickets: | -----------------------------+---------------------------------- Consider this program consisting of two modules: {{{ {-# LANGUAGE MagicHash #-} module AddWraps where import GHC.Exts {-# NOINLINE foo #-} foo :: Double# -> Double# -> Double# foo a b = (a +## b) }}} {{{ {-# LANGUAGE MagicHash #-} module Main where import AddWraps float_text = case (0.0## `foo` 1.2##) of 0.0## -> "1" _ -> "0" main = putStrLn (float_text) }}} This program segfaults when compiled on i386 with HEAD: {{{ [t-jastol@cam-05-unx : ~] $HOME/master-i386/bin/ghc -fforce-recomp add- double-extern.hs [1 of 2] Compiling AddWraps ( AddWraps.hs, AddWraps.o ) [2 of 2] Compiling Main ( add-double-extern.hs, add-double- extern.o ) Linking add-double-extern ... [t-jastol@cam-05-unx : ~] ./add-double-extern Segmentation fault (core dumped) }}} The problem does not occur: * on x86_64 * on 7.6.3 * when optimizations are turned on * fot `Int#`, `Word#` and `Char#` - only `Float#` and `Double#` are affected Segfault happens on line 223 of `rts/ThreadPaused.c` (`switch (info->i.type)`), which probably means that the stack gets corrupted. It turns out that Cmm generated for the `foo` is the same in both cases: {{{ [section "data" { AddWraps.foo_closure: const AddWraps.foo_info; }, AddWraps.foo_slow() // [R1] { info_tbl: [] stack_info: arg_space: 20 updfr_space: Just 4 } {offset cfx: _rf9::P32 = R1; _B2::F64 = F64[Sp]; _B1::F64 = F64[Sp + 8]; D2 = _B1::F64; D1 = _B2::F64; R1 = _rf9::P32; Sp = Sp + 16; call AddWraps.foo_info(D2, D1, R1) args: 4, res: 0, upd: 4; } }, AddWraps.foo_entry() // [D2, D1] { info_tbl: [(cfB, label: AddWraps.foo_info rep:HeapRep static { Fun {arity: 2 fun_type: ArgGen [True, True, True, True]} })] stack_info: arg_space: 4 updfr_space: Just 4 } {offset cfB: _B1::F64 = D2; _B2::F64 = D1; goto cfD; cfD: _cfA::F64 = %MO_F_Add_W64(_B2::F64, _B1::F64); D1 = _cfA::F64; call (P32[Sp])(D1) args: 4, res: 0, upd: 4; } }] }}} The difference lies in how the calls are generated. When `foo` is in the same module as caller the generated call looks like this: {{{ cjY: I32[Sp - 8] = stg_bh_upd_frame_info; P32[Sp - 4] = Hp - 4; I32[Sp - 12] = ck0; D2 = 1.2 :: W64; D1 = 0.0 :: W64; Sp = Sp - 12; call Main.foo_info(D2, D1) returns to ck0, args: 4, res: 4, upd: 12; ck0: _sjs::F64 = D1; Hp = Hp + 12; if (Hp > HpLim) goto ckf; else goto ckc; }}} Whereas placing `foo` in separate module leads to this code: {{{ ck5: I32[Sp - 8] = stg_bh_upd_frame_info; P32[Sp - 4] = Hp - 4; I32[Sp - 12] = ck7; D1 = 0.0 :: W64; R1 = AddWraps.foo_closure; I32[Sp - 24] = stg_ap_d_info; F64[Sp - 20] = 1.0 :: W64; Sp = Sp - 24; call stg_ap_d_fast(D1, R1) returns to ck7, args: 16, res: 4, upd: 12; ck7: _sjP::F64 = D1; Hp = Hp + 12; if (Hp > HpLim) goto ckm; else goto ckj; }}} The second version causes a segfault. This currently blocks merging of #6135 patches. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+--------------------------- Reporter: jstolarek | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: #6135 | Related Tickets: ----------------------------------+--------------------------- Changes (by jstolarek): * cc: jan.stolarek@… (added) * blocking: 6135 => #6135 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+--------------------------- Reporter: jstolarek | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: 6135 | Related Tickets: ----------------------------------+--------------------------- Changes (by simonmar): * priority: normal => highest * milestone: => 7.8.1 Comment: I tried and failed to reproduce this today, with a freshly built GHC on a 32-bit x86 Amazon EC2 instance running Ubuntu 12.04. {{{ ubuntu@ip-10-245-94-31:~/scratch$ ~/ghc/inplace/bin/ghc-stage2 8103.hs -fforce-recomp [1 of 2] Compiling AddWraps ( AddWraps.hs, AddWraps.o ) [2 of 2] Compiling Main ( 8103.hs, 8103.o ) Linking 8103 ... ubuntu@ip-10-245-94-31:~/scratch$ ./8103 0 }}} Incidentally the Cmm code above cannot be generated on x86, because it mentions D1 and D2 which are never used by the x86 backend. Maybe you generated it on x86_64? I'm stumped on this one - I tried the repro in #7953 too and that didn't crash for me either. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+--------------------------- Reporter: jstolarek | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: 6135 | Related Tickets: ----------------------------------+--------------------------- Comment (by jstolarek): I still can reproduce it on one of the older HEAD builds: {{{ [t-jastol@cam-05-unx : ~/tests/bool-primops/T8103] /5playpen/t-jastol/sandboxes/ghc/master-i386/bin/ghc --print-build- platform i386-unknown-linux [t-jastol@cam-05-unx : ~/tests/bool-primops/T8103] /5playpen/t-jastol/sandboxes/ghc/master-i386/bin/ghc --print-target- platform i386-unknown-linux [t-jastol@cam-05-unx : ~/tests/bool-primops/T8103] /5playpen/t-jastol/sandboxes/ghc/master-i386/bin/ghc -fforce-recomp 8103.hs -ddump-cmm | grep D1 D1 = _B2::F64; call AddWraps.foo_info(D2, D1, R1) args: 4, res: 0, upd: 4; AddWraps.foo_entry() // [D2, D1] _B2::F64 = D1; D1 = _cfE::F64; call (P32[(old + 4)])(D1) args: 4, res: 0, upd: 4; D1 = _B2::F64; call AddWraps.foo_info(D2, D1, R1) args: 4, res: 0, upd: 4; ... Truncated for clarity [t-jastol@cam-05-unx : ~/tests/bool-primops/T8103] ./8103 Segmentation fault (core dumped) }}} I'm doing a fresh build at the moment - if this changes anything I'll report back. Perhaps an important detail here is that this is not a true 32bit machine, but a 32-bit sandbox. I don't know if this is relevant in any way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+--------------------------- Reporter: jstolarek | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: 6135 | Related Tickets: ----------------------------------+--------------------------- Comment (by jstolarek): I just built latest HEAD (a27895b) and I can't reproduce this bug. This time the call looks different from two versions I pasted in the bug report: {{{ ck4: I32[Sp - 8] = stg_bh_upd_frame_info; P32[Sp - 4] = Hp - 4; I32[Sp - 12] = ck6; R1 = AddWraps.foo_closure; F64[Sp - 32] = 0.0 :: W64; I32[Sp - 24] = stg_ap_d_info; F64[Sp - 20] = 1.2 :: W64; Sp = Sp - 32; call stg_ap_d_fast(R1) returns to ck6, args: 24, res: 4, upd: 12; ck6: _sjO::F64 = D1; Hp = Hp + 12; if (Hp > HpLim) goto ckh; else goto ckg; }}} Still, there are references to D1 (but not D2). I'll run more tests tomorrow and if indeed the problem has disappeared I'll add regression test and close this report. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+--------------------------- Reporter: jstolarek | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: 6135 | Related Tickets: ----------------------------------+--------------------------- Comment (by kazu-yamamoto): Austin guesses that 3e598fe0b01f4692f50c377ac91010040227e7ce fixed this bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+--------------------------- Reporter: jstolarek | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: 6135 | Related Tickets: ----------------------------------+--------------------------- Changes (by kazu-yamamoto): * cc: kazu@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+----------------------------- Reporter: jstolarek | Owner: jstolarek Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: 6135 | Related Tickets: ----------------------------------+----------------------------- Changes (by jstolarek): * owner: => jstolarek -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+----------------------------- Reporter: jstolarek | Owner: jstolarek Type: bug | Status: closed Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: 6135 | Related Tickets: ----------------------------------+----------------------------- Changes (by jstolarek): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ----------------------------------+----------------------------- Reporter: jstolarek | Owner: jstolarek Type: bug | Status: closed Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: 6135 | Related Tickets: ----------------------------------+----------------------------- Comment (by jstolarek): It seems that problem was indeed solved by Geoffrey's patch. I added a regression test to the testsuite. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ---------------------------------------------+----------------------------- Reporter: jstolarek | Owner: jstolarek Type: bug | Status: closed Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: codeGen/should_run/T8103 | Blocked By: Blocking: 6135 | Related Tickets: ---------------------------------------------+----------------------------- Changes (by simonpj): * testcase: => codeGen/should_run/T8103 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8103: Segfault when passing unboxed Float# and Double# across modules ---------------------------------------------+----------------------------- Reporter: jstolarek | Owner: jstolarek Type: bug | Status: closed Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Runtime crash | Difficulty: Unknown Test Case: codeGen/should_run/T8103 | Blocked By: Blocking: 6135 | Related Tickets: ---------------------------------------------+----------------------------- Comment (by simonmar): Interesting. Geoff's accidental change to the calling convention ''almost'' worked, it was just the generic apply functions that were still using the old convention because that code has its own implementation of the calling conventions (`utils/genapply`). So that's why reproducing the bug relied on not inlining something, thus using the generic apply code. The reference to `D1` is correct, because that's part of the ''return'' convention, which always uses `D1` regardless of whether it's a real register or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8103#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC