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

Safe HaskellNone
LanguageHaskell98

Graphics.UI.Threepenny.Core

Contents

Synopsis

Synopsis

Core functionality of the Threepenny GUI library.

Server

To display the user interface, you have to start a server using startGUI. Then, visit the URL http://localhost:8023/ in your browser (assuming that you use the default server configuration defaultConfig, or have set the port number to jsPort=Just 8023.)

The server is multithreaded. FFI calls can be made concurrently, but events are handled sequentially.

FFI calls can be buffered, so in some circumstances, it may happen that you manipulate the browser window, but the effect is not immediately visible. See CallBufferMode for more information.

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

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.

startGUI Source #

Arguments

:: Config

Server configuration.

-> (Window -> UI ())

Action to run whenever a client browser connects.

-> IO () 

Start server for GUI sessions.

loadFile Source #

Arguments

:: String

MIME type

-> FilePath

Local path to the file

-> UI String

Relative URI under which this file is now accessible

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

loadDirectory :: FilePath -> UI String Source #

Make a local directory available under a relative URI.

UI monad

data UI a Source #

User interface elements are created and manipulated in the UI monad.

This monad is essentially just a thin wrapper around the familiar IO monad. Use the liftIO function to access IO operations like reading and writing from files.

There are several subtle reasons why Threepenny uses a custom UI monad instead of the standard IO monad:

  • More convenience when calling JavaScript. The monad keeps track of a browser Window context in which JavaScript function calls are executed.
  • Recursion for functional reactive programming.

Instances

Monad UI Source # 

Methods

(>>=) :: UI a -> (a -> UI b) -> UI b #

(>>) :: UI a -> UI b -> UI b #

return :: a -> UI a #

fail :: String -> UI a #

Functor UI Source # 

Methods

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

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

MonadFix UI Source # 

Methods

mfix :: (a -> UI a) -> UI a #

Applicative UI Source # 

Methods

pure :: a -> UI a #

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

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

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

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

MonadIO UI Source # 

Methods

liftIO :: IO a -> UI a #

MonadThrow UI Source # 

Methods

throwM :: Exception e => e -> UI a #

MonadCatch UI Source # 

Methods

catch :: Exception e => UI a -> (e -> UI a) -> UI a #

MonadUI UI Source # 

Methods

liftUI :: UI a -> UI a Source #

runUI :: Window -> UI a -> IO a Source #

Execute an UI action in a particular browser window. Also runs all scheduled IO actions.

class Monad m => MonadUI m where Source #

Minimal complete definition

liftUI

Methods

liftUI :: UI a -> m a Source #

Lift a computation from the UI monad.

Instances

MonadUI UI Source # 

Methods

liftUI :: UI a -> UI a Source #

askWindow :: UI Window Source #

Retrieve current Window context in the UI monad.

liftIOLater :: IO () -> UI () Source #

Schedule an IO action to be run later.

Browser Window

data Window Source #

The type Window represents a browser window.

title :: WriteAttr Window String Source #

Title of the client window.

DOM elements

Create and manipulate DOM elements.

data Element Source #

Instances

mkElement :: String -> UI Element Source #

Make a new DOM element with a given tag name.

mkElementNamespace :: Maybe String -> String -> UI Element Source #

Make a new DOM element with a namespace and a given tag name.

A namespace Nothing corresponds to the default HTML namespace.

delete :: Element -> UI () Source #

Delete the given element.

This operation removes the element from the browser window DOM and marks it for garbage collection on the Haskell side. The element is unuseable afterwards.

NOTE: If you wish to temporarily remove an element from the DOM tree, change the children property of its parent element instead.

string :: String -> UI Element Source #

Make a span element with a given text content.

getHead :: Window -> UI Element Source #

Get the head of the page.

getBody :: Window -> UI Element Source #

Get the body of the page.

