barbies-2.0.4.0: Classes for working with types that can change clothes.
Safe Haskell None
Language Haskell2010

Data.Barbie.Constraints

Description

Deprecated: Use Data.Functor.Barbie or Barbie.Constraints

Synopsis

Instance dictionaries

data Dict c a where Source #

Dict c a is evidence that there exists an instance of c 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 .

Constructors

Dict :: c a => Dict c a

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 (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 .

type AllB c b = GAll 0 c ( GAllRepB b)

Methods

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

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

Instances

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

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c Proxy Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint ) (f :: k0 -> Type ). 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 Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint ) (f :: k0 -> Type ). 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 Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint ) (f :: k0 -> Type ). 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) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint ) (f :: k0 -> Type ). 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) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint ) (f :: k0 -> Type ). 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) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint ) (f :: k0 -> Type ). 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) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint ) (f :: k0 -> Type ). 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) Source #

Methods

baddDicts :: forall (c :: k0 -> Constraint ) (f0 :: k0 -> Type ). AllB c ( Compose f b) => Compose f b f0 -> Compose f b ( Product ( Dict c) f0) Source #

class ( ConstraintsB b, ProductB b) => ProductBC (b :: (k -> Type ) -> Type ) where Source #

Minimal complete definition

Nothing

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 .

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))
  

class c (f a) => ClassF c f a Source #

ClassF has one universal instance that makes ClassF c f a equivalent to c (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

Instances details
c (f a) => ClassF (c :: k1 -> Constraint ) (f :: k2 -> k1) (a :: k2) Source #
Instance details

Defined in Barbies.Internal.Dicts

class c (f a) (g a) => ClassFG c f g a Source #

Like ClassF but for binary relations.

Instances

Instances details
c (f a) (g a) => ClassFG (c :: k1 -> k2 -> Constraint ) (f :: k3 -> k1) (g :: k3 -> k2) (a :: k3) Source #
Instance details

Defined in Barbies.Internal.Dicts