constraints-0.10: Constraint manipulation

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Constraint

Contents

Description

ConstraintKinds made type classes into types of a new kind, Constraint.

Eq :: * -> Constraint
Ord :: * -> Constraint
Monad :: (* -> *) -> Constraint

The need for this extension was first publicized in the paper

Scrap your boilerplate with class: extensible generic functions

by Ralf Lämmel and Simon Peyton Jones in 2005, which shoehorned all the things they needed into a custom Sat typeclass.

With ConstraintKinds we can put into code a lot of tools for manipulating these new types without such awkward workarounds.

Synopsis

The Kind of Constraints

data Constraint :: * #

The kind of constraints, like Show a

Dictionary

data Dict :: Constraint -> * where Source #

Values of type Dict p capture a dictionary for a constraint of type p.

e.g.

Dict :: Dict (Eq Int)

captures a dictionary that proves we have an:

instance Eq 'Int

Pattern matching on the Dict constructor will bring this instance into scope.

Constructors

Dict :: a => Dict a 

Instances

a :=> (Monoid (Dict a)) Source # 

Methods

ins :: a :- Monoid (Dict a) Source #

a :=> (Read (Dict a)) Source # 

Methods

ins :: a :- Read (Dict a) Source #

a :=> (Bounded (Dict a)) Source # 

Methods

ins :: a :- Bounded (Dict a) Source #

a :=> (Enum (Dict a)) Source # 

Methods

ins :: a :- Enum (Dict a) Source #

() :=> (Eq (Dict a)) Source # 

Methods

ins :: () :- Eq (Dict a) Source #

() :=> (Ord (Dict a)) Source # 

Methods

ins :: () :- Ord (Dict a) Source #

() :=> (Show (Dict a)) Source # 

Methods

ins :: () :- Show (Dict a) Source #

() :=> (Semigroup (Dict a)) Source # 

Methods

ins :: () :- Semigroup (Dict a) Source #

a => Bounded (Dict a) Source # 

Methods

minBound :: Dict a #

maxBound :: Dict a #

a => Enum (Dict a) Source # 

Methods

succ :: Dict a -> Dict a #

pred :: Dict a -> Dict a #

toEnum :: Int -> Dict a #

fromEnum :: Dict a -> Int #

enumFrom :: Dict a -> [Dict a] #

enumFromThen :: Dict a -> Dict a -> [Dict a] #

enumFromTo :: Dict a -> Dict a -> [Dict a] #

enumFromThenTo :: Dict a -> Dict a -> Dict a -> [Dict a] #

Eq (Dict a) Source # 

Methods

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

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

(Typeable Constraint p, p) => Data (Dict p) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dict p -> c (Dict p) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dict p) #

toConstr :: Dict p -> Constr #

dataTypeOf :: Dict p -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Dict p)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dict p)) #

gmapT :: (forall b. Data b => b -> b) -> Dict p -> Dict p #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dict p -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dict p -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

Ord (Dict a) Source # 

Methods

compare :: Dict a -> Dict a -> Ordering #

(<) :: Dict a -> Dict a -> Bool #

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

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

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

max :: Dict a -> Dict a -> Dict a #

min :: Dict a -> Dict a -> Dict a #

a => Read (Dict a) Source # 
Show (Dict a) Source # 

Methods

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

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

Semigroup (Dict a) Source # 

Methods

(<>) :: Dict a -> Dict a -> Dict a #

sconcat :: NonEmpty (Dict a) -> Dict a #

stimes :: Integral b => b -> Dict a -> Dict a #

a => Monoid (Dict a) Source # 

Methods

mempty :: Dict a #

mappend :: Dict a -> Dict a -> Dict a #

mconcat :: [Dict a] -> Dict a #

NFData (Dict c) Source # 

Methods

rnf :: Dict c -> () #

withDict :: Dict a -> (a => r) -> r Source #

From a Dict, takes a value in an environment where the instance witnessed by the Dict is in scope, and evaluates it.

Essentially a deconstruction of a Dict into its continuation-style form.

Entailment

newtype a :- b infixr 9 Source #

This is the type of entailment.

a :- b is read as a "entails" b.

With this we can actually build a category for Constraint resolution.

e.g.

Because Eq a is a superclass of Ord a, we can show that Ord a entails Eq a.

