Safe Haskell | None |
---|---|
Language | Haskell2010 |
Prologue.Data.Traversable
Synopsis
- type family Traversables (lst :: [Type -> Type]) :: Constraint where ...
- sequence :: (Traversable t, Applicative f) => t (f a) -> f (t a)
- bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
- mapM2 :: (Monad m, Traversables '[t1, t2]) => (a -> m b) -> t2 (t1 a) -> m (t2 (t1 b))
- mapM3 :: (Monad m, Traversables '[t1, t2, t3]) => (a -> m b) -> t3 (t2 (t1 a)) -> m (t3 (t2 (t1 b)))
- mapM4 :: (Monad m, Traversables '[t1, t2, t3, t4]) => (a -> m b) -> t4 (t3 (t2 (t1 a))) -> m (t4 (t3 (t2 (t1 b))))
- mapM5 :: (Monad m, Traversables '[t1, t2, t3, t4, t5]) => (a -> m b) -> t5 (t4 (t3 (t2 (t1 a)))) -> m (t5 (t4 (t3 (t2 (t1 b)))))
- (<$>=) :: (Monad m, Traversable t1) => (a -> m b) -> t1 a -> m (t1 b)
- (<<$>>=) :: (Monad m, Traversables '[t1, t2]) => (a -> m b) -> t2 (t1 a) -> m (t2 (t1 b))
- (<<<$>>>=) :: (Monad m, Traversables '[t1, t2, t3]) => (a -> m b) -> t3 (t2 (t1 a)) -> m (t3 (t2 (t1 b)))
- (<<<<$>>>>=) :: (Monad m, Traversables '[t1, t2, t3, t4]) => (a -> m b) -> t4 (t3 (t2 (t1 a))) -> m (t4 (t3 (t2 (t1 b))))
- (<<<<<$>>>>>=) :: (Monad m, Traversables '[t1, t2, t3, t4, t5]) => (a -> m b) -> t5 (t4 (t3 (t2 (t1 a)))) -> m (t5 (t4 (t3 (t2 (t1 b)))))
- (<|$>=) :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t (a, b))
- (<$|>=) :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t (b, a))
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
- bimapM :: (Bitraversable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
- class (Bifunctor t, Bifoldable t) => Bitraversable (t :: Type -> Type -> Type) where
- bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
- for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
Documentation
type family Traversables (lst :: [Type -> Type]) :: Constraint where ... Source #
Equations
Traversables '[] = () | |
Traversables (t ': ts) = (Traversable t, Traversables ts) |
sequence :: (Traversable t, Applicative f) => t (f a) -> f (t a) Source #
bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) Source #
mapM2 :: (Monad m, Traversables '[t1, t2]) => (a -> m b) -> t2 (t1 a) -> m (t2 (t1 b)) Source #
mapM3 :: (Monad m, Traversables '[t1, t2, t3]) => (a -> m b) -> t3 (t2 (t1 a)) -> m (t3 (t2 (t1 b))) Source #
mapM4 :: (Monad m, Traversables '[t1, t2, t3, t4]) => (a -> m b) -> t4 (t3 (t2 (t1 a))) -> m (t4 (t3 (t2 (t1 b)))) Source #
mapM5 :: (Monad m, Traversables '[t1, t2, t3, t4, t5]) => (a -> m b) -> t5 (t4 (t3 (t2 (t1 a)))) -> m (t5 (t4 (t3 (t2 (t1 b))))) Source #
(<$>=) :: (Monad m, Traversable t1) => (a -> m b) -> t1 a -> m (t1 b) infixl 4 Source #
(<<$>>=) :: (Monad m, Traversables '[t1, t2]) => (a -> m b) -> t2 (t1 a) -> m (t2 (t1 b)) infixl 4 Source #
(<<<$>>>=) :: (Monad m, Traversables '[t1, t2, t3]) => (a -> m b) -> t3 (t2 (t1 a)) -> m (t3 (t2 (t1 b))) infixl 4 Source #
(<<<<$>>>>=) :: (Monad m, Traversables '[t1, t2, t3, t4]) => (a -> m b) -> t4 (t3 (t2 (t1 a))) -> m (t4 (t3 (t2 (t1 b)))) infixl 4 Source #
(<<<<<$>>>>>=) :: (Monad m, Traversables '[t1, t2, t3, t4, t5]) => (a -> m b) -> t5 (t4 (t3 (t2 (t1 a)))) -> m (t5 (t4 (t3 (t2 (t1 b))))) infixl 4 Source #
(<|$>=) :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t (a, b)) infixl 4 Source #
(<$|>=) :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t (b, a)) infixl 4 Source #
class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where #
Functors representing data structures that can be traversed from left to right.
A definition of traverse
must satisfy the following laws:
- naturality
t .
for every applicative transformationtraverse
f =traverse
(t . f)t
- identity
traverse
Identity = Identity- composition
traverse
(Compose .fmap
g . f) = Compose .fmap
(traverse
g) .traverse
f
A definition of sequenceA
must satisfy the following laws:
- naturality
t .
for every applicative transformationsequenceA
=sequenceA
.fmap
tt
- identity
sequenceA
.fmap
Identity = Identity- composition
sequenceA
.fmap
Compose = Compose .fmap
sequenceA
.sequenceA
where an applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative
operations, i.e.
and the identity functor Identity
and composition of functors Compose
are defined as
newtype Identity a = Identity a instance Functor Identity where fmap f (Identity x) = Identity (f x) instance Applicative Identity where pure x = Identity x Identity f <*> Identity x = Identity (f x) newtype Compose f g a = Compose (f (g a)) instance (Functor f, Functor g) => Functor (Compose f g) where fmap f (Compose x) = Compose (fmap (fmap f) x) instance (Applicative f, Applicative g) => Applicative (Compose f g) where pure x = Compose (pure (pure x)) Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
(The naturality law is implied by parametricity.)
Instances are similar to Functor
, e.g. given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Traversable Tree where traverse f Empty = pure Empty traverse f (Leaf x) = Leaf <$> f x traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
This is suitable even for abstract types, as the laws for <*>
imply a form of associativity.
The superclass instances should satisfy the following:
- In the
Functor
instance,fmap
should be equivalent to traversal with the identity applicative functor (fmapDefault
). - In the
Foldable
instance,foldMap
should be equivalent to traversal with a constant applicative functor (foldMapDefault
).
Methods
traverse :: Applicative f => (a -> f b) -> t a -> f (t b) #
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_
.
mapM :: Monad m => (a -> m b) -> t a -> m (t b) #
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_
.
Instances
Traversable [] | Since: base-2.1 |
Defined in Data.Traversable | |
Traversable Maybe | Since: base-2.1 |
Traversable Par1 | Since: base-4.9.0.0 |
Traversable Complex | Since: base-4.9.0.0 |
Traversable Min | Since: base-4.9.0.0 |
Traversable Max | Since: base-4.9.0.0 |
Traversable First | Since: base-4.9.0.0 |
Traversable Last | Since: base-4.9.0.0 |
Traversable Option | Since: base-4.9.0.0 |
Traversable ZipList | Since: base-4.9.0.0 |
Traversable Identity | Since: base-4.9.0.0 |
Traversable First | Since: base-4.8.0.0 |
Traversable Last | Since: base-4.8.0.0 |
Traversable Dual | Since: base-4.8.0.0 |
Traversable Sum | Since: base-4.8.0.0 |
Traversable Product | Since: base-4.8.0.0 |
Traversable Down | Since: base-4.12.0.0 |
Traversable NonEmpty | Since: base-4.9.0.0 |
Traversable IntMap | |
Traversable Tree | |
Traversable Seq | |
Traversable FingerTree | |
Defined in Data.Sequence.Internal Methods traverse :: Applicative f => (a -> f b) -> FingerTree a -> f (FingerTree b) # sequenceA :: Applicative f => FingerTree (f a) -> f (FingerTree a) # mapM :: Monad m => (a -> m b) -> FingerTree a -> m (FingerTree b) # sequence :: Monad m => FingerTree (m a) -> m (FingerTree a) # | |
Traversable Digit | |
Traversable Node | |
Traversable Elem | |
Traversable ViewL | |
Traversable ViewR | |
Traversable Vector | |
Traversable SmallArray | |
Defined in Data.Primitive.SmallArray Methods traverse :: Applicative f => (a -> f b) -> SmallArray a -> f (SmallArray b) # sequenceA :: Applicative f => SmallArray (f a) -> f (SmallArray a) # mapM :: Monad m => (a -> m b) -> SmallArray a -> m (SmallArray b) # sequence :: Monad m => SmallArray (m a) -> m (SmallArray a) # | |
Traversable Array | |
Traversable OneTuple Source # | |
Traversable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Traversable (V1 :: Type -> Type) | Since: base-4.9.0.0 |
Traversable (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Traversable ((,) a) | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Traversable (HashMap k) | |
Defined in Data.HashMap.Base | |
Traversable (Map k) | |
Ix i => Traversable (Array i) | Since: base-2.1 |
Traversable (Arg a) | Since: base-4.9.0.0 |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Traversable f => Traversable (MaybeT f) | |
Defined in Control.Monad.Trans.Maybe | |
Traversable f => Traversable (Cofree f) | |
Defined in Control.Comonad.Cofree | |
Traversable f => Traversable (Free f) | |
Traversable (ImpossibleM1 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM1 a -> f (ImpossibleM1 b) # sequenceA :: Applicative f => ImpossibleM1 (f a) -> f (ImpossibleM1 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM1 a -> m (ImpossibleM1 b) # sequence :: Monad m => ImpossibleM1 (m a) -> m (ImpossibleM1 a) # | |
Traversable f => Traversable (Yoneda f) | |
Defined in Data.Functor.Yoneda | |
Traversable (Level i) | |
Traversable (ListF a) | |
Traversable (NonEmptyF a) | |
Defined in Data.Functor.Base | |
Traversable f => Traversable (Rec1 f) | Since: base-4.9.0.0 |
Traversable (URec Char :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Double :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Float :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec Int :: Type -> Type) | Since: base-4.9.0.0 |
Traversable (URec Word :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Traversable (URec (Ptr ()) :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Traversable Methods traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) # sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) # mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) # sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) # | |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Traversable f => Traversable (Ap f) | Since: base-4.12.0.0 |
Traversable f => Traversable (Alt f) | Since: base-4.12.0.0 |
Bitraversable p => Traversable (Join p) | |
Bitraversable p => Traversable (Fix p) | |
Traversable f => Traversable (IdentityT f) | |
Defined in Control.Monad.Trans.Identity | |
Traversable f => Traversable (ExceptT e f) | |
Defined in Control.Monad.Trans.Except | |
Traversable f => Traversable (FreeF f a) | |
Defined in Control.Monad.Trans.Free | |
(Monad m, Traversable m, Traversable f) => Traversable (FreeT f m) | |
Defined in Control.Monad.Trans.Free | |
Traversable f => Traversable (CofreeF f a) | |
Defined in Control.Comonad.Trans.Cofree Methods traverse :: Applicative f0 => (a0 -> f0 b) -> CofreeF f a a0 -> f0 (CofreeF f a b) # sequenceA :: Applicative f0 => CofreeF f a (f0 a0) -> f0 (CofreeF f a a0) # mapM :: Monad m => (a0 -> m b) -> CofreeF f a a0 -> m (CofreeF f a b) # sequence :: Monad m => CofreeF f a (m a0) -> m (CofreeF f a a0) # | |
(Traversable f, Traversable w) => Traversable (CofreeT f w) | |
Defined in Control.Comonad.Trans.Cofree | |
Traversable f => Traversable (ErrorT e f) | |
Defined in Control.Monad.Trans.Error | |
Traversable (Tagged s) | |
Traversable (K1 i c :: Type -> Type) | Since: base-4.9.0.0 |
(Traversable f, Traversable g) => Traversable (f :+: g) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (f :*: g) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
(Traversable f, Traversable g) => Traversable (Sum f g) | Since: base-4.9.0.0 |
Traversable (ImpossibleM2 t1 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM2 t1 a -> f (ImpossibleM2 t1 b) # sequenceA :: Applicative f => ImpossibleM2 t1 (f a) -> f (ImpossibleM2 t1 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM2 t1 a -> m (ImpossibleM2 t1 b) # sequence :: Monad m => ImpossibleM2 t1 (m a) -> m (ImpossibleM2 t1 a) # | |
Traversable (Magma i t b) | |
Defined in Control.Lens.Internal.Magma | |
Traversable f => Traversable (M1 i c f) | Since: base-4.9.0.0 |
(Traversable f, Traversable g) => Traversable (f :.: g) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
(Traversable f, Traversable g) => Traversable (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
Bitraversable p => Traversable (WrappedBifunctor p a) | |
Defined in Data.Bifunctor.Wrapped Methods traverse :: Applicative f => (a0 -> f b) -> WrappedBifunctor p a a0 -> f (WrappedBifunctor p a b) # sequenceA :: Applicative f => WrappedBifunctor p a (f a0) -> f (WrappedBifunctor p a a0) # mapM :: Monad m => (a0 -> m b) -> WrappedBifunctor p a a0 -> m (WrappedBifunctor p a b) # sequence :: Monad m => WrappedBifunctor p a (m a0) -> m (WrappedBifunctor p a a0) # | |
Traversable g => Traversable (Joker g a) | |
Defined in Data.Bifunctor.Joker | |
Bitraversable p => Traversable (Flip p a) | |
Defined in Data.Bifunctor.Flip | |
Traversable (Clown f a :: Type -> Type) | |
Defined in Data.Bifunctor.Clown | |
Traversable (ImpossibleM3 t1 t2 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM3 t1 t2 a -> f (ImpossibleM3 t1 t2 b) # sequenceA :: Applicative f => ImpossibleM3 t1 t2 (f a) -> f (ImpossibleM3 t1 t2 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM3 t1 t2 a -> m (ImpossibleM3 t1 t2 b) # sequence :: Monad m => ImpossibleM3 t1 t2 (m a) -> m (ImpossibleM3 t1 t2 a) # | |
(Traversable f, Bitraversable p) => Traversable (Tannen f p a) | |
Defined in Data.Bifunctor.Tannen Methods traverse :: Applicative f0 => (a0 -> f0 b) -> Tannen f p a a0 -> f0 (Tannen f p a b) # sequenceA :: Applicative f0 => Tannen f p a (f0 a0) -> f0 (Tannen f p a a0) # mapM :: Monad m => (a0 -> m b) -> Tannen f p a a0 -> m (Tannen f p a b) # sequence :: Monad m => Tannen f p a (m a0) -> m (Tannen f p a a0) # | |
Traversable (ImpossibleM4 t1 t2 t3 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM4 t1 t2 t3 a -> f (ImpossibleM4 t1 t2 t3 b) # sequenceA :: Applicative f => ImpossibleM4 t1 t2 t3 (f a) -> f (ImpossibleM4 t1 t2 t3 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM4 t1 t2 t3 a -> m (ImpossibleM4 t1 t2 t3 b) # sequence :: Monad m => ImpossibleM4 t1 t2 t3 (m a) -> m (ImpossibleM4 t1 t2 t3 a) # | |
(Bitraversable p, Traversable g) => Traversable (Biff p f g a) | |
Defined in Data.Bifunctor.Biff Methods traverse :: Applicative f0 => (a0 -> f0 b) -> Biff p f g a a0 -> f0 (Biff p f g a b) # sequenceA :: Applicative f0 => Biff p f g a (f0 a0) -> f0 (Biff p f g a a0) # mapM :: Monad m => (a0 -> m b) -> Biff p f g a a0 -> m (Biff p f g a b) # sequence :: Monad m => Biff p f g a (m a0) -> m (Biff p f g a a0) # | |
Traversable (ImpossibleM5 t1 t2 t3 t4 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM5 t1 t2 t3 t4 a -> f (ImpossibleM5 t1 t2 t3 t4 b) # sequenceA :: Applicative f => ImpossibleM5 t1 t2 t3 t4 (f a) -> f (ImpossibleM5 t1 t2 t3 t4 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM5 t1 t2 t3 t4 a -> m (ImpossibleM5 t1 t2 t3 t4 b) # sequence :: Monad m => ImpossibleM5 t1 t2 t3 t4 (m a) -> m (ImpossibleM5 t1 t2 t3 t4 a) # | |
Traversable (ImpossibleM6 t1 t2 t3 t4 t5 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM6 t1 t2 t3 t4 t5 a -> f (ImpossibleM6 t1 t2 t3 t4 t5 b) # sequenceA :: Applicative f => ImpossibleM6 t1 t2 t3 t4 t5 (f a) -> f (ImpossibleM6 t1 t2 t3 t4 t5 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM6 t1 t2 t3 t4 t5 a -> m (ImpossibleM6 t1 t2 t3 t4 t5 b) # sequence :: Monad m => ImpossibleM6 t1 t2 t3 t4 t5 (m a) -> m (ImpossibleM6 t1 t2 t3 t4 t5 a) # | |
Traversable (ImpossibleM7 t1 t2 t3 t4 t5 t6 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM7 t1 t2 t3 t4 t5 t6 a -> f (ImpossibleM7 t1 t2 t3 t4 t5 t6 b) # sequenceA :: Applicative f => ImpossibleM7 t1 t2 t3 t4 t5 t6 (f a) -> f (ImpossibleM7 t1 t2 t3 t4 t5 t6 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM7 t1 t2 t3 t4 t5 t6 a -> m (ImpossibleM7 t1 t2 t3 t4 t5 t6 b) # sequence :: Monad m => ImpossibleM7 t1 t2 t3 t4 t5 t6 (m a) -> m (ImpossibleM7 t1 t2 t3 t4 t5 t6 a) # | |
Traversable (ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 a -> f (ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 b) # sequenceA :: Applicative f => ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 (f a) -> f (ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 a -> m (ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 b) # sequence :: Monad m => ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 (m a) -> m (ImpossibleM8 t1 t2 t3 t4 t5 t6 t7 a) # | |
Traversable (ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 :: Type -> Type) | |
Defined in Data.Impossible Methods traverse :: Applicative f => (a -> f b) -> ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 a -> f (ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 b) # sequenceA :: Applicative f => ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 (f a) -> f (ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 a) # mapM :: Monad m => (a -> m b) -> ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 a -> m (ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 b) # sequence :: Monad m => ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 (m a) -> m (ImpossibleM9 t1 t2 t3 t4 t5 t6 t7 t8 a) # |
bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d) #
bifor
is bitraverse
with the structure as the first argument. For a
version that ignores the results, see bifor_
.
Since: base-4.10.0.0
bimapM :: (Bitraversable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) #
Alias for bitraverse
.
Since: base-4.10.0.0
class (Bifunctor t, Bifoldable t) => Bitraversable (t :: Type -> Type -> Type) where #
Bitraversable
identifies bifunctorial data structures whose elements can
be traversed in order, performing Applicative
or Monad
actions at each
element, and collecting a result structure with the same shape.
As opposed to Traversable
data structures, which have one variety of
element on which an action can be performed, Bitraversable
data structures
have two such varieties of elements.
A definition of bitraverse
must satisfy the following laws:
- naturality
for every applicative transformationbitraverse
(t . f) (t . g) ≡ t .bitraverse
f gt
- identity
bitraverse
Identity
Identity
≡Identity
- composition
Compose
.fmap
(bitraverse
g1 g2) .bitraverse
f1 f2 ≡traverse
(Compose
.fmap
g1 . f1) (Compose
.fmap
g2 . f2)
where an applicative transformation is a function
t :: (Applicative
f,Applicative
g) => f a -> g a
preserving the Applicative
operations:
t (pure
x) =pure
x t (f<*>
x) = t f<*>
t x
and the identity functor Identity
and composition functors Compose
are
defined as
newtype Identity a = Identity { runIdentity :: a } instance Functor Identity where fmap f (Identity x) = Identity (f x) instance Applicative Identity where pure = Identity Identity f <*> Identity x = Identity (f x) newtype Compose f g a = Compose (f (g a)) instance (Functor f, Functor g) => Functor (Compose f g) where fmap f (Compose x) = Compose (fmap (fmap f) x) instance (Applicative f, Applicative g) => Applicative (Compose f g) where pure = Compose . pure . pure Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
Some simple examples are Either
and '(,)':
instance Bitraversable Either where bitraverse f _ (Left x) = Left <$> f x bitraverse _ g (Right y) = Right <$> g y instance Bitraversable (,) where bitraverse f g (x, y) = (,) <$> f x <*> g y
Bitraversable
relates to its superclasses in the following ways:
bimap
f g ≡runIdentity
.bitraverse
(Identity
. f) (Identity
. g)bifoldMap
f g =getConst
.bitraverse
(Const
. f) (Const
. g)
These are available as bimapDefault
and bifoldMapDefault
respectively.
Since: base-4.10.0.0
Minimal complete definition
Nothing
Methods
bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) #
Evaluates the relevant functions at each element in the structure, running the action, and builds a new structure with the same shape, using the results produced from sequencing the actions.
bitraverse
f g ≡bisequenceA
.bimap
f g
For a version that ignores the results, see bitraverse_
.
Since: base-4.10.0.0
Instances
Bitraversable Either | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) # | |
Bitraversable (,) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (a, b) -> f (c, d) # | |
Bitraversable Arg | Since: base-4.10.0.0 |
Defined in Data.Semigroup Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Arg a b -> f (Arg c d) # | |
Bitraversable ListF | |
Defined in Data.Functor.Foldable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> ListF a b -> f (ListF c d) # | |
Bitraversable NonEmptyF | |
Defined in Data.Functor.Base Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> NonEmptyF a b -> f (NonEmptyF c d) # | |
Bitraversable ((,,) x) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, a, b) -> f (x, c, d) # | |
Bitraversable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) # | |
Traversable f => Bitraversable (FreeF f) | |
Defined in Control.Monad.Trans.Free Methods bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> FreeF f a b -> f0 (FreeF f c d) # | |
Traversable f => Bitraversable (CofreeF f) | |
Defined in Control.Comonad.Trans.Cofree Methods bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> CofreeF f a b -> f0 (CofreeF f c d) # | |
Bitraversable (Tagged :: Type -> Type -> Type) | |
Defined in Data.Tagged Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tagged a b -> f (Tagged c d) # | |
Bitraversable (K1 i :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> K1 i a b -> f (K1 i c d) # | |
Bitraversable ((,,,) x y) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, a, b) -> f (x, y, c, d) # | |
Bitraversable ((,,,,) x y z) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, a, b) -> f (x, y, z, c, d) # | |
Bitraversable p => Bitraversable (WrappedBifunctor p) | |
Defined in Data.Bifunctor.Wrapped Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> WrappedBifunctor p a b -> f (WrappedBifunctor p c d) # | |
Traversable g => Bitraversable (Joker g :: Type -> Type -> Type) | |
Defined in Data.Bifunctor.Joker Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Joker g a b -> f (Joker g c d) # | |
Bitraversable p => Bitraversable (Flip p) | |
Defined in Data.Bifunctor.Flip Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Flip p a b -> f (Flip p c d) # | |
Traversable f => Bitraversable (Clown f :: Type -> Type -> Type) | |
Defined in Data.Bifunctor.Clown Methods bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Clown f a b -> f0 (Clown f c d) # | |
Bitraversable ((,,,,,) x y z w) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, w, a, b) -> f (x, y, z, w, c, d) # | |
(Bitraversable p, Bitraversable q) => Bitraversable (Sum p q) | |
Defined in Data.Bifunctor.Sum Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Sum p q a b -> f (Sum p q c d) # | |
(Bitraversable f, Bitraversable g) => Bitraversable (Product f g) | |
Defined in Data.Bifunctor.Product Methods bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Product f g a b -> f0 (Product f g c d) # | |
Bitraversable ((,,,,,,) x y z w v) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, w, v, a, b) -> f (x, y, z, w, v, c, d) # | |
(Traversable f, Bitraversable p) => Bitraversable (Tannen f p) | |
Defined in Data.Bifunctor.Tannen Methods bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Tannen f p a b -> f0 (Tannen f p c d) # | |
(Bitraversable p, Traversable f, Traversable g) => Bitraversable (Biff p f g) | |
Defined in Data.Bifunctor.Biff Methods bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Biff p f g a b -> f0 (Biff p f g c d) # |
for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) #