wilton-ffi-0.3.0.3: 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 DeriveGeneric #-}
{-# LANGUAGE ForeignFunctionInterface #-}

Import aeson, wilton-ffi and other deps:

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

Declare input/output structs:

data MyIn = MyIn {} deriving (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 a b. (FromJSON a, ToJSON b) => ByteString -> (a -> IO b) -> 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 must return a data that implements Data.Aeson.ToJSON. Function input argument is converted from a JavaScript object into a 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 :: ByteString: name for this call, that should be used from JavaScript to invoke the function
  • callback :: (a -> IO b): Function, that will be called from JavaScript

Return value: error status.

invokeWiltonCall :: forall a b. (ToJSON a, FromJSON b) => ByteString -> a -> IO (Either ByteString b) Source #

Invoke a function from WiltonCall registry

Allows to call a specified function, that was previously registered as a WiltonCall passing arguments as a data that can be converted to JSON and receiving the result as a data parsed from JSON.

Arguments

  • callName :: ByteString: name of the previously registered WiltonCall
  • callData :: a: a data that implements Data.Aeson.ToJSON or an Aeson.Value for dynamic JSON conversion

Return value: either error ByteString or a call response as a data that implements Data.Aeson.FromJSON or an Aeson.Value for dynamic JSON conversion

Example:

-- call data definition

data FileUploadArgs = FileUploadArgs
    { url :: Text
    , filePath :: Text
    } deriving (Generic, Show)
instance ToJSON FileUploadArgs

let callData = FileUploadArgs "http://127.0.0.1:8080/some/path" "path/to/file"
-- perform a call (sending a specified file over HTTP) and check the results
respEither <- invokeWiltonCall "httpclient_send_file" callData
either (\err -> ...) (\resp -> ...) respEither

invokeWiltonCallByteString :: ByteString -> ByteString -> IO (Either ByteString ByteString) Source #

Invoke a function from WiltonCall registry

Allows to call a specified function, that was previously registered as a WiltonCall passing arguments and receiving result as ByteStrings.

Arguments

  • callName :: ByteString: name of the previously registered WiltonCall
  • callData :: ByteString: argument (usually JSON) that is passes to the specified WiltonCall

Return value: either error string or a call response as a ByteString

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