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

Safe HaskellNone
LanguageHaskell2010

Data.Barbie.Internal.Product

Synopsis

Documentation

class FunctorB b => ProductB b where Source #

Barbie-types that can form products, subject to the laws:

bmap (Pair a _) . uncurry . bprod = fst
bmap (Pair _ b) . uncurry . bprod = snd

Notice that because of the laws, having an internal product structure is not enough to have a lawful instance. E.g.

data Ok  f = Ok {o1 :: f String, o2 :: f Int}        -- has an instance
data Bad f = Bad{b1 :: f String, hiddenFromArg: Int} -- no lawful instance

Intuitively, the laws for this class require that b hides no structure from its argument f. Because of this, any x :: forall a . f a determines a unique value of b f, witnessed by the buniq method. Formally:

const (buniq x) = bmap (const x)

There is a default implementation of bprod and buniq for Generic types, so instances can derived automatically.

Methods

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

buniq :: (forall a. f a) -> b f Source #

bprod :: CanDeriveGenericInstance b => b f -> b g -> b (Product f g) Source #

buniq :: CanDeriveGenericInstance' b => (forall a. f a) -> b f Source #

Instances
ProductB b => ProductB (Barbie b) Source # 
Instance details

Defined in Data.Barbie.Internal.Instances

Methods

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

buniq :: (forall a. f a) -> Barbie b f Source #

bzip :: ProductB b => b f -> b g -> b (Product f g) Source #

An alias of bprod, since this is like a zip for Barbie-types.

bunzip :: ProductB b => b (Product f g) -> (b f, b g) Source #

An equivalent of unzip for Barbie-types.

bzipWith :: ProductB b => (forall a. f a -> g a -> h a) -> b f -> b g -> b h Source #

An equivalent of zipWith for Barbie-types.

bzipWith3 :: ProductB b => (forall a. f a -> g a -> h a -> i a) -> b f -> b g -> b h -> b i Source #

An equivalent of zipWith3 for Barbie-types.

bzipWith4 :: ProductB b => (forall a. f a -> g a -> h a -> i a -> j a) -> b f -> b g -> b h -> b i -> b j Source #

An equivalent of zipWith4 for Barbie-types.

(/*/) :: ProductB b => b f -> b g -> b (Prod '[f, g]) infixr 4 Source #

Like bprod, but returns a binary Prod, instead of Product, which composes better.

See /*/ for usage.

(/*) :: ProductB b => b f -> b (Prod fs) -> b (Prod (f ': fs)) infixr 4 Source #

Similar to /*/ but one of the sides is already a 'Prod fs'.

Note that /*, /*/ and uncurryn are meant to be used together: /* and /*/ combine b f1, b f2...b fn into a single product that can then be consumed by using uncurryn on an n-ary function. E.g.

f :: f a -> g a -> h a -> i a

bmap (uncurryn f) (bf /* bg /*/ bh)

type CanDeriveGenericInstance b = (Generic (b (Target F)), Generic (b (Target G)), Generic (b (Target FxG)), GProductB (Rep (b (Target F))), Rep (b (Target G)) ~ Repl (Target F) (Target G) (Rep (b (Target F))), Rep (b (Target FxG)) ~ Repl (Target F) (Target FxG) (Rep (b (Target F)))) Source #

The requirements to to derive ProductB (B f) are more strict than those for FunctorB or TraversableB. Intuitively, we need:

  • There is an instance of Generic (B f) for every f
  • B has only one constructor.
  • Every field of B' constructor is of the form 'f t'. That is, B has no hidden structure.

type CanDeriveGenericInstance' b = (Generic (b (Target F)), GProductB (Rep (b (Target F)))) Source #

class GProductB b Source #

Minimal complete definition

gbprod, gbuniq

Instances
GProductB (U1 :: * -> *) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

gbprod :: U1 x -> Repl (Target F) (Target G) U1 x -> Repl (Target F) (Target FxG) U1 x

gbuniq :: (forall a. f a) -> U1 x

(GProductB l, GProductB r) => GProductB (l :*: r) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

gbprod :: (l :*: r) x -> Repl (Target F) (Target G) (l :*: r) x -> Repl (Target F) (Target FxG) (l :*: r) x

gbuniq :: (forall a. f a) -> (l :*: r) x

GProductB x => GProductB (M1 i c x) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

gbprod :: M1 i c x x0 -> Repl (Target F) (Target G) (M1 i c x) x0 -> Repl (Target F) (Target FxG) (M1 i c x) x0

gbuniq :: (forall a. f a) -> M1 i c x x0

gbprodDefault :: CanDeriveGenericInstance b => b f -> b g -> b (Product f g) Source #

Default implementation of bprod based on Generic.

gbuniqDefault :: CanDeriveGenericInstance' b => (forall a. f a) -> b f Source #