base-4.16.0.0: Basic libraries
CopyrightConor McBride and Ross Paterson 2005
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Traversable

Description

Class of data structures that can be traversed from left to right, performing an action on each element.

Synopsis

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.

Minimal complete definition

traverse | sequenceA

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 see traverse_.

Examples

Expand

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

Expand

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

Expand

mapM is literally a traverse with a type signature restricted to Monad. Its implementation may be more efficient due to additional power of Monad.

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

Expand

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

Instances details
Traversable ZipList Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> ZipList a -> f (ZipList b) Source #

sequenceA :: Applicative f => ZipList (f a) -> f (ZipList a) Source #

mapM :: Monad m => (a -> m b) -> ZipList a -> m (ZipList b) Source #

sequence :: Monad m => ZipList (m a) -> m (ZipList a) Source #

Traversable Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

traverse :: Applicative f => (a -> f b) -> Complex a -> f (Complex b) Source #

sequenceA :: Applicative f => Complex (f a) -> f (Complex a) Source #

mapM :: Monad m => (a -> m b) -> Complex a -> m (Complex b) Source #

sequence :: Monad m => Complex (m a) -> m (Complex a) Source #

Traversable Identity Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) Source #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) Source #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) Source #

sequence :: Monad m => Identity (m a) -> m (Identity a) Source #

Traversable First Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> First a -> f (First b) Source #

sequenceA :: Applicative f => First (f a) -> f (First a) Source #

mapM :: Monad m => (a -> m b) -> First a -> m (First b) Source #

sequence :: Monad m => First (m a) -> m (First a) Source #

Traversable Last Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Last a -> f (Last b) Source #

sequenceA :: Applicative f => Last (f a) -> f (Last a) Source #

mapM :: Monad m => (a -> m b) -> Last a -> m (Last b) Source #

sequence :: Monad m => Last (m a) -> m (Last a) Source #

Traversable Down Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Down a -> f (Down b) Source #

sequenceA :: Applicative f => Down (f a) -> f (Down a) Source #

mapM :: Monad m => (a -> m b) -> Down a -> m (Down b) Source #

sequence :: Monad m => Down (m a) -> m (Down a) Source #

Traversable First Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a -> f b) -> First a -> f (First b) Source #

sequenceA :: Applicative f => First (f a) -> f (First a) Source #

mapM :: Monad m => (a -> m b) -> First a -> m (First b) Source #

sequence :: Monad m => First (m a) -> m (First a) Source #

Traversable Last Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a -> f b) -> Last a -> f (Last b) Source #

sequenceA :: Applicative f => Last (f a) -> f (Last a) Source #

mapM :: Monad m => (a -> m b) -> Last a -> m (Last b) Source #

sequence :: Monad m => Last (m a) -> m (Last a) Source #

Traversable Max Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a -> f b) -> Max a -> f (Max b) Source #

sequenceA :: Applicative f => Max (f a) -> f (Max a) Source #

mapM :: Monad m => (a -> m b) -> Max a -> m (Max b) Source #

sequence :: Monad m => Max (m a) -> m (Max a) Source #

Traversable Min Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a -> f b) -> Min a -> f (Min b) Source #

sequenceA :: Applicative f => Min (f a) -> f (Min a) Source #

mapM :: Monad m => (a -> m b) -> Min a -> m (Min b) Source #

sequence :: Monad m => Min (m a) -> m (Min a) Source #

Traversable Dual Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Dual a -> f (Dual b) Source #

sequenceA :: Applicative f => Dual (f a) -> f (Dual a) Source #

mapM :: Monad m => (a -> m b) -> Dual a -> m (Dual b) Source #

sequence :: Monad m => Dual (m a) -> m (Dual a) Source #

Traversable Product Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Product a -> f (Product b) Source #

sequenceA :: Applicative f => Product (f a) -> f (Product a) Source #

mapM :: Monad m => (a -> m b) -> Product a -> m (Product b) Source #

sequence :: Monad m => Product (m a) -> m (Product a) Source #

Traversable Sum Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Sum a -> f (Sum b) Source #

sequenceA :: Applicative f => Sum (f a) -> f (Sum a) Source #

mapM :: Monad m => (a -> m b) -> Sum a -> m (Sum b) Source #

sequence :: Monad m => Sum (m a) -> m (Sum a) Source #

Traversable NonEmpty Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) Source #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) Source #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) Source #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) Source #

Traversable Par1 Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Par1 a -> f (Par1 b) Source #

sequenceA :: Applicative f => Par1 (f a) -> f (Par1 a) Source #

mapM :: Monad m => (a -> m b) -> Par1 a -> m (Par1 b) Source #

sequence :: Monad m => Par1 (m a) -> m (Par1 a) Source #

