| Copyright | (C) 2011-2016 Edward Kmett |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | libraries@haskell.org |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Data.Bitraversable
Description
Since: 4.10.0.0
class (Bifunctor t,Bifoldable t) =>Bitraversable twhereSource#
Bitraversable identifies bifunctorial data structures whose elements can be traversed in order, performingApplicative orMonad actions at each element, and collecting a result structure with the same shape.
As opposed toTraversable 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 ofbitraverse must satisfy the following laws:
bitraverse (t . f) (t . g) ≡ t .bitraverse f g for every applicative transformationtbitraverseIdentityIdentity ≡IdentityCompose .fmap (bitraverse g1 g2) .bitraverse f1 f2 ≡traverse (Compose .fmap g1 . f1) (Compose .fmap g2 . f2)where anapplicative transformation is a function
t :: (Applicativef,Applicativeg) => f a -> g a
preserving theApplicative operations:
t (purex) =purext (f<*>x) = t f<*>t x
and the identity functorIdentity and composition functorsCompose 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 areEither and '(,)':
instance Bitraversable Either where bitraverse f _ (Left x) = Left <$> f x bitraverse _ g (Right y) = Right <$> g yinstance Bitraversable (,) where bitraverse f g (x, y) = (,) <$> f x <*> g y
Bitraversable relates to its superclasses in the following ways:
bimapf g ≡runIdentity.bitraverse(Identity. f) (Identity. g)bifoldMapf g =getConst.bitraverse(Const. f) (Const. g)
These are available asbimapDefault andbifoldMapDefault respectively.
Since: 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)Source#
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.
bitraversef g ≡bisequenceA.bimapf g
For a version that ignores the results, seebitraverse_.
Since: 4.10.0.0
| BitraversableEitherSource# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) ->Either a b -> f (Either c d)Source# | |
| Bitraversable(,)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) -> (a, b) -> f (c, d)Source# | |
| BitraversableArgSource# | Since: 4.10.0.0 |
Instance detailsDefined inData.Semigroup Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) ->Arg a b -> f (Arg c d)Source# | |
| Bitraversable ((,,) x)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) -> (x, a, b) -> f (x, c, d)Source# | |
| Bitraversable (Const ::Type ->Type ->Type)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) ->Const a b -> f (Const c d)Source# | |
| Bitraversable (K1 i ::Type ->Type ->Type)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) ->K1 i a b -> f (K1 i c d)Source# | |
| Bitraversable ((,,,) x y)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) -> (x, y, a, b) -> f (x, y, c, d)Source# | |
| Bitraversable ((,,,,) x y z)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, a, b) -> f (x, y, z, c, d)Source# | |
| Bitraversable ((,,,,,) x y z w)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, w, a, b) -> f (x, y, z, w, c, d)Source# | |
| Bitraversable ((,,,,,,) x y z w v)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.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)Source# | |
bisequenceA :: (Bitraversable t,Applicative f) => t (f a) (f b) -> f (t a b)Source#
Alias forbisequence.
Since: 4.10.0.0
bisequence :: (Bitraversable t,Applicative f) => t (f a) (f b) -> f (t a b)Source#
Sequences all the actions in a structure, building a new structure with the same shape using the results of the actions. For a version that ignores the results, seebisequence_.
bisequence≡bitraverseidid
Since: 4.10.0.0
bimapM :: (Bitraversable t,Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)Source#
Alias forbitraverse.
Since: 4.10.0.0
bifor :: (Bitraversable t,Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)Source#
bifor isbitraverse with the structure as the first argument. For a version that ignores the results, seebifor_.
Since: 4.10.0.0
biforM :: (Bitraversable t,Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)Source#
Alias forbifor.
Since: 4.10.0.0
bimapAccumL ::Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)Source#
ThebimapAccumL function behaves like a combination ofbimap andbifoldl; it traverses a structure from left to right, threading a state of typea and using the given actions to compute new elements for the structure.
Since: 4.10.0.0
bimapAccumR ::Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)Source#
ThebimapAccumR function behaves like a combination ofbimap andbifoldl; it traverses a structure from right to left, threading a state of typea and using the given actions to compute new elements for the structure.
Since: 4.10.0.0
bimapDefault ::forall t a b c d.Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b dSource#
A default definition ofbimap in terms of theBitraversable operations.
bimapDefaultf g ≡runIdentity.bitraverse(Identity. f) (Identity. g)
Since: 4.10.0.0
bifoldMapDefault ::forall t m a b. (Bitraversable t,Monoid m) => (a -> m) -> (b -> m) -> t a b -> mSource#
A default definition ofbifoldMap in terms of theBitraversable operations.
bifoldMapDefaultf g ≡getConst.bitraverse(Const. f) (Const. g)
Since: 4.10.0.0
Produced byHaddock version 2.20.0