barbies-2.0.2.0: Classes for working with types that can change clothes.

Safe HaskellNone
LanguageHaskell2010

Barbies.Bi

Contents

Synopsis

Functor

A bifunctor is simultaneously a FunctorT and a FunctorB.

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.

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 #

Conceptually, this is like simultaneously using bpure and tpure.

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

newtype Flip b l r Source #

Convert a FunctorB into a FunctorT and vice-versa.

Constructors

Flip 

Fields

Instances
(forall (f :: k'). FunctorB (b f)) => FunctorT (Flip b :: (k -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

tmap :: (forall (a :: k0). f a -> g a) -> forall (x :: k'0). Flip b f x -> Flip b g x Source #

(forall (f :: k'). TraversableB (b f)) => TraversableT (Flip b :: (k -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

ttraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> forall (x :: k'0). Flip b f x -> e (Flip b g x) Source #

(forall (f :: k'). ApplicativeB (b f)) => ApplicativeT (Flip b :: (k -> Type) -> k' -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

tpure :: (forall (a :: k0). f a) -> forall (x :: k'0). Flip b f x Source #

tprod :: Flip b f x -> Flip b g x -> Flip b (Product f g) x Source #

(forall (f :: i). DistributiveB (b f)) => DistributiveT (Flip b :: (Type -> Type) -> i -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

tdistribute :: Functor f => f (Flip b g x) -> Flip b (Compose f g) x Source #

FunctorT b => FunctorB (Flip b f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

bmap :: (forall (a :: k). f0 a -> g a) -> Flip b f f0 -> Flip b f g Source #

TraversableT b => TraversableB (Flip b f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

btraverse :: Applicative e => (forall (a :: k). f0 a -> e (g a)) -> Flip b f f0 -> e (Flip b f g) Source #

DistributiveT b => DistributiveB (Flip b f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

bdistribute :: Functor f0 => f0 (Flip b f g) -> Flip b f (Compose f0 g) Source #

ApplicativeT b => ApplicativeB (Flip b f :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Bi

Methods

bpure :: (forall (a :: k). f0 a) -> Flip b f f0 Source #

bprod :: Flip b f f0 -> Flip b f g -> Flip b f (Product f0 g) Source #

Eq (b r l) => Eq (Flip b l r) Source # 
Instance details

Defined in Barbies.Bi

Methods

(==) :: Flip b l r -> Flip b l r -> Bool #

(/=) :: Flip b l r -> Flip b l r -> Bool #

Ord (b r l) => Ord (Flip b l r) Source # 
Instance details

Defined in Barbies.Bi

Methods

compare :: Flip b l r -> Flip b l r -> Ordering #

(<) :: Flip b l r -> Flip b l r -> Bool #

(<=) :: Flip b l r -> Flip b l r -> Bool #

(>) :: Flip b l r -> Flip b l r -> Bool #

(>=) :: Flip b l r -> Flip b l r -> Bool #

max :: Flip b l r -> Flip b l r -> Flip b l r #

min :: Flip b l r -> Flip b l r -> Flip b l r #

Read (b r l) => Read (Flip b l r) Source # 
Instance details

Defined in Barbies.Bi

Methods

readsPrec :: Int -> ReadS (Flip b l r) #

readList :: ReadS [Flip b l r] #

readPrec :: ReadPrec (Flip b l r) #

readListPrec :: ReadPrec [Flip b l r] #

Show (b r l) => Show (Flip b l r) Source # 
Instance details

Defined in Barbies.Bi

Methods

showsPrec :: Int -> Flip b l r -> ShowS #

show :: Flip b l r -> String #

showList :: [Flip b l r] -> ShowS #