Because instance Ord a => Ord [a] exists, we can show that Ord a entails Ord [a] as well.

This relationship is captured in the :- entailment type here.

Since p :- p and entailment composes, :- forms the arrows of a Category of constraints. However, Category only became sufficiently general to support this instance in GHC 7.8, so prior to 7.8 this instance is unavailable.

But due to the coherence of instance resolution in Haskell, this Category has some very interesting properties. Notably, in the absence of IncoherentInstances, this category is "thin", which is to say that between any two objects (constraints) there is at most one distinguishable arrow.

This means that for instance, even though there are two ways to derive Ord a :- Eq [a], the answers from these two paths _must_ by construction be equal. This is a property that Haskell offers that is pretty much unique in the space of languages with things they call "type classes".

What are the two ways?

Well, we can go from Ord a :- Eq a via the superclass relationship, and then from Eq a :- Eq [a] via the instance, or we can go from Ord a :- Ord [a] via the instance then from Ord [a] :- Eq [a] through the superclass relationship and this diagram by definition must "commute".

Diagrammatically,

                   Ord a
               ins /     \ cls
                  v       v
            Ord [a]     Eq a
               cls \     / ins
                    v   v
                   Eq [a]

This safety net ensures that pretty much anything you can write with this library is sensible and can't break any assumptions on the behalf of library authors.

Constructors

Sub (a => Dict b) 

Instances

Category Constraint (:-) Source #

Possible since GHC 7.8, when Category was made polykinded.

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

() :=> (Eq ((:-) a b)) Source # 

Methods

ins :: () :- Eq (a :- b) Source #

() :=> (Ord ((:-) a b)) Source # 

Methods

ins :: () :- Ord (a :- b) Source #

() :=> (Show ((:-) a b)) Source # 

Methods

ins :: () :- Show (a :- b) Source #

Eq ((:-) a b) Source #

Assumes IncoherentInstances doesn't exist.

Methods

(==) :: (a :- b) -> (a :- b) -> Bool #

(/=) :: (a :- b) -> (a :- b) -> Bool #

(Typeable Constraint p, Typeable Constraint q, p, q) => Data ((:-) p q) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> (p :- q) -> c (p :- q) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (p :- q) #

toConstr :: (p :- q) -> Constr #

dataTypeOf :: (p :- q) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (p :- q)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (p :- q)) #

gmapT :: (forall b. Data b => b -> b) -> (p :- q) -> p :- q #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (p :- q) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (p :- q) -> r #

gmapQ :: (forall d. Data d => d -> u) -> (p :- q) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> (p :- q) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) #

Ord ((:-) a b) Source #

Assumes IncoherentInstances doesn't exist.

Methods

compare :: (a :- b) -> (a :- b) -> Ordering #

(<) :: (a :- b) -> (a :- b) -> Bool #

(<=) :: (a :- b) -> (a :- b) -> Bool #

(>) :: (a :- b) -> (a :- b) -> Bool #

(>=) :: (a :- b) -> (a :- b) -> Bool #

max :: (a :- b) -> (a :- b) -> a :- b #

min :: (a :- b) -> (a :- b) -> a :- b #

Show ((:-) a b) Source # 

Methods

showsPrec :: Int -> (a :- b) -> ShowS #

show :: (a :- b) -> String #

showList :: [a :- b] -> ShowS #

a => NFData ((:-) a b) Source # 

Methods

rnf :: (a :- b) -> () #

(\\) :: a => (b => r) -> (a :- b) -> r infixl 1 Source #

Given that a :- b, derive something that needs a context b, using the context a

weaken1 :: (a, b) :- a Source #

Weakening a constraint product

The category of constraints is Cartesian. We can forget information.

weaken2 :: (a, b) :- b Source #

Weakening a constraint product

The category of constraints is Cartesian. We can forget information.

contract :: a :- (a, a) Source #

Contracting a constraint / diagonal morphism

The category of constraints is Cartesian. We can reuse information.

strengthen1 :: Dict b -> (a :- c) -> a :- (b, c) Source #

strengthen2 :: Dict b -> (a :- c) -> a :- (c, b) Source #

(&&&) :: (a :- b) -> (a :- c) -> a :- (b, c) Source #

