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 |
Since: 4.10.0.0
- class (Bifunctor t, Bifoldable t) => Bitraversable t where
- bisequenceA :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
- bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
- bimapM :: (Bitraversable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
- bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
- biforM :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
- bimapAccumL :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)
- bimapAccumR :: Bitraversable t => (a -> b -> (a, c)) -> (a -> d -> (a, e)) -> a -> t b d -> (a, t c e)
- bimapDefault :: forall t a b c d. Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d
- bifoldMapDefault :: forall t m a b. (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m
Documentation
class (Bifunctor t, Bifoldable t) => Bitraversable t where Source #
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: 4.10.0.0
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.
bitraverse
f g ≡bisequenceA
.bimap
f g
For a version that ignores the results, see bitraverse_
.
Since: 4.10.0.0
Bitraversable Either # | Since: 4.10.0.0 |
Bitraversable (,) # | Since: 4.10.0.0 |
Bitraversable Arg # | Since: 4.10.0.0 |
Bitraversable ((,,) x) # | Since: 4.10.0.0 |
Bitraversable (Const *) # | Since: 4.10.0.0 |
Bitraversable (K1 * i) # | Since: 4.10.0.0 |
Bitraversable ((,,,) x y) # | Since: 4.10.0.0 |
Bitraversable ((,,,,) x y z) # | Since: 4.10.0.0 |
Bitraversable ((,,,,,) x y z w) # | Since: 4.10.0.0 |
Bitraversable ((,,,,,,) x y z w v) # | Since: 4.10.0.0 |
bisequenceA :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) Source #
Alias for bisequence
.
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, see bisequence_
.
bisequence
≡bitraverse
id
id
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 for bitraverse
.
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
is bitraverse
with the structure as the first argument. For a
version that ignores the results, see bifor_
.
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 for bifor
.
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 #
The bimapAccumL
function behaves like a combination of bimap
and
bifoldl
; it traverses a structure from left to right, threading a state
of type a
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 #
The bimapAccumR
function behaves like a combination of bimap
and
bifoldl
; it traverses a structure from right to left, threading a state
of type a
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 d Source #
A default definition of bimap
in terms of the Bitraversable
operations.
bimapDefault
f 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 -> m Source #
A default definition of bifoldMap
in terms of the Bitraversable
operations.
bifoldMapDefault
f g ≡getConst
.bitraverse
(Const
. f) (Const
. g)
Since: 4.10.0.0