[Git][ghc/ghc][master] Add a RULE to make lookup fuse
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Wed Aug 2 10:00:43 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
74a882dc by MorrowM at 2023-08-02T06:00:03-04:00
Add a RULE to make lookup fuse
See https://github.com/haskell/core-libraries-committee/issues/175
Metric Increase:
T18282
- - - - -
5 changed files:
- libraries/base/GHC/List.hs
- libraries/base/changelog.md
- + testsuite/tests/perf/compiler/LookupFusion.hs
- + testsuite/tests/perf/compiler/LookupFusion.stdout
- testsuite/tests/perf/compiler/all.T
Changes:
=====================================
libraries/base/GHC/List.hs
=====================================
@@ -1405,6 +1405,11 @@ lookup _key [] = Nothing
lookup key ((x,y):xys)
| key == x = Just y
| otherwise = lookup key xys
+{-# NOINLINE [1] lookup #-} -- see Note [Fusion for lookup]
+{-# RULES
+"lookup/build" forall x (g :: forall b. ((k, a) -> b -> b) -> b -> b).
+ lookup x (build g) = g (\(k, v) r -> if x == k then Just v else r) Nothing
+#-}
-- | Map a function returning a list over a list and concatenate the results.
-- 'concatMap' can be seen as the composition of 'concat' and 'map'.
@@ -1609,6 +1614,15 @@ NB: Zips for larger tuples are in the List module.
happens in phase 1.
Ditto rule "zipWithList".
+
+Note [Fusion for lookup]
+~~~~~~~~~~~~~~~~~~~~~~~~
+Implementing lookup with foldr has the potential to cause code duplication
+if fusion doesn't occur, so we use RULES instead so that lookup can participate
+in list fusion.
+The NONINLINE pragma gives the RULE a chance to fire.
+It's recursive, so won't inline anyway, but saying so is more explicit.
+See the discussion in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10715/
-}
----------------------------------------------
=====================================
libraries/base/changelog.md
=====================================
@@ -1,5 +1,8 @@
# Changelog for [`base` package](http://hackage.haskell.org/package/base)
+## 4.20.0.0 *TBA*
+ * Add a `RULE` to `Prelude.lookup`, allowing it to participate in list fusion ([CLC proposal #174](https://github.com/haskell/core-libraries-committee/issues/175))
+
## 4.19.0.0 *TBA*
* Add `{-# WARNING in "x-partial" #-}` to `Data.List.{head,tail}`.
Use `{-# OPTIONS_GHC -Wno-x-partial #-}` to disable it.
=====================================
testsuite/tests/perf/compiler/LookupFusion.hs
=====================================
@@ -0,0 +1,6 @@
+module Main where
+
+import Data.List (iterate')
+
+main :: IO ()
+main = print $ lookup (2^20) $ iterate' (\(!k,!v) -> (k + 1, v + 2)) (0 :: Int, 0 :: Int)
=====================================
testsuite/tests/perf/compiler/LookupFusion.stdout
=====================================
@@ -0,0 +1 @@
+Just 2097152
\ No newline at end of file
=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -690,3 +690,8 @@ test('T22744',
],
multimod_compile,
['T22744', '-v0'])
+
+test ('LookupFusion',
+ [collect_stats('bytes allocated',2), when(wordsize(32), skip)],
+ compile_and_run,
+ ['-O2 -package base'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/74a882dc0b7cd1cd28634baedd0b2b933f418a9b
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/74a882dc0b7cd1cd28634baedd0b2b933f418a9b
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/20230802/0a644e15/attachment-0001.html>
More information about the ghc-commits
mailing list