constraints-0.9.1: Constraint manipulation

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

Data.Constraint.Forall

Description

This module uses a trick to provide quantification over constraints.

Synopsis

Documentation

type family Forall (p :: k -> Constraint) :: Constraint Source #

A representation of the quantified constraint forall a. p a.

Instances

type Forall k p Source # 
type Forall k p

inst :: forall p a. Forall p :- p a Source #

Instantiate a quantified Forall p constraint at type a.

class Forall (ComposeC p f) => ForallF p f Source #

A representation of the quantified constraint forall a. p (f a).

Instances

Forall k1 (ComposeC k1 k2 p f) => ForallF k1 k2 p f Source # 

instF :: forall p f a. ForallF p f :- p (f a) Source #

Instantiate a quantified ForallF p f constraint at type a.

type Forall1 p = Forall p Source #

inst1 :: forall p f. Forall p :- p f Source #

Instantiate a quantified constraint on kind * -> *. This is now redundant since inst became polykinded.

class Forall (Q p t) => ForallT p t Source #

A representation of the quantified constraint forall f a. p (t f a).

Instances

Forall (k1 -> k2) (Q k3 (k1 -> k2) k4 p t) => ForallT k3 k2 k1 k4 p t Source # 

instT :: forall p t f a. ForallT p t :- p (t f a) Source #

Instantiate a quantified ForallT p t constraint at types f and a.

type family ForallV :: k -> Constraint Source #

A representation of the quantified constraint forall a1 a2 ... an . p a1 a2 ... an, supporting a variable number of parameters.

Instances

type ForallV k Source # 
type ForallV k

class InstV p c | k c -> p where Source #

Instantiate a quantified ForallV p constraint as c, where c ~ p a1 a2 ... an.

Minimal complete definition

instV

Methods

instV :: ForallV p :- c Source #

Instances

(~) Constraint p c => InstV Constraint p c Source # 

Associated Types

type ForallV' p (c :: p) :: Constraint

Methods

instV :: ForallV p c :- c Source #

InstV (k2 -> k3) (p a) c => InstV (k1 -> k2 -> k3) p c Source # 

Associated Types

type ForallV' p (c :: p) :: Constraint

Methods

instV :: ForallV p c :- c Source #

(~) Constraint (p a) c => InstV (k -> Constraint) p c Source # 

Associated Types

type ForallV' p (c :: p) :: Constraint

Methods

instV :: ForallV p c :- c Source #

forall :: forall p. (forall a. Dict (p a)) -> Dict (Forall p) Source #