| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Function.Poly
- type family TypeListToArity xs r :: *
- type family ArityToTypeList r :: [*]
- type family Result f :: *
- type family ArityMinusTypeList r xs :: *
- type ArityTypeListIso c l r = (ArityMinusTypeList c l ~ r, c ~ TypeListToArity l r)
- type family InjectLast x f :: *
- type family Append xs x :: [*]
- type family ExpectArity xs f :: Constraint
- type family ExpectLast x f :: Constraint
- type family Head xs :: k
- type family Tail xs :: [k]
- class ExpectArity xs f => ConsumeArity xs f result | xs f -> result where
- appN :: f -> HList xs -> result
- type family HasResult f r :: Constraint
Documentation
type family TypeListToArity xs r :: * Source
Provide a type-level list of types xs, and a final result type r,
construct a chain of arrows -> / n-ary function (which is right-associative)
of each type in xs, ending in r.
Equations
| TypeListToArity `[]` r = r | |
| TypeListToArity (x : xs) r = x -> TypeListToArity xs r |
type family ArityToTypeList r :: [*] Source
The inverse of TypeListToArity.
Equations
| ArityToTypeList (x -> r) = x : ArityToTypeList r | |
| ArityToTypeList r = `[]` |
type family ArityMinusTypeList r xs :: * Source
Trim an n-ary function / chain of arrows -> with a type-level list of
types xs, where each element of xs must unify with each element of
the cons-list made with ->.
Equations
| ArityMinusTypeList r `[]` = r | |
| ArityMinusTypeList (x -> r) (x : xs) = ArityMinusTypeList r xs |
type ArityTypeListIso c l r = (ArityMinusTypeList c l ~ r, c ~ TypeListToArity l r) Source
type family InjectLast x f :: * Source
Injects a type to the base of the function arity chain.
Equations
| InjectLast x f = TypeListToArity (Append (ArityToTypeList f) x) (Result f) |
type family ExpectArity xs f :: Constraint Source
Inductively constrain a function's initial arity to match a type list; as a read-only style of static arity assurance.
Equations
| ExpectArity `[]` f = () | |
| ExpectArity (x : xs) (x -> remainder) = ExpectArity xs remainder |
type family ExpectLast x f :: Constraint Source
Expect the last parameter in your stack of arity to have a type.
Equations
| ExpectLast x (x -> remainder) = () | |
| ExpectLast x (y -> remainder) = ExpectLast x remainder |
type family Head xs :: k Source
Duplicate of singletons
Head function for kind-polymorphic type-level lists.
Equations
| Head (x : xs) = x |
class ExpectArity xs f => ConsumeArity xs f result | xs f -> result where Source
Lift the HList's internal type-level list of types to a constraint context.
Methods
appN :: f -> HList xs -> result Source
Use a heterogeneously-typed list of values as input to an n-ary function, where types must unify statically.
Instances
| ConsumeArity ([] *) r r Source | |
| (ConsumeArity xs f r, ExpectArity ((:) * x xs) (x -> f)) => ConsumeArity ((:) * x xs) (x -> f) r Source |