[GHC] #14532: Missing constant folding for Numeric.Natural
GHC
ghc-devs at haskell.org
Mon Nov 27 17:00:53 UTC 2017
#14532: Missing constant folding for Numeric.Natural
-------------------------------------+-------------------------------------
Reporter: reinerp | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.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:
-------------------------------------+-------------------------------------
The following Haskell code
{{{#!hs
module Zero where
import Numeric.Natural
zero :: Natural
zero = 0
}}}
generates this Core:
{{{#!hs
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
zero1
zero1 = 0
-- RHS size: {terms: 39, types: 12, coercions: 0, joins: 0/0}
zero
zero
= case zero1 of {
S# i#_a2c6 ->
case tagToEnum# (>=# i#_a2c6 0#) of {
False -> underflowError;
True -> NatS# (int2Word# i#_a2c6)
};
Jp# dt_a2cg ->
case uncheckedIShiftRL# (sizeofByteArray# dt_a2cg) 3# of {
__DEFAULT ->
case sizeofByteArray# dt_a2cg of {
__DEFAULT -> NatJ# dt_a2cg;
0# -> underflowError
};
1# ->
case indexWordArray# dt_a2cg 0# of wild2_a2ck { __DEFAULT ->
NatS# wild2_a2ck
}
};
Jn# ipv_a2cn -> underflowError
}
}}}
It should instead generate this:
{{{#!hs
zero = NatS# 0##
}}}
This kind of code is generated whenever one uses `GHC.TypeLits.natVal`,
even at a constant `Nat`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14532>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list