[GHC] #16372: GHC can't constant fold even basic power (^) applications for Int (and others?)
GHC
ghc-devs at haskell.org
Thu Feb 28 12:06:19 UTC 2019
#16372: GHC can't constant fold even basic power (^) applications for Int (and
others?)
-------------------------------------+-------------------------------------
Reporter: Fuuzetsu | Owner: (none)
Type: bug | 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: |
-------------------------------------+-------------------------------------
Comment (by hsyl20):
For the record, currently `(^)` is defined as:
{{{#!hs
-- | raise a number to a non-negative integral power
{-# SPECIALISE [1] (^) ::
Integer -> Integer -> Integer,
Integer -> Int -> Integer,
Int -> Int -> Int #-}
{-# INLINABLE [1] (^) #-} -- See Note [Inlining (^)]
(^) :: (Num a, Integral b) => a -> b -> a
x0 ^ y0 | y0 < 0 = errorWithoutStackTrace "Negative exponent"
| y0 == 0 = 1
| otherwise = f x0 y0
where -- f : x0 ^ y0 = x ^ y
f x y | even y = f (x * x) (y `quot` 2)
| y == 1 = x
| otherwise = g (x * x) (y `quot` 2) x -- See Note
[Half of y - 1]
-- g : x0 ^ y0 = (x ^ y) * z
g x y z | even y = g (x * x) (y `quot` 2) z
| y == 1 = x * z
| otherwise = g (x * x) (y `quot` 2) (x * z) -- See Note
[Half of y - 1]
{- Note [Half of y - 1]
~~~~~~~~~~~~~~~~~~~~~
Since y is guaranteed to be odd and positive here,
half of y - 1 can be computed as y `quot` 2, optimising subtraction
away.
-}
}}}
To perform constant folding, it would be better to have primitives such
as:
{{{#!hs
ipowInt :: Int# -> Int# -> Int#
ipowWord :: Word# -> Word# -> Word#
}}}
that we can match on in Core.
Then we could add `(^)` as a method of `Num a`, change its type to be `(^)
:: a -> a -> a` and use the appropriate primitives (or fall back to the
generic implementation otherwise). Exactly like we do for other
primitives.
Changing the type of `(^)` is a breaking change but it shouldn't harm
much. It needs the approval of the CLC though.
------
By the way, the generic implementation isn't very efficient for Int/Word.
The following one that I've just adapted from [1] performs at least twice
as fast in my tests:
{{{#!hs
ipowInt :: Int -> Int -> Int
ipowInt x y
| y < 0 = errorWithoutStackTrace "Negative exponent"
| otherwise = go 1 x y
where
go r b e =
let
e1 = e .&. 1
r' = r * (b * e1 + (e1 `xor` 1)) -- branchless
e' = e `unsafeShiftR` 1
in case e' of
0 -> r'
_ -> go r' (b*b) e'
}}}
This is another pretty compelling argument in favor of performing the
change mentioned above.
[1] https://stackoverflow.com/questions/101439/the-most-efficient-way-to-
implement-an-integer-based-power-function-powint-int
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16372#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list