Skip to content
Snippets Groups Projects
Commit 4549cadf authored by Andreas Klebinger's avatar Andreas Klebinger Committed by Marge Bot
Browse files

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.
parent 6a92f59d
No related branches found
No related tags found
No related merge requests found
......@@ -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
......
{-# 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)
......@@ -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
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment