Portability | portable |
---|---|
Stability | experimental |
Maintainer | libraries@haskell.org |
Safe Haskell | Trustworthy |
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, 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, and online at http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/#iterator.
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.
- 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 :: Traversable t => (a -> b) -> t a -> t b
- foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
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,foldMap
should be equivalent to traversal with a constant applicative functor (foldMapDefault
).
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.
Traversable [] | |
Traversable Maybe | |
Ix i => Traversable (Array i) |
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
fmapDefault :: Traversable t => (a -> b) -> t a -> t bSource
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.)
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> mSource