[commit: ghc] wip/T14880-2: 14880, part 0: insertion order (c8a1f9c)

git at git.haskell.org git at git.haskell.org
Mon Sep 10 11:37:58 UTC 2018


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

On branch  : wip/T14880-2
Link       : http://ghc.haskell.org/trac/ghc/changeset/c8a1f9c42a37eb0c3514aef1a716fdbcb912da31/ghc

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

commit c8a1f9c42a37eb0c3514aef1a716fdbcb912da31
Author: Tobias Dammers <tdammers at gmail.com>
Date:   Mon Sep 10 11:13:36 2018 +0200

    14880, part 0: insertion order


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

c8a1f9c42a37eb0c3514aef1a716fdbcb912da31
 compiler/utils/FV.hs      |  3 ++-
 compiler/utils/UniqDFM.hs | 19 ++++++++++++++-----
 2 files changed, 16 insertions(+), 6 deletions(-)

diff --git a/compiler/utils/FV.hs b/compiler/utils/FV.hs
index 6d0dc2b..f4b6e28 100644
--- a/compiler/utils/FV.hs
+++ b/compiler/utils/FV.hs
@@ -185,7 +185,8 @@ filterFV fv_cand2 fv fv_cand1 in_scope acc =
 mapUnionFV :: (a -> FV) -> [a] -> FV
 mapUnionFV _f [] _fv_cand _in_scope acc = acc
 mapUnionFV f (a:as) fv_cand in_scope acc =
-  mapUnionFV f as fv_cand in_scope $! f a fv_cand in_scope $! acc
+  -- NB: preserve ordering of the input list by treating a before as
+  f a fv_cand in_scope $! mapUnionFV f as fv_cand in_scope $! acc
 {-# INLINABLE mapUnionFV #-}
 
 -- | Union many free variable computations.
diff --git a/compiler/utils/UniqDFM.hs b/compiler/utils/UniqDFM.hs
index 38bf79d..a7a0ef8 100644
--- a/compiler/utils/UniqDFM.hs
+++ b/compiler/utils/UniqDFM.hs
@@ -81,7 +81,7 @@ import UniqFM (UniqFM, listToUFM_Directly, nonDetUFMToList, ufmToIntMap)
 -- order then `udfmToList` returns them in deterministic order.
 --
 -- There is an implementation cost: each element is given a serial number
--- as it is added, and `udfmToList` sorts it's result by this serial
+-- as it is added, and `udfmToList` sorts its result by this serial
 -- number. So you should only use `UniqDFM` if you need the deterministic
 -- property.
 --
@@ -193,9 +193,10 @@ delFromUDFM (UDFM m i) k = UDFM (M.delete (getKey $ getUnique k) m) i
 
 plusUDFM_C :: (elt -> elt -> elt) -> UniqDFM elt -> UniqDFM elt -> UniqDFM elt
 plusUDFM_C f udfml@(UDFM _ i) udfmr@(UDFM _ j)
-  -- we will use the upper bound on the tag as a proxy for the set size,
-  -- to insert the smaller one into the bigger one
-  | i > j = insertUDFMIntoLeft_C f udfml udfmr
+  -- We will use the upper bound on the tag as a proxy for the set size,
+  -- to insert the smaller one into the bigger one.
+  -- See Note [Order of insertion].
+  | i >= j = insertUDFMIntoLeft_C f udfml udfmr
   | otherwise = insertUDFMIntoLeft_C f udfmr udfml
 
 -- Note [Overflow on plusUDFM]
@@ -230,12 +231,20 @@ plusUDFM_C f udfml@(UDFM _ i) udfmr@(UDFM _ j)
 -- O(m log m) for extracting the elements from the smaller set in the
 -- insertion order and O(m * min(n+m, W)) to insert them into the bigger
 -- set.
+--
+-- Note [Order of insertion]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~
+-- When two UDFMs have the same maximum tag, we choose to insert the right
+-- argument into the left. This preserves left-to-right ordering when unioning
+-- a bunch of one-element sets, for example - if we inserted the left argument
+-- into the right one, then the two elements would be transposed.
 
 plusUDFM :: UniqDFM elt -> UniqDFM elt -> UniqDFM elt
 plusUDFM udfml@(UDFM _ i) udfmr@(UDFM _ j)
   -- we will use the upper bound on the tag as a proxy for the set size,
   -- to insert the smaller one into the bigger one
-  | i > j = insertUDFMIntoLeft udfml udfmr
+  -- See Note [Order of insertion].
+  | i >= j = insertUDFMIntoLeft udfml udfmr
   | otherwise = insertUDFMIntoLeft udfmr udfml
 
 insertUDFMIntoLeft :: UniqDFM elt -> UniqDFM elt -> UniqDFM elt



More information about the ghc-commits mailing list