Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- btmap :: (FunctorB (b f), FunctorT b) => (forall a. f a -> f' a) -> (forall a. g a -> g' a) -> b f g -> b f' g'
- btmap1 :: (FunctorB (b f), FunctorT b) => (forall a. f a -> g a) -> b f f -> b g g
- bttraverse :: (TraversableB (b f), TraversableT b, Monad t) => (forall a. f a -> t (f' a)) -> (forall a. g a -> t (g' a)) -> b f g -> t (b f' g')
- bttraverse1 :: (TraversableB (b f), TraversableT b, Monad t) => (forall a. f a -> t (g a)) -> b f f -> t (b g g)
- bttraverse_ :: (TraversableB (b f), TraversableT b, Monad e) => (forall a. f a -> e c) -> (forall a. g a -> e d) -> b f g -> e ()
- btfoldMap :: (TraversableB (b f), TraversableT b, Monoid m) => (forall a. f a -> m) -> (forall a. g a -> m) -> b f g -> m
- btpure :: (ApplicativeB (b Unit), FunctorT b) => (forall a. f a) -> (forall a. g a) -> b f g
- btpure1 :: (ApplicativeB (b Unit), FunctorT b) => (forall a. f a) -> b f f
- btprod :: (ApplicativeB (b (Alt (Product f f'))), FunctorT b, Alternative f, Alternative f') => b f g -> b f' g' -> b (f `Product` f') (g `Product` g')
- newtype Flip b l r = Flip {
- runFlip :: b r l
Functor
btmap :: (FunctorB (b f), FunctorT b) => (forall a. f a -> f' a) -> (forall a. g a -> g' a) -> b f g -> b f' g' Source #
Map over both arguments at the same time.
btmap1 :: (FunctorB (b f), FunctorT b) => (forall a. f a -> g a) -> b f f -> b g g Source #
A version of btmap
specialized to a single argument.
Traversable
A traversable bifunctor is simultaneously a TraversableT
and a TraversableB
.
bttraverse :: (TraversableB (b f), TraversableT b, Monad t) => (forall a. f a -> t (f' a)) -> (forall a. g a -> t (g' a)) -> b f g -> t (b f' g') Source #
Traverse over both arguments, first over f
, then over g
..
bttraverse1 :: (TraversableB (b f), TraversableT b, Monad t) => (forall a. f a -> t (g a)) -> b f f -> t (b g g) Source #
A version of bttraverse
specialized to a single argument.
bttraverse_ :: (TraversableB (b f), TraversableT b, Monad e) => (forall a. f a -> e c) -> (forall a. g a -> e d) -> b f g -> e () Source #
Map each element to an action, evaluate these actions from left to right and ignore the results.
btfoldMap :: (TraversableB (b f), TraversableT b, Monoid m) => (forall a. f a -> m) -> (forall a. g a -> m) -> b f g -> m Source #
Map each element to a monoid, and combine the results.
Applicative
If t
is an ApplicativeT
, the type of tpure
shows that its
second argument must be a phantom-type, so there are really no
interesting types that are both ApplicativeT
and ApplicativeB
.
However, we can sometimes reconstruct a bi-applicative from an
ApplicativeB
and a FunctorT
.
btpure :: (ApplicativeB (b Unit), FunctorT b) => (forall a. f a) -> (forall a. g a) -> b f g Source #
btpure1 :: (ApplicativeB (b Unit), FunctorT b) => (forall a. f a) -> b f f Source #
A version of btpure
specialized to a single argument.
btprod :: (ApplicativeB (b (Alt (Product f f'))), FunctorT b, Alternative f, Alternative f') => b f g -> b f' g' -> b (f `Product` f') (g `Product` g') Source #
Simultaneous product on both arguments.
Wrappers
Instances
(forall (f :: k'). ApplicativeB (b f)) => ApplicativeT (Flip b :: (k -> Type) -> k' -> Type) Source # | |
(forall (f :: k'). FunctorB (b f)) => FunctorT (Flip b :: (k -> Type) -> k' -> Type) Source # | |
(forall (f :: k'). TraversableB (b f)) => TraversableT (Flip b :: (k -> Type) -> k' -> Type) Source # | |
Defined in Barbies.Bi | |
(forall (f :: i). DistributiveB (b f)) => DistributiveT (Flip b :: (Type -> Type) -> i -> Type) Source # | |
Defined in Barbies.Bi | |
ApplicativeT b => ApplicativeB (Flip b f :: (k1 -> Type) -> Type) Source # | |
DistributiveT b => DistributiveB (Flip b f :: (Type -> Type) -> Type) Source # | |
Defined in Barbies.Bi | |
FunctorT b => FunctorB (Flip b f :: (k1 -> Type) -> Type) Source # | |
TraversableT b => TraversableB (Flip b f :: (k1 -> Type) -> Type) Source # | |
Defined in Barbies.Bi | |
Read (b r l) => Read (Flip b l r) Source # | |
Show (b r l) => Show (Flip b l r) Source # | |
Eq (b r l) => Eq (Flip b l r) Source # | |
Ord (b r l) => Ord (Flip b l r) Source # | |