javascript-bridge-0.2.0: Remote Monad for JavaScript on the browser

Safe HaskellNone
LanguageHaskell2010

Network.JavaScript

Contents

Synopsis

Sending Remote Monads and Packets

send :: Engine -> RemoteMonad a -> IO a Source #

send a remote monad for execution on a JavaScript engine. The monad may be split into several packets for transmission and exection.

sendA :: Engine -> Packet a -> IO a Source #

send an (applicative) Packet. This packet always sent atomically to JavaScript.

sendE :: Engine -> RemoteMonad a -> IO (Either Value a) Source #

send with all JavaScript exceptions caught and returned.

Building Remote Monads and Packets

command :: Command f => JavaScript -> f () Source #

command statement to execute in JavaScript. ';' is not needed as a terminator. Should never throw an exception, which may be reported to console.log.

procedure :: forall a f. (Procedure f, FromJSON a) => JavaScript -> f a Source #

procedure expression to execute in JavaScript. ';' is not needed as a terminator. Should never throw an exception, but any exceptions are returned to the send as Haskell exceptions.

Procedures can return Promises. Before completing the transaction, all the values for all the procedures that are promises are fulfilled (using Promises.all).

If a procedure throws an exception, future commands and procedures in the same packet will not be executed. Use promises to allow all commands and procedures to be invoked, if needed.

constructor :: forall a f. Command f => JavaScript -> f (RemoteValue a) Source #

constructor expression to execute in JavaScript. ';' is not needed as a terminator. Should never throw an exception, but any exceptions are returned to the send as Haskell exceptions.

The value returned in not returned to Haskell. Instead, a handle is returned, that can be used to access the remote value. Examples of remote values include objects that can not be serialized, or values that are too large to serialize.

The first type argument is the phantom type of the RemoteValue, so that type application can be used to specify the type.

Remote Applicative and Monads, and classes for building them

data Packet a Source #

The Remote Applicative Packet

Instances
Functor Packet Source # 
Instance details

Defined in Network.JavaScript.Internal

Methods

fmap :: (a -> b) -> Packet a -> Packet b #

(<$) :: a -> Packet b -> Packet a #

Applicative Packet Source # 
Instance details

Defined in Network.JavaScript.Internal

Methods

pure :: a -> Packet a #

(<*>) :: Packet (a -> b) -> Packet a -> Packet b #

liftA2 :: (a -> b -> c) -> Packet a -> Packet b -> Packet c #

(*>) :: Packet a -> Packet b -> Packet b #

(<*) :: Packet a -> Packet b -> Packet a #

Procedure Packet Source # 
Instance details

Defined in Network.JavaScript.Internal

Command Packet Source # 
Instance details

Defined in Network.JavaScript.Internal

class Procedure f Source #

Minimal complete definition

internalProcedure

Remote Values

delete :: Command f => RemoteValue a -> f () Source #

delete a remote value.

localize :: Procedure f => RemoteValue a -> f Value Source #

localize brings a remote value into Haskell.

remote :: Command f => Value -> f (RemoteValue a) Source #

remote sends a local value to JavaScript.

JavaScript builders

var :: RemoteValue a -> JavaScript Source #

generate the text for a RemoteValue. They can be used as assignment targets as well, but exposes the JavaScript scoping semantics.

value :: ToJSON v => v -> JavaScript Source #

Generate a JavaScript value, including for RemoteValue's.

call :: JavaScript -> [JavaScript] -> JavaScript Source #

Generate a function call

number :: Double -> JavaScript Source #

Generate JavaScript number

string :: Text -> JavaScript Source #

Generate (quoted) JavaScript string

Events

event :: ToJSON v => v -> JavaScript Source #

Send an event back to Haskell

addListener :: Engine -> (Value -> IO ()) -> IO ThreadId Source #

Add a listener for events. There can be many. non-blocking.

From JavaScript, you can call event(..) to send values to this listener. Any valid JSON value can be sent.

listen :: Engine -> IO Value Source #

listen for the next event. blocking.

From JavaScript, you can call event(..) to send values to this listener. Any valid JSON value can be sent.

readEventChan :: Engine -> STM (Value, UTCTime) Source #

readEventChan uses STM to read the next event.

From JavaScript, you can call event(..) to send values to this channel. Any valid JSON value can be sent.

Web services

start :: (Engine -> IO ()) -> Application -> Application Source #

This accepts WebSocket requests, calls the callback with an Engine that can be used to access JavaScript.

data Engine Source #

An Engine is a handle to a specific JavaScript engine

type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #

The WAI application.

Note that, since WAI 3.0, this type is structured in continuation passing style to allow for proper safe resource handling. This was handled in the past via other means (e.g., ResourceT). As a demonstration:

app :: Application
app req respond = bracket_
    (putStrLn "Allocating scarce resource")
    (putStrLn "Cleaning up")
    (respond $ responseLBS status200 [] "Hello World")