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

Safe HaskellNone
LanguageHaskell2010

Data.Barbie.Constraints

Contents

Description

Support for operating on Barbie-types with constrained functions.

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.

This module adds support to overcome this problem.

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 
Instances
Show1 (Dict c) Source # 
Instance details

Defined in Data.Barbie.Internal.Dicts

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Dict c a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Dict c a] -> ShowS #

Eq (Dict c a) Source # 
Instance details

Defined in Data.Barbie.Internal.Dicts

Methods

(==) :: Dict c a -> Dict c a -> Bool #

(/=) :: Dict c a -> Dict c a -> Bool #

Show (Dict c a) Source # 
Instance details

Defined in Data.Barbie.Internal.Dicts

Methods

showsPrec :: Int -> Dict c a -> ShowS #

show :: Dict c a -> String #

showList :: [Dict c a] -> ShowS #

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 -> *) -> *) 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 if we given a T f, we need to use the Show instance of their fields, we can use:

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

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 Barbie ~ (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 Data.Barbie.Internal.Constraints

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 Data.Barbie.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 Data.Barbie.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 Data.Barbie.Internal.Constraints

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 Data.Barbie.Internal.Instances

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 Data.Barbie.Internal.Constraints

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 Data.Barbie.Internal.Constraints

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 Data.Barbie.Internal.Constraints

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 #

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

Every type b that is an instance of both ProductB and ConstraintsB can be made an instance of ProductBC as well.

Intuitively, in addition to buniq from ProductB, one can define buniqC that takes into account constraints:

buniq :: (forall a . f a) -> b f
buniqC :: AllB c b => (forall a . c a => f a) -> b f

For technical reasons, buniqC is not currently provided as a method of this class and is instead defined in terms bdicts, which is similar to baddDicts but can produce the instance dictionaries out-of-the-blue. bdicts could also be defined in terms of buniqC, so they are essentially equivalent.

bdicts :: forall c b . AllB c b => b (Dict c)
bdicts = buniqC (Dict @c)

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

Minimal complete definition

Nothing

Methods

bdicts :: AllB c b => b (Dict c) Source #

bdicts :: (CanDeriveProductBC c b, AllB c b) => b (Dict c) Source #

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

Defined in Data.Barbie.Internal.ProductC

Methods

bdicts :: AllB c Proxy => Proxy (Dict c) Source #

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

Defined in Data.Barbie.Trivial

Methods

bdicts :: AllB c Unit => Unit (Dict c) Source #

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

Defined in Data.Barbie.Internal.Instances

Methods

bdicts :: AllB c (Barbie b) => Barbie b (Dict c) Source #

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

Defined in Data.Barbie.Internal.ProductC

Methods

bdicts :: AllB c (Product a b) => Product a b (Dict c) Source #

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)

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   Barbie ~ (Show    String,  Show    Int)
  AllBF Show f Barbie ~ (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
c (f a) => ClassF (c :: k2 -> Constraint) (f :: k1 -> k2) (a :: k1) Source # 
Instance details

Defined in Data.Barbie.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 :: k2 -> k3 -> Constraint) (f :: k1 -> k2) (g :: k1 -> k3) (a :: k1) Source # 
Instance details

Defined in Data.Barbie.Internal.Dicts

Deprecated

type ConstraintsOf c f b = AllBF c f b Source #

Deprecated: Renamed to AllBF (now based on AllB)

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

Deprecated: Renamed to baddDicts

type ProofB b = ProductBC b Source #

Deprecated: Class was renamed to ProductBC