threepenny-gui-0.7.0.1: 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. 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.

data Config Source #

Configuration of a Foreign.JavaScript server.

Constructors

Config 

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 ()

    Print a single log message.

defaultConfig :: Config Source #

Default configuration.

Port from environment variable or 8023, listening on localhost, no custom HTML, no static directory, logging to stderr.

data Window Source #

Representation of a browser window.

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 # 

Methods

render :: Bool -> IO JSCode Source #

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

ToJS Char Source # 

Methods

render :: Char -> IO JSCode Source #

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

ToJS Double Source # 

Methods

render :: Double -> IO JSCode Source #

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

ToJS Float Source # 

Methods

render :: Float -> IO JSCode Source #

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

ToJS Int Source # 

Methods

render :: Int -> IO JSCode Source #

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

ToJS Text Source # 

Methods

render :: Text -> IO JSCode Source #

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

ToJS Value Source # 

Methods

render :: Value -> IO JSCode Source #

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

ToJS JSObject Source # 

Methods

render :: JSObject -> IO JSCode Source #

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

ToJS Element Source # 

Methods

render :: Element -> IO JSCode Source #

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

ToJS a => ToJS [a] Source # 

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 # 

Methods

fromJS :: FromJS' Double

FromJS Float Source # 

Methods

fromJS :: FromJS' Float

FromJS Int Source # 

Methods

fromJS :: FromJS' Int

FromJS () Source # 

Methods

fromJS :: FromJS' ()

FromJS String Source # 

Methods

fromJS :: FromJS' String

FromJS Text Source # 

Methods

fromJS :: FromJS' Text

FromJS Value Source # 

Methods

fromJS :: FromJS' Value

FromJS NewJSObject Source # 

Methods

fromJS :: FromJS' NewJSObject

FromJS JSObject Source # 

Methods

fromJS :: FromJS' JSObject

FromJS [JSObject] Source # 

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.

Methods

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

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

FromJS b => FFI (JSFunction b) Source # 

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 # 

Methods

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

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

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.

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

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.

class IsHandler a Source #

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

Minimal complete definition

convertArgs, handle

Instances

IsHandler (IO ()) Source # 

Methods

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

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

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

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.