Traversable Maybe Source #

Since: base-2.1

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) Source #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) Source #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) Source #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) Source #

Traversable Solo Source #

Since: base-4.15

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Solo a -> f (Solo b) Source #

sequenceA :: Applicative f => Solo (f a) -> f (Solo a) Source #

mapM :: Monad m => (a -> m b) -> Solo a -> m (Solo b) Source #

sequence :: Monad m => Solo (m a) -> m (Solo a) Source #

Traversable [] Source #

Since: base-2.1

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> [a] -> f [b] Source #

sequenceA :: Applicative f => [f a] -> f [a] Source #

mapM :: Monad m => (a -> m b) -> [a] -> m [b] Source #

sequence :: Monad m => [m a] -> m [a] Source #

Traversable (Either a) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a0 -> f b) -> Either a a0 -> f (Either a b) Source #

sequenceA :: Applicative f => Either a (f a0) -> f (Either a a0) Source #

mapM :: Monad m => (a0 -> m b) -> Either a a0 -> m (Either a b) Source #

sequence :: Monad m => Either a (m a0) -> m (Either a a0) Source #

Traversable (Proxy :: Type -> Type) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) Source #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) Source #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) Source #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) Source #

Traversable (Arg a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

traverse :: Applicative f => (a0 -> f b) -> Arg a a0 -> f (Arg a b) Source #

sequenceA :: Applicative f => Arg a (f a0) -> f (Arg a a0) Source #

mapM :: Monad m => (a0 -> m b) -> Arg a a0 -> m (Arg a b) Source #

sequence :: Monad m => Arg a (m a0) -> m (Arg a a0) Source #

Ix i => Traversable (Array i) Source #

Since: base-2.1

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Array i a -> f (Array i b) Source #

sequenceA :: Applicative f => Array i (f a) -> f (Array i a) Source #

mapM :: Monad m => (a -> m b) -> Array i a -> m (Array i b) Source #

sequence :: Monad m => Array i (m a) -> m (Array i a) Source #

Traversable (U1 :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> U1 a -> f (U1 b) Source #

sequenceA :: Applicative f => U1 (f a) -> f (U1 a) Source #

mapM :: Monad m => (a -> m b) -> U1 a -> m (U1 b) Source #

sequence :: Monad m => U1 (m a) -> m (U1 a) Source #

Traversable (UAddr :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) Source #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) Source #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) Source #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) Source #

Traversable (UChar :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UChar a -> f (UChar b) Source #

sequenceA :: Applicative f => UChar (f a) -> f (UChar a) Source #

mapM :: Monad m => (a -> m b) -> UChar a -> m (UChar b) Source #

sequence :: Monad m => UChar (m a) -> m (UChar a) Source #

Traversable (UDouble :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UDouble a -> f (UDouble b) Source #

sequenceA :: Applicative f => UDouble (f a) -> f (UDouble a) Source #

mapM :: Monad m => (a -> m b) -> UDouble a -> m (UDouble b) Source #

sequence :: Monad m => UDouble (m a) -> m (UDouble a) Source #

Traversable (UFloat :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UFloat a -> f (UFloat b) Source #

sequenceA :: Applicative f => UFloat (f a) -> f (UFloat a) Source #

mapM :: Monad m => (a -> m b) -> UFloat a -> m (UFloat b) Source #

sequence :: Monad m => UFloat (m a) -> m (UFloat a) Source #

Traversable (UInt :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UInt a -> f (UInt b) Source #

sequenceA :: Applicative f => UInt (f a) -> f (UInt a) Source #

mapM :: Monad m => (a -> m b) -> UInt a -> m (UInt b) Source #

sequence :: Monad m => UInt (m a) -> m (UInt a) Source #

Traversable (UWord :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UWord a -> f (UWord b) Source #

sequenceA :: Applicative f => UWord (f a) -> f (UWord a) Source #

mapM :: Monad m => (a -> m b) -> UWord a -> m (UWord b) Source #

sequence :: Monad m => UWord (m a) -> m (UWord a) Source #

Traversable (V1 :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> V1 a -> f (V1 b) Source #

sequenceA :: Applicative f => V1 (f a) -> f (V1 a) Source #

mapM :: Monad m => (a -> m b) -> V1 a -> m (V1 b) Source #

sequence :: Monad m => V1 (m a) -> m (V1 a) Source #

Traversable ((,) a) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a0 -> f b) -> (a, a0) -> f (a, b) Source #

sequenceA :: Applicative f => (a, f a0) -> f (a, a0) Source #

mapM :: Monad m => (a0 -> m b) -> (a, a0) -> m (a, b) Source #

sequence :: Monad m => (a, m a0) -> m (a, a0) Source #

Traversable (Const m :: Type -> Type) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Const m a -> f (Const m b) Source #

sequenceA :: Applicative f => Const m (f a) -> f (Const m a) Source #

mapM :: Monad m0 => (a -> m0 b) -> Const m a -> m0 (Const m b) Source #

sequence :: Monad m0 => Const m (m0 a) -> m0 (Const m a) Source #

Traversable f => Traversable (Ap f) Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Ap f a -> f0 (Ap f b) Source #

sequenceA :: Applicative f0 => Ap f (f0 a) -> f0 (Ap f a) Source #

mapM :: Monad m => (a -> m b) -> Ap f a -> m (Ap f b) Source #

sequence :: Monad m => Ap f (m a) -> m (Ap f a) Source #

Traversable f => Traversable (Alt f) Source #

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Alt f a -> f0 (Alt f b) Source #

sequenceA :: Applicative f0 => Alt f (f0 a) -> f0 (Alt f a) Source #

mapM :: Monad m => (a -> m b) -> Alt f a -> m (Alt f b) Source #

sequence :: Monad m => Alt f (m a) -> m (Alt f a) Source #

Traversable f => Traversable (Rec1 f) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Rec1 f a -> f0 (Rec1 f b) Source #

sequenceA :: Applicative f0 => Rec1 f (f0 a) -> f0 (Rec1 f a) Source #

mapM :: Monad m => (a -> m b) -> Rec1 f a -> m (Rec1 f b) Source #

sequence :: Monad m => Rec1 f (m a) -> m (Rec1 f a) Source #

(Traversable f, Traversable g) => Traversable (Product f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

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 g) => Traversable (Sum f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Sum f g a -> f0 (Sum f g b) Source #

sequenceA :: Applicative f0 => Sum f g (f0 a) -> f0 (Sum f g a) Source #

mapM :: Monad m => (a -> m b) -> Sum f g a -> m (Sum f g b) Source #

sequence :: Monad m => Sum f g (m a) -> m (Sum f g a) Source #

(Traversable f, Traversable g) => Traversable (f :*: g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) Source #

sequenceA :: Applicative f0 => (f :*: g) (f0 a) -> f0 ((f :*: g) a) Source #

mapM :: Monad m => (a -> m b) -> (f :*: g) a -> m ((f :*: g) b) Source #

sequence :: Monad m => (f :*: g) (m a) -> m ((f :*: g) a) Source #

(Traversable f, Traversable g) => Traversable (f :+: g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) Source #

sequenceA :: Applicative f0 => (f :+: g) (f0 a) -> f0 ((f :+: g) a) Source #

mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) Source #

sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) Source #

Traversable (K1 i c :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> K1 i c a -> f (K1 i c b) Source #

sequenceA :: Applicative f => K1 i c (f a) -> f (K1 i c a) Source #

mapM :: Monad m => (a -> m b) -> K1 i c a -> m (K1 i c b) Source #

sequence :: Monad m => K1 i c (m a) -> m (K1 i c a) Source #

(Traversable f, Traversable g) => Traversable (Compose f g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

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 #

(Traversable f, Traversable g) => Traversable (f :.: g) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) Source #

sequenceA :: Applicative f0 => (f :.: g) (f0 a) -> f0 ((f :.: g) a) Source #

mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) Source #

sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) Source #

Traversable f => Traversable (M1 i c f) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> M1 i c f a -> f0 (M1 i c f b) Source #

sequenceA :: Applicative f0 => M1 i c f (f0 a) -> f0 (M1 i c f a) Source #

mapM :: Monad m => (a -> m b) -> M1 i c f a -> m (M1 i c f b) Source #

sequence :: Monad m => M1 i c f (m a) -> m (M1 i c f a) Source #

Utility functions

for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) Source #

for is traverse with its arguments flipped. For a version that ignores the results see for_.

forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) Source #

forM is mapM with its arguments flipped. For a version that ignores the results see forM_.

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

Expand

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

Expand

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 #

This function may be used as a value for foldMap in a Foldable instance.

foldMapDefault f ≡ getConst . traverse (Const . f)

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 = ...

Then traverse nameAndLineCount ["etcpasswd","etchosts"] could return

[("etcpasswd",56),("etchosts",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 unnecessary 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 with Maybe it is Nothing. With Either e a we have an empty case for each value of e.

  • If the base case is a singleton a, then traverse can take that a, apply f :: a -> F b getting an F b, then fmap singleton over that, getting F (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 . traverse f = traverse (t . f) for every applicative transformation 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 . sequenceA = sequenceA . fmap t for every applicative transformation t
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:

See also