[commit: packages/containers] ghc-head: Add splitTree to Map.Base. Not exposed publically yet. (db1b1b8)

git at git.haskell.org git at git.haskell.org
Thu Jan 16 07:50:58 UTC 2014


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

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

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

commit db1b1b8e670f7f17cd625d4677cd1676fd45d9f3
Author: Ryan Newton <rrnewton at gmail.com>
Date:   Mon Oct 7 00:13:59 2013 -0400

    Add splitTree to Map.Base.  Not exposed publically yet.


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

db1b1b8e670f7f17cd625d4677cd1676fd45d9f3
 Data/Map/Base.hs |   13 +++++++++++++
 1 file changed, 13 insertions(+)

diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 36da982..083b803 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -258,6 +258,7 @@ module Data.Map.Base (
     , trim
     , trimLookupLo
     , foldlStrict
+    , splitTree
     , MaybeS(..)
     , filterGt
     , filterLt
@@ -2813,3 +2814,15 @@ 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 Map into pieces.  No guarantee is made as to the sizes of
+-- the pieces, but some of them will be balanced, and some may be empty.
+splitTree :: Map k b -> Maybe (Map k b, Map k b, Map k b)
+splitTree orig =
+  case orig of 
+    Tip           -> Nothing
+    Bin 1 k v l r -> Just (singleton k v, l, r)
+{-# INLINE splitTree #-}
+
+



More information about the ghc-commits mailing list