| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.Function.Variadic
Synopsis
- class (ConstructFunction args r ~ f, DeconstructFunction f ~ '(args, r)) => Function f args r argC where
- createFunction :: proxy argC -> (forall a. argC a => acc -> a -> acc) -> (acc -> r) -> acc -> f
- transformFunction :: proxy argC -> (forall a. argC a => acc -> a -> acc) -> (acc -> r0 -> r) -> acc -> ConstructFunction args r0 -> f
- type family ConstructFunction (args :: [Type]) (r :: Type) where ...
- type family DeconstructFunction (f :: Type) :: ([Type], Type) where ...
- class EmptyConstraint a
- class (f x, g x) => (f & g) (x :: k)
Decomposition and creation of functions
class (ConstructFunction args r ~ f, DeconstructFunction f ~ '(args, r)) => Function f args r argC where Source #
Toolkit for creating and transforming functions with a variable number of arguments.
Its parameters are function, list of its arguments, its result, and argC
that constraints all arguments of the function.
Methods
Arguments
| :: proxy argC | Required for unambiguous choice of Function instance |
| -> (forall a. argC a => acc -> a -> acc) | Combine arguments with accumulator |
| -> (acc -> r) | Make result of the function |
| -> acc | Accumulator |
| -> f |
Create a new function
Example usage
>>>printf :: Function Show f args String => f>>>printf = createFunction (Proxy :: Proxy Show) (\acc a -> acc <> show a) id "">>>printf "hello" () :: String"hello()"
Arguments
| :: proxy argC | Required for unambiguous choice of the Function instance |
| -> (forall a. argC a => acc -> a -> acc) | Combine arguments with accumulator |
| -> (acc -> r0 -> r) | Create result of the |
| -> acc | Accumulator |
| -> ConstructFunction args r0 | The function to transform |
| -> f | The new function |
Create a function with the same arguments as given one but may have a different result.
Instances
| '('[] :: [Type], r) ~ DeconstructFunction r => Function r ('[] :: [Type]) r argC Source # | |
Defined in Data.Function.Variadic Methods createFunction :: proxy argC -> (forall a. argC a => acc -> a -> acc) -> (acc -> r) -> acc -> r Source # transformFunction :: proxy argC -> (forall a. argC a => acc -> a -> acc) -> (acc -> r0 -> r) -> acc -> ConstructFunction '[] r0 -> r Source # | |
| (Function f args r argC, argC a) => Function (a -> f) (a ': args) r argC Source # | |
Defined in Data.Function.Variadic Methods createFunction :: proxy argC -> (forall a0. argC a0 => acc -> a0 -> acc) -> (acc -> r) -> acc -> a -> f Source # transformFunction :: proxy argC -> (forall a0. argC a0 => acc -> a0 -> acc) -> (acc -> r0 -> r) -> acc -> ConstructFunction (a ': args) r0 -> a -> f Source # | |
type family ConstructFunction (args :: [Type]) (r :: Type) where ... Source #
Given the types of function arguments and its result, make a type of a function.
Equations
| ConstructFunction '[] r = r | |
| ConstructFunction (a ': args) r = a -> ConstructFunction args r |
type family DeconstructFunction (f :: Type) :: ([Type], Type) where ... Source #
Extract list of arguments and the result from the function.
Equations
| DeconstructFunction (a -> f) = MapFst ((:) a) (DeconstructFunction f) | |
| DeconstructFunction x = '('[], x) |
Helper classes for argument constraints
class EmptyConstraint a Source #
When the arguments are not constrained, use this as the argC parameter of Function.
Instances
| EmptyConstraint (a :: k) Source # | |
Defined in Data.Function.Variadic | |
class (f x, g x) => (f & g) (x :: k) Source #
Combine constraints. For example, Function f args x (Show & Num).
Instances
| (f x, g x) => ((f :: k -> Constraint) & (g :: k -> Constraint)) (x :: k) Source # | |
Defined in Data.Function.Variadic | |