jsmw-0.1: Javascript Monadic Writer base package.

Portabilityportable
Stabilityexperimental
Maintainergolubovsky@gmail.com

Language.JSMW.Monad

Contents

Description

A special monad: the core of the Writer.

Synopsis

The Monad itself

type JSMW e a = RWS (Expression e) [Statement ()] Int aSource

A type of the writer: based on the RWS Monad. The Reader part holds an expression to reference the curent HTML container element. The Writer part is the list of Javascript statements being formed. Container may be any DOM Element, but not a Text node or anything else.

runJSMWSource

Arguments

:: Int

Initial state (usually 0)

-> JSMW THTMLBodyElement (Expression a)

The JSMW expression to process

-> (Expression a, Int, [Statement ()])

Result: (final expression, final state, produced statements),

Run the code writer (raw way, returns both state and log). Container will be initialized into the body of the current HTML document. Same as runJSMWWith currDocBody

runJSMWWithSource

Arguments

:: CElement e 
=> Expression e

container

-> Int

Initial state (usually 0)

-> JSMW e (Expression a)

The JSMW expression to process

-> (Expression a, Int, [Statement ()])

Result: (final expression, final state, produced statements),

Run the code writer (raw way, returns both state and log) with explicitly specified container.

getBlock :: (Expression a, Int, [Statement ()]) -> Statement ()Source

Obtain a block statement from the result of runJSWM. The last expression forms a 'return' statement, so the resulting block may be used as a function's body.

currDocBody :: Expression THTMLBodyElementSource

Body of the current document: use it to start the toplevel instance of the Writer as a container for runJSMWWith.

Compilation control

once :: Expression a -> JSMW e (Expression a)Source

The JSMW code consists of monadic smart constructors forming Javascript method calls. These constructors are inlined each time they are referenced. The once combinator causes a variable assignment statement to be formed with the variable assigned to the expression returned. All future references will be to the variable rather than to the expression. Since the expression will be evaluated when assigned to the variable, referencing the variable will reference the result, and possible effect will not be repeated.

mkNewVar :: JSMW e StringSource

Create a unique variable name. This function increments the internal state of the monad and produces a string consisting of the letter 'v' and a unique number.

writeStmt :: Statement () -> JSMW e ()Source

Write out a statement. This function utilizes the Writer part of the monad, and adds the Javascript statement provided to the Writer's log.

Create Javascript values, Monadic versions

stringM :: String -> JSMW e (Expression String)Source

Create a Javascript string literal out of a string, monadic version.

numberM :: Integral n => n -> JSMW e (Expression Double)Source

Create a Javascript numeric literal out of a numeric value, monadic version.

boolM :: Bool -> JSMW e (Expression Bool)Source

Create a Javascript boolean literal out of a Boolean, monadic version.

Layout control

type ECRF e n = Expression THTMLDocument -> JSMW e (Expression n)Source

Type of a function creating HTML elements, e. g. mkButton, mkDiv

passiveSource

Arguments

:: (CNode n, CElement e) 
=> ECRF e n

function that creates a HTML element

-> JSMW e (Expression ())

passive does not return a value

Insert a passive element into the current container.

nestSource

Arguments

:: (CNode n, CElement e, CElement p) 
=> ECRF e n

function that creates a HTML element to nest

-> Expression p

parent element (implicit if >>= is used)

-> JSMW e (Expression n)

nested element is returned (per addChild)

Nest an element inside another element via monadic composition. Example usage:

ask >>= nest mkButton >>= nest (mkText $ string "Foo")

inserts a button with text "Foo" into the current container.

The type system makes sure that only an instance of a DOM Element can nest other elements, e. g.

 ... mkText (string "Foo") >>= nest mkDiv

would not typecheck.

Example: a text, a newline, and two buttons: ask retrieves the current container.

 q = do
   passive (mkText $ string "Hello")
   passive mkBr
   ask >>= nest mkButton >>= nest (mkText $ string "Foo")
   ask >>= nest mkButton >>= nest (mkText $ string "Bar")

containerSource

