[GHC] #14170: 8.2.1 regression: GHC fails to simplify `natVal`
GHC
ghc-devs at haskell.org
Wed Aug 30 19:34:22 UTC 2017
#14170: 8.2.1 regression: GHC fails to simplify `natVal`
-------------------------------------+-------------------------------------
Reporter: vagarenko | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
I was able to track this down to commit
1fcede43d2b30f33b7505e25eb6b1f321be0407f (`Introduce GHC.TypeNats module,
change KnownNat evidence to be Natural`), which hints at the problem. In
that commit, we switched the internal representation of `Nat`s from
`Integer`s to `Natural`s (from `Numeric.Natural`). For whatever reason,
however, `Natural` values don't seem to simplify as well as `Integers`, as
evidenced by this simpler program:
{{{#!hs
module Bug where
import Numeric.Natural
foo :: Natural
foo = 0
}}}
which also produces essentially identical core:
{{{#!hs
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Bug.foo1 :: Integer
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 100 0}]
Bug.foo1 = 0
-- RHS size: {terms: 39, types: 12, coercions: 0, joins: 0/0}
foo :: Natural
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False,
WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 126 60}]
foo
= case Bug.foo1 of {
integer-gmp-1.0.1.0:GHC.Integer.Type.S# i#_a2bZ ->
case GHC.Prim.tagToEnum# @ Bool (GHC.Prim.>=# i#_a2bZ 0#) of {
False -> GHC.Natural.underflowError @ Natural;
True -> GHC.Natural.NatS# (GHC.Prim.int2Word# i#_a2bZ)
};
integer-gmp-1.0.1.0:GHC.Integer.Type.Jp# dt_a2c9 ->
case GHC.Prim.uncheckedIShiftRL#
(GHC.Prim.sizeofByteArray# dt_a2c9) 3#
of {
__DEFAULT ->
case GHC.Prim.sizeofByteArray# dt_a2c9 of {
__DEFAULT -> GHC.Natural.NatJ# dt_a2c9;
0# -> GHC.Natural.underflowError @ Natural
};
1# ->
case GHC.Prim.indexWordArray# dt_a2c9 0# of wild2_a2cd
{ __DEFAULT ->
GHC.Natural.NatS# wild2_a2cd
}
};
integer-gmp-1.0.1.0:GHC.Integer.Type.Jn# ipv_a2cg ->
GHC.Natural.underflowError @ Natural
}
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14170#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list