[commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, revert-408-bugfix_394: Data.IntMap.Internal: rebasing and minor adjustments (06e0146)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:46:01 UTC 2017


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

On branches: cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/06e01467a269528a91660142007413600907169a

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

commit 06e01467a269528a91660142007413600907169a
Author: wren gayle romano <wren at community.haskell.org>
Date:   Mon Sep 5 16:39:28 2016 -0700

    Data.IntMap.Internal: rebasing and minor adjustments


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

06e01467a269528a91660142007413600907169a
 Data/IntMap/Internal.hs | 21 +++++++++++++++++----
 1 file changed, 17 insertions(+), 4 deletions(-)

diff --git a/Data/IntMap/Internal.hs b/Data/IntMap/Internal.hs
index 3d7de1d..3fb30e9 100644
--- a/Data/IntMap/Internal.hs
+++ b/Data/IntMap/Internal.hs
@@ -1538,7 +1538,7 @@ preserveMissing = WhenMissing
 mapMissing :: Applicative f => (Key -> x -> y) -> WhenMissing f x y
 mapMissing f = WhenMissing
   { missingSubtree = \m -> pure $! mapWithKey f m
-  , missingKey     = \ k x -> pure $ Just (f k x) }
+  , missingKey     = \k x -> pure $ Just (f k x) }
 {-# INLINE mapMissing #-}
 
 
@@ -1594,16 +1594,29 @@ filterAMissing f = WhenMissing
 filterWithKeyA
   :: Applicative f => (Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
 filterWithKeyA _ Nil             = pure Nil
-filterWithKeyA f (Tip k x)       = error "TODO: filterWithKeyA"
+filterWithKeyA f t@(Tip k x)     = (\b -> if b then t else Nil) <$> f k x
 filterWithKeyA f t@(Bin p m l r) = error "TODO: filterWithKeyA"
-  {-
+{-
+-- Implementation Idea 1:
   combine <$> f p m <*> filterWithKeyA f l <*> filterWithKeyA f r
   where
     combine True l' r'
       | l' `ptrEq` l && r' `ptrEq` r = t
       | otherwise                    = link p m l' r'
     combine False l' r'              = link2 l' r'
-  -}
+
+-- Implementation Idea 2:
+  combine p m <$> filterWithKeyA f l <*> filterWithKeyA f r
+  where
+    combine _ _ Nil r' = r'
+    combine _ _ l' Nil = l'
+    combine p m l' r'
+      | l' `ptrEq` l && r' `ptrEq` r = t
+      | otherwise                    = link pl l' pr r'
+    combine p m l' r'                = link2 l' r'
+
+link k (Tip k x) p t@(Bin p m _ _ \/ Tip p _) | nomatch k p m \/ k/=p
+-}
 
 -- | This wasn't in Data.Bool until 4.7.0, so we define it here
 bool :: a -> a -> Bool -> a



More information about the ghc-commits mailing list