| 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
Traversable classclass (Functor t,Foldable t) =>Traversable twhereSource#
Functors representing data structures that can be traversed from left to right.
A definition oftraverse must satisfy the following laws:
t .traverse f =traverse (t . f) for every applicative transformationttraverse Identity = Identitytraverse (Compose .fmap g . f) = Compose .fmap (traverse g) .traverse fA definition ofsequenceA must satisfy the following laws:
t .sequenceA =sequenceA .fmap t for every applicative transformationtsequenceA .fmap Identity = IdentitysequenceA .fmap Compose = Compose .fmapsequenceA .sequenceAwhere anapplicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving theApplicative operations, i.e.
and the identity functorIdentity and composition of functorsCompose 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 toFunctor, 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:
Functor instance,fmap should be equivalent to traversal with the identity applicative functor (fmapDefault).Foldable instance,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. For a version that ignores the results seetraverse_.
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 seesequenceA_.
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 seemapM_.
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 seesequence_.
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 ::forall t a b.Traversable t => (a -> b) -> t a -> t bSource#
This function may be used as a value forfmap in aFunctor instance, provided thattraverse is defined. (UsingfmapDefault with aTraversable instance defined only bysequenceA will result in infinite recursion.)
fmapDefaultf ≡runIdentity.traverse(Identity. f)
foldMapDefault ::forall t m a. (Traversable t,Monoid m) => (a -> m) -> t a -> mSource#
Produced byHaddock version 2.20.0