[commit: packages/base] master: Add Foldable/Traversable instances for 'Const m' (dbd9181)
git at git.haskell.org
git at git.haskell.org
Wed Sep 25 05:13:26 CEST 2013
Repository : ssh://git@git.haskell.org/base
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/dbd9181e06e4e06ca30a52f8dd30e38151e6b52d/base
>---------------------------------------------------------------
commit dbd9181e06e4e06ca30a52f8dd30e38151e6b52d
Author: Austin Seipp <austin at well-typed.com>
Date: Tue Sep 24 22:11:27 2013 -0500
Add Foldable/Traversable instances for 'Const m'
These were proposed a while ago but never went anywhere.
Authored-by: Edward Kmett <ekmett at gmail.com>
Signed-off-by: Austin Seipp <austin at well-typed.com>
>---------------------------------------------------------------
dbd9181e06e4e06ca30a52f8dd30e38151e6b52d
Data/Foldable.hs | 3 +++
Data/Traversable.hs | 3 +++
2 files changed, 6 insertions(+)
diff --git a/Data/Foldable.hs b/Data/Foldable.hs
index e61972d..0f0d5bf 100644
--- a/Data/Foldable.hs
+++ b/Data/Foldable.hs
@@ -201,6 +201,9 @@ instance Foldable Proxy where
foldr1 _ _ = error "foldr1: Proxy"
{-# INLINE foldr1 #-}
+instance Foldable (Const m) where
+ foldMap _ _ = mempty
+
-- | Monadic fold over the elements of a structure,
-- associating to the right, i.e. from right to left.
foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
diff --git a/Data/Traversable.hs b/Data/Traversable.hs
index 5fa91e8..e69d2b3 100644
--- a/Data/Traversable.hs
+++ b/Data/Traversable.hs
@@ -199,6 +199,9 @@ instance Traversable Proxy where
sequence _ = return Proxy
{-# INLINE sequence #-}
+instance Traversable (Const m) where
+ traverse _ (Const m) = pure $ Const m
+
-- general functions
-- | 'for' is 'traverse' with its arguments flipped.
More information about the ghc-commits
mailing list