| 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.
- class (Functor t, Foldable t) => Traversable t where
- 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 transformation- traversef =- traverse(t . f)- t
- identity
- traverseIdentity = Identity
- composition
- traverse(Compose .- fmapg . f) = Compose .- fmap(- traverseg) .- traversef
A definition of sequenceA must satisfy the following laws:
- naturality
- t .for every applicative transformation- sequenceA=- sequenceA.- fmapt- t
- identity
- sequenceA.- fmapIdentity = Identity
- composition
- sequenceA.- fmapCompose = 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.
and the identity functor Identity and composition of functors Compose
 are defined as
  newtype Identity a = Identity a
  instance Functor Identity where
    fmap f (Identity x) = Identity (f x)
  instance Applicative Identity where
    pure x = Identity x
    Identity f <*> Identity x = Identity (f x)
  newtype Compose f g a = Compose (f (g a))
  instance (Functor f, Functor g) => Functor (Compose f g) where
    fmap f (Compose x) = Compose (fmap (fmap f) x)
  instance (Applicative f, Applicative g) => Applicative (Compose f g) where
    pure x = Compose (pure (pure x))
    Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)(The naturality law is implied by parametricity.)
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 Functorinstance,fmapshould be equivalent to traversal with the identity applicative functor (fmapDefault).
- In the Foldableinstance,foldMapshould be equivalent to traversal with a constant applicative functor (foldMapDefault).
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
 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
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.)
fmapDefaultf ≡runIdentity.traverse(Identity. f)
foldMapDefault :: forall t m a. (Traversable t, Monoid m) => (a -> m) -> t a -> m Source #