[GHC] #13144: FoatOut is not floating bottoming expressions properly
GHC
ghc-devs at haskell.org
Tue Jan 17 23:12:11 UTC 2017
#13144: FoatOut is not floating bottoming expressions properly
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider part of Eric's program in #13143, and pretty much exactly what is
in `GHC.Arr`.
{{{
{-# INLINE index #-}
index :: (Int, Int) -> Int -> Int
index b@(l,h) i
| l <= i && i < h = 0
| otherwise = indexError b i 0
{-# NOINLINE indexError #-}
indexError :: (Int, Int) -> Int -> Int -> b
indexError rng i tp = error (show rng)
}}}
Before float-out we have
{{{
index =
\ (b_ay8 :: (Int, Int)) (i_ayb :: Int) ->
case b_ay8 of wild_Xe { (l_ay9, h_aya) ->
case &&
(leInt l_ay9 i_ayb) (ltInt i_ayb h_aya)
of {
False -> indexError @ Int wild_Xe i_ayb (I# 0#);
True -> GHC.Types.I# 0#
} }
}}}
and after float-out we see
{{{
index =
\ (b_ay8 :: (Int, Int)) (i_ayb :: Int) ->
case b_ay8 of wild_Xe { (l_ay9, h_aya) ->
case &&
(leInt l_ay9 i_ayb) (ltInt i_ayb h_aya)
of {
False -> indexError @ Int b_ay8 i_ayb lvl_s2cd;
True -> GHC.Types.I# 0#
} }
}}}
We've floated the `(I# 0#)`. ''But we should have floated the entire call
to `indexError` thus'':
{{{
False -> lvl_xxx b_ay8 i_ayb
}}}
with
{{{
lvl_xxx b i = indexError @Int b i (I# 0#)
}}}
Why? Because it makes the expression smaller and moves the error handling
code out of the way.
Float-out makes some attempt to to this, but it's not right yet.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13144>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list