[GHC] #14439: Remove redundant subtraction in (^) and stimes
GHC
ghc-devs at haskell.org
Tue Nov 7 21:22:50 UTC 2017
#14439: Remove redundant subtraction in (^) and stimes
-------------------------------------+-------------------------------------
Reporter: Bodigrim | Owner: (none)
Type: task | Status: new
Priority: normal | Milestone:
Component: | Version: 8.2.1
libraries/base |
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:
-------------------------------------+-------------------------------------
Here is the source code of `Data.Real.^`:
{{{#!hs
(^) :: (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 - 1) `quot` 2) x
-- 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 - 1) `quot` 2) (x * z)
}}}
In both cases subtraction `y - 1` is redundant. The value of `y` is
guaranteed
to be positive and odd, so `(y - 1) `quot` 2 = y `quot` 2`.
Same argument applies to `Data.Semigroup.Internal.stimes{Monoid,Default}`.
For instance,
{{{#!hs
stimesMonoid :: (Integral b, Monoid a) => b -> a -> a
stimesMonoid n x0 = case compare n 0 of
LT -> errorWithoutStackTrace "stimesMonoid: negative multiplier"
EQ -> mempty
GT -> f x0 n
where
f x y
| even y = f (x `mappend` x) (y `quot` 2)
| y == 1 = x
| otherwise = g (x `mappend` x) (pred y `quot` 2) x
g x y z
| even y = g (x `mappend` x) (y `quot` 2) z
| y == 1 = x `mappend` z
| otherwise = g (x `mappend` x) (pred y `quot` 2) (x `mappend` z)
}}}
Again, `pred y` is redundant; it is enough to divide `y` itself.
My proposal is to replace `y - 1` and `pred y` by `y`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14439>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list