Safe Haskell | None |
---|---|
Language | Haskell2010 |
Constraints for indexed datatypes.
This module contains code that helps to specify that all elements of an indexed structure must satisfy a particular constraint.
- class (AllF f xs, SListI xs) => All f xs
- type family AllF (c :: k -> Constraint) (xs :: [k]) :: Constraint where ...
- type SListI2 = All SListI
- class (AllF (All f) xss, SListI xss) => All2 f xss
- class (SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip c xs ys
- type family AllZipF (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b]) :: Constraint where ...
- type family SameShapeAs (xs :: [a]) (ys :: [b]) :: Constraint where ...
- type family Head (xs :: [a]) :: a where ...
- type family Tail (xs :: [a]) :: [a] where ...
- class Coercible (f x) (g y) => LiftedCoercible f g x y
- class (AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 f xss yss
- class f (g x) => Compose f g x
- class (f x, g x) => And f g x
- class Top x
- type family AllN (h :: (k -> *) -> l -> *) (c :: k -> Constraint) :: l -> Constraint
- type family AllZipN (h :: (k -> *) -> l -> *) (c :: k1 -> k2 -> Constraint) :: l1 -> l2 -> Constraint
- type family SListIN (h :: (k -> *) -> l -> *) :: l -> Constraint
- data Constraint :: *
Documentation
class (AllF f xs, SListI xs) => All f xs Source #
Require a constraint for every element of a list.
If you have a datatype that is indexed over a type-level
list, then you can use All
to indicate that all elements
of that type-level list must satisfy a given constraint.
Example: The constraint
All Eq '[ Int, Bool, Char ]
is equivalent to the constraint
(Eq Int, Eq Bool, Eq Char)
Example: A type signature such as
f :: All Eq xs => NP I xs -> ...
means that f
can assume that all elements of the n-ary
product satisfy Eq
.
type family AllF (c :: k -> Constraint) (xs :: [k]) :: Constraint where ... Source #
Type family used to implement All
.
class (AllF (All f) xss, SListI xss) => All2 f xss Source #
Require a constraint for every element of a list of lists.
If you have a datatype that is indexed over a type-level
list of lists, then you can use All2
to indicate that all
elements of the innert lists must satisfy a given constraint.
Example: The constraint
All2 Eq '[ '[ Int ], '[ Bool, Char ] ]
is equivalent to the constraint
(Eq Int, Eq Bool, Eq Char)
Example: A type signature such as
f :: All2 Eq xss => SOP I xs -> ...
means that f
can assume that all elements of the sum
of product satisfy Eq
.
class (SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip c xs ys Source #
Require a constraint for pointwise for every pair of elements from two lists.
Example: The constraint
All (~) '[ Int, Bool, Char ] '[ a, b, c ]
is equivalent to the constraint
(Int ~ a, Bool ~ b, Char ~ c)
Since: 0.3.1.0
(SListI a xs, SListI b ys, SameShapeAs b a xs ys, SameShapeAs a b ys xs, AllZipF b a c xs ys) => AllZip b a c xs ys Source # | |
type family AllZipF (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b]) :: Constraint where ... Source #
Type family used to implement AllZip
.
Since: 0.3.1.0
type family SameShapeAs (xs :: [a]) (ys :: [b]) :: Constraint where ... Source #
Type family that forces a type-level list to be of the same shape as the given type-level list.
The main use of this constraint is to help type inference to learn something about otherwise unknown type-level lists.
Since: 0.3.1.0
SameShapeAs '[] ys = ys ~ '[] | |
SameShapeAs (x ': xs) ys = (ys ~ (Head ys ': Tail ys), SameShapeAs xs (Tail ys)) |
type family Head (xs :: [a]) :: a where ... Source #
Utility function to compute the head of a type-level list.
Since: 0.3.1.0
Head (x ': xs) = x |
type family Tail (xs :: [a]) :: [a] where ... Source #
Utility function to compute the tail of a type-level list.
Since: 0.3.1.0
Tail (x ': xs) = xs |
class Coercible (f x) (g y) => LiftedCoercible f g x y Source #
The constraint LiftedCoercible f g x y
is equivalent
to Coercible (f x) (g y)
.
Since: 0.3.1.0
Coercible k1 (f x) (g y) => LiftedCoercible k k1 k2 f g x y Source # | |
class (AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 f xss yss Source #
Require a constraint for pointwise for every pair of elements from two lists of lists.
(AllZipF [b] [a] (AllZip b a f) xss yss, SListI [a] xss, SListI [b] yss, SameShapeAs [b] [a] xss yss, SameShapeAs [a] [b] yss xss) => AllZip2 b a f xss yss Source # | |
class f (g x) => Compose f g x infixr 9 Source #
Composition of constraints.
Note that the result of the composition must be a constraint,
and therefore, in f
, the kind of :.
gf
is k ->
.
The kind of Constraint
g
, however, is l -> k
and can thus be an normal
type constructor.
A typical use case is in connection with All
on an NP
or an
NS
. For example, in order to denote that all elements on an
satisfy NP
f xsShow
, we can say
.All
(Show
:. f) xs
Since: 0.2
type family AllN (h :: (k -> *) -> l -> *) (c :: k -> Constraint) :: l -> Constraint Source #
type family AllZipN (h :: (k -> *) -> l -> *) (c :: k1 -> k2 -> Constraint) :: l1 -> l2 -> Constraint Source #
type family SListIN (h :: (k -> *) -> l -> *) :: l -> Constraint Source #
data Constraint :: * #
The kind of constraints, like Show a