StrictCheck-0.2.0: Keep Your Laziness In Check

Safe HaskellNone
LanguageHaskell2010

Test.StrictCheck.Curry

Contents

Description

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.

Synopsis

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.

Equations

'[] ⋯-> rest = rest 
(a ': args) ⋯-> rest = a -> args ⋯-> rest 

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]

Equations

Args (a -> rest) = a ': Args rest 
Args x = '[] 

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

Equations

Result (a -> rest) = Result rest 
Result r = r 

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

Minimal complete definition

uncurry, curry

Methods

uncurry :: forall result list. List list => (args ⋯-> result) -> list args -> result Source #

curry :: forall result list. List list => (list args -> result) -> args ⋯-> result Source #

Instances
Curry ([] :: [*]) Source # 
Instance details

Defined in Test.StrictCheck.Curry

Methods

uncurry :: List list => ([] ⋯-> result) -> list [] -> result Source #

curry :: List list => (list [] -> result) -> [] ⋯-> result Source #

Curry xs => Curry (x ': xs) Source # 
Instance details

Defined in Test.StrictCheck.Curry

Methods

uncurry :: List list => ((x ': xs) ⋯-> result) -> list (x ': xs) -> result Source #

curry :: List list => (list (x ': xs) -> result) -> (x ': xs) ⋯-> result Source #

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.

Minimal complete definition

nil, cons, uncons

Methods

nil :: list '[] Source #

cons :: x -> list xs -> list (x ': xs) Source #

uncons :: list (x ': xs) -> (x, list xs) Source #

Instances
List (NP I) Source # 
Instance details

Defined in Test.StrictCheck.Curry

Methods

nil :: NP I [] Source #

cons :: x -> NP I xs -> NP I (x ': xs) Source #

uncons :: NP I (x ': xs) -> (x, NP I xs) Source #