[GHC] #16351: Extend constant folding operations to bit manipulations

GHC ghc-devs at haskell.org
Fri Feb 22 03:52:49 UTC 2019


#16351: Extend constant folding operations to bit manipulations
-------------------------------------+-------------------------------------
        Reporter:  Fuuzetsu          |                Owner:  (none)
            Type:  feature request   |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.6.3
      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:                    |
-------------------------------------+-------------------------------------
Description changed by Fuuzetsu:

Old description:

> In #9136 GHC has greatly improved how it folds expressions for Int/Word
> when the basic arithmetic operations {{{+, -, *}}} are involved.
>
> I think that somewhat analogously this extend should be extended to
> binary manipulation operations. For example, consider the below snippet:
>
> {{{#!hs
> {-# OPTIONS_GHC -O2 -ddump-simpl -ddump-to-file -ddump-asm #-}
> module G (bar, baz) where
>
> import Data.Bits ((.|.))
> import Data.Word (Word16)
>
> bar :: Word16 -> Int
> bar w = -9223372036854775808 .|. (281474976710656 .|. fromIntegral w)
>
> baz :: Word16 -> Int
> baz w = -9223372036854775808 + (281474976710656 + fromIntegral w)
> }}}
>
> Let's peek into the Core:
> {{{#!hs
> bar
>   = \ (w_a1hX :: Word16) ->
>       case w_a1hX of { GHC.Word.W16# x#_a1Lu ->
>       GHC.Types.I#
>         (GHC.Prim.orI#
>            -9223372036854775808#
>            (GHC.Prim.orI# 281474976710656# (GHC.Prim.word2Int# x#_a1Lu)))
>       }
>
> baz
>   = \ (w_a1sr :: Word16) ->
>       case w_a1sr of { GHC.Word.W16# x#_a1Lu ->
>       GHC.Types.I#
>         (GHC.Prim.+# -9223090561878065152# (GHC.Prim.word2Int# x#_a1Lu))
>       }
> }}}
>
> Due to #9136, {{{bar}}} gets nicely folded away into a single addition.
> {{{baz}}} however is still in its "naive" form. The above example was
> extracted from an actual program where there may be long such chains of
> {{{orI#}}} and similar operations.
>
> I think it's worth pointing out that if we peek in the ASM, {{{baz}}}
> seems to get folded away eventually but I don't trust it to always happen
> properly at that level and I don't particularly fancy trawling through
> the ASM output every time.
>
> https://stackoverflow.com/a/45909278 has some laws we could use. I'm sure
> we could pick in LLVM source &c. too if we want to.

New description:

 In #9136 GHC has greatly improved how it folds expressions for Int/Word
 when the basic arithmetic operations {{{+, -, *}}} are involved.

 I think that somewhat analogously this should be extended to binary
 manipulation operations. For example, consider the below snippet:

 {{{#!hs
 {-# OPTIONS_GHC -O2 -ddump-simpl -ddump-to-file -ddump-asm #-}
 module G (bar, baz) where

 import Data.Bits ((.|.))
 import Data.Word (Word16)

 bar :: Word16 -> Int
 bar w = -9223372036854775808 .|. (281474976710656 .|. fromIntegral w)

 baz :: Word16 -> Int
 baz w = -9223372036854775808 + (281474976710656 + fromIntegral w)
 }}}

 Let's peek into the Core:
 {{{#!hs
 bar
   = \ (w_a1hX :: Word16) ->
       case w_a1hX of { GHC.Word.W16# x#_a1Lu ->
       GHC.Types.I#
         (GHC.Prim.orI#
            -9223372036854775808#
            (GHC.Prim.orI# 281474976710656# (GHC.Prim.word2Int# x#_a1Lu)))
       }

 baz
   = \ (w_a1sr :: Word16) ->
       case w_a1sr of { GHC.Word.W16# x#_a1Lu ->
       GHC.Types.I#
         (GHC.Prim.+# -9223090561878065152# (GHC.Prim.word2Int# x#_a1Lu))
       }
 }}}

 Due to #9136, {{{bar}}} gets nicely folded away into a single addition.
 {{{baz}}} however is still in its "naive" form. The above example was
 extracted from an actual program where there may be long such chains of
 {{{orI#}}} and similar operations.

 I think it's worth pointing out that if we peek in the ASM, {{{baz}}}
 seems to get folded away eventually but I don't trust it to always happen
 properly at that level and I don't particularly fancy trawling through the
 ASM output every time.

 https://stackoverflow.com/a/45909278 has some laws we could use. I'm sure
 we could pick in LLVM source &c. too if we want to.

--

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16351#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list