#4874: Unnecessary reboxing when using INLINABLE
---------------------------------+------------------------------------------
Reporter: tibbe | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
The intent of the attached library and test harness is to use `INLINABLE`
to generate a specialized `lookup` function at always passes the key as an
unboxed `Int#`. However, when compiled with
{{{
ghc -O2 -fregs-graph -ddump-simpl Test.hs
}}}
we can see that there's reboxing (look for allocation of an `I#`
constructor) going on. I wonder if this is related to the new `INLINABLE`
specialization. If all `INLINABLE` in `Data.FullList` are replaced by
`INLINE`, no reboxing occurs.
Below is a cleaned up version of the Core for the `Test` module. The
reboxing occurs in `$wpoly_go1_rIB`, in the call to `$slookup_$slookupL`.
{{{
test1 :: Int
test1 = I# 1
$wpoly_go_rIx :: forall v. Int# -> FL.List Int v -> Maybe v
$wpoly_go_rIx =
\ (@ v)
(ww_sHY :: Int#)
(w_sI0 :: FL.List Int v) ->
case w_sI0 of _ {
FL.Nil -> Nothing @ v;
FL.Cons ipv_iGX ipv1_iGY ipv2_iGZ ->
case ipv_iGX of _ { I# y_iHB ->
case ==# ww_sHY y_iHB of _ {
False -> $wpoly_go_rIx @ v ww_sHY ipv2_iGZ;
True -> Just @ v ipv1_iGY
}
}
}
poly_go_rIz :: forall v. Int -> FL.List Int v -> Maybe v
poly_go_rIz =
\ (@ v)
(w_sHW :: Int)
(w1_sI0 :: FL.List Int v) ->
case w_sHW of _ { I# ww_sHY ->
$wpoly_go_rIx @ v ww_sHY w1_sI0
}
$slookup_$slookupL :: forall v. Int -> FL.List Int v -> Maybe v
$slookup_$slookupL = poly_go_rIz
$wpoly_go1_rIB :: forall v. Int# -> Int# -> M.HashMap Int v -> Maybe v
$wpoly_go1_rIB =
\ (@ v)
(ww_sI7 :: Int#)
(ww1_sIb :: Int#)
(w_sId :: M.HashMap Int v) ->
case w_sId of _ {
M.Nil -> Nothing @ v;
M.Tip rb_iFO rb1_iFP rb2_iFW rb3_iFX ->
case ==# ww_sI7 rb_iFO of _ {
False -> Nothing @ v;
True ->
case rb1_iFP of _ { I# y_iHB ->
case ==# ww1_sIb y_iHB of _ {
False -> $slookup_$slookupL @ v (I# ww1_sIb) rb3_iFX;
True -> Just @ v rb2_iFW
}
}
};
M.Bin _ rb1_iGj l_iGk r_iGl ->
case eqWord#
(and#
(int2Word# ww_sI7) (int2Word# rb1_iGj))
__word 0
of _ {
False -> $wpoly_go1_rIB @ v ww_sI7 ww1_sIb r_iGl;
True -> $wpoly_go1_rIB @ v ww_sI7 ww1_sIb l_iGk
}
}
poly_go1_rID :: forall v. M.Hash -> Int -> M.HashMap Int v -> Maybe v
poly_go1_rID =
\ (@ v)
(w_sI5 :: M.Hash)
(w1_sI9 :: Int)
(w2_sId :: M.HashMap Int v) ->
case w_sI5 of _ { I# ww_sI7 ->
case w1_sI9 of _ { I# ww1_sIb ->
$wpoly_go1_rIB @ v ww_sI7 ww1_sIb w2_sId
}
}
$slookup :: forall v. Int -> M.HashMap Int v -> Maybe v
$slookup =
\ (@ v)
(k0_iFA :: Int)
(t_iFB :: M.HashMap Int v) ->
poly_go1_rID @ v k0_iFA k0_iFA t_iFB
test :: M.HashMap Int Int -> Maybe Int
test =
\ (m_aBp :: M.HashMap Int Int) ->
$slookup @ Int test1 m_aBp
------ Local rules for imported ids --------
"SPEC FL.lookupL [Int]" [ALWAYS]
forall {@ v_iGO $dEq_sHl :: Eq Int}
FL.lookupL @ Int @ v_iGO $dEq_sHl
= $slookup_$slookupL @ v_iGO
"SPEC M.lookup [Int]" [ALWAYS]
forall {@ v_iFx
$dEq_sHm :: Eq Int
$dHashable_sHn :: Data.Hashable.Hashable Int}
M.lookup @ Int @ v_iFx $dEq_sHm $dHashable_sHn
= $slookup @ v_iFx
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4874>
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