| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Barbie.Internal.Constraints
- class FunctorB b => ConstraintsB b where
- type ConstraintsOf (c :: * -> Constraint) (f :: * -> *) b :: Constraint
- type CanDeriveGenericInstance b = (Generic (b (Target F)), Generic (b (Target PxF)), GAdjProof (ClassifyBarbie b) b (RecRep (b (Target F))), Rep (b (Target PxF)) ~ Repl' (Target F) (Target PxF) (RecRep (b (Target F))))
- type ConstraintsOfMatchesGenericDeriv c f b = (ConstraintsOf c f b ~ GConstraintsOf c f (RecRep (b (Target F))), ConstraintsOf c f b ~ ConstraintByType (ClassifyBarbie b) c f (RecRep (b (Target F))))
- type GConstraintsOf c f r = ConstraintByType (GClassifyBarbie r) c f r
- class GAdjProof (bt :: BarbieType) b rep
- gadjProofDefault :: forall b c f. (CanDeriveGenericInstance b, ConstraintsOfMatchesGenericDeriv c f b, ConstraintsOf c f b) => b f -> b (Product (DictOf c f) f)
- type family ConstraintByType bt (c :: * -> Constraint) (f :: * -> *) r :: Constraint where ...
Documentation
class FunctorB b => ConstraintsB b where Source #
Instances of this class provide means to talk about constraints,
both at compile-time, using ConstraintsOf and at run-time,
in the form of class instance dictionaries, via adjProof.
A manual definition would look like this:
data T f = A (fInt) (fString) | B (fBool) (fInt) instanceConstraintsBT where typeConstraintsOfc f T = (c (fInt), c (fString), c (fBool)) adjProof t = case t of A x y -> A (Pair(packDictx) (packDicty)) B z w -> B (Pair(packDictz) (packDictw))
There is a default implementation of ConstraintsOf for
Generic types, so in practice one will simply do:
derive instanceGenericT instanceConstraintsBT
Associated Types
type ConstraintsOf (c :: * -> Constraint) (f :: * -> *) b :: Constraint Source #
should contain a constraint ConstraintsOf c f bc (f x)
for each f x occurring in b. E.g.:
ConstraintsOfShowf Barbie = (Show(fString),Show(fInt))
Methods
adjProof :: forall c f. ConstraintsOf c f b => b f -> b (Product (DictOf c f) f) Source #
Adjoint a proof-of-instance to a barbie-type.
adjProof :: forall c f. (CanDeriveGenericInstance b, ConstraintsOfMatchesGenericDeriv c f b, ConstraintsOf c f b) => b f -> b (Product (DictOf c f) f) Source #
Adjoint a proof-of-instance to a barbie-type.
Instances
| ConstraintsB b => ConstraintsB (Barbie b) Source # | |
type CanDeriveGenericInstance b = (Generic (b (Target F)), Generic (b (Target PxF)), GAdjProof (ClassifyBarbie b) b (RecRep (b (Target F))), Rep (b (Target PxF)) ~ Repl' (Target F) (Target PxF) (RecRep (b (Target F)))) Source #
Intuivively, the requirements to have derived are:ConstraintsB B
- There is an instance of
for everyGeneric(B f)f - If
fis used as argument to some type in the definition ofB, it is only on a Barbie-type with aConstraintsBinstance.
type ConstraintsOfMatchesGenericDeriv c f b = (ConstraintsOf c f b ~ GConstraintsOf c f (RecRep (b (Target F))), ConstraintsOf c f b ~ ConstraintByType (ClassifyBarbie b) c f (RecRep (b (Target F)))) Source #
type GConstraintsOf c f r = ConstraintByType (GClassifyBarbie r) c f r Source #
gadjProofDefault :: forall b c f. (CanDeriveGenericInstance b, ConstraintsOfMatchesGenericDeriv c f b, ConstraintsOf c f b) => b f -> b (Product (DictOf c f) f) Source #
type family ConstraintByType bt (c :: * -> Constraint) (f :: * -> *) r :: Constraint where ... Source #
Equations
| ConstraintByType bt c f (M1 _i _c x) = ConstraintByType bt c f x | |
| ConstraintByType bt c f V1 = () | |
| ConstraintByType bt c f U1 = () | |
| ConstraintByType bt c f (l :*: r) = (ConstraintByType bt c f l, ConstraintByType bt c f r) | |
| ConstraintByType bt c f (l :+: r) = (ConstraintByType bt c f l, ConstraintByType bt c f r) | |
| ConstraintByType WearBarbie c f (K1 R (NonRec (Target (W F) a))) = (c (Wear f a), Wear f a ~ f a) | |
| ConstraintByType NonWearBarbie c f (K1 R (NonRec (Target F a))) = c (f a) | |
| ConstraintByType bt c f (K1 R (NonRec (b (Target F)))) = ConstraintsOf c f b | |
| ConstraintByType bt c f (K1 R (RecUsage (b (Target F)))) = () | |
| ConstraintByType bt c f (K1 _i _c) = () |