Constraint product

trans weaken1 (f &&& g) = f
trans weaken2 (f &&& g) = g

(***) :: (a :- b) -> (c :- d) -> (a, c) :- (b, d) Source #

due to the hack for the kind of (,) in the current version of GHC we can't actually make instances for (,) :: Constraint -> Constraint -> Constraint, but (,) is a bifunctor on the category of constraints. This lets us map over both sides.

trans :: (b :- c) -> (a :- b) -> a :- c Source #

Transitivity of entailment

If we view (:-) as a Constraint-indexed category, then this is (.)

refl :: a :- a Source #

Reflexivity of entailment

If we view (:-) as a Constraint-indexed category, then this is id

class Any => Bottom where Source #

Any inhabits every kind, including Constraint but is uninhabited, making it impossible to define an instance.

Minimal complete definition

no

Methods

no :: a Source #

top :: a :- () Source #

Every constraint implies truth

These are the terminal arrows of the category, and () is the terminal object.

Given any constraint there is a unique entailment of the () constraint from that constraint.

bottom :: Bottom :- a Source #

This demonstrates the law of classical logic "ex falso quodlibet"

Dict is fully faithful

mapDict :: (a :- b) -> Dict a -> Dict b Source #

Apply an entailment to a dictionary.

From a category theoretic perspective Dict is a functor that maps from the category of constraints (with arrows in :-) to the category Hask of Haskell data types.

unmapDict :: (Dict a -> Dict b) -> a :- b Source #

This functor is fully faithful, which is to say that given any function you can write Dict a -> Dict b there also exists an entailment a :- b in the category of constraints that you can build.

Reflection

class Class b h | h -> b where Source #

Reify the relationship between a class and its superclass constraints as a class

Given a definition such as

class Foo a => Bar a

you can capture the relationship between 'Bar a' and its superclass 'Foo a' with

instance Class (Foo a) (Bar a) where cls = Sub Dict

Now the user can use 'cls :: Bar a :- Foo a'

Minimal complete definition

cls

Methods

cls :: h :- b Source #

Instances

Class () () Source # 

Methods

cls :: () :- () Source #

Class () (Bounded a) Source # 

Methods

cls :: Bounded a :- () Source #

Class () (Enum a) Source # 

Methods

cls :: Enum a :- () Source #

Class () (Eq a) Source # 

Methods

cls :: Eq a :- () Source #

Class () (Functor f) Source # 

Methods

cls :: Functor f :- () Source #

Class () (Num a) Source # 

Methods

cls :: Num a :- () Source #

Class () (Read a) Source # 

Methods

cls :: Read a :- () Source #

Class () (Show a) Source # 

Methods

cls :: Show a :- () Source #

Class () (Semigroup a) Source # 

Methods

cls :: Semigroup a :- () Source #

Class () (Monoid a) Source # 

Methods

cls :: Monoid a :- () Source #

Class b a => () :=> (Class b a) Source # 

Methods

ins :: () :- Class b a Source #

Class () ((:=>) b a) Source # 

Methods

cls :: (b :=> a) :- () Source #

Class () (Class b a) Source # 

Methods

cls :: Class b a :- () Source #

Class (Eq a) (Bits a) Source # 

Methods

cls :: Bits a :- Eq a Source #

Class (Eq a) (Ord a) Source # 

Methods

cls :: Ord a :- Eq a Source #

Class (Fractional a) (Floating a) Source # 
Class (Functor f) (Applicative f) Source # 
Class (Num a) (Fractional a) Source # 

Methods

cls :: Fractional a :- Num a Source #

Class (Applicative f) (Monad f) Source # 

Methods

cls :: Monad f :- Applicative f Source #

Class (Applicative f) (Alternative f) Source # 
Class (Monad f, Alternative f) (MonadPlus f) Source # 

Methods

cls :: MonadPlus f :- (Monad f, Alternative f) Source #

Class (Num a, Ord a) (Real a) Source # 

Methods

cls :: Real a :- (Num a, Ord a) Source #

Class (Real a, Fractional a) (RealFrac a) Source # 

Methods

cls :: RealFrac a :- (Real a, Fractional a) Source #

Class (Real a, Enum a) (Integral a) Source # 

Methods

cls :: Integral a :- (Real a, Enum a) Source #

