Data.Traversable (original) (raw)

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](Control-Applicative.html#t:Applicative "Control.Applicative") (or, therefore, [Monad](Control-Monad.html#t:Monad "Control.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.

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_](Data-Foldable.html#v:traverse%5F "Data.Foldable").

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](Data-Maybe.html#v:Nothing "Data.Maybe") and [Left](Data-Either.html#v:Left "Data.Either") 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_](Data-Foldable.html#v:sequenceA%5F "Data.Foldable").

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](Data-Maybe.html#v:Nothing "Data.Maybe") and [Just](Data-Maybe.html#v:Just "Data.Maybe") will short circuit the resulting structure if present in the input. For more context, check the [Traversable](Data-Traversable.html#t:Traversable "Data.Traversable") instances for [Either](Data-Either.html#t:Either "Data.Either") and [Maybe](Data-Maybe.html#t:Maybe "Data.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_](Data-Foldable.html#v:mapM%5F "Data.Foldable").

Examples

Expand

[mapM](Data-Traversable.html#v:mapM "Data.Traversable") is literally a [traverse](Data-Traversable.html#v:traverse "Data.Traversable") with a type signature restricted to [Monad](Control-Monad.html#t:Monad "Control.Monad"). Its implementation may be more efficient due to additional power of [Monad](Control-Monad.html#t:Monad "Control.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_](Data-Foldable.html#v:sequence%5F "Data.Foldable").

Examples

Expand

Basic usage:

The first two examples are instances where the input and and output of [sequence](Data-Traversable.html#v:sequence "Data.Traversable") 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](Data-Traversable.html#v:sequence "Data.Traversable").

>>> **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 Complex Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Complex Methodstraverse :: 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 First Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Semigroup Methodstraverse :: 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 detailsDefined in Data.Semigroup Methodstraverse :: 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 detailsDefined in Data.Semigroup Methodstraverse :: 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 detailsDefined in Data.Semigroup Methodstraverse :: 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 NonEmpty Source # Since: base-4.9.0.0
Instance detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 Identity Source # Since: base-4.9.0.0
Instance detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 Dual Source # Since: base-4.8.0.0
Instance detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 ZipList Source # Since: base-4.9.0.0
Instance detailsDefined in GHC.Internal.Functor.ZipList Methodstraverse :: 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 Par1 Source # Since: base-4.9.0.0
Instance detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 TyVarBndr Source #
Instance detailsDefined in GHC.Internal.TH.Syntax Methodstraverse :: Applicative f => (a -> f b) -> TyVarBndr a -> f (TyVarBndr b) Source #sequenceA :: Applicative f => TyVarBndr (f a) -> f (TyVarBndr a) Source #mapM :: Monad m => (a -> m b) -> TyVarBndr a -> m (TyVarBndr b) Source #sequence :: Monad m => TyVarBndr (m a) -> m (TyVarBndr a) Source #
Traversable Maybe Source # Since: base-2.1
Instance detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 (Arg a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Semigroup Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 (Either a) Source # Since: base-4.7.0.0
Instance detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 (U1 :: Type -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in Data.Functor.Product Methodstraverse :: 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 detailsDefined in Data.Functor.Sum Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in Data.Functor.Compose Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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 detailsDefined in GHC.Internal.Data.Traversable Methodstraverse :: 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

mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) Source #

The [mapAccumL](Data-Traversable.html#v:mapAccumL "Data.Traversable") function behaves like a combination of [fmap](Control-Monad.html#v:fmap "Control.Monad") and [foldl](Data-Foldable.html#v:foldl "Data.Foldable"); 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 => (s -> a -> (s, b)) -> s -> t a -> (s, t b) Source #

The [mapAccumR](Data-Traversable.html#v:mapAccumR "Data.Traversable") function behaves like a combination of [fmap](Control-Monad.html#v:fmap "Control.Monad") and [foldr](Data-Foldable.html#v:foldr "Data.Foldable"); 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"])

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

The [mapAccumM](Data-Traversable.html#v:mapAccumM "Data.Traversable") function behaves like a combination of [mapM](Data-Traversable.html#v:mapM "Data.Traversable") and[mapAccumL](Data-Traversable.html#v:mapAccumL "Data.Traversable") 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

Expand

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 methodsOverview

Traversable structures support element-wise sequencing of Applicative effects (thus also Monad effects) to construct new structures ofthe same shape as the input.

To illustrate what is meant by same shape, if the input structure is**[a]**, each output structure is a list [b] of the same length as the input. If the input is a Tree a, each output Tree b has the same graph of intermediate nodes and leaves. Similarly, if the input is a 2-tuple (x, a), each output is a 2-tuple (x, b), and so forth.

It is in fact possible to decompose a traversable structure t a into its shape (a.k.a. spine) of type t () and its element list**[a]**. The original structure can be faithfully reconstructed from its spine and element list.

The implementation of a Traversable instance for a given structure follows naturally from its type; see the Construction section for details. Instances must satisfy the laws listed in the Laws section. The diverse uses of Traversable structures result from the many possible choices of Applicative effects. See the Advanced Traversals section for some examples.

Every Traversable structure is both a Functor and Foldable because it is possible to implement the requisite instances in terms of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") by using [fmapDefault](Data-Traversable.html#v:fmapDefault "Data.Traversable") for fmap and [foldMapDefault](Data-Traversable.html#v:foldMapDefault "Data.Traversable") for foldMap. Direct fine-tuned implementations of these superclass methods can in some cases be more efficient.

The traverse and mapM methods

For an Applicative functor f and a Traversable functor t, the type signatures of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") and fmap are rather similar:

fmap :: (a -> f b) -> t a -> t (f b) traverse :: (a -> f b) -> t a -> f (t b)

The key difference is that fmap produces a structure whose elements (of type f b) are individual effects, while [traverse](Data-Traversable.html#v:traverse "Data.Traversable") produces an aggregate effect yielding structures of type t b.

For example, when f is the IO monad, and t is List,fmap yields a list of IO actions, whereas [traverse](Data-Traversable.html#v:traverse "Data.Traversable") constructs an IO action that evaluates to a list of the return values of the individual actions performed left-to-right.

traverse :: (a -> IO b) -> [a] -> IO [b]

The [mapM](Data-Traversable.html#v:mapM "Data.Traversable") function is a specialisation of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") to the case when**f** is a Monad. For monads, [mapM](Data-Traversable.html#v:mapM "Data.Traversable") is more idiomatic than [traverse](Data-Traversable.html#v:traverse "Data.Traversable"). The two are otherwise generally identical (though [mapM](Data-Traversable.html#v:mapM "Data.Traversable") may be specifically optimised for monads, and could be more efficient than using the more general [traverse](Data-Traversable.html#v:traverse "Data.Traversable")).

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)

When the traversable term is a simple variable or expression, and the monadic action to run is a non-trivial do block, it can be more natural to write the action last. This idiom is supported by [for](Data-Traversable.html#v:for "Data.Traversable"), [forM](Data-Traversable.html#v:forM "Data.Traversable"), and[forAccumM](Data-Traversable.html#v:forAccumM "Data.Traversable") which are the flipped versions of [traverse](Data-Traversable.html#v:traverse "Data.Traversable"), [mapM](Data-Traversable.html#v:mapM "Data.Traversable"), and[mapAccumM](Data-Traversable.html#v:mapAccumM "Data.Traversable") respectively.

Their Foldable, just the effects, analogues.

The [traverse](Data-Traversable.html#v:traverse "Data.Traversable") and [mapM](Data-Traversable.html#v:mapM "Data.Traversable") methods have analogues in the Data.Foldable module. These are traverse_ and mapM_, and their flipped variantsfor_ and forM_, respectively. The result type is f (), they don't return an updated structure, and can be used to sequence effects over all the elements of a Traversable (any Foldable) structure just for their side-effects.

If the Traversable structure is empty, the result is pure (). When effects short-circuit, the f () result may, for example, be Nothing if f is Maybe, or `Left` e when it is `Either` e.

It is perhaps worth noting that Maybe is not only a potentialApplicative functor for the return value of the first argument of[traverse](Data-Traversable.html#v:traverse "Data.Traversable"), but is also itself a [Traversable](Data-Traversable.html#t:Traversable "Data.Traversable") structure with either zero or one element. A convenient idiom for conditionally executing an action just for its effects on a Just value, and doing nothing otherwise is:

-- action :: Monad m => a -> m () -- mvalue :: Maybe a mapM_ action mvalue -- :: m ()

which is more concise than:

maybe (return ()) action mvalue

The mapM_ idiom 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 Left case).

Result multiplicity

When [traverse](Data-Traversable.html#v:traverse "Data.Traversable") or [mapM](Data-Traversable.html#v:mapM "Data.Traversable") is applied to an empty structure ts (one for which `null` ts is True) the return value is pure ts regardless of the provided function g :: a -> f b. It is not possible to apply the function when no values of type a are available, but its type determines the relevant instance of pure.

null ts ==> traverse g ts == pure ts

Otherwise, when ts is non-empty and at least one value of type b results from each f a, the structures t b have the same shape (list length, graph of tree nodes, ...) as the input structure t a, but the slots previously occupied by elements of type a now hold elements of type b.

A single traversal may produce one, zero or many such structures. The zero case happens when one of the effects f a sequenced as part of the traversal yields no replacement values. Otherwise, the many case happens when one of sequenced effects yields multiple values.

The [traverse](Data-Traversable.html#v:traverse "Data.Traversable") function does not perform selective filtering of slots in the output structure as with e.g. [mapMaybe](Data-Maybe.html#v:mapMaybe "Data.Maybe").

>>> let incOdd n = if odd n then Just $ n + 1 else Nothing** **>>> mapMaybe incOdd [1, 2, 3]** **[2,4] >>> **traverse incOdd [1, 3, 5]** ****Just [2,4,6] >>> **traverse incOdd [1, 2, 3]** ****Nothing

In the above examples, with Maybe as the Applicative f, we see that the number of t b structures produced by [traverse](Data-Traversable.html#v:traverse "Data.Traversable") may differ from one: it is zero when the result short-circuits to Nothing. The same can happen when f is List and the result is [], or**f** is Either e and the result is Left (x :: e), or perhaps the [empty](Control-Applicative.html#v:empty "Control.Applicative") value of some[Alternative](Control-Applicative.html#v:Alternative "Control.Applicative") functor.

When f is e.g. List, and the map g :: a -> [b] returns more than one value for some inputs a (and at least one for all**a**), the result of mapM g ts will contain multiple structures of the same shape as ts:

List.length (mapM g ts) == List.product (fmap (List.length . g) ts)

For example:

>>> **List.length $ mapM (\n -> [1..n]) [1..6]** ****720 >>> **List.product $ List.length . (\n -> [1..n]) <$> [1..6]** ****720

In other words, a traversal with a function g :: a -> [b], over an input structure t a, yields a list [t b], whose length is the product of the lengths of the lists that g returns for each element of the input structure! The individual elements a of the structure are replaced by each element of g a in turn:

>>> mapM (\n -> [1..n]) $ Just 3** **[Just 1,Just 2,Just 3] >>> mapM (\n -> [1..n]) [1..3]** **[[1,1,1],[1,1,2],[1,1,3],[1,2,1],[1,2,2],[1,2,3]]

If any element of the structure t a is mapped by g to an empty list, then the entire aggregate result is empty, because no value is available to fill one of the slots of the output structure:

>>> mapM (\n -> [1..n]) $ [0..6] -- [1..0] is empty** **[]

The sequenceA and sequence methods

The [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable") and [sequence](Data-Traversable.html#v:sequence "Data.Traversable") methods are useful when what you have is a container of pending applicative or monadic effects, and you want to combine them into a single effect that produces zero or more containers with 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 -- default definition sequence = sequenceA -- default definition

When the monad m is [IO](System-IO.html#v:IO "System.IO"), applying [sequence](Data-Traversable.html#v:sequence "Data.Traversable") 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] -- In this case [(), ()]

For [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable"), 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]]

Because the input list has three (sublist) elements, the result is a list of triples (same shape).

Care with default method implementations

The [traverse](Data-Traversable.html#v:traverse "Data.Traversable") method has a default implementation in terms of [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable"):

traverse g = sequenceA . fmap g

but relying on this default implementation is not recommended, it requires that the structure is already independently a Functor. The definition of[sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable") in terms of traverse id is much simpler than [traverse](Data-Traversable.html#v:traverse "Data.Traversable") expressed via a composition of [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable") and fmap. Instances should generally implement [traverse](Data-Traversable.html#v:traverse "Data.Traversable") explicitly. It may in some cases also make sense to implement a specialised [mapM](Data-Traversable.html#v:mapM "Data.Traversable").

Because [fmapDefault](Data-Traversable.html#v:fmapDefault "Data.Traversable") is defined in terms of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") (whose default definition in terms of [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable") uses fmap), you must not use[fmapDefault](Data-Traversable.html#v:fmapDefault "Data.Traversable") to define the Functor instance if the Traversable instance directly defines only [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable").

Monadic short circuits

When the monad m is Either or Maybe (more generally any[MonadPlus](Control-Monad.html#v:MonadPlus "Control.Monad")), the effect in question is to short-circuit the result on encountering Left or Nothing (more generally[mzero](Control-Monad.html#v:mzero "Control.Monad")).

>>> **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](Data-Traversable.html#v:sequence "Data.Traversable") is all-or-nothing, either structures of exactly the same shape as the input or none at all. The [sequence](Data-Traversable.html#v:sequence "Data.Traversable") function does not perform selective filtering as with e.g. [catMaybes](Data-Maybe.html#v:catMaybes "Data.Maybe") or[rights](Data-Either.html#v:rights "Data.Either"):

>>> catMaybes [Just 1,Nothing,Just 3]** **[1,3] >>> rights [Right 1,Left "sorry",Right 3]** **[1,3]

Example binary tree instance

The definition of a [Traversable](Data-Traversable.html#t:Traversable "Data.Traversable") instance for a binary tree is rather similar to the corresponding instance of Functor, given the data type:

data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)

a canonical Functor instance would be

instance Functor Tree where fmap g Empty = Empty fmap g (Leaf x) = Leaf (g x) fmap g (Node l k r) = Node (fmap g l) (g k) (fmap g r)

a canonical Traversable instance would be

instance Traversable Tree where traverse g Empty = pure Empty traverse g (Leaf x) = Leaf <$> g x traverse g (Node l k r) = Node <$> traverse g l <*> g k <*> traverse g r

This definition works for any g :: a -> f b, with f an Applicative functor, as the laws for (`<*>`) imply the requisite associativity.

We can add an explicit non-default [mapM](Data-Traversable.html#v:mapM "Data.Traversable") if desired:

mapM g Empty = return Empty mapM g (Leaf x) = Leaf <$> g x mapM g (Node l k r) = do ml <- mapM g l mk <- g k mr <- mapM g r return $ Node ml mk mr

See Construction below for a more detailed exploration of the general case, but as mentioned in Overview above, instance definitions are typically rather simple, all the interesting behaviour is a result of an interesting choice of Applicative functor for a traversal.

Pre-order and post-order tree traversal

It is perhaps worth noting that the traversal defined above gives an_in-order_ sequencing of the elements. If instead you want either_pre-order_ (parent first, then child nodes) or post-order (child nodes first, then parent) sequencing, you can define the instance accordingly:

inOrderNode :: Tree a -> a -> Tree a -> Tree a inOrderNode l x r = Node l x r

preOrderNode :: a -> Tree a -> Tree a -> Tree a preOrderNode x l r = Node l x r

postOrderNode :: Tree a -> Tree a -> a -> Tree a postOrderNode l r x = Node l x r

-- Traversable instance with in-order traversal instance Traversable Tree where traverse g t = case t of Empty -> pure Empty Leaf x -> Leaf <$> g x Node l x r -> inOrderNode <$> traverse g l <*> g x <*> traverse g r

-- Traversable instance with pre-order traversal instance Traversable Tree where traverse g t = case t of Empty -> pure Empty Leaf x -> Leaf <$> g x Node l x r -> preOrderNode <$> g x <*> traverse g l <*> traverse g r

-- Traversable instance with post-order traversal instance Traversable Tree where traverse g t = case t of Empty -> pure Empty Leaf x -> Leaf <$> g x Node l x r -> postOrderNode <$> traverse g l <*> traverse g r <*> g x

Since the same underlying Tree structure is used in all three cases, it is possible to use newtype wrappers to make all three available at the same time! The user need only wrap the root of the tree in the appropriatenewtype for the desired traversal order. Tne associated instance definitions are shown below (see coercion if unfamiliar with the use of coerce in the sample code):

{-# LANGUAGE ScopedTypeVariables, TypeApplications #-}

-- Default in-order traversal

import Data.Coerce (coerce) import Data.Traversable

data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) instance Functor Tree where fmap = fmapDefault instance Foldable Tree where foldMap = foldMapDefault

instance Traversable Tree where traverse _ Empty = pure Empty traverse g (Leaf a) = Leaf <$> g a traverse g (Node l a r) = Node <$> traverse g l <*> g a <*> traverse g r

-- Optional pre-order traversal

newtype PreOrderTree a = PreOrderTree (Tree a) instance Functor PreOrderTree where fmap = fmapDefault instance Foldable PreOrderTree where foldMap = foldMapDefault

instance Traversable PreOrderTree where traverse _ (PreOrderTree Empty) = pure $ preOrderEmpty traverse g (PreOrderTree (Leaf x)) = preOrderLeaf <$> g x traverse g (PreOrderTree (Node l x r)) = preOrderNode <$> g x <*> traverse g (coerce l) <*> traverse g (coerce r)

preOrderEmpty :: forall a. PreOrderTree a preOrderEmpty = coerce (Empty @a) preOrderLeaf :: forall a. a -> PreOrderTree a preOrderLeaf = coerce (Leaf @a) preOrderNode :: a -> PreOrderTree a -> PreOrderTree a -> PreOrderTree a preOrderNode x l r = coerce (Node (coerce l) x (coerce r))

-- Optional post-order traversal

newtype PostOrderTree a = PostOrderTree (Tree a) instance Functor PostOrderTree where fmap = fmapDefault instance Foldable PostOrderTree where foldMap = foldMapDefault

instance Traversable PostOrderTree where traverse _ (PostOrderTree Empty) = pure postOrderEmpty traverse g (PostOrderTree (Leaf x)) = postOrderLeaf <$> g x traverse g (PostOrderTree (Node l x r)) = postOrderNode <$> traverse g (coerce l) <*> traverse g (coerce r) <*> g x

postOrderEmpty :: forall a. PostOrderTree a postOrderEmpty = coerce (Empty @a) postOrderLeaf :: forall a. a -> PostOrderTree a postOrderLeaf = coerce (Leaf @a) postOrderNode :: PostOrderTree a -> PostOrderTree a -> a -> PostOrderTree a postOrderNode l r x = coerce (Node (coerce l) x (coerce r))

With the above, given a sample tree:

inOrder :: Tree Int inOrder = Node (Node (Leaf 10) 3 (Leaf 20)) 5 (Leaf 42)

we have:

import Data.Foldable (toList) print $ toList inOrder [10,3,20,5,42]

print $ toList (coerce inOrder :: PreOrderTree Int) [5,3,10,20,42]

print $ toList (coerce inOrder :: PostOrderTree Int) [10,20,3,42,5]

You would typically define instances for additional common type classes, such as Eq, Ord, Show, etc.

Making construction intuitive

In order to be able to reason about how a given type of Applicative effects will be sequenced through a general [Traversable](Data-Traversable.html#t:Traversable "Data.Traversable") structure by itstraversable and related methods, it is helpful to look more closely at how a general [traverse](Data-Traversable.html#v:traverse "Data.Traversable") method is implemented. We'll look at how general traversals are constructed primarily with a view to being able to predict their behaviour as a user, even if you're not defining your own [Traversable](Data-Traversable.html#t:Traversable "Data.Traversable") instances.

Traversable structures t a are assembled incrementally from their constituent parts, perhaps by prepending or appending individual elements of type a, or, more generally, by recursively combining smaller composite traversable building blocks that contain multiple such elements.

As in the tree example above, the components being combined are typically pieced together by a suitable constructor, i.e. a function taking two or more arguments that returns a composite value.

The [traverse](Data-Traversable.html#v:traverse "Data.Traversable") method enriches simple incremental construction with threading of Applicative effects of some function g :: a -> f b.

The basic building blocks we'll use to model the construction of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") are a hypothetical set of elementary functions, some of which may have direct analogues in specific Traversable structures. For example, the**(`:`)** constructor is an analogue for lists of prepend or the more general combine.

empty :: t a -- build an empty container singleton :: a -> t a -- build a one-element container prepend :: a -> t a -> t a -- extend by prepending a new initial element append :: t a -> a -> t a -- extend by appending a new final element combine :: a1 -> a2 -> ... -> an -> t a -- combine multiple inputs

traverse g (append t0 a) = append <$> traverse g t0 <*> g a
= liftA2 append (traverse g t0) (g a)
The origin of the combinatorial product when f is List should now be apparent, when traverse g t0 has n elements and **g a**has m elements, the non-deterministic Applicative instance ofList will produce a result with m * n elements.

The above definitions sequence the Applicative effects of f in the expected order while producing results of the expected shape t.

For lists this becomes:

traverse g [] = pure [] traverse g (x:xs) = liftA2 (:) (g a) (traverse g xs)

The actual definition of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") for lists is an equivalent right fold in order to facilitate list fusion.

traverse g = foldr (\x r -> liftA2 (:) (g x) r) (pure [])

Advanced traversals

In the sections below we'll examine some advanced choices of Applicative effects that give rise to very different transformations of Traversable structures.

These examples cover the implementations of [fmapDefault](Data-Traversable.html#v:fmapDefault "Data.Traversable"), [foldMapDefault](Data-Traversable.html#v:foldMapDefault "Data.Traversable"),[mapAccumL](Data-Traversable.html#v:mapAccumL "Data.Traversable") and [mapAccumR](Data-Traversable.html#v:mapAccumR "Data.Traversable") functions illustrating the use of Identity,Const and stateful Applicative effects. The ZipList example illustrates the use of a less-well known Applicative instance for lists.

This is optional material, which is not essential to a basic understanding ofTraversable structures. If this is your first encounter with Traversable structures, you can come back to these at a later date.

Coercion

Some of the examples make use of an advanced Haskell feature, namelynewtype coercion. This is done for two reasons:

If you're not familiar with coerce, don't worry, it is just a shorthand that, e.g., given:

newtype Foo a = MkFoo { getFoo :: a } newtype Bar a = MkBar { getBar :: a } newtype Baz a = MkBaz { getBaz :: a } f :: Baz Int -> Bar (Foo String)

makes it possible to write:

x :: Int -> String x = coerce f

instead of

x = getFoo . getBar . f . MkBaz

Identity: the fmapDefault function

The simplest Applicative functor is Identity, which just wraps and unwraps pure values and function application. This allows us to define[fmapDefault](Data-Traversable.html#v:fmapDefault "Data.Traversable"):

{-# LANGUAGE ScopedTypeVariables, TypeApplications #-} import Data.Coercible (coerce)

fmapDefault :: forall t a b. Traversable t => (a -> b) -> t a -> t b fmapDefault = coerce (traverse @t @Identity @a @b)

The use of coercion avoids the need to explicitly wrap and unwrap terms via Identity and runIdentity.

As noted in Overview, [fmapDefault](Data-Traversable.html#v:fmapDefault "Data.Traversable") can only be used to define the requisite Functor instance of a [Traversable](Data-Traversable.html#t:Traversable "Data.Traversable") structure when the[traverse](Data-Traversable.html#v:traverse "Data.Traversable") method is explicitly implemented. An infinite loop would result if in addition [traverse](Data-Traversable.html#v:traverse "Data.Traversable") were defined in terms of [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable") and fmap.

State: the mapAccumL, mapAccumR functions

Applicative functors that thread a changing state through a computation are an interesting use-case for [traverse](Data-Traversable.html#v:traverse "Data.Traversable"). The [mapAccumL](Data-Traversable.html#v:mapAccumL "Data.Traversable") and [mapAccumR](Data-Traversable.html#v:mapAccumR "Data.Traversable") functions in this module are each defined in terms of such traversals.

We first define a simplified (not a monad transformer) version of[State](Control-Monad-Trans-State.html#v:State "Control.Monad.Trans.State") that threads a state s through a chain of computations left to right. Its (`<*>`) operator passes the input state first to its left argument, and then the resulting state is passed to its right argument, which returns the final state.

newtype StateL s a = StateL { runStateL :: s -> (s, a) }

instance Functor (StateL s) where fmap f (StateL kx) = StateL $ \ s -> let (s', x) = kx s in (s', f x)

instance Applicative (StateL s) where pure a = StateL $ \s -> (s, a) (StateL kf) <*> (StateL kx) = StateL $ \ s -> let { (s', f) = kf s ; (s'', x) = kx s' } in (s'', f x) liftA2 f (StateL kx) (StateL ky) = StateL $ \ s -> let { (s', x) = kx s ; (s'', y) = ky s' } in (s'', f x y)

With StateL, we can define [mapAccumL](Data-Traversable.html#v:mapAccumL "Data.Traversable") as follows:

{-# LANGUAGE ScopedTypeVariables, TypeApplications #-} mapAccumL :: forall t s a b. Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) mapAccumL g s ts = coerce (traverse @t @(StateL s) @a @b) (flip g) ts s

The use of coercion avoids the need to explicitly wrap and unwrap newtype terms.

The type of flip g is coercible to a -> StateL b, which makes it suitable for use with [traverse](Data-Traversable.html#v:traverse "Data.Traversable"). As part of the Applicativeconstruction of StateL (t b) the state updates will thread left-to-right along the sequence of elements of t a.

While [mapAccumR](Data-Traversable.html#v:mapAccumR "Data.Traversable") has a type signature identical to [mapAccumL](Data-Traversable.html#v:mapAccumL "Data.Traversable"), it differs in the expected order of evaluation of effects, which must take place right-to-left.

For this we need a variant control structure StateR, which threads the state right-to-left, by passing the input state to its right argument and then using the resulting state as an input to its left argument:

newtype StateR s a = StateR { runStateR :: s -> (s, a) }

instance Functor (StateR s) where fmap f (StateR kx) = StateR $ \s -> let (s', x) = kx s in (s', f x)

instance Applicative (StateR s) where pure a = StateR $ \s -> (s, a) (StateR kf) <*> (StateR kx) = StateR $ \ s -> let { (s', x) = kx s ; (s'', f) = kf s' } in (s'', f x) liftA2 f (StateR kx) (StateR ky) = StateR $ \ s -> let { (s', y) = ky s ; (s'', x) = kx s' } in (s'', f x y)

With StateR, we can define [mapAccumR](Data-Traversable.html#v:mapAccumR "Data.Traversable") as follows:

{-# LANGUAGE ScopedTypeVariables, TypeApplications #-} mapAccumR :: forall t s a b. Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) mapAccumR g s0 ts = coerce (traverse @t @(StateR s) @a @b) (flip g) ts s0

The use of coercion avoids the need to explicitly wrap and unwrap newtype terms.

Various stateful traversals can be constructed from [mapAccumL](Data-Traversable.html#v:mapAccumL "Data.Traversable") and[mapAccumR](Data-Traversable.html#v:mapAccumR "Data.Traversable") for suitable choices of g, or built directly along similar lines.

Const: the foldMapDefault function

The Const Functor enables applications of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") that summarise the input structure to an output value without constructing any output values of the same type or shape.

As noted above, the Foldable superclass constraint is justified by the fact that it is possible to construct foldMap, foldr, etc., from [traverse](Data-Traversable.html#v:traverse "Data.Traversable"). The technique used is useful in its own right, and is explored below.

A key feature of folds is that they can reduce the input structure to a summary value. Often neither the input structure nor a mutated clone is needed once the fold is computed, and through list fusion the input may not even have been memory resident in its entirety at the same time.

The [traverse](Data-Traversable.html#v:traverse "Data.Traversable") method does not at first seem to be a suitable building block for folds, because its return value f (t b) appears to retain mutated copies of the input structure. But the presence of t b in the type signature need not mean that terms of type t b are actually embedded in f (t b). The simplest way to elide the excess terms is by basing the Applicative functor used with [traverse](Data-Traversable.html#v:traverse "Data.Traversable") on Const.

Not only does Const a b hold just an a value, with the b parameter merely a phantom type, but when m has a Monoid instance,Const m is an Applicative functor:

import Data.Coerce (coerce) newtype Const a b = Const { getConst :: a } deriving (Eq, Ord, Show) -- etc. instance Functor (Const m) where fmap = const coerce instance Monoid m => Applicative (Const m) where pure _ = Const mempty (<*>) = coerce (mappend :: m -> m -> m) liftA2 _ = coerce (mappend :: m -> m -> m)

The use of coercion avoids the need to explicitly wrap and unwrap newtype terms.

We can therefore define a specialisation of [traverse](Data-Traversable.html#v:traverse "Data.Traversable"):

{-# LANGUAGE ScopedTypeVariables, TypeApplications #-} traverseC :: forall t a m. (Monoid m, Traversable t) => (a -> Const m ()) -> t a -> Const m (t ()) traverseC = traverse @t @(Const m) @a @()

For which the Applicative construction of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") leads to:

null ts ==> traverseC g ts = Const mempty

traverseC g (prepend x xs) = Const (g x) <> traverseC g xs

In other words, this makes it possible to define:

{-# LANGUAGE ScopedTypeVariables, TypeApplications #-} foldMapDefault :: forall t a m. (Monoid m, Traversable t) => (a -> m) -> t a -> m foldMapDefault = coerce (traverse @t @(Const m) @a @())

Which is sufficient to define a Foldable superclass instance:

The use of coercion avoids the need to explicitly wrap and unwrap newtype terms.

instance Traversable t => Foldable t where foldMap = foldMapDefault

It may however be instructive to also directly define candidate default implementations of foldr and foldl', which take a bit more machinery to construct:

{-# LANGUAGE ScopedTypeVariables, TypeApplications #-} import Data.Coerce (coerce) import Data.Functor.Const (Const(..)) import Data.Semigroup (Dual(..), Endo(..)) import GHC.Exts (oneShot)

foldrDefault :: forall t a b. Traversable t => (a -> b -> b) -> b -> t a -> b foldrDefault f z = \t -> coerce (traverse @t @(Const (Endo b)) @a @()) f t z

foldlDefault' :: forall t a b. Traversable t => (b -> a -> b) -> b -> t a -> b foldlDefault' f z = \t -> coerce (traverse @t @(Const (Dual (Endo b))) @a @()) f' t z where f' :: a -> b -> b f' a = oneShot $ \ b -> b seq f b a

In the above we're using the `[Endo](Data-Monoid.html#v:Endo "Data.Monoid")` b Monoid and itsDual to compose a sequence of b -> b accumulator updates in either left-to-right or right-to-left order.

The use of seq in the definition of foldlDefault' ensures strictness in the accumulator.

The use of coercion avoids the need to explicitly wrap and unwrap newtype terms.

The [oneShot](GHC-Exts.html#v:oneShot "GHC.Exts") function gives a hint to the compiler that aids in correct optimisation of lambda terms that fire at most once (for each element a) and so should not try to pre-compute and re-use subexpressions that pay off only on repeated execution. Otherwise, it is just the identity function.

ZipList: transposing lists of lists

As a warm-up for looking at the ZipList Applicative functor, we'll first look at a simpler analogue. First define a fixed width 2-element Vec2 type, whose Applicative instance combines a pair of functions with a pair of values by applying each function to the corresponding value slot:

data Vec2 a = Vec2 a a instance Functor Vec2 where fmap f (Vec2 a b) = Vec2 (f a) (f b) instance Applicative Vec2 where pure x = Vec2 x x liftA2 f (Vec2 a b) (Vec2 p q) = Vec2 (f a p) (f b q) instance Foldable Vec2 where foldr f z (Vec2 a b) = f a (f b z) foldMap f (Vec2 a b) = f a <> f b instance Traversable Vec2 where traverse f (Vec2 a b) = Vec2 <$> f a <*> f b

Along with a similar definition for fixed width 3-element vectors:

data Vec3 a = Vec3 a a a instance Functor Vec3 where fmap f (Vec3 x y z) = Vec3 (f x) (f y) (f z) instance Applicative Vec3 where pure x = Vec3 x x x liftA2 f (Vec3 p q r) (Vec3 x y z) = Vec3 (f p x) (f q y) (f r z) instance Foldable Vec3 where foldr f z (Vec3 a b c) = f a (f b (f c z)) foldMap f (Vec3 a b c) = f a <> f b <> f c instance Traversable Vec3 where traverse f (Vec3 a b c) = Vec3 <$> f a <*> f b <*> f c

With the above definitions, `[sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable")` (same as `[traverse](Data-Traversable.html#v:traverse "Data.Traversable")` `id`) acts as a matrix transpose operation on Vec2 (Vec3 Int) producing a corresponding Vec3 (Vec2 Int):

Let t = Vec2 (Vec3 1 2 3) (Vec3 4 5 6) be our [Traversable](Data-Traversable.html#t:Traversable "Data.Traversable") structure, and g = id :: Vec3 Int -> Vec3 Int be the function used to traverse**t**. We then have:

traverse g t = Vec2 <$> (Vec3 1 2 3) <*> (Vec3 4 5 6) = Vec3 (Vec2 1 4) (Vec2 2 5) (Vec2 3 6)

This construction can be generalised from fixed width vectors to variable length lists via [ZipList](Control-Applicative.html#v:ZipList "Control.Applicative"). This gives a transpose operation that works well for lists of equal length. If some of the lists are longer than others, they're truncated to the longest common length.

We've already looked at the standard Applicative instance of List for which applying m functions f1, f2, ..., fm to n input values a1, a2, ..., an produces m * n outputs:

>>> :set -XTupleSections** **>>> [("f1",), ("f2",), ("f3",)] <*> [1,2]** **[("f1",1),("f1",2),("f2",1),("f2",2),("f3",1),("f3",2)]

There are however two more common ways to turn lists into Applicative control structures. The first is via `Const` [a], since lists are monoids under concatenation, and we've already seen that `Const` m is an Applicative functor when m is a Monoid. The second, is based on [zipWith](Data-List.html#v:zipWith "Data.List"), and is called [ZipList](Control-Applicative.html#v:ZipList "Control.Applicative"):

{-# LANGUAGE GeneralizedNewtypeDeriving #-} newtype ZipList a = ZipList { getZipList :: [a] } deriving (Show, Eq, ..., Functor)

instance Applicative ZipList where liftA2 f (ZipList xs) (ZipList ys) = ZipList $ zipWith f xs ys pure x = repeat x

The liftA2 definition is clear enough, instead of applying f to each pair (x, y) drawn independently from the xs and ys, only corresponding pairs at each index in the two lists are used.

The definition of pure may look surprising, but it is needed to ensure that the instance is lawful:

liftA2 f (pure x) ys == fmap (f x) ys

Since ys can have any length, we need to provide an infinite supply of x values in pure x in order to have a value to pair with each element y.

When [ZipList](Control-Applicative.html#v:ZipList "Control.Applicative") is the Applicative functor used in theconstruction of a traversal, a ZipList holding a partially built structure with m elements is combined with a component holding**n** elements via zipWith, resulting in min m n outputs!

Therefore [traverse](Data-Traversable.html#v:traverse "Data.Traversable") with g :: a -> ZipList b will produce a ZipList of t b structures whose element count is the minimum length of the ZipLists g a with a ranging over the elements of t. When**t** is empty, the length is infinite (as expected for a minimum of an empty set).

If the structure t holds values of type ZipList a, we can use the identity function id :: ZipList a -> ZipList a for the first argument of [traverse](Data-Traversable.html#v:traverse "Data.Traversable"):

traverse (id :: ZipList a -> ZipList a) :: t (ZipList a) -> ZipList (t a)

The number of elements in the output ZipList will be the length of the shortest ZipList element of t. Each output t a will have the_same shape_ as the input t (ZipList a), i.e. will share its number of elements.

If we think of the elements of t (ZipList a) as its rows, and the elements of each individual ZipList as the columns of that row, we see that our traversal implements a transpose operation swapping the rows and columns of t, after first truncating all the rows to the column count of the shortest one.

Since in fact `[traverse](Data-Traversable.html#v:traverse "Data.Traversable")` id is just [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable") the above boils down to a rather concise definition of transpose, with coercion used to implicitly wrap and unwrap the ZipList newtype as needed, giving a function that operates on a list of lists:

>>> :set -XScopedTypeVariables** **>>> import Control.Applicative (ZipList(..))** **>>> import Data.Coerce (coerce)** **>>> ** **>>> :{** **>>> let** **>>> transpose :: forall a. [[a]] -> [[a]]** **>>> transpose = coerce (sequenceA :: [ZipList a] -> ZipList [a])** **>>> in transpose [[1,2,3],[4..],[7..]]** **>>> :}** **[[1,4,7],[2,5,8],[3,6,9]]

The use of coercion avoids the need to explicitly wrap and unwrap ZipList terms.

Laws

A definition of [traverse](Data-Traversable.html#v:traverse "Data.Traversable") must satisfy the following laws:

Naturality

t . `[traverse](Data-Traversable.html#v:traverse "Data.Traversable")` f = `[traverse](Data-Traversable.html#v:traverse "Data.Traversable")` (t . f) for every applicative transformation t

Identity

`[traverse](Data-Traversable.html#v:traverse "Data.Traversable")` `Identity` = `Identity`

Composition

`[traverse](Data-Traversable.html#v:traverse "Data.Traversable")` (`[Compose](Data-Functor-Compose.html#v:Compose "Data.Functor.Compose")` . `fmap` g . f) = `[Compose](Data-Functor-Compose.html#v:Compose "Data.Functor.Compose")` . `fmap` (`[traverse](Data-Traversable.html#v:traverse "Data.Traversable")` g) . `[traverse](Data-Traversable.html#v:traverse "Data.Traversable")` f

A definition of [sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable") must satisfy the following laws:

Naturality

t . `[sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable")` = `[sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable")` . `fmap` t for every applicative transformation t

Identity

`[sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable")` . `fmap` `Identity` = `Identity`

Composition

`[sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable")` . `fmap` `[Compose](Data-Functor-Compose.html#v:Compose "Data.Functor.Compose")` = `[Compose](Data-Functor-Compose.html#v:Compose "Data.Functor.Compose")` . `fmap` `[sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable")` . `[sequenceA](Data-Traversable.html#v:sequenceA "Data.Traversable")`

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](Data-Functor-Compose.html#v:Compose "Data.Functor.Compose") are from Data.Functor.Identity andData.Functor.Compose.

A result of the naturality law is a purity law for [traverse](Data-Traversable.html#v:traverse "Data.Traversable")

[traverse](Data-Traversable.html#v:traverse "Data.Traversable") pure = pure

The superclass instances should satisfy the following:

Note: the Functor superclass means that (in GHC) Traversable structures cannot impose any constraints on the element type. A Haskell implementation that supports constrained functors could make it possible to define constrained Traversable structures.

See also