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.
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, performing an action on each element.
A more detailed description can be found in the overview section of Data.Traversable.
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_
.
Examples
Basic usage:
In the first two examples we show each evaluated action mapping to the output structure.
>>>
traverse Just [1,2,3,4]
Just [1,2,3,4]
>>>
traverse id [Right 1, Right 2, Right 3, Right 4]
Right [1,2,3,4]
In the next examples, we show that Nothing
and Left
values short
circuit the created structure.
>>>
traverse (const Nothing) [1,2,3,4]
Nothing
>>>
traverse (\x -> if odd x then Just x else Nothing) [1,2,3,4]
Nothing
>>>
traverse id [Right 1, Right 2, Right 3, Right 4, Left 0]
Left 0
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_
.
Examples
Basic usage:
For the first two examples we show sequenceA fully evaluating a a structure and collecting the results.
>>>
sequenceA [Just 1, Just 2, Just 3]
Just [1,2,3]
>>>
sequenceA [Right 1, Right 2, Right 3]
Right [1,2,3]
The next two example show Nothing
and Just
will short circuit
the resulting structure if present in the input. For more context,
check the Traversable
instances for Either
and Maybe
.
>>>
sequenceA [Just 1, Just 2, Just 3, Nothing]
Nothing
>>>
sequenceA [Right 1, Right 2, Right 3, Left 4]
Left 4
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_
.
Examples
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_
.
Examples
Basic usage:
The first two examples are instances where the input and
and output of sequence
are isomorphic.
>>>
sequence $ Right [1,2,3,4]
[Right 1,Right 2,Right 3,Right 4]
>>>
sequence $ [Right 1,Right 2,Right 3,Right 4]
Right [1,2,3,4]
The following examples demonstrate short circuit behavior
for sequence
.
>>>
sequence $ Left [1,2,3,4]
Left [1,2,3,4]
>>>
sequence $ [Left 0, Right 1,Right 2,Right 3,Right 4]
Left 0
Instances
Traversable [] # | Since: base-2.1 |
Traversable Maybe # | Since: base-2.1 |
Traversable Par1 # | Since: base-4.9.0.0 |
Traversable Solo # | Since: base-4.15 |
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 (UAddr :: Type -> Type) # | Since: base-4.9.0.0 |
Traversable (UChar :: Type -> Type) # | Since: base-4.9.0.0 |
Traversable (UDouble :: Type -> Type) # | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (UFloat :: Type -> Type) # | Since: base-4.9.0.0 |
Traversable (UInt :: Type -> Type) # | Since: base-4.9.0.0 |
Traversable (UWord :: 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 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 #
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.
Examples
Basic usage:
>>>
mapAccumL (\a b -> (a + b, a)) 0 [1..10]
(55,[0,1,3,6,10,15,21,28,36,45])
>>>
mapAccumL (\a b -> (a <> show b, a)) "0" [1..5]
("012345",["0","01","012","0123","01234"])
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.
Examples
Basic usage:
>>>
mapAccumR (\a b -> (a + b, a)) 0 [1..10]
(55,[54,52,49,45,40,34,27,19,10,0])
>>>
mapAccumR (\a b -> (a <> show b, a)) "0" [1..5]
("054321",["05432","0543","054","05","0"])
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 #
Overview
Traversable functors can be thought of as polymorphic containers that support mapping of applicative (or monadic) effects over the container (element-wise) to create a new container of the same shape, with the effects sequenced in a natural order for the container type in question.
The Functor
base class means that the container cannot impose any
constraints on the element type, so containers that require elements to
be comparable, or hashable, etc., cannot be instances of the Traversable
class.
The traverse
and mapM
methods
For an Applicative
functor f
and a Traversable functor t
, the
type signatures of traverse
and fmap
are rather similar:
fmap :: (a -> f b) -> t a -> t (f b) traverse :: (a -> f b) -> t a -> f (t b)
with one crucial difference: fmap
produces a container of effects, while
traverse produces an aggregate container-valued effect. For example, when
f
is the IO
monad, and t
is the List functor, while fmap
returns a list of pending IO actions traverse
returns an IO action that
evaluates to a list of the return values of the individual actions performed
left-to-right.
More concretely, if nameAndLineCount
counts the number of lines in a file,
returning a pair with input filename and the line count, then traversal
over a list of file names produces an IO action that evaluates to a list
of (fileName, lineCount)
pairs:
>>>
nameAndLineCount :: FilePath -> IO (FilePath, Int)
>>>
nameAndLineCount fn = ...
>>>
traverse nameAndLineCount ["/etc/passwd","/etc/hosts"]
[("/etc/passwd",56),("/etc/hosts",32)]
The specialisation of traverse
to the case when f
is a monad is
called mapM
. The two are otherwise generally identical:
traverse :: (Applicative f, Traversable t) => (a -> f b) -> t a -> f (t b) mapM :: (Monad m, Traversable t) => (a -> m b) -> t a -> m (t b)
The behaviour of traverse
and mapM
can be at first surprising when the
applicative functor f
is []
(i.e. the List monad). The List
monad is said to be non-deterministic, by which is meant that applying a
list of n
functions [a -> b]
to a list of k
values
[a]
produces a list of n*k
values of each function applied to
each input value.
As a result, traversal with a function f :: a -> [b]
, over an input
container t a
, yields a list [t b]
, whose length is the product
of the lengths of the lists that the function returns for each element of
the input container! The individual elements a
of the container are
replaced by each element of f a
in turn:
>>>
mapM (\n -> [0..n]) $ Just 2
[Just 0, Just 1, Just 2]>>>
mapM (\n -> [0..n]) [0..2]
[[0,0,0],[0,0,1],[0,0,2],[0,1,0],[0,1,1],[0,1,2]]
If any element of the container is mapped to an empty list, then the aggregate result is empty (no value is available to fill one of the slots of the output container).
>>>
traverse (const []) $ Just 0
[]
When however the traversed container is empty, the result is always a singleton of the empty container, the function is never evaluated as there are no input values for it to be applied to.
>>>
traverse (const []) Nothing
[Nothing]
The result of traverse
is all-or-nothing, either containers of exactly the
same shape as the input or a failure (Nothing
, Left
, empty list, etc.).
The traverse
function does not perform selective filtering as with e.g.
mapMaybe
:
>>>
let incOdd n = if odd n then Just $ n + 1 else Nothing
>>>
traverse incOdd [1, 2, 3]
Nothing>>>
mapMaybe incOdd [1, 2, 3]
[2,4]
Validation use-case
A hypothetical application of the above is to validate a structure:
>>>
validate :: Int -> Either (String, Int) Int
>>>
validate i = if odd i then Left ("That's odd", i) else Right i
>>>
traverse validate [2,4,6,8,10]
Right [2,4,6,8,10]>>>
traverse validate [2,4,6,8,9]
Left ("That's odd",9)
>>>
-- Since 'Nothing' is an empty structure, none of its elements are odd.
>>>
traverse validate Nothing
Right Nothing>>>
traverse validate (Just 42)
Right (Just 42)>>>
traverse validate (Just 17)
Left ("That's odd",17)
However, this is not terribly efficient, because we pay the cost of
reconstructing the entire structure as a side effect of validation.
It is generally cheaper to just check all the elements and then use
the original structure if it is valid. This can be done via the
methods of the Foldable
superclass, which perform only the
side effects without generating a new structure:
>>>
traverse_ validate [2,4,6,8,10]
Right ()>>>
traverse_ validate [2,4,6,8,9]
Left ("That's odd",9)
The Foldable
instance should be defined in a manner that avoids
construction of an unnecesary copy of the container.
The Foldable
method mapM_
and its flipped version forM_
can be used
to sequence IO actions over all the elements of a Traversable
container
(just for their side-effects, ignoring any results) . One special
case is a Maybe
container that optionally holds a value. Given:
action :: a -> IO () mvalue :: Maybe a
if you want to evaluate the action
in the Just
case, and do
nothing otherwise, you can write the more concise and more general:
mapM_ action mvalue
rather than
maybe (return ()) action mvalue
The mapM_
form works verbatim if the type of mvalue
is later
refactored from Maybe a
to Either e a
(assuming it remains
OK to silently do nothing in the error case).
There's even a generic way to handle empty values (Nothing
, Left
, etc.):
case traverse_ (const Nothing) mvalue of Nothing -> mapM_ action mvalue -- mvalue is non-empty Just () -> ... handle empty mvalue ...
The sequenceA
and sequence
methods
The sequenceA
and sequence
methods are useful when what you have is a
container of applicative or, respectively, monadic actions, and you want to
evaluate them left-to-right to obtain a container of the computed values.
sequenceA :: (Applicative f, Traversable t) => t (f a) -> f (t a) sequence :: (Monad m, Traversable t) => t (m a) -> m (t a) sequenceA = traverse id sequence = mapM id
When the monad m
is IO
, applying sequence
to a list of
IO actions, performs each in turn, returning a list of the results:
sequence [putStr "Hello ", putStrLn "World!"] = (\a b -> [a,b]) <$> putStr "Hello " <*> putStrLn "World!" = do u1 <- putStr "Hello " u2 <- putStrLn "World!" return (u1, u2)
For sequenceA
, the non-deterministic behaviour of List
is most easily
seen in the case of a list of lists (of elements of some common fixed type).
The result is a cross-product of all the sublists:
>>>
sequenceA [[0, 1, 2], [30, 40], [500]]
[[0,30,500],[0,40,500],[1,30,500],[1,40,500],[2,30,500],[2,40,500]]
When the monad m
is Maybe
or Either
, the effect in question is to
short-circuit the computation on encountering Nothing
or Left
.
>>>
sequence [Just 1,Just 2,Just 3]
Just [1,2,3]>>>
sequence [Just 1,Nothing,Just 3]
Nothing>>>
sequence [Right 1,Right 2,Right 3]
Right [1,2,3]>>>
sequence [Right 1,Left "sorry",Right 3]
Left "sorry"
The result of sequence
is all-or-nothing, either containers of exactly the
same shape as the input or a failure (Nothing
, Left
, empty list, etc.).
The sequence
function does not perform selective filtering as with e.g.
catMaybes
or rights
:
>>>
catMaybes [Just 1,Nothing,Just 3]
[1,3]>>>
rights [Right 1,Left "sorry",Right 3]
[1,3]
Sample instance
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 definition works for any applicative functor in the co-domain of f
,
as the laws for <*>
imply a form of associativity.
Construction
How do Traversable
functors manage to construct a new container of the
same shape by sequencing effects over their elements? Well, left-to-right
traversal with sequencing of effects suggests induction from a base case, so
the first question is what is the base case? A Traversable
container with
elements of type a
generally has some minimal form that is either
"empty" or has just a single element (think Data.List vs.
Data.List.Nonempty).
If the base case is empty (no associated first value of
a
) then traversal just reproduces the empty structure with no side effects, so we have:traverse _ empty = pure empty
With the List monad, "empty" is
[]
, while withMaybe
it isNothing
. WithEither e a
we have an empty case for each value ofe
.If the base case is a
singleton a
, thentraverse
can take thata
, applyf :: a -> F b
getting anF b
, thenfmap singleton
over that, gettingF (singleton b)
:traverse f (singleton a) = singleton <$> f a
Since Maybe
and Either
are either empty or singletons, we have
traverse _ Nothing = pure Nothing traverse f (Just a) = Just <$> f a
traverse _ (Left e) = pure (Left e) traverse f (Right a) = Right <$> f a
Similarly, for List, we have:
traverse f [] = pure [] traverse f [a] = fmap (:[]) (f a) = (:) <$> f a <*> pure []
What remains to be done is an inductive step beyond the empty and singleton
cases. For a concrete Traversable
functor T
we need to be able to
extend our structure incrementally by filling in holes. We can view a
partially built structure t0 :: T a
as a function
append :: a -> T a
that takes one more element a
to insert into
the container to the right of the existing elements to produce a larger
structure. Conversely, we can view an element a
as a function
prepend :: T a -> T a
of a partially built structure that inserts the
element to the left of the existing elements.
Assuming that traverse
has already been defined on the partially built
structure:
f0 = traverse f t0 :: F (T b)
we aim to define traverse f (append t0 a)
and/or
traverse f (prepend a t0)
.
We can lift append
and apply it to f0
to get:
append <$> f0 :: F (b -> T b)
and from the next element a
we can obtain f a :: F b
, and
this is where we'll make use of the applicative instance of F
. Adding
one more element on the right is then:
traverse f (append t0 a) = append <$> traverse f t0 <*> f a
while prepending an element on the left is:
traverse f (prepend a t0) = prepend <$> f a <*> traverse f t0
The (binary) Tree
instance example makes use of both, after defining the
Empty
base case and the singleton Leaf
node case, non-empty internal
nodes introduce both a prepended child node on the left and an appended
child node on the right:
traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
The above definitions sequence the Applicative
effects of F
in the
expected order while producing results of the expected shape T
.
For lists we get the natural order of effects by using
(prepend <$> f a)
as the operator and (traverse f as)
as the
operand (the actual definition is written as an equivalent right fold
in order to enable fusion rules):
traverse f [] = pure [] traverse f (a:as) = (:) <$> f a <*> traverse f as
The origin of the combinatorial product when F
is []
should now
be apparent, the non-deterministic definition of <*>
for List
makes
multiple independent choices for each element of the structure.
Laws
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.
A result of the naturality law is a purity law for traverse
traverse
pure
=pure
(The naturality law is implied by parametricity and thus so is the purity law [1, p15].)
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
).
See also
- [1] "The Essence of the Iterator Pattern", by Jeremy Gibbons and Bruno Oliveira, in Mathematically-Structured Functional Programming, 2006, online at http://www.cs.ox.ac.uk/people/jeremy.gibbons/publications/#iterator.
- "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.
- "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.