[Git][ghc/ghc][wip/T22324] Make (^) INLINE (#22324)

Sebastian Graf (@sgraf812) gitlab at gitlab.haskell.org
Thu Dec 1 10:13:31 UTC 2022



Sebastian Graf pushed to branch wip/T22324 at Glasgow Haskell Compiler / GHC


Commits:
e64882ed by Sebastian Graf at 2022-12-01T11:13:25+01:00
Make (^) INLINE (#22324)

So that we get to cancel away the allocation for the lazily used base.

We can move `powImpl` (which *is* strict in the base) to the top-level
so that we don't duplicate too much code and move the SPECIALISATION
pragmas onto `powImpl`.

The net effect of this change is that `(^)` plays along much better with
inlining thresholds and loopification (#22227), for example in `x2n1`.

Fixes #22324.

- - - - -


2 changed files:

- libraries/base/GHC/Real.hs
- testsuite/tests/simplCore/should_compile/T12603.stdout


Changes:

=====================================
libraries/base/GHC/Real.hs
=====================================
@@ -671,27 +671,37 @@ odd             =  not . even
 
 -------------------------------------------------------
 -- | 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 (^)]
+{-# INLINE [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]
+        | otherwise = powImpl x0 y0
+
+{-# SPECIALISE powImpl ::
+        Integer -> Integer -> Integer,
+        Integer -> Int -> Integer,
+        Int -> Int -> Int #-}
+{-# INLINABLE powImpl #-}    -- See Note [Inlining (^)]
+powImpl :: (Num a, Integral b) => a -> b -> a
+-- powImpl : x0 ^ y0 = (x ^ y)
+powImpl x y | even y    = powImpl (x * x) (y `quot` 2)
+            | y == 1    = x
+            | otherwise = powImplAcc (x * x) (y `quot` 2) x -- See Note [Half of y - 1]
+
+{-# SPECIALISE powImplAcc ::
+        Integer -> Integer -> Integer -> Integer,
+        Integer -> Int -> Integer -> Integer,
+        Int -> Int -> Int -> Int #-}
+{-# INLINABLE powImplAcc #-}    -- See Note [Inlining (^)]
+powImplAcc :: (Num a, Integral b) => a -> b -> a -> a
+-- powImplAcc : x0 ^ y0 = (x ^ y) * z
+powImplAcc x y z | even y    = powImplAcc (x * x) (y `quot` 2) z
+                 | y == 1    = x * z
+                 | otherwise = powImplAcc (x * x) (y `quot` 2) (x * z) -- See Note [Half of y - 1]
 
 -- | raise a number to an integral power
 (^^)            :: (Fractional a, Integral b) => a -> b -> a
-{-# INLINABLE [1] (^^) #-}         -- See Note [Inlining (^)
+{-# INLINE [1] (^^) #-}         -- See Note [Inlining (^)
 x ^^ n          =  if n >= 0 then x^n else recip (x^(negate n))
 
 {- Note [Half of y - 1]
@@ -699,20 +709,30 @@ x ^^ n          =  if n >= 0 then x^n else recip (x^(negate n))
 Since y is guaranteed to be odd and positive here,
 half of y - 1 can be computed as y `quot` 2, optimising subtraction away.
 
-Note [Inlining (^)
-~~~~~~~~~~~~~~~~~~
-The INLINABLE [1] pragma allows (^) to be specialised at its call sites.
-If it is called repeatedly at the same type, that can make a huge
-difference, because of those constants which can be repeatedly
-calculated.
+Note [Inlining (^)]
+~~~~~~~~~~~~~~~~~~~
+We mark (^) as INLINE[1] so that it inlines aggressively (after the RULEs in
+Note [Powers with small exponent] had a chance to fire before phase 1) and we
+expose the strict loop `powImpl`, so that we don't need to allocate a box for
+the base `x0`. Then we mark `powImpl` as INLINABLE so that auto-specialisation
+in client modules to, e.g., `Complex Double` can happen and we see its deep
+strictness.
 
-We don't inline until phase 1, to give a chance for the RULES
-"^2/Int" etc to fire first.
+Specialisation can make a huge difference for repeated calls, because of
+constants which would otherwise be calculated repeatedly and unboxing of
+arguments.
 
 Currently the fromInteger calls are not floated because we get
           \d1 d2 x y -> blah
 after the gentle round of simplification.
 
+Why not make (^) strict in `x0` with a bang and make it INLINABLE? Well, because
+it is futile: Being strict in the `Complex Double` pair won't be enough to unbox
+the `Double`s anyway. Even after deep specisalisation, we will only unbox the
+`Double`s when we inline (^), because (^) remains lazy in the `Double` fields.
+Given that (^) must always inline to yield good code, we can just as well mark
+it as such.
+
 Note [Powers with small exponent]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 For small exponents, (^) is inefficient compared to manually


=====================================
testsuite/tests/simplCore/should_compile/T12603.stdout
=====================================
@@ -1 +1 @@
-lvl = case GHC.Real.$wf1 2# 8# of v { __DEFAULT -> GHC.Types.I# v }
+  = case GHC.Real.$w$spowImpl1 2# 8# of v { __DEFAULT ->



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e64882ed371becec194d441730f3e6cab340e938

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e64882ed371becec194d441730f3e6cab340e938
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20221201/45943c8c/attachment-0001.html>


More information about the ghc-commits mailing list