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

Safe HaskellNone
LanguageHaskell2010

Data.Functor.Barbie

Contents

Description

Functors from indexed-types to types.

Synopsis

Functor

class FunctorB (b :: (k -> Type) -> Type) where Source #

Barbie-types that can be mapped over. Instances of FunctorB should satisfy the following laws:

bmap id = id
bmap f . bmap g = bmap (f . g)

There is a default bmap implementation for Generic types, so instances can derived automatically.

Minimal complete definition

Nothing

Methods

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

bmap :: forall f g. CanDeriveFunctorB b f g => (forall a. f a -> g a) -> b f -> b g Source #

Instances
FunctorB (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Proxy f -> Proxy g Source #

FunctorB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Void f -> Void g Source #

FunctorB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Unit f -> Unit g Source #

FunctorB (Constant x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Constant x f -> Constant x g Source #

FunctorB (Const x :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Const x f -> Const x g Source #

FunctorB b => FunctorB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

bmap :: (forall (a :: k0). f a -> g a) -> Barbie b f -> Barbie b g Source #

(FunctorB a, FunctorB b) => FunctorB (Sum a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a0 :: k0). f a0 -> g a0) -> Sum a b f -> Sum a b g Source #

(FunctorB a, FunctorB b) => FunctorB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a0 :: k0). f a0 -> g a0) -> Product a b f -> Product a b g Source #