Arguments

:: (CElement n, CElement e) 
=> ECRF e n

function that creates a new container

-> JSMW n (Expression x)

whatever goes into that container

-> JSMW e (Expression ())

container does not return a value

Specify a new container that in nested into the current one. As long as the container is active, all subsequently defined elements will be inserted into it.

Example: a Button with two text labels separated with a newline:

   mkButton `container` (do
     passive (mkText $ string "Hello") 
     passive mkBr
     passive (mkText $ string "GoodBye"))

Everything defined within a do expression is inserted into the button which is the new container.

Element references

Sometimes it may be necessary to create an element, but "engage" it later. Element references help achieve this. References also can be useful when several elements have to interact with each other: elements created with nest or container are accessible only from the "inside" code. To enable interaction, a reference to an element has to be made known to another element's event handler.

A rather contrived example below shows how to create an input element, and insert it into a button later.

 import qualified Data.DOM.HTMLInputElement as I
 ...
 inp <- ref I.mkInput -- create a reference
 inp `inside` (setStyle ["border-color" := "green"]) -- do something with the reference
 ...
 inpr <- ref2ecrf inp -- simulate an element creation function
 mkButton `container` (inpr `container` (ask >>= I.set'value (string "foo")))

ref :: (CNode e, CElement n) => ECRF e n -> JSMW e (Expression n)Source

Create an element for future use, and return a reference to it. The element may be inserted into a container different from one it was created with (when ref was called). But it should be used within the same document it was created inside.

ref2ecrf :: (CElement e1, CElement e2, CNode n) => Expression n -> JSMW e1 (ECRF e2 n)Source

Turn an element reference into element creation function. It can be useful when an element created earlier has to be used as a container, or a passive element, or nested. The type signature of ref2ecrf reflects the fact that the element was created when one container was current, but may be used with another container.

insideSource

Arguments

:: (CElement n, CElement e) 
=> Expression n

reference to an element

-> JSMW n (Expression x)

whatever goes into that element

-> JSMW e (Expression ())

inside does not return a value

Essentially same as container except that a reference to an element has to be supplied rather than an element creation function. Another difference from container: element referenced is not added as a child to the current container.

Inline style and other decorations

data CSSDeco Source

Data type for building inline style assignment expressions.

Constructors

String := String 

setStyle :: CHTMLElement e => [CSSDeco] -> JSMW e (Expression ())Source

An action to use within a container to update its inline style. setStyle called with an empty list does not change the inline style. Note that style settings are compile-time only.

Example: a DIV element with style settings applied and a text:

   mkDiv `container` (do
     setStyle ["display" := "inline"
              ,"float" := "right"
              ,"width" := "45%"
              ,"text-align" := "center"
              ,"background-color" := "green"
              ,"color" := "white"
              ,"font-weight" := "bold"]
     passive (mkText $ string "Styled"))

Event handling

type OnHandler e c = Expression e -> JSMW c (Expression Bool)Source

A type for a on-style event handler. It represents a function which takes an event and returns a boolean.

setHandler :: (CHTMLElement c, CEvent e) => String -> OnHandler e c -> JSMW c (Expression ())Source

Set a on-style (e. g. onclick) event handler on the current container.

Example: a button with a click handler which shows the X coordinate of the click.

  mkButton `container` (do
    passive (mkText $ string "Click Me")
    setHandler "click" clickHandler)
  ...
  clickHandler :: OnHandler TMouseEvent THTMLButtonElement
  clickHandler e = do
    getm'clientX e >>= toString >>= alert
    return true

A handler function has one argument which gets the reference to the event caught. The handler function also may implicitly address the container it was set on by calling ask or passive. For example, calling passive (mkText $ string "x") within a handler will result in a text node being added to the container.

Also note that the OnHandler type may be parameterized by the type of containers it can be set on. In the example above, the handler may only be set on buttons.

The MSIE-specific code to obtain event from the static attribute of the current window is inserted in the beginning of the handler automatically.

ask :: MonadReader r m => m r

Retrieves the monad environment.