[commit: packages/containers] ghc-head: Switch to in-order splitRoot. Provide the same for IntSet/IntMap. (7320588)

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


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

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

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

commit 73205883bf238eef4363783255bd5cd5bed3db08
Author: Ryan Newton <rrnewton at gmail.com>
Date:   Tue Dec 3 17:10:26 2013 -0500

    Switch to in-order splitRoot.  Provide the same for IntSet/IntMap.


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

73205883bf238eef4363783255bd5cd5bed3db08
 Data/IntMap/Base.hs   |   27 +++++++++++++++++++++++++++
 Data/IntMap/Lazy.hs   |    1 +
 Data/IntMap/Strict.hs |    1 +
 Data/IntSet.hs        |    1 +
 Data/IntSet/Base.hs   |   27 +++++++++++++++++++++++++++
 Data/Map/Base.hs      |   17 +++++++++++------
 Data/Set/Base.hs      |   17 +++++++++++------
 7 files changed, 79 insertions(+), 12 deletions(-)

diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index 1c6448b..5f238ac 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -165,6 +165,7 @@ module Data.IntMap.Base (
 
     , split
     , splitLookup
+    , splitRoot
 
     -- * Submap
     , isSubmapOf, isSubmapOfBy
@@ -2077,6 +2078,32 @@ foldlStrict f = go
     go z (x:xs) = let z' = f z x in z' `seq` go z' xs
 {-# INLINE foldlStrict #-}
 
+-- | /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.  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:
+--     
+-- > splitRoot (fromList (zip [1..6::Int] ['a'..])) ==
+-- >   [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d'),(5,'e'),(6,'f')]]
+-- 
+-- > splitRoot empty == []
+--
+--  Note that the current implementation will not return more than two submaps,
+--  but you should not depend on this remaining the case in future versions.
+splitRoot :: IntMap a -> [IntMap a]
+splitRoot orig =
+  case orig of
+    Nil           -> []
+    x@(Tip _ _)   -> [x]
+    Bin _ _ l r   -> [l, r]
+{-# INLINE splitRoot #-}
+
+
 {--------------------------------------------------------------------
   Debugging
 --------------------------------------------------------------------}
diff --git a/Data/IntMap/Lazy.hs b/Data/IntMap/Lazy.hs
index 6de26f8..ab89e1a 100644
--- a/Data/IntMap/Lazy.hs
+++ b/Data/IntMap/Lazy.hs
@@ -175,6 +175,7 @@ module Data.IntMap.Lazy (
 
     , split
     , splitLookup
+    , splitRoot
 
     -- * Submap
     , isSubmapOf, isSubmapOfBy
diff --git a/Data/IntMap/Strict.hs b/Data/IntMap/Strict.hs
index 9b42c4f..2ca3707 100644
--- a/Data/IntMap/Strict.hs
+++ b/Data/IntMap/Strict.hs
@@ -181,6 +181,7 @@ module Data.IntMap.Strict (
 
     , split
     , splitLookup
+    , splitRoot
 
     -- * Submap
     , isSubmapOf, isSubmapOfBy
diff --git a/Data/IntSet.hs b/Data/IntSet.hs
index 0f2221c..49dd10c 100644
--- a/Data/IntSet.hs
+++ b/Data/IntSet.hs
@@ -90,6 +90,7 @@ module Data.IntSet (
             , partition
             , split
             , splitMember
+            , splitRoot
 
             -- * Map
             , IS.map
diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs
index 9e0320b..0d88363 100644
--- a/Data/IntSet/Base.hs
+++ b/Data/IntSet/Base.hs
@@ -111,6 +111,7 @@ module Data.IntSet.Base (
     , partition
     , split
     , splitMember
+    , splitRoot
 
     -- * Map
     , map
@@ -1483,3 +1484,29 @@ foldlStrict f = go
     go z []     = z
     go z (x:xs) = let z' = f z x in z' `seq` go z' xs
 {-# INLINE foldlStrict #-}
+
+-- | /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.  However, it is guaranteed that the pieces
+-- returned will be in ascending order (all elements in the first subset less than all
+-- elements in the second, and so on).
+--
+-- Examples:
+--     
+-- > splitRoot (fromList [1..120]) == [fromList [1..63],fromList [64..120]]
+-- > splitRoot empty == []
+--
+--  Note that the current implementation will not return more than two subsets, but
+--  you should not depend on this remaining the case in future versions.  Also, the
+--  current version will not continue splitting all the way to individual singleton
+--  sets -- it will stop before that.
+splitRoot :: IntSet -> [IntSet]
+splitRoot orig =
+  case orig of
+    Nil           -> []
+    -- NOTE: we don't currently split below Tip, but we could.    
+    x@(Tip _ _)   -> [x]
+    Bin _ _ l r   -> [l, r]
+{-# INLINE splitRoot #-}
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 5c1c076..8753afa 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -2817,20 +2817,25 @@ foldlStrict f = go
 
 
 -- | /O(1)/.  Decompose a map into pieces based on the structure of the underlying
--- tree.  No guarantee is made as to the sizes of the pieces; an internal, but
--- deterministic process determines this.  
+-- 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.  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:
 --     
 -- > splitRoot (fromList (zip [1..6] ['a'..])) ==
--- >   [fromList [(4,'d')],fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(5,'e'),(6,'f')]]
+-- >   [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d')],fromList [(5,'e'),(6,'f')]]
 --
--- > splitRoot M.empty == []
+-- > splitRoot empty == []
 --
---  This function is useful for consuming a map in parallel.
+--  Note that the current implementation will not return more than three subsets,
+--  but you should not depend on this remaining the case in future versions.
 splitRoot :: Map k b -> [Map k b]
 splitRoot orig =
   case orig of 
     Tip           -> []
-    Bin _ k v l r -> [singleton k v, l, r]
+    Bin _ k v l r -> [l, singleton k v, r]
 {-# INLINE splitRoot #-}
diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs
index e3758eb..63c5340 100644
--- a/Data/Set/Base.hs
+++ b/Data/Set/Base.hs
@@ -1406,22 +1406,27 @@ foldlStrict f = go
 {-# INLINE foldlStrict #-}
 
 -- | /O(1)/.  Decompose a set into pieces based on the structure of the underlying
--- tree.  No guarantee is made as to the sizes of the pieces; an internal, but
--- deterministic process determines this. 
+-- 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.  However, it is guaranteed that the pieces
+-- returned will be in ascending order (all elements in the first subset less than all
+-- elements in the second, and so on).
 --
 -- Examples:
 --     
 -- > splitRoot (fromList [1..6]) ==
--- >   [fromList [4],fromList [1,2,3],fromList [5,6]]
+-- >   [fromList [1,2,3],fromList [4],fromList [5,6]]
 --    
--- > splitRoot M.empty == []
+-- > splitRoot empty == []
 --
---  This function is useful for consuming a set in parallel.    
+--  Note that the current implementation will not return more than three subsets,
+--  but you should not depend on this remaining the case in future versions.
 splitRoot :: Set a -> [Set a]
 splitRoot orig =
   case orig of 
     Tip           -> []
-    Bin _ v l r -> [singleton v, l, r]
+    Bin _ v l r -> [l, singleton v, r]
 {-# INLINE splitRoot #-}
 
 



More information about the ghc-commits mailing list