Safe Haskell | None |
---|---|
Language | Haskell98 |
Graphics.UI.Threepenny.Core
Contents
- data Config = Config {
- jsPort :: Maybe Int
- jsAddr :: Maybe ByteString
- jsCustomHTML :: Maybe FilePath
- jsStatic :: Maybe FilePath
- jsLog :: ByteString -> IO ()
- defaultConfig :: Config
- startGUI :: Config -> (Window -> UI ()) -> IO ()
- data UI a
- runUI :: Window -> UI a -> IO a
- askWindow :: UI Window
- liftIOLater :: IO () -> UI ()
- module Control.Monad.IO.Class
- module Control.Monad.Fix
- data Window
- title :: WriteAttr Window String
- data Element
- getWindow :: Element -> IO Window
- mkElement :: String -> UI Element
- mkElementNamespace :: Maybe String -> String -> UI Element
- delete :: Element -> UI ()
- string :: String -> UI Element
- getHead :: Window -> UI Element
- getBody :: Window -> UI Element
- (#+) :: UI Element -> [UI Element] -> UI Element
- children :: WriteAttr Element [Element]
- text :: WriteAttr Element String
- html :: WriteAttr Element String
- attr :: String -> WriteAttr Element String
- style :: WriteAttr Element [(String, String)]
- value :: Attr Element String
- getElementsByTagName :: Window -> String -> UI [Element]
- getElementById :: Window -> String -> UI (Maybe Element)
- getElementsByClassName :: Window -> String -> UI [Element]
- grid :: [[UI Element]] -> UI Element
- row :: [UI Element] -> UI Element
- column :: [UI Element] -> UI Element
- type EventData = Value
- domEvent :: String -> Element -> Event EventData
- unsafeFromJSON :: FromJSON a => EventData -> a
- disconnect :: Window -> Event ()
- on :: (element -> Event a) -> element -> (a -> UI void) -> UI ()
- onEvent :: Event a -> (a -> UI void) -> UI ()
- onChanges :: Behavior a -> (a -> UI void) -> UI ()
- module Reactive.Threepenny
- (#) :: a -> (a -> b) -> b
- (#.) :: UI Element -> String -> UI Element
- type Attr x a = ReadWriteAttr x a a
- type WriteAttr x i = ReadWriteAttr x i ()
- type ReadAttr x o = ReadWriteAttr x () o
- data ReadWriteAttr x i o = ReadWriteAttr {}
- set :: ReadWriteAttr x i o -> i -> UI x -> UI x
- sink :: ReadWriteAttr x i o -> Behavior i -> UI x -> UI x
- get :: ReadWriteAttr x i o -> x -> UI o
- mkReadWriteAttr :: (x -> UI o) -> (i -> x -> UI ()) -> ReadWriteAttr x i o
- mkWriteAttr :: (i -> x -> UI ()) -> WriteAttr x i
- mkReadAttr :: (x -> UI o) -> ReadAttr x o
- bimapAttr :: (i' -> i) -> (o -> o') -> ReadWriteAttr x i o -> ReadWriteAttr x i' o'
- fromObjectProperty :: (FromJS a, ToJS a, FFI (JSFunction a)) => String -> Attr Element a
- class Widget w where
- getElement :: w -> Element
- element :: MonadIO m => Widget w => w -> m Element
- widget :: Widget w => w -> UI w
- debug :: String -> UI ()
- class ToJS a
- class FFI a
- data JSFunction a
- ffi :: FFI a => String -> a
- runFunction :: JSFunction () -> UI ()
- callFunction :: JSFunction a -> UI a
- ffiExport :: IsHandler a => a -> UI JSObject
- fromJQueryProp :: String -> (Value -> a) -> (a -> Value) -> Attr Element a
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=8023
.)
The server is multithreaded. FFI calls can be made concurrently, but events are handled sequentially.
Configuration of a Foreign.JavaScript server.
Constructors
Config | |
Fields
|
defaultConfig :: Config Source
Default configuration.
Port from environment variable or 8023
,
listening on localhost
, no custom HTML, no static directory,
logging to stderr.
Arguments
:: Config | Server configuration. |
-> (Window -> UI ()) | Action to run whenever a client browser connects. |
-> IO () |
Start server for GUI sessions.
UI monad
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.
liftIOLater :: IO () -> UI () Source
Schedule an IO
action to be run later.
module Control.Monad.IO.Class
module Control.Monad.Fix
Browser Window
DOM elements
Create and manipulate DOM elements.
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.
(#+) :: UI Element -> [UI Element] -> UI Element infixl 8 Source
Append DOM elements as children to a given element.
value :: Attr Element String Source
Value attribute of an element.
Particularly relevant for control widgets like input
.
Arguments
:: Window | Browser window |
-> String | The tag name. |
-> UI [Element] | All elements with that tag name. |
Get all elements of the given tag name.
Arguments
:: Window | Browser window |
-> String | The ID string. |
-> UI (Maybe Element) | Element (if any) with given ID. |
Get an element by a particular ID.
FIXME: Misleading type, throws a JavaScript exception when element not found.
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.
Events
For a list of predefined events, see Graphics.UI.Threepenny.Events.
Events may carry data. At the moment, they may return a single JSON value, as defined in the Data.Aeson module.
Arguments
:: String | Event name. A full list can be found at
http://www.w3schools.com/jsref/dom_obj_event.asp.
Note that the |
-> 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.
module Reactive.Threepenny
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
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 | |
Instances
Functor (ReadWriteAttr x i) |
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.
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, FFI (JSFunction a)) => String -> Attr Element a Source
Turn a JavaScript object property .prop = ...
into an attribute.
Widgets
Widgets are data types that have a visual representation.
Methods
getElement :: w -> Element Source
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.
Helper class for rendering Haskell values as JavaScript expressions.
Minimal complete definition
Helper class for making ffi
a variable argument function.
Minimal complete definition
fancy
data JSFunction a Source
A JavaScript function with a given output type a
.
Instances
Functor JSFunction | Change the output type of a |
FromJS b => FFI (JSFunction b) |
ffi :: FFI a => String -> a Source
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.
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 a Source
Run the given JavaScript function and wait for results. Blocks.
The client window uses JavaScript's eval()
function to run the code.
ffiExport :: IsHandler a => a -> UI JSObject Source
Export the given Haskell function so that it can be called from JavaScript code.
FIXME: At the moment, the function is not garbage collected.