[Haskell] Expecting more inlining for bit shifting

roconnor at theorem.ca roconnor at theorem.ca
Tue Oct 10 13:54:03 EDT 2006


As an experiment, I tried the following modification of my code

module Test where

import GHC.Word
import GHC.Base
import GHC.Prim

a `shiftRLT` b | b >=# 32# = int2Word# 0#
                | otherwise = a `uncheckedShiftRL#` b

(W32# x#) `shift` (I# i#) =
{- we do an actual case analysis on i# to try to give us a discount -}
   case i# of
    {- For some bizzare reason removing the `shiftRLT` 0# makes the
       inlining fail again -}
    0# -> W32# (x# `shiftRLT` 0#)
    _ -> if i# >=# 0# then W32# (narrow32Word# (x# `shiftL#` i#))
         else W32# (x# `shiftRLT` negateInt# i#)

x `shiftR` y = x `shift` (-y)

shift7 x = x `shiftR` 7


ghc -fglasgow-exts --make -O3 Test.hs && ghc --show-iface Test.hi
yields:
...
12 shift7 :: GHC.Word.Word32 -> GHC.Word.Word32
      {- Arity: 1 HasNoCafRefs Strictness: U(L)m
         Unfolding:
         (\ x :: GHC.Word.Word32 ->
          case @ GHC.Word.Word32 x of w { W32# ww ->
          GHC.Word.W32# (GHC.Prim.uncheckedShiftRL# ww 7) }) -}
...

so the inline is successful.  But removing the 0# case 
yields:
...
14 shift7 :: GHC.Word.Word32 -> GHC.Word.Word32
      {- Arity: 1 HasNoCafRefs Strictness: U(L)m
         Unfolding:
         (\ x :: GHC.Word.Word32 ->
          case @ GHC.Word.Word32 x of w { W32# ww ->
          case @ GHC.Word.Word32 $wshift ww (-7) of ww1 { DEFAULT ->
          GHC.Word.W32# ww1 } }) -}
...

and the inlining doesn't occur.  (BTW, this is so much better than reading 
the generated C code :)

So, my hypothesis is that the inliner doesn't recognise that
``if (x >= 0) then ...'' is effectively a case analysis on x, and thus the 
argument discount is not fired.  So we need to figure out how to extend 
this criterion for when to apply the argument discount.

My best guess is that an argument x should be considered scrutinised by a 
case when there is a case analysis on an expression without any recursive 
sub-expressions whose only free variable is x.  Perhaps there are some 
better ideas.

(This whole idea of argument discounting seems rather ad hoc.  Is it not 
possible try out an inline, and remove it if in the end it doesn't get 
reduced in size sufficently?)

-- 
Russell O'Connor                                      <http://r6.ca/>
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''


More information about the Glasgow-haskell-users mailing list