Class (RealFrac a, Floating a) (RealFloat a) Source # 

Methods

cls :: RealFloat a :- (RealFrac a, Floating a) Source #

class b :=> h | h -> b where infixr 9 Source #

Reify the relationship between an instance head and its body as a class

Given a definition such as

instance Foo a => Foo [a]

you can capture the relationship between the instance head and its body with

instance Foo a :=> Foo [a] where ins = Sub Dict

Minimal complete definition

ins

Methods

ins :: b :- h Source #

Instances

() :=> () Source # 

Methods

ins :: () :- () Source #

a :=> (Monoid (Dict a)) Source # 

Methods

ins :: a :- Monoid (Dict a) Source #

a :=> (Read (Dict a)) Source # 

Methods

ins :: a :- Read (Dict a) Source #

a :=> (Bounded (Dict a)) Source # 

Methods

ins :: a :- Bounded (Dict a) Source #

a :=> (Enum (Dict a)) Source # 

Methods

ins :: a :- Enum (Dict a) Source #

() :=> (Bounded Bool) Source # 

Methods

ins :: () :- Bounded Bool Source #

() :=> (Bounded Char) Source # 

Methods

ins :: () :- Bounded Char Source #

() :=> (Bounded Int) Source # 

Methods

ins :: () :- Bounded Int Source #

() :=> (Bounded Ordering) Source # 

Methods

ins :: () :- Bounded Ordering Source #

() :=> (Bounded Word) Source # 

Methods

ins :: () :- Bounded Word Source #

() :=> (Bounded ()) Source # 

Methods

ins :: () :- Bounded () Source #

() :=> (Enum Bool) Source # 

Methods

ins :: () :- Enum Bool Source #

() :=> (Enum Char) Source # 

Methods

ins :: () :- Enum Char Source #

() :=> (Enum Double) Source # 

Methods

ins :: () :- Enum Double Source #

() :=> (Enum Float) Source # 

Methods

ins :: () :- Enum Float Source #

() :=> (Enum Int) Source # 

Methods

ins :: () :- Enum Int Source #

() :=> (Enum Integer) Source # 

Methods

ins :: () :- Enum Integer Source #

() :=> (Enum Natural) Source # 

Methods

ins :: () :- Enum Natural Source #

() :=> (Enum Ordering) Source # 

Methods

ins :: () :- Enum Ordering Source #

() :=> (Enum Word) Source # 

Methods

ins :: () :- Enum Word Source #

() :=> (Enum ()) Source # 

Methods

ins :: () :- Enum () Source #

() :=> (Eq Bool) Source # 

Methods

ins :: () :- Eq Bool Source #

() :=> (Eq Double) Source # 

Methods

ins :: () :- Eq Double Source #

() :=> (Eq Float) Source # 

Methods

ins :: () :- Eq Float Source #

() :=> (Eq Int) Source # 

Methods

ins :: () :- Eq Int Source #

() :=> (Eq Integer) Source # 

Methods

ins :: () :- Eq Integer Source #

() :=> (Eq Natural) Source # 

Methods

ins :: () :- Eq Natural Source #

() :=> (Eq Word) Source # 

Methods

ins :: () :- Eq Word Source #

() :=> (Eq ()) Source # 

Methods

ins :: () :- Eq () Source #

() :=> (Eq ((:-) a b)) Source # 

Methods

ins :: () :- Eq (a :- b) Source #

() :=> (Eq (Dict a)) Source # 

Methods

ins :: () :- Eq (Dict a) Source #

() :=> (Floating Double) Source # 

Methods

ins :: () :- Floating Double Source #

() :=> (Floating Float) Source # 

Methods

ins :: () :- Floating Float Source #

() :=> (Fractional Double) Source # 
() :=> (Fractional Float) Source # 

Methods

ins :: () :- Fractional Float Source #

() :=> (Integral Int) Source # 

Methods

ins :: () :- Integral Int Source #

() :=> (Integral Integer) Source # 

Methods

ins :: () :- Integral Integer Source #

() :=> (Integral Natural) Source # 

Methods

ins :: () :- Integral Natural Source #

() :=> (Integral Word) Source # 

Methods

ins :: () :- Integral Word Source #

