[GHC] #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE
GHC
ghc-devs at haskell.org
Thu May 19 16:39:07 UTC 2016
#12022: unsafeShiftL and unsafeShiftR are not marked as INLINE
-------------------------------------+-------------------------------------
Reporter: Rufflewind | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version: 7.10.3
Resolution: | Keywords: performance,
| inline, bits
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by thomie):
* failure: None/Unknown => Runtime performance bug
Comment:
I was confused at first. From `Data.Bits` in `libraries/base`, it is clear
that `unsafeShiftL` and `unsafeShiftR` //are// marked `INLINE`:
{{{
class Eq a => Bits a where
...
unsafeShiftL :: a -> Int -> a
{-# INLINE unsafeShiftL #-}
x `unsafeShiftL` i = x `shiftL` i
unsafeShiftR :: a -> Int -> a
{-# INLINE unsafeShiftR #-}
x `unsafeShiftR` i = x `shiftR` i
....
}}}
But I guess you're talking about these instances, which indeed aren't
marked `INLINE`:
{{{
instance Bits Int where
...
(I# x#) `unsafeShiftL` (I# i#) = I# (x# `uncheckedIShiftL#` i#)
(I# x#) `unsafeShiftR` (I# i#) = I# (x# `uncheckedIShiftRA#` i#)
...
}}}
{{{
instance Bits Word where
...
(W# x#) `unsafeShiftL` (I# i#) = W# (x# `uncheckedShiftL#` i#)
(W# x#) `unsafeShiftR` (I# i#) = W# (x# `uncheckedShiftRL#` i#)
...
}}}
There is a `Note` which suggests explicit `INLINE`s aren't necessary,
except for `rotate`:
{{{
{- Note [Constant folding for rotate]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The INLINE on the Int instance of rotate enables it to be constant
folded. For example:
...
All other Bits instances seem to inline well enough on their
own to enable constant folding; for example 'shift':
sumU . mapU (`shift` 3) . replicateU 10000000 $ (7 :: Int)
goes to:
Main.$wfold =
\ (ww_sOb :: Int#) (ww1_sOf :: Int#) ->
case ww1_sOf of wild_XM {
__DEFAULT -> Main.$wfold (+# ww_sOb 56) (+# wild_XM 1);
10000000 -> ww_sOb
}
-}
}}}
But that `Note` is older (2008) than the commit that introduced
`unsafeShiftL/R` (f1c593e01d740fde1202f84aa37ad4cc95ec7272, 2011).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12022#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list