| 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: base-4.10.0.0
Synopsis
- 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)
 
- 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 :: Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d
- bifoldMapDefault :: (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m
Documentation
class (Bifunctor t, Bifoldable t) => Bitraversable (t :: Type -> Type -> Type) 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
- bitraverse(t . f) (t . g) ≡ t .- bitraversef g- t
- Identity
- bitraverse- Identity- Identity≡- Identity
- Composition
- Compose.- fmap(- bitraverseg1 g2) .- bitraversef1 f2 ≡- bitraverse(- Compose.- fmapg1 . f1) (- Compose.- fmapg2 . f2)
where an applicative transformation is a function
t :: (Applicativef,Applicativeg) => f a -> g a
preserving the Applicative operations:
t (purex) =purex t (f<*>x) = t f<*>t x
and the identity functor Identity and composition functors
 Compose are from Data.Functor.Identity and
 Data.Functor.Compose.
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:
bimapf g ≡runIdentity.bitraverse(Identity. f) (Identity. g)bifoldMapf g =getConst.bitraverse(Const. f) (Const. g)
These are available as bimapDefault and bifoldMapDefault respectively.
Since: base-4.10.0.0
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, see bitraverse_.
Examples
Basic usage:
>>>bitraverse listToMaybe (find odd) (Left [])Nothing
>>>bitraverse listToMaybe (find odd) (Left [1, 2, 3])Just (Left 1)
>>>bitraverse listToMaybe (find odd) (Right [4, 5])Just (Right 5)
>>>bitraverse listToMaybe (find odd) ([1, 2, 3], [4, 5])Just (1,5)
>>>bitraverse listToMaybe (find odd) ([], [4, 5])Nothing
Since: base-4.10.0.0
Instances
| Bitraversable Either Source # | 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) Source # | |
| Bitraversable Arg Source # | 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) Source # | |
| Bitraversable (,) Source # | 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) Source # | |
| Bitraversable (Const :: Type -> Type -> Type) Source # | 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) Source # | |
| Bitraversable ((,,) x) Source # | 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) Source # | |
| Bitraversable (K1 i :: Type -> Type -> Type) Source # | 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) Source # | |
| Bitraversable ((,,,) x y) Source # | 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) Source # | |
| Bitraversable ((,,,,) x y z) Source # | 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) Source # | |
| Bitraversable ((,,,,,) x y z w) Source # | 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) Source # | |
| Bitraversable ((,,,,,,) x y z w v) Source # | 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) Source # | |
bisequenceA :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) Source #
Alias for bisequence.
Since: base-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≡bitraverseidid
Examples
Basic usage:
>>>bisequence (Just 4, Nothing)Nothing
>>>bisequence (Just 4, Just 5)Just (4,5)
>>>bisequence ([1, 2, 3], [4, 5])[(1,4),(1,5),(2,4),(2,5),(3,4),(3,5)]
Since: base-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: base-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_.
Examples
Basic usage:
>>>bifor (Left []) listToMaybe (find even)Nothing
>>>bifor (Left [1, 2, 3]) listToMaybe (find even)Just (Left 1)
>>>bifor (Right [4, 5]) listToMaybe (find even)Just (Right 4)
>>>bifor ([1, 2, 3], [4, 5]) listToMaybe (find even)Just (1,4)
>>>bifor ([], [4, 5]) listToMaybe (find even)Nothing
Since: base-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: base-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.
Examples
Basic usage:
>>>bimapAccumL (\acc bool -> (acc + 1, show bool)) (\acc string -> (acc * 2, reverse string)) 3 (True, "foo")(8,("True","oof"))
Since: base-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
 bifoldr; 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.
Examples
Basic usage:
>>>bimapAccumR (\acc bool -> (acc + 1, show bool)) (\acc string -> (acc * 2, reverse string)) 3 (True, "foo")(7,("True","oof"))
Since: base-4.10.0.0
bimapDefault :: Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d Source #
A default definition of bimap in terms of the Bitraversable
 operations.
bimapDefaultf g ≡runIdentity.bitraverse(Identity. f) (Identity. g)
Since: base-4.10.0.0
bifoldMapDefault :: (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m Source #
A default definition of bifoldMap in terms of the Bitraversable
 operations.
bifoldMapDefaultf g ≡getConst.bitraverse(Const. f) (Const. g)
Since: base-4.10.0.0