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

Safe HaskellNone

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:10000/ in your browser (assuming that you have set the port number to tpPort=10000 in the server configuration).

The server is multithreaded, a separate thread is used to communicate with a single browser Window. However, each window should only be accessed from a single thread, otherwise the behavior will be undefined, i.e. you could run an element search and get a click event as a result if you don't access each window in a single-threaded fashion.

data Config Source

Record for configuring the Threepenny GUI server.

Constructors

Config 

Fields

tpPort :: 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.

tpCustomHTML :: Maybe FilePath

Custom HTML file to replace the default one.

tpStatic :: Maybe FilePath

Directory that is served under /static.

tpLog :: ByteString -> IO ()

Print a single log message.

defaultConfig :: ConfigSource

Default configuration.

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

startGUISource

Arguments

:: Config

Server configuration.

-> (Window -> UI ())

Action to run whenever a client browser connects.

-> IO () 

Start server for GUI sessions.

loadFileSource

Arguments

:: String

MIME type

-> FilePath

Local path to the file

-> UI String

Generated URI

Make a local file available as a relative URI.

loadDirectory :: FilePath -> UI StringSource

Make a local directory available as 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.

runUI :: Window -> UI a -> IO aSource

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

askWindow :: UI WindowSource

Retrieve current Window context in the UI monad.

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

Schedule an IO action to be run later.

Browser Window

type Window = SessionSource

The client browser window.

title :: WriteAttr Window StringSource

Title of the client window.

cookies :: ReadAttr Window [(String, String)]Source

Cookies on the client.

getRequestLocation :: Window -> IO URISource

Get the request location.

DOM elements

Create and manipulate DOM elements.

mkElementSource

Arguments

:: String

Tag name

-> UI Element 

Make a new DOM element.

getWindow :: Element -> IO WindowSource

Retrieve the browser Window in which the element resides.

delete :: Element -> UI ()Source

Delete the given element.

(#+) :: UI Element -> [UI Element] -> UI ElementSource

Append DOM elements as children to a given element.

string :: String -> UI ElementSource

Make a span element with a given text content.

getHead :: Window -> UI ElementSource

Get the head of the page.

getBody :: Window -> UI ElementSource

Get the body of the page.

children :: WriteAttr Element [Element]Source

Child elements of a given element.

text :: WriteAttr Element StringSource

Text content of an element.

html :: WriteAttr Element StringSource

Child elements of a given element as a HTML string.

attr :: String -> WriteAttr Element StringSource

HTML attributes of an element.

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

Set CSS style of an Element

value :: Attr Element StringSource

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

getValuesListSource

Arguments

:: [Element]

A list of elements to get the values of.

-> UI [String]

The list of plain text values.

Get values from inputs. Blocks. This is faster than many getValue invocations.

getElementsByTagNameSource

Arguments

:: Window

Browser window

-> String

The tag name.

-> UI [Element]

All elements with that tag name.

Get all elements of the given tag name. Blocks.

getElementByIdSource

Arguments

:: Window

Browser window

-> String

The ID string.

-> UI (Maybe Element)

Element (if any) with given ID.

Get an element by a particular ID. Blocks.

getElementsByClassNameSource

Arguments

:: Window

Browser window

-> String

The class string.

-> UI [Element]

Elements with given class.

Get a list of elements by particular class. Blocks.

Layout

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

grid :: [[UI Element]] -> UI ElementSource

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 ElementSource

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

column :: [UI Element] -> UI ElementSource

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

Events

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

data EventData Source

Data from an event. At the moment it is empty.

Constructors

EventData [Maybe String] 

domEventSource

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.

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

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 ElementSource

Convenient combinator for setting the CSS class on element creation.

type Attr x a = ReadWriteAttr x a aSource

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

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

get' :: x -> UI o
 
set' :: i -> x -> UI ()
 

set :: ReadWriteAttr x i o -> i -> UI x -> UI xSource

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

sink :: ReadWriteAttr x i o -> Behavior i -> UI x -> UI xSource

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 oSource

Get attribute value.

mkReadWriteAttrSource

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 iSource

Build attribute from a setter.

mkReadAttr :: (x -> UI o) -> ReadAttr x oSource

Build attribute from a getter.

Widgets

class Widget w whereSource

Widgets are data types that have a visual representation.

Methods

getElement :: w -> ElementSource

element :: MonadIO m => Widget w => w -> m ElementSource

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

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

class ToJS a Source

Helper class for rendering Haskell values as JavaScript expressions.

class FFI a Source

Helper class for making ffi a variable argument function.

Instances

FFI (JSFunction String) 
FFI (JSFunction ()) 
FFI (JSFunction Value) 
(ToJS a, FFI b) => FFI (a -> b) 

ffi :: FFI a => String -> aSource

Simple JavaScript FFI with string substitution.

Inspired by the Fay language. http://fay-lang.org/

 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.

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.

data JSFunction a Source

A JavaScript function with a given output type a.

runFunction :: JSFunction () -> UI ()Source

Run the given JavaScript function and carry on. Doesn't block.

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

callFunction :: JSFunction a -> UI aSource

Run the given JavaScript function and wait for results. Blocks.

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

callDeferredFunctionSource

Arguments

:: Window

Browser window

-> String

The function name.

-> [String]

Parameters.

-> ([Maybe String] -> IO ())

The continuation to call if/when the function completes.

-> IO () 

Call the given function with the given continuation. Doesn't block.

atomic :: Window -> IO a -> IO aSource

Atomically execute the given computation in the context of a browser window

Internal and oddball functions

fromProp :: String -> (Value -> a) -> (a -> Value) -> Attr Element aSource

toElement :: Element -> ElementSource

audioPlay :: Element -> UI ()Source

Invoke the JavaScript expression audioElement.play();.

audioStop :: Element -> UI ()Source

Invoke the JavaScript expression audioElement.stop();.