[commit: ghc] wip/cmmsink: CmmSink: Use a UniqSet instead of a list (e2b7dff)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 05:39:36 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/cmmsink
Link       : http://ghc.haskell.org/trac/ghc/changeset/e2b7dff7108a2b3715a04c9c22f99077446ac6dc/ghc

>---------------------------------------------------------------

commit e2b7dff7108a2b3715a04c9c22f99077446ac6dc
Author: alexbiehl <alex.biehl at gmail.com>
Date:   Fri Oct 27 07:37:57 2017 +0200

    CmmSink: Use a UniqSet instead of a list
    
    Vanilla:
    
      39,547,770,160 bytes allocated in the heap
       3,923,879,584 bytes copied during GC
         113,403,744 bytes maximum residency (39 sample(s))
             778,848 bytes maximum slop
                 303 MB total memory in use (0 MB lost due to fragmentation)
    
                                         Tot time (elapsed)  Avg pause  Max pause
      Gen  0      2595 colls,     0 par   10.290s  10.495s     0.0040s    0.3172s
      Gen  1        39 colls,     0 par    0.023s   0.024s     0.0006s    0.0030s
    
      TASKS: 4 (1 bound, 3 peak workers (3 total), using -N1)
    
      SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled)
    
      INIT    time    0.000s  (  0.003s elapsed)
      MUT     time   52.526s  ( 54.734s elapsed)
      GC      time   10.314s  ( 10.519s elapsed)
      EXIT    time    0.017s  (  0.051s elapsed)
      Total   time   62.857s  ( 65.308s elapsed)
    
      Alloc rate    752,919,176 bytes per MUT second
    
      Productivity  83.6% of total user, 83.9% of total elapsed
    
    gc_alloc_block_sync: 0
    whitehole_spin: 0
    gen[0].sync: 0
    gen[1].sync: 0
    
    `skipped` as UniqSet:
    
      41,426,419,720 bytes allocated in the heap
       3,953,425,208 bytes copied during GC
         116,264,392 bytes maximum residency (39 sample(s))
             664,480 bytes maximum slop
                 314 MB total memory in use (0 MB lost due to fragmentation)
    
                                         Tot time (elapsed)  Avg pause  Max pause
      Gen  0      3244 colls,     0 par   10.307s  10.504s     0.0032s    0.3317s
      Gen  1        39 colls,     0 par    0.024s   0.025s     0.0006s    0.0030s
    
      TASKS: 4 (1 bound, 3 peak workers (3 total), using -N1)
    
      SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled)
    
      INIT    time    0.000s  (  0.003s elapsed)
      MUT     time   37.890s  ( 40.121s elapsed)
      GC      time   10.331s  ( 10.529s elapsed)
      EXIT    time    0.019s  (  0.063s elapsed)
      Total   time   48.241s  ( 50.715s elapsed)
    
      Alloc rate    1,093,320,118 bytes per MUT second
    
      Productivity  78.6% of total user, 79.2% of total elapsed
    
    gc_alloc_block_sync: 0
    whitehole_spin: 0
    gen[0].sync: 0
    gen[1].sync: 0


>---------------------------------------------------------------

e2b7dff7108a2b3715a04c9c22f99077446ac6dc
 compiler/cmm/CmmSink.hs | 15 ++++++++-------
 1 file changed, 8 insertions(+), 7 deletions(-)

diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs
index a674e54..1892e28 100644
--- a/compiler/cmm/CmmSink.hs
+++ b/compiler/cmm/CmmSink.hs
@@ -18,6 +18,7 @@ import Platform (isARM, platformArch)
 
 import DynFlags
 import UniqFM
+import UniqSet
 import PprCmm ()
 
 import Data.List (partition)
@@ -399,7 +400,7 @@ tryToInline
       , Assignments             -- Remaining assignments
       )
 
-tryToInline dflags live node assigs = go usages node [] assigs
+tryToInline dflags live node assigs = go usages node emptyUniqSet assigs
  where
   usages :: UniqFM Int -- Maps each LocalReg to a count of how often it is used
   usages = foldLocalRegsUsed dflags addUsage emptyUFM node
@@ -422,7 +423,7 @@ tryToInline dflags live node assigs = go usages node [] assigs
         inline_and_keep    = keep inl_node -- inline the assignment, keep it
 
         keep node' = (final_node, a : rest')
-          where (final_node, rest') = go usages' node' (l:skipped) rest
+          where (final_node, rest') = go usages' node' (addOneToUniqSet skipped l) rest
                 usages' = foldLocalRegsUsed dflags (\m r -> addToUFM m r 2)
                                             usages rhs
                 -- we must not inline anything that is mentioned in the RHS
@@ -430,7 +431,7 @@ tryToInline dflags live node assigs = go usages node [] assigs
                 -- usages of the regs on the RHS to 2.
 
         cannot_inline = skipped `regsUsedIn` rhs -- Note [dependent assignments]
-                        || l `elem` skipped
+                        || l `elementOfUniqSet` skipped
                         || not (okToInline dflags rhs node)
 
         l_usages = lookupUFM usages l
@@ -521,11 +522,11 @@ And we do that right here in tryToInline, just as we do cmmMachOpFold.
 addUsage :: UniqFM Int -> LocalReg -> UniqFM Int
 addUsage m r = addToUFM_C (+) m r 1
 
-regsUsedIn :: [LocalReg] -> CmmExpr -> Bool
-regsUsedIn [] _ = False
+regsUsedIn :: UniqSet LocalReg -> CmmExpr -> Bool
+regsUsedIn ls _ | isEmptyUniqSet ls = False
 regsUsedIn ls e = wrapRecExpf f e False
-  where f (CmmReg (CmmLocal l))      _ | l `elem` ls = True
-        f (CmmRegOff (CmmLocal l) _) _ | l `elem` ls = True
+  where f (CmmReg (CmmLocal l))      _ | l `elementOfUniqSet` ls = True
+        f (CmmRegOff (CmmLocal l) _) _ | l `elementOfUniqSet` ls = True
         f _ z = z
 
 -- we don't inline into CmmUnsafeForeignCall if the expression refers



More information about the ghc-commits mailing list