barbies-2.1.1.0: Classes for working with types that can change clothes.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Barbies.Constraints

Description

Support for operating on Barbie-types with constrained functions.

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

Instances details
Show1 (Dict c) Source # 
Instance details

Defined in Barbies.Internal.Dicts

Methods

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

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

Show (Dict c a) Source # 
Instance details

Defined in Barbies.Internal.Dicts

Methods

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

show :: Dict c a -> String #

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

Eq (Dict c a) Source # 
Instance details

Defined in Barbies.Internal.Dicts

Methods

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

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

requiringDict :: (c a => r) -> Dict c a -> r Source #

Turn a constrained-function into an unconstrained one that uses the packed instance dictionary instead.

Getting constraints

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

Helpers

class (c a, d a) => (c & d) a Source #

Instances

Instances details
(c a, d a) => ((c :: k -> Constraint) & (d :: k -> Constraint)) (a :: k) Source # 
Instance details

Defined in Barbies.Internal.ConstraintsB