FoatOut is not floating bottoming expressions properly
Consider part of Eric's program in #13143 (closed), 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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |