DOM-2.0.0: DOM Level 2 bindings for the WebBits package.Source codeContentsIndex
Data.DOM
Portabilityportable
Stabilityexperimental
Maintainergolubovsky@gmail.com
Contents
Module Data.DOM.WBTypes re-exported for convenience
Additional DOM support functions
Functions to construct Javascript values
Description

This module will most likely be imported by any Haskell program that uses DOM. Other modules from Data.DOM namespace are to be imported as needed, sometimes qualified because there are some name clashes in attributes and methods across the DOM interfaces.

Below is an example of Haskell code which generates Javascript to display traditional Hello World. This example shows that even a simplest Control.Monad.Identity will do. Of course, a more sofisticated Monad might provide more benefits, such as assigning some of expressions to Javascript variables to share and prevent repeated evaluation, automatic declaration of functions, etc.

 module Main where
 import WebBits.JavaScript
 import Control.Monad
 import Control.Monad.Identity
 import Data.DOM
 import Data.DOM.Dom
 import Data.DOM.Node
 import Data.DOM.HTMLDocument
 main = putStrLn $ show $ pp $ 
   FunctionStmt undefined (Id undefined "main") [] 
     (ExprStmt undefined $ runIdentity q)
 q = do
   d <- htmlDocument
   t <- mkText (string "Hello World") d
   b <- getm'body d
   addChild t b

Below is Javascript generated by this example. All expressions just nest where necessary, and method calls may be chained.

 
 function main()
 {
 window.document.body.appendChild(window.document.createTextNode("Hello World"));
 }
Synopsis
module Data.DOM.WBTypes
window :: Monad m => m (Expression TWindow)
document :: Monad m => m (Expression TDocument)
htmlDocument :: Monad m => m (Expression THTMLDocument)
documentBody :: (Monad mn, CHTMLDocument this) => Expression this -> mn (Expression THTMLBodyElement)
documentHead :: (Monad mn, CHTMLDocument this) => Expression this -> mn (Expression THTMLHeadElement)
inlineStyle :: (Monad mn, CHTMLElement this) => Expression this -> mn (Expression TCSS2Properties)
inlineStyleDecl :: (Monad mn, CHTMLElement this) => Expression this -> mn (Expression TCSSStyleDeclaration)
mkText :: (Monad mn, CDocument this) => Expression String -> Expression this -> mn (Expression TText)
addChild :: (Monad m, CNode c, CNode p) => Expression c -> Expression p -> m (Expression c)
string :: String -> Expression String
number :: Integral n => n -> Expression Double
bool :: Bool -> Expression Bool
true :: Expression Bool
false :: Expression Bool
Module Data.DOM.WBTypes re-exported for convenience
module Data.DOM.WBTypes
Additional DOM support functions
window :: Monad m => m (Expression TWindow)Source
Access the global Window object.
document :: Monad m => m (Expression TDocument)Source
Access the current document. This indeed should be made through the Window interface, but current (incomplete) specification does not provide an easy way for that.
htmlDocument :: Monad m => m (Expression THTMLDocument)Source
Same as above, using the HTMLDocument interface.
documentBody :: (Monad mn, CHTMLDocument this) => Expression this -> mn (Expression THTMLBodyElement)Source
Access the BODY node of the current HTML document. Same as 'get\'body', but with proper type of the returned value.
documentHead :: (Monad mn, CHTMLDocument this) => Expression this -> mn (Expression THTMLHeadElement)Source
Access the HEAD node of the current HTML document.
inlineStyle :: (Monad mn, CHTMLElement this) => Expression this -> mn (Expression TCSS2Properties)Source
Obtain an inline style (TCSS2Properties) interface of an object
inlineStyleDecl :: (Monad mn, CHTMLElement this) => Expression this -> mn (Expression TCSSStyleDeclaration)Source
Obtain an inline style (TCSSStyleDeclaration) interface of an object
mkText :: (Monad mn, CDocument this) => Expression String -> Expression this -> mn (Expression TText)Source
A maker function for a TEXT element.
addChild :: (Monad m, CNode c, CNode p) => Expression c -> Expression p -> m (Expression c)Source
Same as appendChild, but with type signature reflecting that returned value is the node added.
Functions to construct Javascript values
string :: String -> Expression StringSource
Create a Javascript string literal out of a string.
number :: Integral n => n -> Expression DoubleSource
Create a Javascript numeric literal out of a numeric value.
bool :: Bool -> Expression BoolSource
Create a Javascript boolean literal out of a Boolean.
true :: Expression BoolSource
Javascript True value
false :: Expression BoolSource
Javascript False value
Produced by Haddock version 2.4.2