wilton-ffi-0.1.0.0: Haskell modules support for Wilton JavaScript runtime

Copyright(c) 2018 alex at staticlibs.net
LicenseMIT
Maintaineralex at staticlibs.net
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foreign.Wilton.FFI

Contents

Description

Haskell modules support for Wilton JavaScript runtime.

Synopsis

Usage example:

Add aeson and wilton-ffi deps to package.yaml:

dependencies:
   - ...
   - aeson
   - wilton-ffi

Inside Lib.hs, enable required extensions:

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ForeignFunctionInterface #-}

Import aeson, wilton-ffi and other deps:

import Data.Aeson
import Data.Data
import GHC.Generics
import Foreign.C.String
import Foreign.Wilton.FFI

Declare input/output structs:

data MyIn = MyIn {} deriving (Typeable, Data, Generic, Show)
instance FromJSON MyIn
data MyOut = MyOut {} deriving (Generic, Show)
instance ToJSON MyObjOut

Write a function that does some work:

hello :: MyIn -> IO MyOut
hello obj = ...

Register that function inside the wilton_module_init function, that will be called by Wilton during the Haskell module load:

foreign export ccall wilton_module_init :: IO CString
wilton_module_init :: IO CString
wilton_module_init = do
    -- register a call, error checking omitted
    _ <- registerWiltoncall "hello" hello
    -- return success status to Wilton
    createWiltonError Nothing

Build the module as shared library (change RTS version as needed):

> stack build
> stack ghc -- --make -dynamic -shared -fPIC -threaded -lHSrts_thr-ghc8.2.2 src/Lib.hs -o libsome_name.so

See an example how to load and use Haskell library from JavaScript.

registerWiltoncall :: forall from to. (Data from, FromJSON from, ToJSON to) => String -> (from -> IO to) -> IO (Maybe ByteString) Source #

Registers a function, that can be called from javascript

This function takes a function and registers it with Wilton, so it can be called from JavaScript using wiltoncall API.

Function must take a single argument - a data that implements Data.Aeson.FromJSON and Data.Data.Data, and must return a data that implements Data.Aeson.ToJSON. Function input argument is converted from JavaScript object to Haskell data object. Function output is returned to JavaScript as a JSON (that can be immediately converted to JavaScript object).

If function raises and Exception, its error message is converted into JavasSript Error message (that can be caught and handled on JavaScript side).

Arguments:

  • name :: String: name for this call, that should be used from JavaScript to invoke the function
  • callback :: (from -> IO to): Function, that will be called from JavaScript

Return value: error status.

createWiltonError :: Maybe ByteString -> IO CString Source #

Create an error message, that can be passed back to Wilton

Helper function, that can be used with a Maybe ByteString value returned from registerWiltoncall function.

Arguments:

  • error :: Maybe ByteString: error status

Return value: error status, that can be returned back to Wilton