[commit: packages/containers] develop-0.6, develop-0.6-questionable, master, zip-devel: Define some new Foldable methods for containers (61b9066)
git at git.haskell.org
git at git.haskell.org
Fri Jan 23 22:39:20 UTC 2015
Repository : ssh://git@git.haskell.org/containers
On branches: develop-0.6,develop-0.6-questionable,master,zip-devel
Link : http://git.haskell.org/packages/containers.git/commitdiff/61b9066d79ac346743dfe56425307e27e2e5d060
>---------------------------------------------------------------
commit 61b9066d79ac346743dfe56425307e27e2e5d060
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Tue Oct 14 20:25:29 2014 +0200
Define some new Foldable methods for containers
This is a first attempt at addressing #56
>---------------------------------------------------------------
61b9066d79ac346743dfe56425307e27e2e5d060
Data/IntMap/Base.hs | 15 +++++++++++++++
Data/Map/Base.hs | 15 +++++++++++++++
Data/Sequence.hs | 7 +++++++
Data/Set/Base.hs | 20 ++++++++++++++++++++
Data/Tree.hs | 7 +++++++
5 files changed, 64 insertions(+)
diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index fec5abe..0de3e5b 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -320,6 +320,21 @@ instance Foldable.Foldable IntMap where
go (Bin _ _ l r) = go l `mappend` go r
{-# INLINE foldMap #-}
+#if MIN_VERSION_base(4,6,0)
+ foldl' = foldl'
+ {-# INLINE foldl' #-}
+ foldr' = foldr'
+ {-# INLINE foldr' #-}
+#endif
+#if MIN_VERSION_base(4,8,0)
+ length = size
+ {-# INLINE length #-}
+ null = null
+ {-# INLINE null #-}
+ toList = elems -- NB: Foldable.toList /= IntMap.toList
+ {-# INLINE toList #-}
+#endif
+
instance Traversable IntMap where
traverse f = traverseWithKey (\_ -> f)
{-# INLINE traverse #-}
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index d1d8ffe..d01367b 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -2653,6 +2653,21 @@ instance Foldable.Foldable (Map k) where
go (Bin _ _ v l r) = go l `mappend` (f v `mappend` go r)
{-# INLINE foldMap #-}
+#if MIN_VERSION_base(4,6,0)
+ foldl' = foldl'
+ {-# INLINE foldl' #-}
+ foldr' = foldr'
+ {-# INLINE foldr' #-}
+#endif
+#if MIN_VERSION_base(4,8,0)
+ length = size
+ {-# INLINE length #-}
+ null = null
+ {-# INLINE null #-}
+ toList = elems -- NB: Foldable.toList /= Map.toList
+ {-# INLINE toList #-}
+#endif
+
instance (NFData k, NFData a) => NFData (Map k a) where
rnf Tip = ()
rnf (Bin _ kx x l r) = rnf kx `seq` rnf x `seq` rnf l `seq` rnf r
diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index 6bbebdb..f1385f5 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -189,6 +189,13 @@ instance Foldable Seq where
foldl1 f (Seq xs) = getElem (foldl1 f' xs)
where f' (Elem x) (Elem y) = Elem (f x y)
+#if MIN_VERSION_base(4,8,0)
+ length = length
+ {-# INLINE length #-}
+ null = null
+ {-# INLINE null #-}
+#endif
+
instance Traversable Seq where
traverse f (Seq xs) = Seq <$> traverse (traverse f) xs
diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs
index 6c39a8e..9260aeb 100644
--- a/Data/Set/Base.hs
+++ b/Data/Set/Base.hs
@@ -262,6 +262,26 @@ instance Foldable.Foldable Set where
go (Bin _ k l r) = go l `mappend` (f k `mappend` go r)
{-# INLINE foldMap #-}
+#if MIN_VERSION_base(4,6,0)
+ foldl' = foldl'
+ {-# INLINE foldl' #-}
+ foldr' = foldr'
+ {-# INLINE foldr' #-}
+#endif
+#if MIN_VERSION_base(4,8,0)
+ length = size
+ {-# INLINE length #-}
+ null = null
+ {-# INLINE null #-}
+ toList = toList
+ {-# INLINE toList #-}
+ minimum = findMin
+ {-# INLINE minimum #-}
+ maximum = findMax
+ {-# INLINE maximum #-}
+#endif
+
+
#if __GLASGOW_HASKELL__
{--------------------------------------------------------------------
diff --git a/Data/Tree.hs b/Data/Tree.hs
index dab25c2..2f18c68 100644
--- a/Data/Tree.hs
+++ b/Data/Tree.hs
@@ -79,6 +79,13 @@ instance Traversable Tree where
instance Foldable Tree where
foldMap f (Node x ts) = f x `mappend` foldMap (foldMap f) ts
+#if MIN_VERSION_base(4,8,0)
+ null _ = False
+ {-# INLINE null #-}
+ toList = flatten
+ {-# INLINE toList #-}
+#endif
+
instance NFData a => NFData (Tree a) where
rnf (Node x ts) = rnf x `seq` rnf ts
More information about the ghc-commits
mailing list