() :=> (Monad ((->) LiftedRep LiftedRep a)) Source # 

Methods

ins :: () :- Monad ((LiftedRep -> LiftedRep) a) Source #

() :=> (Monad []) Source # 

Methods

ins :: () :- Monad [] Source #

() :=> (Monad IO) Source # 

Methods

ins :: () :- Monad IO Source #

() :=> (Monad (Either a)) Source # 

Methods

ins :: () :- Monad (Either a) Source #

() :=> (Monad Identity) Source # 

Methods

ins :: () :- Monad Identity Source #

() :=> (Functor ((->) LiftedRep LiftedRep a)) Source # 

Methods

ins :: () :- Functor ((LiftedRep -> LiftedRep) a) Source #

() :=> (Functor []) Source # 

Methods

ins :: () :- Functor [] Source #

() :=> (Functor Maybe) Source # 

Methods

ins :: () :- Functor Maybe Source #

() :=> (Functor IO) Source # 

Methods

ins :: () :- Functor IO Source #

() :=> (Functor (Either a)) Source # 

Methods

ins :: () :- Functor (Either a) Source #

() :=> (Functor ((,) a)) Source # 

Methods

ins :: () :- Functor ((,) a) Source #

() :=> (Functor Identity) Source # 

Methods

ins :: () :- Functor Identity Source #

() :=> (Functor (Const * a)) Source # 

Methods

ins :: () :- Functor (Const * a) Source #

() :=> (Num Double) Source # 

Methods

ins :: () :- Num Double Source #

() :=> (Num Float) Source # 

Methods

ins :: () :- Num Float Source #

() :=> (Num Int) Source # 

Methods

ins :: () :- Num Int Source #

() :=> (Num Integer) Source # 

Methods

ins :: () :- Num Integer Source #

() :=> (Num Natural) Source # 

Methods

ins :: () :- Num Natural Source #

() :=> (Num Word) Source # 

Methods

ins :: () :- Num Word Source #

() :=> (Ord Bool) Source # 

Methods

ins :: () :- Ord Bool Source #

() :=> (Ord Char) Source # 

Methods

ins :: () :- Ord Char Source #

() :=> (Ord Double) Source # 

Methods

ins :: () :- Ord Double Source #

() :=> (Ord Float) Source # 

Methods

ins :: () :- Ord Float Source #

() :=> (Ord Int) Source # 

Methods

ins :: () :- Ord Int Source #

() :=> (Ord Integer) Source # 

Methods

ins :: () :- Ord Integer Source #

() :=> (Ord Natural) Source # 

Methods

ins :: () :- Ord Natural Source #

() :=> (Ord Word) Source # 

Methods

ins :: () :- Ord Word Source #

() :=> (Ord ()) Source # 

Methods

ins :: () :- Ord () Source #

() :=> (Ord ((:-) a b)) Source # 

Methods

ins :: () :- Ord (a :- b) Source #

() :=> (Ord (Dict a)) Source # 

Methods

ins :: () :- Ord (Dict a) Source #

() :=> (Read Bool) Source # 

Methods

ins :: () :- Read Bool Source #

() :=> (Read Char) Source # 

Methods

ins :: () :- Read Char Source #

() :=> (Read Int) Source # 

Methods

ins :: () :- Read Int Source #

() :=> (Read Natural) Source # 

Methods

ins :: () :- Read Natural Source #

() :=> (Read Ordering) Source # 

Methods

ins :: () :- Read Ordering Source #

() :=> (Read Word) Source # 

Methods

ins :: () :- Read Word Source #

() :=> (Read ()) Source # 

Methods

ins :: () :- Read () Source #

() :=> (Real Double) Source # 

Methods

ins :: () :- Real Double Source #

() :=> (Real Float) Source # 

Methods

ins :: () :- Real Float Source #

() :=> (Real Int) Source # 

Methods

ins :: () :- Real Int Source #

() :=> (Real Integer) Source # 

Methods

ins :: () :- Real Integer Source #

() :=> (Real Natural) Source # 

Methods

ins :: () :- Real Natural Source #

() :=> (Real Word) Source # 

Methods

ins :: () :- Real Word Source #

() :=> (RealFloat Double) Source # 

Methods

ins :: () :- RealFloat Double Source #

