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 |
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.
(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
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. 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
Traversable [] # | Since: base-2.1 |
Traversable Maybe # | Since: base-2.1 |
Traversable Par1 # | Since: base-4.9.0.0 |
Traversable NonEmpty # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable Down # | Since: base-4.12.0.0 |
Traversable Product # | Since: base-4.8.0.0 |
Defined in Data.Traversable | |
Traversable Sum # | Since: base-4.8.0.0 |
Traversable Dual # | Since: base-4.8.0.0 |
Traversable Last # | Since: base-4.8.0.0 |
Traversable First # | Since: base-4.8.0.0 |
Traversable Identity # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable ZipList # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable Option # | Since: base-4.9.0.0 |
Traversable Last # | Since: base-4.9.0.0 |
Traversable First # | Since: base-4.9.0.0 |
Traversable Max # | Since: base-4.9.0.0 |
Traversable Min # | Since: base-4.9.0.0 |
Traversable Complex # | Since: base-4.9.0.0 |
Defined in Data.Complex | |
Traversable (Either a) # | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Traversable (V1 :: Type -> Type) # | Since: base-4.9.0.0 |
Traversable (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Traversable ((,) a) # | Since: base-4.7.0.0 |
Ix i => Traversable (Array i) # | Since: base-2.1 |
Defined in Data.Traversable | |
Traversable (Proxy :: Type -> Type) # | Since: base-4.7.0.0 |
Traversable (Arg a) # | Since: base-4.9.0.0 |
Traversable f => Traversable (Rec1 f) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Double :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec Double a -> f (URec Double b) Source # sequenceA :: Applicative f => URec Double (f a) -> f (URec Double a) Source # mapM :: Monad m => (a -> m b) -> URec Double a -> m (URec Double b) Source # sequence :: Monad m => URec Double (m a) -> m (URec Double a) Source # | |
Traversable (URec Float :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec Float a -> f (URec Float b) Source # sequenceA :: Applicative f => URec Float (f a) -> f (URec Float a) Source # mapM :: Monad m => (a -> m b) -> URec Float a -> m (URec Float b) Source # sequence :: Monad m => URec Float (m a) -> m (URec Float a) Source # | |
Traversable (URec Int :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Word :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec (Ptr ()) :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) Source # sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) Source # mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) Source # sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) Source # | |
Traversable f => Traversable (Alt f) # | Since: base-4.12.0.0 |
Traversable f => Traversable (Ap f) # | Since: base-4.12.0.0 |
Traversable (Const m :: Type -> Type) # | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Traversable (K1 i c :: Type -> Type) # | Since: base-4.9.0.0 |
(Traversable f, Traversable g) => Traversable (f :+: g) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (f :*: g) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (Sum f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Traversable f, Traversable g) => Traversable (Product f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Product 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 # | |
Traversable f => Traversable (M1 i c f) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (f :.: g) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (Compose f g) # | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose 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 #