
#14079: Failure to do CPR in the presence of a local letrec
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.3
Keywords: JoinPoints | 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 this code:
{{{
{-# LANGUAGE BangPatterns #-}
module NoCPR (e) where
e :: (Int, Int) -> Int -> Int -> (Int, Int)
e x y n = je x y
where je !x y | y > 0 = x
| otherwise = je x (y + n)
}}}
(which is adapted from #5949).
We get this Core:
{{{
-- RHS size: {terms: 38, types: 27, coercions: 0, joins: 1/1}
e :: (Int, Int) -> Int -> Int -> (Int, Int)
[GblId,
Arity=3,
Caf=NoCafRefs,
Str=m, Unf=OtherCon []]
$wje (ww5 [Occ=Once*] :: Int)
(ww6 [Occ=Once*] :: Int)
(ww7 :: Int#)
= case ># ww7 0# of {
__DEFAULT ->
case n of { I# y1 [Occ=Once] ->
case +# ww7 y1 of sat { __DEFAULT -> jump $wje ww5 ww6 sat
}
};
1# -> (ww5, ww6)
}; } in
jump $wje ww1 ww2 ww4
}
}
}}}
Why is there no CPR happening for `e`? In fact, why is there no unboxing
happening – it was for the following similar code:
{{{
e :: (Int, Int) -> Int -> (Int, Int)
e x y = x `seq` if y > 10
then x
else e x (y + 1)
}}}
(This is a spin-off of the dicussion at
https://phabricator.haskell.org/D3811#107708).
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14079
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler