base-4.3.0.0: Basic libraries

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org

Data.Traversable

Description

Class of data structures that can be traversed from left to right, performing an action on each element.

See also

Note that the functions mapM and sequence generalize Prelude functions of the same names from lists to any Traversable functor. To avoid ambiguity, either import the Prelude hiding these names or qualify uses of these function names with an alias for this module.

Synopsis

Documentation

class (Functor t, Foldable t) => Traversable t whereSource

Functors representing data structures that can be traversed from left to right.

Minimal complete definition: traverse or sequenceA.

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, Data.Foldable.foldMap should 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.

sequenceA :: Applicative f => t (f a) -> f (t a)Source

Evaluate each action in the structure from left to right, and collect the results.

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.

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.

Instances

for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)Source

for is traverse with its arguments flipped.

forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)Source

forM is mapM with its arguments flipped.

mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)Source

The mapAccumL function behaves like a combination of fmap and foldl; it applies a function to each element of a structure, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new structure.

mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)Source

The mapAccumR function behaves like a combination of fmap and foldr; it applies a function to each element of a structure, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new structure.

fmapDefault :: Traversable t => (a -> b) -> t a -> t bSource

This function may be used as a value for fmap in a Functor instance.

foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> mSource

This function may be used as a value for Data.Foldable.foldMap in a Foldable instance.