Copyright | Conor McBride and Ross Paterson 2005 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Data.Traversable
Description
Class of data structures that can be traversed from left to right, performing an action on each element.
See also
- "Applicative Programming with Effects", by Conor McBride and Ross Paterson, Journal of Functional Programming 18:1 (2008) 1-13, online at http://www.soi.city.ac.uk/~ross/papers/Applicative.html.
- "The Essence of the Iterator Pattern", by Jeremy Gibbons and Bruno Oliveira, in Mathematically-Structured Functional Programming, 2006, online at http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/#iterator.
- "An Investigation of the Laws of Traversals", by Mauro Jaskelioff and Ondrej Rypacek, in Mathematically-Structured Functional Programming, 2012, online at http://arxiv.org/pdf/1202.2919.
Synopsis
- class (Functor t, Foldable t) => Traversable t where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
- for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- fmapDefault :: forall t a b. Traversable t => (a -> b) -> t a -> t b
- foldMapDefault :: forall t m a. (Traversable t, Monoid m) => (a -> m) -> t a -> m
The Traversable
class
class (Functor t, Foldable t) => Traversable t where Source #
Functors representing data structures that can be traversed from left to right.
A definition of traverse
must satisfy the following laws:
- Naturality
t .
for every applicative transformationtraverse
f =traverse
(t . f)t
- Identity
traverse
Identity
=Identity
- Composition
traverse
(Compose
.fmap
g . f) =Compose
.fmap
(traverse
g) .traverse
f
A definition of sequenceA
must satisfy the following laws:
- Naturality
t .
for every applicative transformationsequenceA
=sequenceA
.fmap
tt
- Identity
sequenceA
.fmap
Identity
=Identity
- Composition
sequenceA
.fmap
Compose
=Compose
.fmap
sequenceA
.sequenceA
where an applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative
operations, i.e.
t (pure
x) =pure
x t (f<*>
x) = t f<*>
t x
and the identity functor Identity
and composition functors
Compose
are from Data.Functor.Identity and
Data.Functor.Compose.
A result of the naturality law is a purity law for traverse
traverse
pure
=pure
(The naturality law is implied by parametricity and thus so is the purity law [1, p15].)
Instances are similar to Functor
, e.g. given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Traversable Tree where traverse f Empty = pure Empty traverse f (Leaf x) = Leaf <$> f x traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
This is suitable even for abstract types, as the laws for <*>
imply a form of associativity.
The superclass instances should satisfy the following:
- In the
Functor
instance,fmap
should be equivalent to traversal with the identity applicative functor (fmapDefault
). - In the
Foldable
instance,foldMap
should be equivalent to traversal with a constant applicative functor (foldMapDefault
).
References: [1] The Essence of the Iterator Pattern, Jeremy Gibbons and Bruno C. d. S. Oliveira
Methods
traverse :: Applicative f => (a -> f b) -> t a -> f (t b) Source #
Map each element of a structure to an action, evaluate these actions
from left to right, and collect the results. For a version that ignores
the results see traverse_
.
sequenceA :: Applicative f => t (f a) -> f (t a) Source #
Evaluate each action in the structure from left to right, and
collect the results. For a version that ignores the results
see sequenceA_
.
mapM :: Monad m => (a -> m b) -> t a -> m (t b) Source #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
sequence :: Monad m => t (m a) -> m (t a) Source #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
Instances
Instances details
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Semigroup
Instance details
Defined in Data.Semigroup
Instance details
Defined in Data.Semigroup
Instance details
Defined in Data.Complex
Instance details
Defined in Data.Traversable
Methods
traverse :: Applicative f => (a0 -> f b) -> Either a a0 -> f (Either a b) Source #
sequenceA :: Applicative f => Either a (f a0) -> f (Either a a0) Source #
mapM :: Monad m => (a0 -> m b) -> Either a a0 -> m (Either a b) Source #
sequence :: Monad m => Either a (m a0) -> m (Either a a0) Source #
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Semigroup
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Instance details
Defined in Data.Traversable
Methods
traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) Source #
sequenceA :: Applicative f0 => (f :+: g) (f0 a) -> f0 ((f :+: g) a) Source #
mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) Source #
sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) Source #
Instance details
Defined in Data.Traversable
Methods
traverse :: Applicative f0 => (a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) Source #
sequenceA :: Applicative f0 => (f :*: g) (f0 a) -> f0 ((f :*: g) a) Source #
mapM :: Monad m => (a -> m b) -> (f :*: g) a -> m ((f :*: g) b) Source #
sequence :: Monad m => (f :*: g) (m a) -> m ((f :*: g) a) Source #
Instance details
Defined in Data.Functor.Sum
Instance details
Defined in Data.Functor.Product
Methods
traverse :: Applicative f0 => (a -> f0 b) -> Product f g a -> f0 (Product f g b) Source #
sequenceA :: Applicative f0 => Product f g (f0 a) -> f0 (Product f g a) Source #
mapM :: Monad m => (a -> m b) -> Product f g a -> m (Product f g b) Source #
sequence :: Monad m => Product f g (m a) -> m (Product f g a) Source #
Instance details
Defined in Data.Traversable
Methods
traverse :: Applicative f0 => (a -> f0 b) -> M1 i c f a -> f0 (M1 i c f b) Source #
sequenceA :: Applicative f0 => M1 i c f (f0 a) -> f0 (M1 i c f a) Source #
mapM :: Monad m => (a -> m b) -> M1 i c f a -> m (M1 i c f b) Source #
sequence :: Monad m => M1 i c f (m a) -> m (M1 i c f a) Source #
Instance details
Defined in Data.Traversable
Methods
traverse :: Applicative f0 => (a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) Source #
sequenceA :: Applicative f0 => (f :.: g) (f0 a) -> f0 ((f :.: g) a) Source #
mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) Source #
sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) Source #
Instance details
Defined in Data.Functor.Compose
Methods
traverse :: Applicative f0 => (a -> f0 b) -> Compose f g a -> f0 (Compose f g b) Source #
sequenceA :: Applicative f0 => Compose f g (f0 a) -> f0 (Compose f g a) Source #
mapM :: Monad m => (a -> m b) -> Compose f g a -> m (Compose f g b) Source #
sequence :: Monad m => Compose f g (m a) -> m (Compose f g a) Source #
Utility functions
for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) Source #
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) Source #
mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) Source #
mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) Source #
General definitions for superclass methods
fmapDefault :: forall t a b. Traversable t => (a -> b) -> t a -> t b Source #
This function may be used as a value for fmap
in a Functor
instance, provided that traverse
is defined. (Using
fmapDefault
with a Traversable
instance defined only by
sequenceA
will result in infinite recursion.)
fmapDefault
f ≡runIdentity
.traverse
(Identity
. f)
foldMapDefault :: forall t m a. (Traversable t, Monoid m) => (a -> m) -> t a -> m Source #