Copyright | Conor McBride and Ross Paterson 2005 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | libraries@haskell.org |
Stability | stable |
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. Instances are expected to satisfy the listed laws.
Synopsis
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) 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)
- forAccumM :: (Monad m, Traversable t) => s -> t a -> (s -> a -> m (s, b)) -> m (s, t b)
- mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
- mapAccumR :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
- mapAccumM :: (Monad m, Traversable t) => (s -> a -> m (s, b)) -> s -> t a -> m (s, t b)
- fmapDefault :: Traversable t => (a -> b) -> t a -> t b
- foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
The Traversable
class
class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where Source #
Functors representing data structures that can be transformed to
structures of the same shape by performing an Applicative
(or,
therefore, Monad
) action on each element from left to right.
A more detailed description of what same shape means, the various methods, how traversals are constructed, and example advanced use-cases can be found in the Overview section of Data.Traversable.
For the class laws see the Laws 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
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 #
forAccumM :: (Monad m, Traversable t) => s -> t a -> (s -> a -> m (s, b)) -> m (s, t b) Source #
mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) 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 => (s -> a -> (s, b)) -> s -> t a -> (s, t b) 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"])
mapAccumM :: (Monad m, Traversable t) => (s -> a -> m (s, b)) -> s -> t a -> m (s, t b) Source #
The mapAccumM
function behaves like a combination of mapM
and
mapAccumL
that traverses the structure while evaluating the actions
and passing an accumulating parameter from left to right.
It returns a final value of this accumulator together with the new structure.
The accumulator is often used for caching the intermediate results of a computation.
Examples
Basic usage:
>>>
let expensiveDouble a = putStrLn ("Doubling " <> show a) >> pure (2 * a)
>>>
:{
mapAccumM (\cache a -> case lookup a cache of Nothing -> expensiveDouble a >>= \double -> pure ((a, double):cache, double) Just double -> pure (cache, double) ) [] [1, 2, 3, 1, 2, 3] :} Doubling 1 Doubling 2 Doubling 3 ([(3,6),(2,4),(1,2)],[2,4,6,2,4,6])
Since: base-4.18.0.0
General definitions for superclass methods
fmapDefault :: 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 :: (Traversable t, Monoid m) => (a -> m) -> t a -> m Source #