call-haskell-from-anything-0.2.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 translateCall to make any function take such a single TypeList instead of multiple function arguments.

There is currently a technical limitation: The result type must be wrapped in the Identity monad.

Example:

-- Assume your library provides some unpack function, e.g. it allows you to write:
unpack someBytestring :: (Int, String, Double)

-- and you have a function
f :: Int -> String -> Double -> Identity Char

-- then you can use:
f' :: (Int, String, Double) -> Identity Char
f' = translateCall f

result = f' (unpack someBytestring)

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.

Instances

type Param (IO r) = [] * Source 
type Param (Identity r) = [] * Source

For pure functions, we need an Identity monad wrapper here to not conflict with a -> f.

type Param (a -> f) = (:) * a (Param f) Source 

type family Result f :: * Source

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

Instances

type Result (IO r) = IO r Source 
type Result (Identity r) = r Source

For pure functions, we need an Identity monad wrapper here to not conflict with a -> f.

type Result (a -> f) = Result f Source 

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

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

Recursive case: A function of type a -> ... -> r can be translated to TypeList [a, ...] -> r.

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

Base case: An IO function without arguments (just Identity 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 (just Identity r) can be translated to TypeList Nil -> r.

Length of type-level lists

data Proxy k Source

A proxy type that can contain an arbitrary type.

Needed for some type-level computations, like paramLength.

Constructors

Proxy 

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 (undefined :: Proxy l)

Instances

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