() :=> (RealFloat Float) Source # 

Methods

ins :: () :- RealFloat Float Source #

() :=> (RealFrac Double) Source # 

Methods

ins :: () :- RealFrac Double Source #

() :=> (RealFrac Float) Source # 

Methods

ins :: () :- RealFrac Float Source #

() :=> (Show Bool) Source # 

Methods

ins :: () :- Show Bool Source #

() :=> (Show Char) Source # 

Methods

ins :: () :- Show Char Source #

() :=> (Show Int) Source # 

Methods

ins :: () :- Show Int Source #

() :=> (Show Natural) Source # 

Methods

ins :: () :- Show Natural Source #

() :=> (Show Ordering) Source # 

Methods

ins :: () :- Show Ordering Source #

() :=> (Show Word) Source # 

Methods

ins :: () :- Show Word Source #

() :=> (Show ()) Source # 

Methods

ins :: () :- Show () Source #

() :=> (Show ((:-) a b)) Source # 

Methods

ins :: () :- Show (a :- b) Source #

() :=> (Show (Dict a)) Source # 

Methods

ins :: () :- Show (Dict a) Source #

() :=> (Applicative ((->) LiftedRep LiftedRep a)) Source # 

Methods

ins :: () :- Applicative ((LiftedRep -> LiftedRep) a) Source #

() :=> (Applicative []) Source # 

Methods

ins :: () :- Applicative [] Source #

() :=> (Applicative Maybe) Source # 
() :=> (Applicative IO) Source # 

Methods

ins :: () :- Applicative IO Source #

() :=> (Applicative (Either a)) Source # 

Methods

ins :: () :- Applicative (Either a) Source #

() :=> (Semigroup [a]) Source # 

Methods

ins :: () :- Semigroup [a] Source #

() :=> (Semigroup Ordering) Source # 
() :=> (Semigroup ()) Source # 

Methods

ins :: () :- Semigroup () Source #

() :=> (Semigroup (Dict a)) Source # 

Methods

ins :: () :- Semigroup (Dict a) Source #

() :=> (Monoid [a]) Source # 

Methods

ins :: () :- Monoid [a] Source #

() :=> (Monoid Ordering) Source # 

Methods

ins :: () :- Monoid Ordering Source #

() :=> (Monoid ()) Source # 

Methods

ins :: () :- Monoid () Source #

() :=> (Bits Bool) Source # 

Methods

ins :: () :- Bits Bool Source #

() :=> (Bits Int) Source # 

Methods

ins :: () :- Bits Int Source #

() :=> (Bits Integer) Source # 

Methods

ins :: () :- Bits Integer Source #

() :=> (Bits Natural) Source # 

Methods

ins :: () :- Bits Natural Source #

() :=> (Bits Word) Source # 

Methods

ins :: () :- Bits Word Source #

() :=> (Alternative []) Source # 

Methods

ins :: () :- Alternative [] Source #

() :=> (Alternative Maybe) Source # 
() :=> (MonadPlus []) Source # 

Methods

ins :: () :- MonadPlus [] Source #

() :=> (MonadPlus Maybe) Source # 

Methods

ins :: () :- MonadPlus Maybe Source #

(:=>) b a => () :=> ((:=>) b a) Source # 

Methods

ins :: () :- (b :=> a) Source #

Class b a => () :=> (Class b a) Source # 

Methods

ins :: () :- Class b a Source #

Class () ((:=>) b a) Source # 

Methods

cls :: (b :=> a) :- () Source #

(Bounded a) :=> (Bounded (Const * a b)) Source # 

Methods

ins :: Bounded a :- Bounded (Const * a b) Source #

(Bounded a) :=> (Bounded (Identity a)) Source # 
(Enum a) :=> (Enum (Const * a b)) Source # 

Methods

ins :: Enum a :- Enum (Const * a b) Source #

(Enum a) :=> (Enum (Identity a)) Source # 

Methods

ins :: Enum a :- Enum (Identity a) Source #

(Eq a) :=> (Eq (Const * a b)) Source # 

Methods

ins :: Eq a :- Eq (Const * a b) Source #

(Eq a) :=> (Eq (Identity a)) Source # 

Methods

ins :: Eq a :- Eq (Identity a) Source #

(Eq a) :=> (Eq (Ratio a)) Source # 

