#3767: SpecConstr for join points
---------------------------------+------------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 6.14 branch
Component: Compiler | Version: 6.12.1
Keywords: | Difficulty:
Os: Unknown/Multiple | Testcase:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
The attached file `Spec.hs` has a case (from Roman's fusion code) where
`SpecConstr` is not doing the right thing. Let's look at one of the
mutually recursive loops that `SpecConstr` generates for foo:
{{{
lvl_rzY :: GHC.Types.Int
lvl_rzY = GHC.Types.I# 2147483647
lvl1_rA0 :: Data.Either.Either GHC.Types.Int GHC.Types.Int
lvl1_rA0 = Data.Either.Left @ GHC.Types.Int @ GHC.Types.Int lvl_rzY
$s$wgo_szT :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
$s$wgo_szT =
\ (sc_sz6 :: GHC.Prim.Int#) (sc1_sz7 :: GHC.Prim.Int#) ->
let {
$w$j_syG
:: GHC.Prim.Int#
-> Data.Either.Either GHC.Types.Int GHC.Types.Int
-> GHC.Prim.Int#
[LclId, Arity=2, Str=DmdType LS]
$w$j_syG =
\ (ww_sy6 :: GHC.Prim.Int#)
(w2_sy8 :: Data.Either.Either GHC.Types.Int GHC.Types.Int) ->
case GHC.Prim.<=# ww_sy6 0 of _ {
GHC.Bool.False -> $wgo_syE (GHC.Prim.+# sc_sz6 ww_sy6) w2_sy8;
GHC.Bool.True -> $wgo_syE sc_sz6 w2_sy8
} } in
case GHC.Prim.># sc1_sz7 0 of _ {
GHC.Bool.False -> $s$wgo1_szS sc_sz6 ipv_swo;
GHC.Bool.True ->
case sc1_sz7 of wild1_awb {
__DEFAULT ->
case GHC.Prim.remInt# wild1_awb 2 of _ {
__DEFAULT -> $s$wgo_szT sc_sz6 (GHC.Prim.-# wild1_awb 1);
0 ->
case w1_syr of _ { GHC.Types.I# ww_sy6 ->
$w$j_syG
ww_sy6
(Data.Either.Left
@ GHC.Types.Int
@ GHC.Types.Int
(GHC.Types.I# (GHC.Prim.-# wild1_awb 1)))
}
};
(-2147483648) ->
case w1_syr of _ { GHC.Types.I# ww_sy6 ->
$w$j_syG ww_sy6 lvl1_rA0
}
}
};
}}}
Note that the join point has an argument of type `(Either Int Int)` but it
is always called with `(Left (I# <n>))`. This means that the recursive
call in the join point is always of the form `($wgo_syE <m> (Left (I#
<n>)))` and we have a specialisation for that. However the join point
itself doesn't scrutinse its argument, and that means that GHC ignores the
potential specialisation.
Simon
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3767>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs