dovetail-0.1.0.0
Safe HaskellNone
LanguageHaskell2010

Dovetail.FFI.Builder

Description

This module provides a higher-level API on top of the Dovetail.FFI module. It is not as expressive as the functions in that module, but has the benefit that it is much harder to use this module to construct an FFI which will result in runtime errors, since it attempts to synthesize the types of the Haskell implementations from the types of the declared PureScript foreign imports.

Synopsis

FFI Builder API

data FFIBuilder m a Source #

A monad for constructing FFI data structures.

For example:

FFI.evalFFIBuilder (ModuleName "Example") do
  FFI.foreignImport (P.Ident "example")
    (a -> a ~> a)
    pure

Instances

Instances details
Monad (FFIBuilder m) Source # 
Instance details

Defined in Dovetail.FFI.Builder

Methods

(>>=) :: FFIBuilder m a -> (a -> FFIBuilder m b) -> FFIBuilder m b #

(>>) :: FFIBuilder m a -> FFIBuilder m b -> FFIBuilder m b #

return :: a -> FFIBuilder m a #

Functor (FFIBuilder m) Source # 
Instance details

Defined in Dovetail.FFI.Builder

Methods

fmap :: (a -> b) -> FFIBuilder m a -> FFIBuilder m b #

(<$) :: a -> FFIBuilder m b -> FFIBuilder m a #

Applicative (FFIBuilder m) Source # 
Instance details

Defined in Dovetail.FFI.Builder

Methods

pure :: a -> FFIBuilder m a #

(<*>) :: FFIBuilder m (a -> b) -> FFIBuilder m a -> FFIBuilder m b #

liftA2 :: (a -> b -> c) -> FFIBuilder m a -> FFIBuilder m b -> FFIBuilder m c #

(*>) :: FFIBuilder m a -> FFIBuilder m b -> FFIBuilder m b #

(<*) :: FFIBuilder m a -> FFIBuilder m b -> FFIBuilder m a #

runFFIBuilder :: ModuleName -> FFIBuilder m a -> (a, FFI m) Source #

Run a computation in the FFIBuilder monad, returning the result of the computation alongside the constructed FFI.

evalFFIBuilder :: ModuleName -> FFIBuilder m a -> FFI m Source #

Run a computation in the FFIBuilder monad, returning only the constructed FFI.

foreignImport :: (MonadFix m, ToValue m a, ForAll m a ty) => Ident -> ty -> a -> FFIBuilder m () Source #

Define a value which will be implemented in Haskell.

The first argument gives a name to the value on the PureScript side.

The second argument is a function which describes its PureScript type. See ForAll for an explanation of its purpose.

The final argument is the Haskell implementation of the value.

The type checker will ensure that the PureScript and Haskell types are compatible.

Supported FFI types

data FunctionType m l r Source #

Instances

Instances details
ForAll m a (FunctionType m a r_) Source # 
Instance details

Defined in Dovetail.FFI.Builder

Methods

forAll :: FunctionType m a r_ -> TypeScheme m a

string :: FunctionType m Text (EvalT m Text) Source #

The PureScript string type

char :: FunctionType m Char (EvalT m Char) Source #

The PureScript char type

boolean :: FunctionType m Bool (EvalT m Bool) Source #

The PureScript boolean type

number :: FunctionType m Double (EvalT m Double) Source #

The PureScript number type

int :: FunctionType m Integer (EvalT m Integer) Source #

The PureScript integer type

array :: FunctionType m l r -> FunctionType m (Vector l) (EvalT m (Vector l)) Source #

Construct a PureScript array type

(~>) :: FunctionType m al ar -> FunctionType m bl br -> FunctionType m (al -> br) (al -> br) infixr 0 Source #

Construct a PureScript function type

class ForAll m r a | a -> m r Source #

This type class exists to facilitate the concise description of PureScript type schemes using the foreignImport function. It is best understood via its examples:

foreignImport (Ident "identity") a -> a ~> a
  :: MonadFix m 
  => (Value m -> EvalT m (Value m)) 
  -> FFIBuilder m ()

foreignImport (Ident "flip") a b c -> (a ~> b ~> c) ~> b ~> a ~> c
  :: MonadFix m 
  => ((Value m -> Value m -> EvalT m (Value m))
  ->   Value m -> Value m -> EvalT m (Value m))
  -> FFIBuilder m ()

These Haskell functions applications describe the PureScript type schemes for the identity and flip functions respectively.

Notice that the result type of these applications indicates the corresponding Haskell type which must be implemented in order to satisfy the contract of the FFI. Note, these types have been are inferred, which highlights why this type class is worth its seeming complexity: the goal is to allow the user to express the PureScript type, and have the compiler compute the Haskell type for us. This is about as simple as things can get - we cannot simply specify the Haskell implementation and infer the PureScript type, because there is not a single best PureScript type for every given Haskell type.

Minimal complete definition

forAll

Instances

Instances details
(ForAll m r o, a ~ FunctionType m (Value m) (EvalT m (Value m))) => ForAll m r (a -> o) Source # 
Instance details

Defined in Dovetail.FFI.Builder

Methods

forAll :: (a -> o) -> TypeScheme m r

ForAll m a (FunctionType m a r_) Source # 
Instance details

Defined in Dovetail.FFI.Builder

Methods

forAll :: FunctionType m a r_ -> TypeScheme m a