Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Deprecated: Use Data.Functor.Barbie or Barbie.Constraints
Synopsis
- data Dict c a where
- requiringDict :: (c a => r) -> Dict c a -> r
- class FunctorB b => ConstraintsB (b :: (k -> Type) -> Type) where
- type AllB (c :: k -> Constraint) b :: Constraint
- baddDicts :: forall c f. AllB c b => b f -> b (Dict c `Product` f)
- class (ConstraintsB b, ProductB b) => ProductBC (b :: (k -> Type) -> Type) where
- bmapC :: forall c b f g. (AllB c b, ConstraintsB b) => (forall a. c a => f a -> g a) -> b f -> b g
- 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)
- type AllBF c f b = AllB (ClassF c f) b
- class c (f a) => ClassF c f a
- class c (f a) (g a) => ClassFG c f g a
Instance dictionaries
is evidence that there exists an instance of Dict
c ac a
.
It is essentially equivalent to Dict (c a)
from the
constraints package,
but because of its kind, it allows us to define things like
.Dict
Show
requiringDict :: (c a => r) -> Dict c a -> r Source #
Turn a constrained-function into an unconstrained one that uses the packed instance dictionary instead.
Retrieving dictionaries
class FunctorB b => ConstraintsB (b :: (k -> Type) -> Type) 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 (fInt
) (fString
) | B (fBool
) (fInt
) instanceConstraintsB
T where typeAllB
c T = (cInt
, cString
, cBool
)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 instanceGeneric
(T f) instanceConstraintsB
T
Nothing
type AllB (c :: k -> Constraint) b :: Constraint Source #
Instances
ConstraintsB (Unit :: (k -> Type) -> Type) Source # | |
ConstraintsB (Void :: (k -> Type) -> Type) Source # | |
ConstraintsB (Proxy :: (k -> Type) -> Type) Source # | |
ConstraintsB b => ConstraintsB (Barbie b :: (k -> Type) -> TYPE LiftedRep) Source # | |
ConstraintsB (Const a :: (k -> Type) -> Type) Source # | |
(ConstraintsB a, ConstraintsB b) => ConstraintsB (Product a b :: (k -> Type) -> Type) Source # | |
(ConstraintsB a, ConstraintsB b) => ConstraintsB (Sum a b :: (k -> Type) -> Type) Source # | |
(Functor f, ConstraintsB b) => ConstraintsB (Compose f b :: (k -> Type) -> Type) Source # | |
class (ConstraintsB b, ProductB b) => ProductBC (b :: (k -> Type) -> Type) where Source #
Nothing
Instances
ProductBC (Unit :: (k -> Type) -> Type) Source # | |
Defined in Data.Barbie.Internal.ProductC | |
ProductBC (Proxy :: (k -> Type) -> Type) Source # | |
Defined in Data.Barbie.Internal.ProductC | |
ProductBC b => ProductBC (Barbie b :: (k -> Type) -> TYPE LiftedRep) Source # | |
Defined in Data.Barbie.Internal.ProductC | |
(ProductBC a, ProductBC b) => ProductBC (Product a b :: (k -> Type) -> Type) Source # | |
Defined in Data.Barbie.Internal.ProductC |
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 Show
able 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)
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
.
class c (f a) => ClassF c f a Source #
ClassF
has one universal instance that makes
equivalent to ClassF
c f ac (f a)
. However, we have
'ClassF c f :: k -> Constraint
This is useful since it allows to define constraint-constructors like
ClassF
Monoid
Maybe
Instances
c (f a) => ClassF (c :: k1 -> Constraint) (f :: k2 -> k1) (a :: k2) Source # | |
Defined in Barbies.Internal.Dicts |
class c (f a) (g a) => ClassFG c f g a Source #
Like ClassF
but for binary relations.
Instances
c (f a) (g a) => ClassFG (c :: k1 -> k2 -> Constraint) (f :: k3 -> k1) (g :: k3 -> k2) (a :: k3) Source # | |
Defined in Barbies.Internal.Dicts |