(Functor f, FunctorB b) => FunctorB (Compose f b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap :: (forall (a :: k0). f0 a -> g a) -> Compose f b f0 -> Compose f b g 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 #

Traversable

class FunctorB b => TraversableB (b :: (k -> Type) -> Type) where Source #

Barbie-types that can be traversed from left to right. Instances should satisfy the following laws:

 t . btraverse f   = btraverse (t . f)  -- naturality
btraverse Identity = Identity           -- identity
btraverse (Compose . fmap g . f) = Compose . fmap (btraverse g) . btraverse f -- composition

There is a default btraverse implementation for Generic types, so instances can derived automatically.

Minimal complete definition

Nothing

Methods

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

btraverse :: (Applicative e, CanDeriveTraversableB b f g) => (forall a. f a -> e (g a)) -> b f -> e (b g) Source #

Instances
TraversableB (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Proxy f -> e (Proxy g) Source #

TraversableB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Void f -> e (Void g) Source #

TraversableB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Unit f -> e (Unit g) Source #

TraversableB (Constant a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Constant a f -> e (Constant a g) Source #

TraversableB (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Const a f -> e (Const a g) Source #

TraversableB b => TraversableB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

btraverse :: Applicative e => (forall (a :: k0). f a -> e (g a)) -> Barbie b f -> e (Barbie b g) Source #

(TraversableB a, TraversableB b) => TraversableB (Sum a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Sum a b f -> e (Sum a b g) Source #

(TraversableB a, TraversableB b) => TraversableB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a0 :: k0). f a0 -> e (g a0)) -> Product a b f -> e (Product a b g) Source #

(Traversable f, TraversableB b) => TraversableB (Compose f b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverse :: Applicative e => (forall (a :: k0). f0 a -> e (g a)) -> Compose f b f0 -> e (Compose f b 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 #

Utility functions

btraverse_ :: (TraversableB b, Applicative e) => (forall a. f a -> e c) -> b f -> e () Source #

Map each element to an action, evaluate these actions from left to right, and ignore the results.

bfoldMap :: (TraversableB b, Monoid m) => (forall a. f a -> m) -> b f -> m Source #

Map each element to a monoid, and combine the results.

bsequence :: (Applicative e, TraversableB b) => b (Compose e f) -> e (b f) Source #

Evaluate each action in the structure from left to right, and collect the results.

bsequence' :: (Applicative e, TraversableB b) => b e -> e (b Identity) Source #

A version of bsequence with f specialized to Identity.

Distributive

class FunctorB b => DistributiveB (b :: (k -> Type) -> Type) where Source #

A FunctorB where the effects can be distributed to the fields: bdistribute turns an effectful way of building a Barbie-type into a pure Barbie-type with effectful ways of computing the values of its fields.

This class is the categorical dual of TraversableB, with bdistribute the dual of bsequence and bcotraverse the dual of btraverse. As such, instances need to satisfy these laws:

bdistribute . h = bmap (Compose . h . getCompose) . bdistribute    -- naturality
bdistribute . Identity = bmap (Compose . Identity)                 -- identity
bdistribute . Compose = bmap (Compose . Compose . fmap getCompose . getCompose) . bdistribute . fmap bdistribute -- composition

By specializing f to ((->) a) and g to Identity, we can define a function that decomposes a function on distributive barbies into a collection of simpler functions:

bdecompose :: DistributiveB b => (a -> b Identity) -> b ((->) a)
bdecompose = bmap (fmap runIdentity . getCompose) . bdistribute

Lawful instances of the class can then be characterized as those that satisfy:

brecompose . bdecompose = id
bdecompose . brecompose = id

This means intuitively that instances need to have a fixed shape (i.e. no sum-types can be involved). Typically, this means record types, as long as they don't contain fields where the functor argument is not applied.

There is a default implementation of bdistribute based on Generic. Intuitively, it works on product types where the shape of a pure value is uniquely defined and every field is covered by the argument f.

Minimal complete definition

Nothing

Methods

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

bdistribute :: forall f g. CanDeriveDistributiveB b f g => Functor f => f (b g) -> b (Compose f g) Source #

Instances
DistributiveB (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveB

Methods

bdistribute :: Functor f => f (Proxy g) -> Proxy (Compose f g) Source #

DistributiveB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bdistribute :: Functor f => f (Unit g) -> Unit (Compose f g) Source #

(DistributiveB a, DistributiveB b) => DistributiveB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveB

Methods

bdistribute :: Functor f => f (Product a b g) -> Product a b (Compose 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 #

(Distributive h, DistributiveB b) => DistributiveB (Compose h b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.DistributiveB

Methods

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

bdistribute' :: (DistributiveB b, Functor f) => f (b Identity) -> b f Source #

A version of bdistribute with g specialized to Identity.

bcotraverse :: (DistributiveB b, Functor f) => (forall a. f (g a) -> f a) -> f (b g) -> b f Source #

Dual of btraverse

bdecompose :: DistributiveB b => (a -> b Identity) -> b ((->) a) Source #

Decompose a function returning a distributive barbie, into a collection of simpler functions.

brecompose :: FunctorB b => b ((->) a) -> a -> b Identity Source #

Recompose a decomposed function.

Applicative

class FunctorB b => ApplicativeB (b :: (k -> Type) -> Type) where Source #

A FunctorB with application, providing operations to:

  • embed an "empty" value (bpure)
  • align and combine values (bprod)

It should satisfy the following laws:

Naturality of bprod
bmap ((Pair a b) -> Pair (f a) (g b)) (u `bprod' v) = bmap f u `bprod' bmap g v
Left and right identity
bmap ((Pair _ b) -> b) (bpure e `bprod' v) = v
bmap ((Pair a _) -> a) (u `bprod' bpure e) = u
Associativity
bmap ((Pair a (Pair b c)) -> Pair (Pair a b) c) (u `bprod' (v `bprod' w)) = (u `bprod' v) `bprod' w

It is to FunctorB in the same way as Applicative relates to Functor. For a presentation of Applicative as a monoidal functor, see Section 7 of Applicative Programming with Effects.

There is a default implementation of bprod and bpure based on Generic. Intuitively, it works on types where the value of bpure is uniquely defined. This corresponds rougly to record types (in the presence of sums, there would be several candidates for bpure), where every field is either a Monoid or covered by the argument f.

Minimal complete definition

Nothing

Methods

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

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

bpure :: CanDeriveApplicativeB b f f => (forall a. f a) -> b f Source #

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

Instances
(ProductB b, FunctorB b) => ApplicativeB (b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Barbie.Internal.Product

Methods

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

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

ApplicativeB (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure :: (forall (a :: k0). f a) -> Proxy f Source #

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

ApplicativeB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Methods

bpure :: (forall (a :: k0). f a) -> Unit f Source #

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

Monoid a => ApplicativeB (Constant a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure :: (forall (a0 :: k0). f a0) -> Constant a f Source #

bprod :: Constant a f -> Constant a g -> Constant a (Product f g) Source #

Monoid a => ApplicativeB (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure :: (forall (a0 :: k0). f a0) -> Const a f Source #

bprod :: Const a f -> Const a g -> Const a (Product f g) Source #

ApplicativeB b => ApplicativeB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Methods

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

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

(ApplicativeB a, ApplicativeB b) => ApplicativeB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure :: (forall (a0 :: k0). f a0) -> Product a b f Source #

bprod :: Product a b f -> Product a b g -> Product a b (Product f 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 #

Utility functions

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

An alias of bprod, since this is like a zip.

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

An equivalent of unzip.

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

An equivalent of zipWith.

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

An equivalent of zipWith3.

bzipWith4 :: ApplicativeB 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.

Constraints and instance dictionaries

Consider the following function:

showIt :: Show a => Maybe a -> Const String a
showIt = Const . show

We would then like to be able to do:

bmap showIt :: FunctorB b => b Maybe -> b (Const String)

This however doesn't work because of the (Show a) constraint in the the type of showIt.

The ConstraintsB class let us overcome this problem.

class FunctorB b => ConstraintsB (b :: (k -> *) -> *) where Source #

Instances of this class provide means to talk about constraints, both at compile-time, using AllB, and at run-time, in the form of Dict, via baddDicts.

A manual definition would look like this:

data T f = A (f Int) (f String) | B (f Bool) (f Int)

instance ConstraintsB T where
  type AllB c T = (c Int, c String, c Bool)

  baddDicts t = case t of
    A x y -> A (Pair Dict x) (Pair Dict y)
    B z w -> B (Pair Dict z) (Pair Dict w)

Now, when we given a T f, if we need to use the Show instance of their fields, we can use:

baddDicts :: AllB Show b => b f -> b (Dict Show `Product' f)

There is a default implementation of ConstraintsB for Generic types, so in practice one will simply do:

derive instance Generic (T f)
instance ConstraintsB T

Minimal complete definition

Nothing

Associated Types

type AllB (c :: k -> Constraint) b :: Constraint Source #

AllB c b should contain a constraint c a for each a occurring under an f in b f. E.g.:

AllB Show Person ~ (Show String, Show Int)

For requiring constraints of the form c (f a), use AllBF.

Methods

baddDicts :: forall c f. AllB c b => b f -> b (Dict c `Product` f) Source #

baddDicts :: forall c f. (CanDeriveConstraintsB c b f, AllB c b) => b f -> b (Dict c `Product` f) Source #

Instances
ConstraintsB (Proxy :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c Proxy :: Constraint Source #

Methods

baddDicts :: AllB c Proxy => Proxy f -> Proxy (Product (Dict c) f) Source #

ConstraintsB (Void :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type AllB c Void :: Constraint Source #

Methods

baddDicts :: AllB c Void => Void f -> Void (Product (Dict c) f) Source #

ConstraintsB (Unit :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type AllB c Unit :: Constraint Source #

Methods

baddDicts :: AllB c Unit => Unit f -> Unit (Product (Dict c) f) Source #

ConstraintsB (Const a :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Const a) :: Constraint Source #

Methods

baddDicts :: AllB c (Const a) => Const a f -> Const a (Product (Dict c) f) Source #

ConstraintsB b => ConstraintsB (Barbie b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.Wrappers

Associated Types

type AllB c (Barbie b) :: Constraint Source #

Methods

baddDicts :: AllB c (Barbie b) => Barbie b f -> Barbie b (Product (Dict c) f) Source #

(ConstraintsB a, ConstraintsB b) => ConstraintsB (Sum a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Sum a b) :: Constraint Source #

Methods

baddDicts :: AllB c (Sum a b) => Sum a b f -> Sum a b (Product (Dict c) f) Source #

(ConstraintsB a, ConstraintsB b) => ConstraintsB (Product a b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Product a b) :: Constraint Source #

Methods

baddDicts :: AllB c (Product a b) => Product a b f -> Product a b (Product (Dict c) f) Source #

(Functor f, ConstraintsB b) => ConstraintsB (Compose f b :: (k -> Type) -> Type) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c (Compose f b) :: Constraint Source #

Methods

baddDicts :: AllB c (Compose f b) => Compose f b f0 -> Compose f b (Product (Dict c) f0) Source #

type AllBF c f b = AllB (ClassF c f) b Source #

Similar to AllB but will put the functor argument f between the constraint c and the type a. For example:

  AllB  Show   Person ~ (Show    String,  Show    Int)
  AllBF Show f Person ~ (Show (f String), Show (f Int))
  

Utility functions

bdicts :: forall c b. (ConstraintsB b, ApplicativeB b, AllB c b) => b (Dict c) Source #

Similar to baddDicts but can produce the instance dictionaries "out of the blue".

bmapC :: forall c b f g. (AllB c b, ConstraintsB b) => (forall a. c a => f a -> g a) -> b f -> b g Source #

Like bmap but a constraint is allowed to be required on each element of b

E.g. If all fields of b are Showable then you could store each shown value in it's slot using Const:

showFields :: (AllB Show b, ConstraintsB b) => b Identity -> b (Const String)
showFields = bmapC @Show showField
  where
    showField :: forall a. Show a => Identity a -> Const String a
    showField (Identity a) = Const (show a)

bfoldMapC :: forall c b m f. (TraversableB b, ConstraintsB b, AllB c b, Monoid m) => (forall a. c a => f a -> m) -> b f -> m Source #

btraverseC :: forall c b f g e. (TraversableB b, ConstraintsB b, AllB c b, Applicative e) => (forall a. c a => f a -> e (g a)) -> b f -> e (b g) Source #

Like btraverse but with a constraint on the elements of b.

bpureC :: forall c f b. (AllB c b, ConstraintsB b, ApplicativeB b) => (forall a. c a => f a) -> b f Source #

Like bpure but a constraint is allowed to be required on each element of b.

bzipWithC :: forall c b f g h. (AllB c b, ConstraintsB b, ApplicativeB b) => (forall a. c a => f a -> g a -> h a) -> b f -> b g -> b h Source #

Like bzipWith but with a constraint on the elements of b.

bzipWith3C :: forall c b f g h i. (AllB c b, ConstraintsB b, ApplicativeB b) => (forall a. c a => f a -> g a -> h a -> i a) -> b f -> b g -> b h -> b i Source #

Like bzipWith3 but with a constraint on the elements of b.

bzipWith4C :: forall c b f g h i j. (AllB c b, ConstraintsB b, ApplicativeB b) => (forall a. c a => f a -> g a -> h a -> i a -> j a) -> b f -> b g -> b h -> b i -> b j Source #

Like bzipWith4 but with a constraint on the elements of b.

bmempty :: forall f b. (AllBF Monoid f b, ConstraintsB b, ApplicativeB b) => b f Source #

Builds a b f, by applying mempty on every field of b.

Support for generic derivations

newtype Rec (p :: Type) a x Source #

Constructors

Rec 

Fields

Instances
GTraversable (n :: k3) (f :: k2 -> Type) (g :: k2 -> Type) (Rec a a :: k1 -> Type) (Rec a a :: k1 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Traversable

Methods

gtraverse :: Applicative t => Proxy n -> (forall (a0 :: k). f a0 -> t (g a0)) -> Rec a a x -> t (Rec a a x) Source #

GConstraints n (c :: k3 -> Constraint) (f :: k2) (Rec a' a :: Type -> Type) (Rec a a :: k1 -> Type) (Rec a a :: k1 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Constraints

Methods

gaddDicts :: GAll n c (Rec a' a) => Rec a a x -> Rec a a x Source #

Monoid x => GApplicative (n :: k3) (f :: k2 -> Type) (g :: k2 -> Type) (Rec x x :: k1 -> Type) (Rec x x :: k1 -> Type) (Rec x x :: k1 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Applicative

Methods

gprod :: Proxy n -> Proxy f -> Proxy g -> Rec x x x0 -> Rec x x x0 -> Rec x x x0 Source #

gpure :: (f ~ g, Rec x x ~ Rec x x) => Proxy n -> Proxy f -> Proxy (Rec x x) -> Proxy (Rec x x) -> (forall (a :: k). f a) -> Rec x x x0 Source #

GFunctor n (f :: k2 -> Type) (g :: k2 -> Type) (Rec x x :: k1 -> Type) (Rec x x :: k1 -> Type) Source # 
Instance details

Defined in Barbies.Generics.Functor

Methods

gmap :: Proxy n -> (forall (a :: k). f a -> g a) -> Rec x x x0 -> Rec x x x0 Source #

repbi ~ repbb => GBare n (Rec repbi repbi :: k -> Type) (Rec repbb repbb :: k -> Type) Source # 
Instance details

Defined in Barbies.Generics.Bare

Methods

gstrip :: Proxy n -> Rec repbi repbi x -> Rec repbb repbb x Source #

gcover :: Proxy n -> Rec repbb repbb x -> Rec repbi repbi x Source #

type GAll n (c :: k -> Constraint) (Rec a a :: Type -> Type) Source # 
Instance details

Defined in Barbies.Generics.Constraints

type GAll n (c :: k -> Constraint) (Rec a a :: Type -> Type) = ()