threepenny-gui-0.8.3.0: GUI framework that uses the web browser as a display.

Safe HaskellNone
LanguageHaskell98

Foreign.JavaScript

Contents

Synopsis

Synopsis

A JavaScript foreign function interface (FFI).

This module implements a web server that communicates with a web browser and allows you to execute arbitrary JavaScript code on it.

NOTE: This module is used internally by the Graphics.UI.Threepenny library, but the types are not compatible directly (although some escape hatches are provided). Use Foreign.JavaScript only if you want to roll your own interface to the web browser.

Server

serve Source #

Arguments

:: Config

Configuration options.

-> (Window -> IO ())

Initialization whenever a client connects.

-> IO () 

Run a Foreign.JavaScript server.

defaultConfig :: Config Source #

Default configuration.

Port from environment variable or 8023, listening on localhost, no custom HTML, no static directory, logging to stderr, do reload on disconnect, buffer FFI calls.

data Config Source #

Static configuration for a Foreign.JavaScript server.

This is a record type which has the following fields:

  • jsPort :: Maybe Int

    Port number. Nothing means that the port number is read from the environment variable PORT. Alternatively, port 8023 is used if this variable is not set.

  • jsAddr :: Maybe ByteString

    Bind address. Nothing means that the bind address is read from the environment variable ADDR. Alternatively, address 127.0.0.1 is used if this variable is not set.

  • jsCustomHTML :: Maybe FilePath

    Custom HTML file to replace the default one.

  • jsStatic :: Maybe FilePath

    Directory that is served under /static.

  • jsLog :: ByteString -> IO ()

    Function to print a single log message.

  • jsWindowReloadOnDisconnect :: Bool

    Reload the browser window if the connection to the server was dropped accidentally, for instance because the computer was put to sleep and awoken again.

  • jsCallBufferMode :: CallBufferMode

    The initial CallBufferMode to use for runFunction. It can be changed at any time with setCallBufferMode.

(For reasons of forward compatibility, the constructor is not exported.)

data Server Source #

Representation of a Foreign.JavaScript server.

Can be used for dynamic configuration, e.g. serving additional files.

type MimeType = String Source #

MIME type.

type URI = String Source #

URI type.

FIXME: Use the correct type from Network.URI

loadFile :: Server -> MimeType -> FilePath -> IO String Source #

Begin to serve a local file with a given MimeType under a URI.

loadDirectory :: Server -> FilePath -> IO String Source #

Begin to serve a local directory under a URI.

data Window Source #

Representation of a browser window.

getServer :: Window -> Server Source #

Server that the browser window communicates with.

getCookies :: Window -> [Cookie] Source #

Cookies that the browser window has sent to the server when connecting.

root :: Window -> RemotePtr () Source #

For the purpose of controlling garbage collection, every Window as an associated RemotePtr that is alive as long as the external JavaScript connection is alive.

JavaScript FFI

class ToJS a where Source #

Helper class for rendering Haskell values as JavaScript expressions.

Minimal complete definition

render

Methods

render :: a -> IO JSCode Source #

renderList :: [a] -> IO JSCode Source #

Instances
ToJS Bool Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: Bool -> IO JSCode Source #

renderList :: [Bool] -> IO JSCode Source #

ToJS Char Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: Char -> IO JSCode Source #

renderList :: [Char] -> IO JSCode Source #

ToJS Double Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: Double -> IO JSCode Source #

renderList :: [Double] -> IO JSCode Source #

ToJS Float Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: Float -> IO JSCode Source #

renderList :: [Float] -> IO JSCode Source #

ToJS Int Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: Int -> IO JSCode Source #

renderList :: [Int] -> IO JSCode Source #

ToJS Text Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: Text -> IO JSCode Source #

renderList :: [Text] -> IO JSCode Source #

ToJS Value Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: Value -> IO JSCode Source #

renderList :: [Value] -> IO JSCode Source #

ToJS JSObject Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: JSObject -> IO JSCode Source #

renderList :: [JSObject] -> IO JSCode Source #

ToJS Element Source # 
Instance details

Defined in Graphics.UI.Threepenny.Internal

Methods

render :: Element -> IO JSCode Source #

renderList :: [Element] -> IO JSCode Source #

ToJS a => ToJS [a] Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

render :: [a] -> IO JSCode Source #

renderList :: [[a]] -> IO JSCode Source #

class FromJS a Source #

Helper class for converting JavaScript values to Haskell values.

Minimal complete definition

fromJS

Instances
FromJS Double Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' Double

FromJS Float Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' Float

FromJS Int Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' Int

FromJS () Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' ()

FromJS String Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' String

FromJS Text Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' Text

FromJS Value Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' Value

FromJS NewJSObject Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' NewJSObject

FromJS JSObject Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' JSObject