Methods

ins :: Eq a :- Eq (Ratio a) Source #

(Eq a) :=> (Eq (Complex a)) Source # 

Methods

ins :: Eq a :- Eq (Complex a) Source #

(Eq a) :=> (Eq (Maybe a)) Source # 

Methods

ins :: Eq a :- Eq (Maybe a) Source #

(Eq a) :=> (Eq [a]) Source # 

Methods

ins :: Eq a :- Eq [a] Source #

(Floating a) :=> (Floating (Const * a b)) Source # 

Methods

ins :: Floating a :- Floating (Const * a b) Source #

(Floating a) :=> (Floating (Identity a)) Source # 
(Fractional a) :=> (Fractional (Const * a b)) Source # 
(Fractional a) :=> (Fractional (Identity a)) Source # 
(Integral a) :=> (RealFrac (Ratio a)) Source # 

Methods

ins :: Integral a :- RealFrac (Ratio a) Source #

(Integral a) :=> (Fractional (Ratio a)) Source # 
(Integral a) :=> (Integral (Const * a b)) Source # 

Methods

ins :: Integral a :- Integral (Const * a b) Source #

(Integral a) :=> (Integral (Identity a)) Source # 
(Integral a) :=> (Real (Ratio a)) Source # 

Methods

ins :: Integral a :- Real (Ratio a) Source #

(Integral a) :=> (Num (Ratio a)) Source # 

Methods

ins :: Integral a :- Num (Ratio a) Source #

(Integral a) :=> (Enum (Ratio a)) Source # 

Methods

ins :: Integral a :- Enum (Ratio a) Source #

(Integral a) :=> (Ord (Ratio a)) Source # 

Methods

ins :: Integral a :- Ord (Ratio a) Source #

(Monad m) :=> (Applicative (WrappedMonad m)) Source # 
(Monad m) :=> (Functor (WrappedMonad m)) Source # 
(Num a) :=> (Num (Const * a b)) Source # 

Methods

ins :: Num a :- Num (Const * a b) Source #

(Num a) :=> (Num (Identity a)) Source # 

Methods

ins :: Num a :- Num (Identity a) Source #

(Ord a) :=> (Ord (Const * a b)) Source # 

Methods

ins :: Ord a :- Ord (Const * a b) Source #

(Ord a) :=> (Ord (Identity a)) Source # 

Methods

ins :: Ord a :- Ord (Identity a) Source #

(Ord a) :=> (Ord [a]) Source # 

Methods

ins :: Ord a :- Ord [a] Source #

(Ord a) :=> (Ord (Maybe a)) Source # 

Methods

ins :: Ord a :- Ord (Maybe a) Source #

(Read a) :=> (Read (Const * a b)) Source # 

Methods

ins :: Read a :- Read (Const * a b) Source #

(Read a) :=> (Read (Identity a)) Source # 

Methods

ins :: Read a :- Read (Identity a) Source #

(Read a) :=> (Read (Maybe a)) Source # 

Methods

ins :: Read a :- Read (Maybe a) Source #

(Read a) :=> (Read [a]) Source # 

Methods

ins :: Read a :- Read [a] Source #

(Read a) :=> (Read (Complex a)) Source # 

Methods

ins :: Read a :- Read (Complex a) Source #

(Real a) :=> (Real (Const * a b)) Source # 

Methods

ins :: Real a :- Real (Const * a b) Source #

(Real a) :=> (Real (Identity a)) Source # 

Methods

ins :: Real a :- Real (Identity a) Source #

(RealFloat a) :=> (RealFloat (Const * a b)) Source # 

Methods

ins :: RealFloat a :- RealFloat (Const * a b) Source #

(RealFloat a) :=> (RealFloat (Identity a)) Source # 
(RealFloat a) :=> (Floating (Complex a)) Source # 
(RealFloat a) :=> (Fractional (Complex a)) Source # 
(RealFloat a) :=> (Num (Complex a)) Source # 

Methods

ins :: RealFloat a :- Num (Complex a) Source #

(RealFrac a) :=> (RealFrac (Const * a b)) Source # 

Methods

ins :: RealFrac a :- RealFrac (Const * a b) Source #

