[GHC] #8103: Segfault when passing unboxed Float# and Double# across modules
GHC
ghc-devs at haskell.org
Mon Jul 29 17:58:53 CEST 2013
#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 at 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 at 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
More information about the ghc-tickets
mailing list