call-haskell-from-anything-1.0.0.0: Call Haskell functions from other languages via serialization and dynamic libraries

Safe HaskellSafe
LanguageHaskell2010

FFI.Anything.TypeUncurry.DataKinds

Contents

Description

Converts function arguments to tuple-like types.

For example, take f :: a -> b -> c -> r. This module can convert it to f' :: (a, b, c) -> r, at compile time.

This is especially useful for (de)serialization. Suppose you have a function that takes multiple arguments and you want to obtain all of its arguments from some serialized data. The serialization library will make it very easy to unpack types like tuples/lists, but de-serializing *fuction arguments* is not that simple.

Using this module, you can write an instance how to unpack the TypeList type, and then use translate to make any function take such a single TypeList instead of multiple function arguments.

Synopsis

Type-level lists (containing types)

data TypeList l where Source

Type-level list that can contain arbitrarily mixed types.

Example:

1 ::: "hello" ::: 2.3 :: TypeList '[Int, String, Double]

Constructors

Nil :: TypeList `[]` 
(:::) :: a -> TypeList l -> TypeList (a : l) infixr 9 

"Uncurrying" functions

type family Param f :: [*] Source

Arguments to a function, e.g. [String, Int] for String -> Int -> r.

Equations

Param (a -> f) = a : Param f 
Param r = `[]` 

type family Result f :: * Source

The result of a function, e.g. r for String -> Int -> r.

Equations

Result (IO r) = IO r 
Result (a -> f) = Result f 
Result r = r 

class (Param f ~ l, Result f ~ r) => ToTypeList f l r where Source

Function f can be translated to TypeList l with result type r.

Methods

translate :: f -> TypeList l -> r Source

Translates a function taking multiple arguments to a function taking a single TypeList containing the types of all arguments.

Example: t1 -> ... -> tn -> r becomes TypeList [t1, ..., tn] -> r.

Instances

((~) [*] (Param f) ([] *), (~) * (Result f) r, (~) * f r) => ToTypeList f ([] *) r Source

Base case: A value r can be translated to TypeList Nil -> r.

ToTypeList (IO r) ([] *) (IO r) Source

Base case: An IO function without arguments (just IO r) can be translated to TypeList Nil -> r.

ToTypeList f l r => ToTypeList (a -> f) ((:) * a l) r Source

Base case: A "pure" function without arguments can be translated to TypeList Nil -> r.

Length of type-level lists

class ParamLength l where Source

Allows to calculate the length of a TypeList, at compile time.

We need to use a Proxy for this.

Methods

paramLength :: Proxy l -> Int Source

Calculates the length of a type list, put into a proxy. Usage:

paramLength (Proxy :: Proxy l)

Instances

ParamLength ([] *) Source 
ParamLength l => ParamLength ((:) * a l) Source