[GHC] #14626: No need to enter a scrutinised value
GHC
ghc-devs at haskell.org
Tue Jan 16 08:17:55 UTC 2018
#14626: No need to enter a scrutinised value
-------------------------------------+-------------------------------------
Reporter: heisenbug | Owner: heisenbug
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
Resolution: | Keywords: performance
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #13861 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by alexbiehl):
I think I found a reproducer for this:
Trac14626_1.hs
{{{
module Trac14626_1 where
data Style = UserStyle Int
| PprDebug
data SDC = SDC !Style !Int
defaultUserStyle :: Bool -> Style
defaultUserStyle True = UserStyle 123
defaultUserStyle False = PprDebug
}}}
Trac14626_2.hs
{{{
module Trac14626_2 where
import Trac14626_1
f :: Int -> SDC
f x = SDC (defaultUserStyle (x > 1)) x
}}}
Compiling with `ghc Trac14626_1 Trac14626_2 -ddump-simpl -O` results in a
similar scenario than the one described by Heisenbug:
{{{
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
defaultUserStyle2
defaultUserStyle2 = I# 123#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
defaultUserStyle1
defaultUserStyle1 = UserStyle defaultUserStyle2
-- RHS size: {terms: 7, types: 2, coercions: 0, joins: 0/0}
defaultUserStyle
defaultUserStyle
= \ ds_dZ7 ->
case ds_dZ7 of {
False -> PprDebug;
True -> defaultUserStyle1
}
}}}
Our `UserStyle 123` constant has been lifted to top-level, just like in
Heisenbugs example.
Now looking at the Core of `f`
{{{
f
f = \ x_a1dk ->
case x_a1dk of { I# x1_a2gV ->
case ># x1_a2gV 1# of {
__DEFAULT -> SDC PprDebug x1_a2gV;
1# -> SDC defaultUserStyle1 x1_a2gV
}
}
}}}
(Note how `f` doesn't scrutinise defaultUserStyle1)
Looking at the CMM for `f` we can see
{{{
...
if (%MO_S_Le_W64(_s2hT::I64, 1)) goto c2ip; else goto c2is;
c2ip:
I64[Hp - 16] = SDC_con_info;
P64[Hp - 8] = PprDebug_closure+2;
I64[Hp] = _s2hT::I64;
R1 = Hp - 15;
Sp = Sp + 8;
call (P64[Sp])(R1) args: 8, res: 0, upd: 8;
c2is:
I64[Hp - 16] = SDC_con_info;
P64[Hp - 8] = defaultUserStyle1_closure; -- defaultUserStyle1
isn't tagged!
I64[Hp] = _s2hT::I64;
R1 = Hp - 15;
Sp = Sp + 8;
call (P64[Sp])(R1) args: 8, res: 0, upd: 8;
}}}
The strange thing: Putting the definitions into one module Core/Stg look
the same but the CMM correctly tags the closure.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14626#comment:37>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list