Copyright | (C) 2011-2015 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Synopsis
- class Bifunctor p => Biapplicative p where
- (<<$>>) :: (a -> b) -> a -> b
- (<<**>>) :: Biapplicative p => p a c -> p (a -> b) (c -> d) -> p b d
- biliftA3 :: Biapplicative w => (a -> b -> c -> d) -> (e -> f -> g -> h) -> w a e -> w b f -> w c g -> w d h
- traverseBia :: (Traversable t, Biapplicative p) => (a -> p b c) -> t a -> p (t b) (t c)
- sequenceBia :: (Traversable t, Biapplicative p) => t (p b c) -> p (t b) (t c)
- traverseBiaWith :: forall p a b c s t. Biapplicative p => (forall f x. Applicative f => (a -> f x) -> s -> f (t x)) -> (a -> p b c) -> s -> p (t b) (t c)
- module Data.Bifunctor
Biapplicative bifunctors
class Bifunctor p => Biapplicative p where Source #
bipure :: a -> b -> p a b Source #
(<<*>>) :: p (a -> b) (c -> d) -> p a c -> p b d infixl 4 Source #
biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> p a d -> p b e -> p c f Source #
Lift binary functions
Instances
Biapplicative (,) Source # | |
Biapplicative Arg Source # | |
Defined in Data.Biapplicative | |
Monoid x => Biapplicative ((,,) x) Source # | |
Defined in Data.Biapplicative | |
Biapplicative (Const :: Type -> Type -> Type) Source # | |
Biapplicative (Tagged :: Type -> Type -> Type) Source # | |
Biapplicative bi => Biapplicative (Biap bi) Source # | |
Defined in Data.Bifunctor.Biap | |
(Monoid x, Monoid y) => Biapplicative ((,,,) x y) Source # | |
Defined in Data.Biapplicative bipure :: a -> b -> (x, y, a, b) Source # (<<*>>) :: (x, y, a -> b, c -> d) -> (x, y, a, c) -> (x, y, b, d) Source # biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> (x, y, a, d) -> (x, y, b, e) -> (x, y, c, f) Source # (*>>) :: (x, y, a, b) -> (x, y, c, d) -> (x, y, c, d) Source # (<<*) :: (x, y, a, b) -> (x, y, c, d) -> (x, y, a, b) Source # | |
(Monoid x, Monoid y, Monoid z) => Biapplicative ((,,,,) x y z) Source # | |
Defined in Data.Biapplicative bipure :: a -> b -> (x, y, z, a, b) Source # (<<*>>) :: (x, y, z, a -> b, c -> d) -> (x, y, z, a, c) -> (x, y, z, b, d) Source # biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> (x, y, z, a, d) -> (x, y, z, b, e) -> (x, y, z, c, f) Source # (*>>) :: (x, y, z, a, b) -> (x, y, z, c, d) -> (x, y, z, c, d) Source # (<<*) :: (x, y, z, a, b) -> (x, y, z, c, d) -> (x, y, z, a, b) Source # | |
Applicative f => Biapplicative (Clown f :: Type -> Type -> Type) Source # | |
Defined in Data.Bifunctor.Clown | |
Biapplicative p => Biapplicative (Flip p) Source # | |
Applicative g => Biapplicative (Joker g :: Type -> Type -> Type) Source # | |
Defined in Data.Bifunctor.Joker | |
Biapplicative p => Biapplicative (WrappedBifunctor p) Source # | |
Defined in Data.Bifunctor.Wrapped bipure :: a -> b -> WrappedBifunctor p a b Source # (<<*>>) :: WrappedBifunctor p (a -> b) (c -> d) -> WrappedBifunctor p a c -> WrappedBifunctor p b d Source # biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> WrappedBifunctor p a d -> WrappedBifunctor p b e -> WrappedBifunctor p c f Source # (*>>) :: WrappedBifunctor p a b -> WrappedBifunctor p c d -> WrappedBifunctor p c d Source # (<<*) :: WrappedBifunctor p a b -> WrappedBifunctor p c d -> WrappedBifunctor p a b Source # | |
(Monoid x, Monoid y, Monoid z, Monoid w) => Biapplicative ((,,,,,) x y z w) Source # | |
Defined in Data.Biapplicative bipure :: a -> b -> (x, y, z, w, a, b) Source # (<<*>>) :: (x, y, z, w, a -> b, c -> d) -> (x, y, z, w, a, c) -> (x, y, z, w, b, d) Source # biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> (x, y, z, w, a, d) -> (x, y, z, w, b, e) -> (x, y, z, w, c, f) Source # (*>>) :: (x, y, z, w, a, b) -> (x, y, z, w, c, d) -> (x, y, z, w, c, d) Source # (<<*) :: (x, y, z, w, a, b) -> (x, y, z, w, c, d) -> (x, y, z, w, a, b) Source # | |
(Biapplicative f, Biapplicative g) => Biapplicative (Product f g) Source # | |
Defined in Data.Bifunctor.Product bipure :: a -> b -> Product f g a b Source # (<<*>>) :: Product f g (a -> b) (c -> d) -> Product f g a c -> Product f g b d Source # biliftA2 :: (a -> b -> c) -> (d -> e -> f0) -> Product f g a d -> Product f g b e -> Product f g c f0 Source # (*>>) :: Product f g a b -> Product f g c d -> Product f g c d Source # (<<*) :: Product f g a b -> Product f g c d -> Product f g a b Source # | |
(Monoid x, Monoid y, Monoid z, Monoid w, Monoid v) => Biapplicative ((,,,,,,) x y z w v) Source # | |
Defined in Data.Biapplicative bipure :: a -> b -> (x, y, z, w, v, a, b) Source # (<<*>>) :: (x, y, z, w, v, a -> b, c -> d) -> (x, y, z, w, v, a, c) -> (x, y, z, w, v, b, d) Source # biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> (x, y, z, w, v, a, d) -> (x, y, z, w, v, b, e) -> (x, y, z, w, v, c, f) Source # (*>>) :: (x, y, z, w, v, a, b) -> (x, y, z, w, v, c, d) -> (x, y, z, w, v, c, d) Source # (<<*) :: (x, y, z, w, v, a, b) -> (x, y, z, w, v, c, d) -> (x, y, z, w, v, a, b) Source # | |
(Applicative f, Biapplicative p) => Biapplicative (Tannen f p) Source # | |
Defined in Data.Bifunctor.Tannen bipure :: a -> b -> Tannen f p a b Source # (<<*>>) :: Tannen f p (a -> b) (c -> d) -> Tannen f p a c -> Tannen f p b d Source # biliftA2 :: (a -> b -> c) -> (d -> e -> f0) -> Tannen f p a d -> Tannen f p b e -> Tannen f p c f0 Source # (*>>) :: Tannen f p a b -> Tannen f p c d -> Tannen f p c d Source # (<<*) :: Tannen f p a b -> Tannen f p c d -> Tannen f p a b Source # | |
(Biapplicative p, Applicative f, Applicative g) => Biapplicative (Biff p f g) Source # | |
Defined in Data.Bifunctor.Biff bipure :: a -> b -> Biff p f g a b Source # (<<*>>) :: Biff p f g (a -> b) (c -> d) -> Biff p f g a c -> Biff p f g b d Source # biliftA2 :: (a -> b -> c) -> (d -> e -> f0) -> Biff p f g a d -> Biff p f g b e -> Biff p f g c f0 Source # (*>>) :: Biff p f g a b -> Biff p f g c d -> Biff p f g c d Source # (<<*) :: Biff p f g a b -> Biff p f g c d -> Biff p f g a b Source # |
(<<**>>) :: Biapplicative p => p a c -> p (a -> b) (c -> d) -> p b d infixl 4 Source #
biliftA3 :: Biapplicative w => (a -> b -> c -> d) -> (e -> f -> g -> h) -> w a e -> w b f -> w c g -> w d h Source #
Lift ternary functions
traverseBia :: (Traversable t, Biapplicative p) => (a -> p b c) -> t a -> p (t b) (t c) Source #
Traverse a Traversable
container in a Biapplicative
.
traverseBia
satisfies the following properties:
- Pairing
traverseBia
(,) t = (t, t)- Composition
traverseBia
(Biff
.bimap
g h . f) =Biff
.bimap
(traverse
g) (traverse
h) .traverseBia
ftraverseBia
(Tannen
.fmap
f . g) =Tannen
.fmap
(traverseBia
f) .traverse
g- Naturality
t .
traverseBia
f =traverseBia
(t . f)for every biapplicative transformation
t
.A biapplicative transformation from a
Biapplicative
P
to aBiapplicative
Q
is a functiont :: P a b -> Q a b
preserving the
Biapplicative
operations. That is,
Performance note
traverseBia
is fairly efficient, and uses compiler rewrite rules
to be even more efficient for a few important types like []
. However,
if performance is critical, you might consider writing a container-specific
implementation.
sequenceBia :: (Traversable t, Biapplicative p) => t (p b c) -> p (t b) (t c) Source #
Perform all the Biappicative
actions in a Traversable
container
and produce a container with all the results.
sequenceBia = traverseBia
id
traverseBiaWith :: forall p a b c s t. Biapplicative p => (forall f x. Applicative f => (a -> f x) -> s -> f (t x)) -> (a -> p b c) -> s -> p (t b) (t c) Source #
A version of traverseBia
that doesn't care how the traversal is
done.
traverseBia
= traverseBiaWith traverse
module Data.Bifunctor