[GHC] #16402: GHC doesnt' notice that (narrowWordFOO (x .&. FOO)) is just `x`.
GHC
ghc-devs at haskell.org
Thu Mar 7 03:36:32 UTC 2019
#16402: GHC doesnt' notice that (narrowWordFOO (x .&. FOO)) is just `x`.
-------------------------------------+-------------------------------------
Reporter: Fuuzetsu | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
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:
-------------------------------------+-------------------------------------
{{{#!hs
{-# OPTIONS_GHC -ddump-simpl -ddump-to-file -dhex-word-literals -O2 #-}
{-# LANGUAGE TypeApplications #-}
module NarrowWord where
import Data.Word
import Data.Bits
smallWord_foo :: Word64 -> Word64
smallWord_foo x = fromIntegral @Word16 $ fromIntegral (x .&. 0xFFFF)
smallWord_bar :: Word64 -> Word64
smallWord_bar x = fromIntegral @Word16 $ fromIntegral x
test :: Bool
test =
let w = 72430412501
in smallWord_foo w == smallWord_bar w
}}}
{{{#!hs
-- RHS size: {terms: 7, types: 3, coercions: 0, joins: 0/0}
smallWord_bar :: Word64 -> Word64
[GblId,
Arity=1,
Caf=NoCafRefs,
Str=<S(S),1*U(U)>m,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
Tmpl= \ (x_a1so [Occ=Once!] :: Word64) ->
case x_a1so of { GHC.Word.W64# x#_a2Mw [Occ=Once] ->
GHC.Word.W64# (GHC.Prim.narrow16Word# x#_a2Mw)
}}]
smallWord_bar
= \ (x_a1so :: Word64) ->
case x_a1so of { GHC.Word.W64# x#_a2Mw ->
GHC.Word.W64# (GHC.Prim.narrow16Word# x#_a2Mw)
}
-- RHS size: {terms: 9, types: 3, coercions: 0, joins: 0/0}
smallWord_foo :: Word64 -> Word64
[GblId,
Arity=1,
Caf=NoCafRefs,
Str=<S(S),1*U(U)>m,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
Tmpl= \ (x_a1hU [Occ=Once!] :: Word64) ->
case x_a1hU of { GHC.Word.W64# x#_a30a [Occ=Once] ->
GHC.Word.W64#
(GHC.Prim.narrow16Word# (GHC.Prim.and# x#_a30a
0xffff##))
}}]
smallWord_foo
= \ (x_a1hU :: Word64) ->
case x_a1hU of { GHC.Word.W64# x#_a30a ->
GHC.Word.W64#
(GHC.Prim.narrow16Word# (GHC.Prim.and# x#_a30a 0xffff##))
}
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
test :: Bool
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)
Tmpl= GHC.Types.True}]
test = GHC.Types.True
}}}
For Word8, Word16, Word32, Word64 and Int8, Int16, Int32, Int64, I would
expect GHC to never produce the {{{and}}}.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16402>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list