[commit: packages/containers] ghc-head: Reinstate the ordering guarantees for Int{Set.Map}.splitRoot. (fac4e64)

git at git.haskell.org git at git.haskell.org
Thu Jan 16 07:51:18 UTC 2014


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

On branch  : ghc-head
Link       : http://git.haskell.org/packages/containers.git/commitdiff/fac4e64ea13053f34d0fb370950d00646e3835f7

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

commit fac4e64ea13053f34d0fb370950d00646e3835f7
Author: Milan Straka <fox at ucw.cz>
Date:   Wed Dec 4 19:31:23 2013 +0100

    Reinstate the ordering guarantees for Int{Set.Map}.splitRoot.


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

fac4e64ea13053f34d0fb370950d00646e3835f7
 Data/IntMap/Base.hs        |   14 ++++++++------
 Data/IntSet/Base.hs        |   14 ++++++++------
 tests/intmap-properties.hs |   11 +++++++++--
 tests/intset-properties.hs |    9 ++++++++-
 4 files changed, 33 insertions(+), 15 deletions(-)

diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index ebdbc12..34a263a 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -2081,9 +2081,10 @@ foldlStrict f = go
 -- | /O(1)/.  Decompose a map into pieces based on the structure of the underlying
 -- tree.  This function is useful for consuming a map in parallel.
 --
--- No guarantee is made as to the sizes of the pieces; an internal, but deterministic
--- process determines this.  Further, there are no guarantees about the ordering
--- relationships of the output subsets.
+-- No guarantee is made as to the sizes of the pieces; an internal, but
+-- deterministic process determines this.  However, it is guaranteed that the
+-- pieces returned will be in ascending order (all elements in the first submap
+-- less than all elements in the second, and so on).
 --
 -- Examples:
 --
@@ -2098,9 +2099,10 @@ foldlStrict f = go
 splitRoot :: IntMap a -> [IntMap a]
 splitRoot orig =
   case orig of
-    Nil           -> []
-    x@(Tip _ _)   -> [x]
-    Bin _ _ l r   -> [l, r]
+    Nil -> []
+    x@(Tip _ _) -> [x]
+    Bin _ m l r | m < 0 -> [r, l]
+                | otherwise -> [l, r]
 {-# INLINE splitRoot #-}
 
 
diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs
index dcff687..be41db5 100644
--- a/Data/IntSet/Base.hs
+++ b/Data/IntSet/Base.hs
@@ -1488,9 +1488,10 @@ foldlStrict f = go
 -- | /O(1)/.  Decompose a set into pieces based on the structure of the underlying
 -- tree.  This function is useful for consuming a set in parallel.
 --
--- No guarantee is made as to the sizes of the pieces; an internal, but deterministic
--- process determines this.  Further, there are no guarantees about the ordering
--- relationships of the output subsets.
+-- No guarantee is made as to the sizes of the pieces; an internal, but
+-- deterministic process determines this.  However, it is guaranteed that the
+-- pieces returned will be in ascending order (all elements in the first submap
+-- less than all elements in the second, and so on).
 --
 -- Examples:
 --
@@ -1505,8 +1506,9 @@ foldlStrict f = go
 splitRoot :: IntSet -> [IntSet]
 splitRoot orig =
   case orig of
-    Nil           -> []
+    Nil -> []
     -- NOTE: we don't currently split below Tip, but we could.
-    x@(Tip _ _)   -> [x]
-    Bin _ _ l r   -> [l, r]
+    x@(Tip _ _) -> [x]
+    Bin _ m l r | m < 0 -> [r, l]
+                | otherwise -> [l, r]
 {-# INLINE splitRoot #-}
diff --git a/tests/intmap-properties.hs b/tests/intmap-properties.hs
index f598021..b37f5bc 100644
--- a/tests/intmap-properties.hs
+++ b/tests/intmap-properties.hs
@@ -160,7 +160,7 @@ main = defaultMain
              , testProperty "fmap"                 prop_fmap
              , testProperty "mapkeys"              prop_mapkeys
              , testProperty "split"                prop_splitModel
-             , testProperty "prop_splitRoot"       prop_splitRoot
+             , testProperty "splitRoot"            prop_splitRoot
              , testProperty "foldr"                prop_foldr
              , testProperty "foldr'"               prop_foldr'
              , testProperty "foldl"                prop_foldl
@@ -996,7 +996,14 @@ prop_splitModel n ys = length ys > 0 ==>
       toAscList r == sort [(k, v) | (k,v) <- xs, k > n]
 
 prop_splitRoot :: IMap -> Bool
-prop_splitRoot s = (s == unions (splitRoot s))
+prop_splitRoot s = loop ls && (s == unions ls)
+ where
+  ls = splitRoot s
+  loop [] = True
+  loop (s1:rst) = List.null
+                  [ (x,y) | x <- toList s1
+                          , y <- toList (unions rst)
+                          , x > y ]
 
 prop_foldr :: Int -> [(Int, Int)] -> Property
 prop_foldr n ys = length ys > 0 ==>
diff --git a/tests/intset-properties.hs b/tests/intset-properties.hs
index abfb96d..1671967 100644
--- a/tests/intset-properties.hs
+++ b/tests/intset-properties.hs
@@ -310,7 +310,14 @@ prop_splitMember s i = case splitMember i s of
     (s1,t,s2) -> all (<i) (toList s1) && all (>i) (toList s2) && t == i `member` s && i `delete` s == union s1 s2
 
 prop_splitRoot :: IntSet -> Bool
-prop_splitRoot s = (s == unions (splitRoot s))
+prop_splitRoot s = loop ls && (s == unions ls)
+ where
+  ls = splitRoot s
+  loop [] = True
+  loop (s1:rst) = List.null
+                  [ (x,y) | x <- toList s1
+                          , y <- toList (unions rst)
+                          , x > y ]
 
 prop_partition :: IntSet -> Int -> Bool
 prop_partition s i = case partition odd s of



More information about the ghc-commits mailing list