(#+) :: UI Element -> [UI Element] -> UI Element infixl 8 Source #

Append DOM elements as children to a given element.

children :: WriteAttr Element [Element] Source #

Child elements of a given element.

text :: WriteAttr Element String Source #

Text content of an element.

html :: WriteAttr Element String Source #

Child elements of a given element as a HTML string.

attr :: String -> WriteAttr Element String Source #

HTML attributes of an element.

style :: WriteAttr Element [(String, String)] Source #

Set CSS style of an Element

value :: Attr Element String Source #

Value attribute of an element. Particularly relevant for control widgets like input.

getElementsByTagName Source #

Arguments

:: Window

Browser window

-> String

The tag name.

-> UI [Element]

All elements with that tag name.

Get all elements of the given tag name.

getElementById Source #

Arguments

:: Window

Browser window

-> String

The ID string.

-> UI (Maybe Element)

Element (if any) with given ID.

Get an element by a particular ID.

getElementsByClassName Source #

Arguments

:: Window

Browser window

-> String

The class string.

-> UI [Element]

Elements with given class.

Get a list of elements by particular class.

Layout

Combinators for quickly creating layouts. They can be adjusted with CSS later on.

grid :: [[UI Element]] -> UI Element Source #

Align given elements in a rectangular grid.

Layout is achieved by using the CSS display:table property. The following element tree will be generated

 <div class="table">
   <div class="table-row">
     <div class="table-cell"> ... </div>
     <div class="table-cell"> ... </div>
   </div>
   <div class="table-row">
     ...
   </div>
  ...
  </div>

You can customatize the actual layout by assigning an id to the element and changing the .table, .table-row and table-column classes in a custom CSS file.

row :: [UI Element] -> UI Element Source #

Align given elements in a row. Special case of grid.

column :: [UI Element] -> UI Element Source #

Align given elements in a column. Special case of grid.

Events

For a list of predefined events, see Graphics.UI.Threepenny.Events.

type EventData = Value Source #

Events may carry data. At the moment, they may return a single JSON value, as defined in the Data.Aeson module.

domEvent Source #

Arguments

:: String

Event name. A full list can be found at http://www.w3schools.com/jsref/dom_obj_event.asp. Note that the on-prefix is not included, the name is click and so on.

-> Element

Element where the event is to occur.

-> Event EventData 

Obtain DOM event for a given element.

unsafeFromJSON :: FromJSON a => EventData -> a Source #

Convert event data to a Haskell value. Throws an exception when the data cannot be converted.

disconnect :: Window -> Event () Source #

Event that occurs whenever the client has disconnected, be it by closing the browser window or by exception.

Note: DOM Elements in a browser window that has been closed can no longer be manipulated.

on :: (element -> Event a) -> element -> (a -> UI void) -> UI () Source #

Convenience function to register Events for Elements.

Example usage.

on click element $ \_ -> ...

onEvent :: Event a -> (a -> UI void) -> UI (UI ()) Source #

Register an UI action to be executed whenever the Event happens.

FIXME: Should be unified with on?

onChanges :: Behavior a -> (a -> UI void) -> UI () Source #

Execute a UI action whenever a Behavior changes. Use sparingly, it is recommended that you use sink instead.

Attributes

For a list of predefined attributes, see Graphics.UI.Threepenny.Attributes.

(#) :: a -> (a -> b) -> b infixl 8 Source #

Reverse function application. Allows convenient notation for setting properties.

Example usage.

mkElement "div"
    # set style     [("color","#CCAABB")]
    # set draggable True
    # set children  otherElements

(#.) :: UI Element -> String -> UI Element infixl 8 Source #

Convenient combinator for setting the CSS class on element creation.

type Attr x a = ReadWriteAttr x a a Source #

Attributes can be set and get.

type WriteAttr x i = ReadWriteAttr x i () Source #

Attribute that only supports the set operation.

type ReadAttr x o = ReadWriteAttr x () o Source #

Attribute that only supports the get operation.

data ReadWriteAttr x i o Source #

Generalized attribute with different types for getting and setting.

Constructors

ReadWriteAttr 

Fields

Instances

Functor (ReadWriteAttr x i) Source # 

Methods

fmap :: (a -> b) -> ReadWriteAttr x i a -> ReadWriteAttr x i b #

(<$) :: a -> ReadWriteAttr x i b -> ReadWriteAttr x i a #

set :: ReadWriteAttr x i o -> i -> UI x -> UI x Source #

Set value of an attribute in the UI monad. Best used in conjunction with #.

sink :: ReadWriteAttr x i o -> Behavior i -> UI x -> UI x Source #

Set the value of an attribute to a Behavior, that is a time-varying value.

Note: For reasons of efficiency, the attribute is only updated when the value changes.

get :: ReadWriteAttr x i o -> x -> UI o Source #

Get attribute value.

mkReadWriteAttr Source #

Arguments

:: (x -> UI o)

Getter.

-> (i -> x -> UI ())

Setter.

-> ReadWriteAttr x i o 

Build an attribute from a getter and a setter.

mkWriteAttr :: (i -> x -> UI ()) -> WriteAttr x i Source #

Build attribute from a setter.

mkReadAttr :: (x -> UI o) -> ReadAttr x o Source #

Build attribute from a getter.

bimapAttr :: (i' -> i) -> (o -> o') -> ReadWriteAttr x i o -> ReadWriteAttr x i' o' Source #

Map input and output type of an attribute.

fromObjectProperty :: (FromJS a, ToJS a) => String -> Attr Element a Source #

Turn a JavaScript object property .prop = ... into an attribute.

Widgets

class Widget w where Source #

Widgets are data types that have a visual representation.

Minimal complete definition

getElement

Methods

getElement :: w -> Element Source #

element :: MonadIO m => Widget w => w -> m Element Source #

Convenience synonym for return to make elements work well with set. Also works on Widgets.

Example usage.

e <- mkElement "button"
element e # set text "Ok"

widget :: Widget w => w -> UI w Source #

Convenience synonym for return to make widgets work well with set.

JavaScript FFI

Direct interface to JavaScript in the browser window.

debug :: String -> UI () Source #

Print a message on the client console if the client has debugging enabled.

timestamp :: UI () Source #

Print a timestamp and the difference to the previous timestamp on the client console if the client has debugging enabled.

class ToJS a Source #

Helper class for rendering Haskell values as JavaScript expressions.

Minimal complete definition

render

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

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

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 :: JSFunction () -> UI () Source #

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

The client window uses JavaScript's eval() function to run the code.

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 :: JSFunction a -> UI a Source #

Call a JavaScript function and wait for the result.

The client window uses JavaScript's eval() function to run the code.

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 :: CallBufferMode -> UI () Source #

Set the call buffering mode for the browser window.

flushCallBuffer :: UI () Source #

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

ffiExport :: IsHandler a => a -> UI JSObject Source #

Export the given Haskell function so that it can be called from JavaScript code.

NOTE: At the moment, the JSObject representing the exported function will be referenced by the browser Window in which it was created, preventing garbage collection until this browser Window is disconnected.

This makes it possible to use it as an event handler on the JavaScript side, but it also means that the Haskell runtime has no way to detect early when it is no longer needed.

In contrast, if you use the function domEvent to register an event handler to an Element, then the handler will be garbage collected as soon as the associated Element is garbage collected.

Internals

toJSObject :: Element -> JSObject Source #

Access to the primitive JSObject for roll-your-own foreign calls.

liftJSWindow :: (Window -> IO a) -> UI a Source #

Access to the primitive Window object, for roll-your-own JS foreign calls.

Internal and oddball functions

fromJQueryProp :: String -> (Value -> a) -> (a -> Value) -> Attr Element a Source #

Turn a jQuery property .prop() into an attribute.