Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines a flexible and efficient way to curry and uncurry functions of any arity. This is useful in the context of StrictCheck to provide a lightweight interface to test developers which does not require them to directly work with heterogeneous lists.
- type family (args :: [*]) ⋯-> (rest :: *) :: * where ...
- type (-..->) args rest = args ⋯-> rest
- type family Args (f :: *) :: [*] where ...
- type family Result (f :: *) :: * where ...
- class Curry (args :: [*]) where
- curryAll :: forall args result list. (List list, Curry args) => (list args -> result) -> args ⋯-> result
- uncurryAll :: forall function list. (List list, Curry (Args function)) => function -> list (Args function) -> Result function
- withCurryIdentity :: forall function r. (function ~ (Args function ⋯-> Result function) => r) -> r
- class List (list :: [*] -> *) where
Computing the types of curried functions
type family (args :: [*]) ⋯-> (rest :: *) :: * where ... Source #
Given a list of argument types and the "rest" of a function type, return a curried function type which takes the specified argument types in order, before returning the given rest
For example:
[Int, Bool] ⋯-> Char ~ Int -> Bool -> Char
This infix unicode symbol is meant to evoke a function arrow with an ellipsis.
type (-..->) args rest = args ⋯-> rest Source #
For those who don't want to type in unicode, we provide this ASCII synonym
for the ellipsis function arrow (⋯->)
type family Args (f :: *) :: [*] where ... Source #
Given a function type, return a list of all its argument types
For example:
Args (Int -> Bool -> Char) ~ [Int, Bool]
type family Result (f :: *) :: * where ... Source #
Strip all arguments from a function type, yielding its (non-function-type) result
For example:
Result (Int -> Bool -> Char) ~ Char
Currying functions at all arities
class Curry (args :: [*]) where Source #
The Curry class witnesses that for any list of arguments, it is always possible to curry/uncurry at that arity
curryAll :: forall args result list. (List list, Curry args) => (list args -> result) -> args ⋯-> result Source #
Curry all arguments to a function from a heterogeneous list to a result
This is a special case of curry
, and may ease type inference.
uncurryAll :: forall function list. (List list, Curry (Args function)) => function -> list (Args function) -> Result function Source #
Uncurry all arguments to a function type
This is a special case of uncurry
, and may ease type inference.
withCurryIdentity :: forall function r. (function ~ (Args function ⋯-> Result function) => r) -> r Source #
For any function type function
, it is always true that
function ~ (Args function ⋯-> Result function)
GHC doesn't know this, however, so withCurryIdentity
provides this proof to
the enclosed computation, by discharging this wanted equality constraint.
Generalized to any heterogeneous list
class List (list :: [*] -> *) where Source #
This currying mechanism is agnostic to the concrete heterogeneous list type
used to carry arguments. The List
class abstracts over the nil and cons
operations of a heterogeneous list: to use your own, just define an instance.