(RealFrac a) :=> (RealFrac (Identity a)) Source # 
(Show a) :=> (Show (Const * a b)) Source # 

Methods

ins :: Show a :- Show (Const * a b) Source #

(Show a) :=> (Show (Identity a)) Source # 

Methods

ins :: Show a :- Show (Identity a) Source #

(Show a) :=> (Show (Maybe a)) Source # 

Methods

ins :: Show a :- Show (Maybe a) Source #

(Show a) :=> (Show [a]) Source # 

Methods

ins :: Show a :- Show [a] Source #

(Show a) :=> (Show (Complex a)) Source # 

Methods

ins :: Show a :- Show (Complex a) Source #

(Semigroup a) :=> (Semigroup (IO a)) Source # 

Methods

ins :: Semigroup a :- Semigroup (IO a) Source #

(Semigroup a) :=> (Semigroup (Identity a)) Source # 
(Semigroup a) :=> (Semigroup (Const * a b)) Source # 

Methods

ins :: Semigroup a :- Semigroup (Const * a b) Source #

(Semigroup a) :=> (Semigroup (Maybe a)) Source # 
(Monoid a) :=> (Applicative (Const * a)) Source # 
(Monoid a) :=> (Applicative ((,) a)) Source # 

Methods

ins :: Monoid a :- Applicative ((,) a) Source #

(Monoid a) :=> (Monoid (IO a)) Source # 

Methods

ins :: Monoid a :- Monoid (IO a) Source #

(Monoid a) :=> (Monoid (Identity a)) Source # 

Methods

ins :: Monoid a :- Monoid (Identity a) Source #

(Monoid a) :=> (Monoid (Const * a b)) Source # 

Methods

ins :: Monoid a :- Monoid (Const * a b) Source #

(Monoid a) :=> (Monoid (Maybe a)) Source # 

Methods

ins :: Monoid a :- Monoid (Maybe a) Source #

(Bits a) :=> (Bits (Const * a b)) Source # 

Methods

ins :: Bits a :- Bits (Const * a b) Source #

(Bits a) :=> (Bits (Identity a)) Source # 

Methods

ins :: Bits a :- Bits (Identity a) Source #

(MonadPlus m) :=> (Alternative (WrappedMonad m)) Source # 
(Bounded a, Bounded b) :=> (Bounded (a, b)) Source # 

Methods

ins :: (Bounded a, Bounded b) :- Bounded (a, b) Source #

(Eq a, Eq b) :=> (Eq (Either a b)) Source # 

Methods

ins :: (Eq a, Eq b) :- Eq (Either a b) Source #

(Eq a, Eq b) :=> (Eq (a, b)) Source # 

Methods

ins :: (Eq a, Eq b) :- Eq (a, b) Source #

(Integral a, Read a) :=> (Read (Ratio a)) Source # 

Methods

ins :: (Integral a, Read a) :- Read (Ratio a) Source #

(Integral a, Show a) :=> (Show (Ratio a)) Source # 

Methods

ins :: (Integral a, Show a) :- Show (Ratio a) Source #

(Ord a, Ord b) :=> (Ord (Either a b)) Source # 

Methods

ins :: (Ord a, Ord b) :- Ord (Either a b) Source #

(Ord a, Ord b) :=> (Ord (a, b)) Source # 

Methods

ins :: (Ord a, Ord b) :- Ord (a, b) Source #

(Read a, Read b) :=> (Read (Either a b)) Source # 

Methods

ins :: (Read a, Read b) :- Read (Either a b) Source #

(Read a, Read b) :=> (Read (a, b)) Source # 

Methods

ins :: (Read a, Read b) :- Read (a, b) Source #

(Show a, Show b) :=> (Show (Either a b)) Source # 

Methods

ins :: (Show a, Show b) :- Show (Either a b) Source #

(Show a, Show b) :=> (Show (a, b)) Source # 

Methods

ins :: (Show a, Show b) :- Show (a, b) Source #

(Semigroup a, Semigroup b) :=> (Semigroup (a, b)) Source # 

Methods

ins :: (Semigroup a, Semigroup b) :- Semigroup (a, b) Source #

(Monoid a, Monoid b) :=> (Monoid (a, b)) Source # 

Methods

ins :: (Monoid a, Monoid b) :- Monoid (a, b) Source #