FromJS [JSObject] Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' [JSObject]

data JSFunction a Source #

A JavaScript function with a given output type a.

Instances
Functor JSFunction Source #

Change the output type of a JSFunction.

Instance details

Defined in Foreign.JavaScript.Marshal

Methods

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

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

FromJS b => FFI (JSFunction b) Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fancy :: ([JSCode] -> IO JSCode) -> JSFunction b

type JSObject = RemotePtr JSPtr Source #

A mutable JavaScript object.

class FFI a Source #

Helper class for making ffi a variable argument function.

Minimal complete definition

fancy

Instances
FromJS b => FFI (JSFunction b) Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fancy :: ([JSCode] -> IO JSCode) -> JSFunction b

(ToJS a, FFI b) => FFI (a -> b) Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fancy :: ([JSCode] -> IO JSCode) -> a -> b

ffi :: FFI a => String -> a Source #

Simple JavaScript FFI with string substitution.

Inspired by the Fay language. https://github.com/faylang/fay/wiki

example :: String -> Int -> JSFunction String
example = ffi "$(%1).prop('checked',%2)"

The ffi function takes a string argument representing the JavaScript code to be executed on the client. Occurrences of the substrings %1 to %9 will be replaced by subequent arguments. The substring %% in the original will be replaced by % (character escape).

Note: Always specify a type signature! The types automate how values are marshalled between Haskell and JavaScript. The class instances for the FFI class show which conversions are supported.

runFunction :: Window -> JSFunction () -> IO () Source #

Run a JavaScript function, but do not wait for a result.

NOTE: The JavaScript function need not be executed immediately, it can be buffered and sent to the browser window at a later time. See setCallBufferMode and flushCallBuffer for more.

callFunction :: Window -> JSFunction a -> IO a Source #

Call a JavaScript function and wait for the result.

data NewJSObject Source #

A mutable JavaScript object that has just been created. This a dummy type used for additional type safety.

Instances
FromJS NewJSObject Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

fromJS :: FromJS' NewJSObject

unsafeCreateJSObject :: Window -> JSFunction NewJSObject -> IO JSObject Source #

Run a JavaScript function that creates a new object. Return a corresponding JSObject without waiting for the browser to send a result.

WARNING: This function assumes that the supplied JavaScript code does, in fact, create an object that is new.

data CallBufferMode Source #

Specification of how JavaScript functions should be called.

Constructors

NoBuffering

When runFunction is used to call a JavaScript function, immediately send a message to the browser window to execute said function.

BufferRun

When runFunction is used to call a JavaScript function, hold back any message to the server. All JavaScript functions that are held back in this way are combined into a single message, which is finally sent whenever callFunction or flushCallBuffer are used, or an exported Haskell function is called.

FlushOften

The same as BufferRun, but this mode indicates client libraries and programs are encouraged to flush the buffer more often to simplify usage. Users may choose BufferRun instead if they want more control over flushing the buffer.

FlushPeriodically

The same as BufferRun, except that the buffer will also be flushed every 300ms.

setCallBufferMode :: Window -> CallBufferMode -> IO () Source #

Set the call buffering mode for the given browser window.

getCallBufferMode :: Window -> IO CallBufferMode Source #

Get the call buffering mode for the given browser window.

flushCallBuffer :: Window -> IO () Source #

Flush the call buffer, i.e. send all outstanding JavaScript to the client in one single message.

class IsHandler a Source #

Helper class for exporting Haskell functions to JavaScript as event handlers.

Minimal complete definition

convertArgs, handle

Instances
IsHandler (IO ()) Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

convertArgs :: IO () -> Int -> [JSCode]

handle :: IO () -> Window -> [Value] -> IO ()

(FromJS a, IsHandler b) => IsHandler (a -> b) Source # 
Instance details

Defined in Foreign.JavaScript.Marshal

Methods

convertArgs :: (a -> b) -> Int -> [JSCode]

handle :: (a -> b) -> Window -> [Value] -> IO ()

exportHandler :: IsHandler a => Window -> a -> IO JSObject Source #

Export a Haskell function as an event handler.

The result is a JavaScript Function object that can be called from JavaScript like a regular function. However, the corresponding Haskell function will not be run immediately, rather it will be added to the event queue and processed like an event. In other words, this the Haskell code is only called asynchronously.

WARNING: The event handler will be garbage collected unless you keep a reference to it on the Haskell side! Registering it with a JavaScript function will generally not keep it alive.

onDisconnect :: Window -> IO () -> IO () Source #

Register an action to be performed when the client disconnects.

debug :: Window -> String -> IO () Source #

Send a debug message to the JavaScript console.

timestamp :: Window -> IO () Source #

Print a timestamp and the time difference to the previous one in the JavaScript console.