[Git][ghc/ghc][master] Make sure mkSplitUniqSupply stores the precomputed mask only.

Marge Bot gitlab at gitlab.haskell.org
Tue Jun 18 20:03:23 UTC 2019



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
4549cadf by Andreas Klebinger at 2019-06-18T20:03:19Z
Make sure mkSplitUniqSupply stores the precomputed mask only.

mkSplitUniqSupply was lazy on the boxed char.

This caused a bunch of issues:
* The closure captured the boxed Char
* The mask was recomputed on every split of the supply.
* It also caused the allocation of MkSplitSupply to happen in it's own
(allocated) closure. The reason of which I did not further investigate.

We know force the computation of the mask inside mkSplitUniqSupply.
* This way the mask is computed at most once per UniqSupply creation.
* It allows ww to kick in, causing the closure to retain the unboxed
value.

Requesting Uniques in a loop is now faster by about 20%.

I did not check the impact on the overall compiler, but I added a test
to avoid regressions.

- - - - -


3 changed files:

- compiler/basicTypes/UniqSupply.hs
- + testsuite/tests/perf/should_run/UniqLoop.hs
- testsuite/tests/perf/should_run/all.T


Changes:

=====================================
compiler/basicTypes/UniqSupply.hs
=====================================
@@ -6,6 +6,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DeriveFunctor #-}
 {-# LANGUAGE PatternSynonyms #-}
+{-# LANGUAGE BangPatterns #-}
 
 #if !defined(GHC_LOADED_INTO_GHCI)
 {-# LANGUAGE UnboxedTuples #-}
@@ -88,7 +89,7 @@ takeUniqFromSupply :: UniqSupply -> (Unique, UniqSupply)
 
 mkSplitUniqSupply c
   = case ord c `shiftL` uNIQUE_BITS of
-     mask -> let
+     !mask -> let
         -- here comes THE MAGIC:
 
         -- This is one of the most hammered bits in the whole compiler


=====================================
testsuite/tests/perf/should_run/UniqLoop.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE BangPatterns #-}
+
+module Main where
+
+import UniqSupply
+import Unique
+
+-- Generate a lot of uniques
+main = do
+    us <- mkSplitUniqSupply 'v'
+    seq (churn us 10000000) (return ())
+
+churn :: UniqSupply -> Int -> Int
+churn !us 0 = getKey $ uniqFromSupply us
+churn us n =
+  let (!x,!us') = takeUniqFromSupply us
+  in churn us' (n-1)


=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -367,3 +367,11 @@ test('T15578',
      only_ways(['normal'])],
     compile_and_run,
     ['-O2'])
+
+# Test performance of creating Uniques.
+test('UniqLoop',
+     [collect_stats('bytes allocated',5),
+      only_ways(['normal'])
+      ],
+     compile_and_run,
+     ['-O -package ghc'])
\ No newline at end of file



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/4549cadf855d14a6b737ceddf4e474faf8e343ff

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/4549cadf855d14a6b737ceddf4e474faf8e343ff
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/20190618/8f656b2b/attachment-0001.html>


More information about the ghc-commits mailing list