[commit: packages/containers] ghc-head: Rename to splitRoot. Add the same for Sets and expose it. (90c2dfb)

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


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

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

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

commit 90c2dfbc6fbd6c7e2886862d476853e63ca4b16e
Author: Ryan Newton <rrnewton at gmail.com>
Date:   Mon Dec 2 23:27:44 2013 -0500

    Rename to splitRoot.  Add the same for Sets and expose it.


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

90c2dfbc6fbd6c7e2886862d476853e63ca4b16e
 Data/Map/Base.hs   |   18 ++++++++----------
 Data/Map/Lazy.hs   |    1 +
 Data/Map/Strict.hs |    1 +
 Data/Set.hs        |    1 +
 Data/Set/Base.hs   |   13 +++++++++++++
 5 files changed, 24 insertions(+), 10 deletions(-)

diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 4767a1d..cafd7d5 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -211,6 +211,7 @@ module Data.Map.Base (
 
     , split
     , splitLookup
+    , splitRoot
 
     -- * Submap
     , isSubmapOf, isSubmapOfBy
@@ -258,7 +259,6 @@ module Data.Map.Base (
     , trim
     , trimLookupLo
     , foldlStrict
-    , splitTree
     , MaybeS(..)
     , filterGt
     , filterLt
@@ -2816,15 +2816,13 @@ foldlStrict f = go
 {-# INLINE foldlStrict #-}
 
 
--- | /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.  This is most useful for consuming a Map in
+-- | /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.  This is most useful for consuming a map in
 -- parallel.
-splitTree :: Map k b -> [Map k b]
-splitTree orig =
+splitRoot :: Map k b -> [Map k b]
+splitRoot orig =
   case orig of 
     Tip           -> []
-    Bin 1 k v l r -> [singleton k v, l, r]
-{-# INLINE splitTree #-}
-
-
+    Bin _ k v l r -> [singleton k v, l, r]
+{-# INLINE splitRoot #-}
diff --git a/Data/Map/Lazy.hs b/Data/Map/Lazy.hs
index 98d9232..119b6a0 100644
--- a/Data/Map/Lazy.hs
+++ b/Data/Map/Lazy.hs
@@ -171,6 +171,7 @@ module Data.Map.Lazy (
 
     , split
     , splitLookup
+    , splitRoot
 
     -- * Submap
     , isSubmapOf, isSubmapOfBy
diff --git a/Data/Map/Strict.hs b/Data/Map/Strict.hs
index 64b47fc..75a29c8 100644
--- a/Data/Map/Strict.hs
+++ b/Data/Map/Strict.hs
@@ -178,6 +178,7 @@ module Data.Map.Strict
 
     , split
     , splitLookup
+    , splitRoot
 
     -- * Submap
     , isSubmapOf, isSubmapOfBy
diff --git a/Data/Set.hs b/Data/Set.hs
index f9397ce..5f1d918 100644
--- a/Data/Set.hs
+++ b/Data/Set.hs
@@ -80,6 +80,7 @@ module Data.Set (
             , partition
             , split
             , splitMember
+            , splitRoot
 
             -- * Indexed
             , lookupIndex
diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs
index d902310..37c0ffa 100644
--- a/Data/Set/Base.hs
+++ b/Data/Set/Base.hs
@@ -126,6 +126,7 @@ module Data.Set.Base (
             , partition
             , split
             , splitMember
+            , splitRoot
 
             -- * Indexed
             , lookupIndex
@@ -1404,6 +1405,18 @@ foldlStrict f = go
     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.  No guarantee is made as to the sizes of the pieces; an internal, but
+-- deterministic process determines this.  This is most useful for consuming a set in
+-- parallel.
+splitRoot :: Set a -> [Set a]
+splitRoot orig =
+  case orig of 
+    Tip           -> []
+    Bin _ v l r -> [singleton v, l, r]
+{-# INLINE splitRoot #-}
+
+
 {--------------------------------------------------------------------
   Debugging
 --------------------------------------------------------------------}



More information about the ghc-commits mailing list