Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.JavaScript
Contents
Synopsis
- send :: Engine -> RemoteMonad a -> IO a
- sendA :: Engine -> Packet a -> IO a
- sendE :: Engine -> RemoteMonad a -> IO (Either Value a)
- newtype JavaScript = JavaScript Text
- command :: Command f => JavaScript -> f ()
- procedure :: forall a f. (Procedure f, FromJSON a) => JavaScript -> f a
- constructor :: forall a f. Command f => JavaScript -> f (RemoteValue a)
- data Packet a
- data RemoteMonad a
- class Command f
- class Procedure f
- data RemoteValue a
- delete :: Command f => RemoteValue a -> f ()
- localize :: Procedure f => RemoteValue a -> f Value
- remote :: Command f => Value -> f (RemoteValue a)
- var :: RemoteValue a -> JavaScript
- value :: ToJSON v => v -> JavaScript
- call :: JavaScript -> [JavaScript] -> JavaScript
- number :: Double -> JavaScript
- string :: Text -> JavaScript
- data JavaScriptException = JavaScriptException Value
- event :: ToJSON v => v -> JavaScript
- addListener :: Engine -> (Value -> IO ()) -> IO ThreadId
- listen :: Engine -> IO Value
- readEventChan :: Engine -> STM (Value, UTCTime)
- start :: (Engine -> IO ()) -> Application -> Application
- data Engine
- type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived
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
newtype JavaScript Source #
Constructors
JavaScript Text |
Instances
Show JavaScript Source # | |
Defined in Network.JavaScript.Internal Methods showsPrec :: Int -> JavaScript -> ShowS # show :: JavaScript -> String # showList :: [JavaScript] -> ShowS # | |
IsString JavaScript Source # | |
Defined in Network.JavaScript.Internal Methods fromString :: String -> JavaScript # | |
Semigroup JavaScript Source # | |
Defined in Network.JavaScript.Internal Methods (<>) :: JavaScript -> JavaScript -> JavaScript # sconcat :: NonEmpty JavaScript -> JavaScript # stimes :: Integral b => b -> JavaScript -> JavaScript # | |
Monoid JavaScript Source # | |
Defined in Network.JavaScript.Internal Methods mempty :: JavaScript # mappend :: JavaScript -> JavaScript -> JavaScript # mconcat :: [JavaScript] -> JavaScript # |
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
The Remote Applicative Packet
Instances
Functor Packet Source # | |
Applicative Packet Source # | |
Procedure Packet Source # | |
Defined in Network.JavaScript.Internal Methods internalProcedure :: FromJSON a => JavaScript -> Packet a Source # | |
Command Packet Source # | |
Defined in Network.JavaScript.Internal Methods internalCommand :: JavaScript -> Packet () Source # internalConstructor :: JavaScript -> Packet (RemoteValue a) Source # |
data RemoteMonad a Source #
The Remote Monad
Instances
Minimal complete definition
Instances
Command RemoteMonad Source # | |
Defined in Network.JavaScript.Internal Methods internalCommand :: JavaScript -> RemoteMonad () Source # internalConstructor :: JavaScript -> RemoteMonad (RemoteValue a) Source # | |
Command Packet Source # | |
Defined in Network.JavaScript.Internal Methods internalCommand :: JavaScript -> Packet () Source # internalConstructor :: JavaScript -> Packet (RemoteValue a) Source # |
Minimal complete definition
Instances
Procedure RemoteMonad Source # | |
Defined in Network.JavaScript.Internal Methods internalProcedure :: FromJSON a => JavaScript -> RemoteMonad a Source # | |
Procedure Packet Source # | |
Defined in Network.JavaScript.Internal Methods internalProcedure :: FromJSON a => JavaScript -> Packet a Source # |
Remote Values
data RemoteValue a Source #
Instances
localize :: Procedure f => RemoteValue a -> f Value Source #
localize
brings a remote value into Haskell.
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
data JavaScriptException Source #
Constructors
JavaScriptException Value |
Instances
Eq JavaScriptException Source # | |
Defined in Network.JavaScript Methods (==) :: JavaScriptException -> JavaScriptException -> Bool # (/=) :: JavaScriptException -> JavaScriptException -> Bool # | |
Show JavaScriptException Source # | |
Defined in Network.JavaScript Methods showsPrec :: Int -> JavaScriptException -> ShowS # show :: JavaScriptException -> String # showList :: [JavaScriptException] -> ShowS # | |
Exception JavaScriptException Source # | |
Defined in Network.JavaScript Methods toException :: JavaScriptException -> SomeException # fromException :: SomeException -> Maybe JavaScriptException # |
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.
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")