Haskell in web browser

From HaskellWiki
Revision as of 03:20, 26 March 2008 by DimitryGolubovsky (talk | contribs) (All sections here)
Jump to navigation Jump to search
Haskell in web browser
A Tutorial

Preface

This Tutorial is written in connection with launch of the experimental Yhc Web Service, an online tool to explore the possibilities of Haskell use as a language to program client part (that is, running in a browser) of Web applications by the means of conversion of Haskell source to Javascript.

The idea of such conversion has been around for a while <insert citations>, and Yhc Javascript backend is its practical implementation. Use of functional languages for client-side Web programming is a relatively new phenomenon, and hopefully this Tutorial along with the Service online will attract more attention and subsequently programmers resources into this area.

Basics of programming for web browser

The most widespread (and natively interpreted by most existing Web browsers) language for client-side Web programming is Javascript. Several APIs are exposed by browser to Javascript programs, such as Document Object Model (DOM), Cascading Style Sheets (CSS), and XML HTTP Request to name a few. In order for a Haskell program to communicate with browser using these APIs, proper language bindings were created. The subsections of this section discuss approaches and methods used to create those bindings. Although direct use fo these bindings may not even be needed in most cases, it is useful to have understanding of how things work at this level. Please note though, that this Tutorial does not focus on the specifics of DOM/CSS/XMLHTTP programming per se; it contains information how to use these interfaces in a Haskell program. For details please refer to the original sources at the Web Consortium. Also, W3 Schools website contains very useful information and practical excercises.

DOM

Formalized description of DOM interfaces is provided by the Web Consortium in the form of OMG IDL definitions. An example of such definitions can be found here.

It was necessary to convert these definitions to Haskell function declarations to make them available to Haskell programs for Web browser. The special utility, domconv is part of the Javascript backend toolset. The utility is based on HaskellDirect, although most of non-IDL related functionality was stripped, and Haskell source generator was completely rewritten. In this section, we discuss the logic of IDL to Haskell conversion.

DOM interfaces vs. Haskell type classes

Web Consortium's DOM definitions are presented as a hierarchy of interfaces. For example, the Node interface is a parent to the majority of other interfaces, such as Document (direct ancestor), or HTMLElement (not a direct ancestor, but HTMLElement should inherit all properties and methods of Node).

This is achieved by defining Haskell type classes whose hierarchy repeats the hierarchy of DOM interfaces. Thus, we have the CNode and CDocument classes. For each DOM interface, also a phantom data type is defined: TNode, and TDocument correspondingly. Phantom types are assigned to concrete values (references to DOM objects) while type classes are used to constrain types of parameters of functions working with those DOM objects. The CDocument class is defined as:

class CNode a => CDocument a
data TNode
data TDocument
instance CNode TNode
instance CDocument TDocument
instance CNode TDocument

to reflect inheritance of Document from Node. Accordingly, continuing our example, for HTMLElement, we have:

class CNode a => CElement a
class CElement a => CHTMLElement a
data THTMLElement
instance CElement THTMLElement
instance CHTMLElement THTMLElement
instance CNode THTMLElement

and so on. This means that a value of THTMLElement may be passed as argument to a function expecting an instance of CNode, but not the opposite. Similarly, a value of TDocument can by no means be passed to a function expecting a THTMLElement. This increases type safety of a program which, if written in Javascript, would have lacked such safety completely (or eventually would end up throwing an exception from runtime type check).

Below is an example of such type constrained function:

hasChildNodes :: CNode this => this -> CPS c Bool

which corresponds to the hasChildNodes function defined within the Node interface. Any DOM object which is a Node can be passed to this function (by reference) as the this argument.

Attributes vs. getters and setters

Within interfaces, DOM specification defines attributes and methods. Attributes are either read-only (such as nodeName of the Node interface) or read-write (such as nodeValue of the same interface). In Haskell bindings, getter (for read-only attributes), and both getter and setter (for read-write attributes) functions are defined in straightforward manner:

get'nodeName :: CNode this => this -> CPS c String
set'nodeValue :: CNode zz => String -> zz -> CPS c zz
get'nodeValue :: CNode this => this -> CPS c String

Getters always take the object containing an attribute as the first argument, this, and it is always constrained to the type class corresponding to the DOM interface. Setters always take the value to be set as the first argument, and the object containing the attribute as the second argument. Setters always return reference to the same object where an attribute was set. The latter property allows to concatenate multiple setters in Continuation-passing style, such as:

........$ \he ->
  (set'id "myid")
  (set'lang "en")
  (set'title "Hello")

This whole construction will pass the same object (he) to the continuation, but continuation will deal with updated object.

The setters in the example above are defined in the DOM.Level2.HTMLElement module.

Methods vs. functions

Interface methods are translated to Haskell functions whose type signatures have proper type coetraints. Thus, the getElementById function defined in the Document interface as

Element getElementById(in DOMString elementId);

translates to Haskell function:

getElementById :: (CDocument this, CElement zz) => this -> String -> CPS c zz

as follows from its type, getElementById does not return a value of concrete type, but rather a type-constrained value. Values of types corresponding to DOM interfaces, translate to type-constrained rather than concrete values. This sometimes makes it necessary to supply explicit type signatures unless a function receiving the returned constrained value has a type signature that brings a constrained type down to a concrete type.

Maker functions

The IDL conversion utility domconv auto-creates convenient functions that serve as constructors of DOM objects corresponding to HTML tags. An example of such maker function is:

mkDiv :: CHTMLDocument a => a -> CPS c THTMLDivElement

which creates a DOM node tagged with <DIV>. Such maker functions are defined for most of HTML elements. Maker functions always return values of concrete type.

Threads

Threads emulation

Execution of Javascript in Web browser is always single-threaded. It is however possible and useful to emulate multi-threaded execution with window.setTimeout method.

Javascript threads available to Haskell programs have must of "real" threads features stripped off: there are no thread identifiers, threads must always explicitly yield execution, time-wise threads scheduling is very loose, etc.

Please refer to the Control.Concurrent.JSThreads module documentation. A working threads example (including inter-thread message passing, see below) can be found here.

CPS and threads

Continuation Passing Style allows for very efficient implementation of threads: in fact, switching context between threads is merely saving a continuation of currently executing thread in some static memory object, and evaluating continuation of (resuming) a thread that was similarly suspended earlier.

Message passing between threads

Threads may pass messages to each other, using Message Boxes. Sending messages is asynchronous (although rescheduling of threads execution occurs to resume the receiving thread). Sending a message may fail if there is a message in the Message Box (no message buffering). Receiving messages is always a blocking operation. Receiving a message may fail if there is already a thread waiting on the Message Box. Therefore more than one thread may send messages to the same Message Box (but sending all messages is not guaranteed unless result of sending is checked, and appropriate action taken if sendMsg fails), but more than one thread may not receive messages from the same Message Box.

Events handling

From Javascript standpoint, attaching an event handler to a HTML element is simply setting appropriate on- attribute with reference to appropriate function to which event information will be passed. The low-level events API available to Haskell programs provides means for a thread to wait on a HTML element for a certain event to occur. Refer to the CDOM.Level2.Events module for more information.

XML HTTP

XML HTTP API is available to Haskell programs running in Web browser. Refer to the Network.XMLHTTP module for more information.

JSON

Although not part of the native browser API, JSON is a useful way to access properties of Javascript objects. Besides, CouchDB on which the Yhc Web Service is based, uses JSON as encoding format for queries and responses.

The JSON API provided to Haskell programs is based on the opaque type JsonNode. Operations over JSON nodes are monadic as they may fail. For example, the getValueByName function fails if the JSON node queried does not have a value with given name. Monadic interface allows to write code that retrieves values from JSON node in do notation and compose operations using >>= (monadic bind).

Thus, the following code:

uri = fromMaybe "----" $ do
  buri <- splitURI loc
  prot <- getValueByName "protocol" buri >>= getString
  auth <- getValueByName "authority" buri >>= getString
  anchor <- getValueByName "anchor" buri >>= getString
  let uri = prot ++ "://" ++ auth ++ "/" ++ anchor
  return uri

retrieves parts of an URI (see below) represented as a JSON node, and composes a new URI out of them. If the URI JSON node does not contain any of the values requested, the whole monadic sequence fails, and the fall-back value "----" will be returned.

Refer to the Data.JsonNode module for more information.

URI

Haskell programs running in Web browser may operate on Uniform Resource Identifiers (URI) by transforming URI strings into JSON nodes. The function for such conversion is splitURI defined in the Network.XMLHTTP module. It also has monadic interface (see example in the JSON section). The function itself is a wrapper for the URI parser based on Steven Levithan's parseUri Javascript function.

Haskell web toolkit

HsWTK is no longer actively developed or maintained.


Haskell Web Toolkit (further referred to as HsWTK) is a thin layer built on top of DOM interfaces. It provides program interfaces to compose static layout of a web application page, and to hook up visual elements of an application to event handlers and XML HTTP communication means. HsWTK hides the low-level DOM APIs where possible; however their knowledge may be necessary to develop certain types of visual components and event handlers.

Widgets

Widgets are basic building blocks of Graphical User Interface (GUI).

To build a web-based GUI, HsWTK defines the following type:

type Widget =  THTMLDocument -> THTMLElement -> Bool

That is, Widget is a function, or, to be a more precise, an action (as evaluation of this function does assume side effects). This action's first argument, of type THTMLDocument, refers to the HTML document containing the GUI elements. The action's second argument, of type THTMLElement, refers to a parent HTML element. This makes perfect sense from the DOM standpoint, as in order to create a visible element on a Web page, it is at least necessary to create an element by calling Document.createElement method (which needs a Document), and next to insert the newly created element into some (parent) node by calling Node.appendChild method.

HTML elements as widgets

So, inside the Widget action, some work may be done to create a HTML element, and make it a child of some other Widget. This is generalized by HsWTK as Element Creation Function, and defined as

type ECRF n = (THTMLDocument -> CPS Bool n)

Now, if we refer to Maker functions defined for HTML-tagged Elements we may see some similarity:

mkDiv :: CHTMLDocument a => a -> CPS c THTMLDivElement

If we substitute n in ECRF definition with THTMLDivElement, and remember that THTMLDocument is an instance of CHTMLDocument, we get a perfect match. From this, it may be concluded that Maker functions may serve as Element creation functions.

Passive widgets

The simpliest form of Widget is passive widget. Passive widgets only display themselves as part of Web GUI, but are not capable of nesting other widgets. A good example of such passive widget is text label or non-clickable image.

HsWTK defines a function passive which given an Element Creation Function, returns a Widget:

passive :: CNode n => ECRF n -> Widget

Thus, given a Maker function (e. g. mkImg), applying passive to it creates an image which will appear in the proper place of a Web page.

For a text element itself, there is a Maker function mkText which produces a text node to be inserted into a < DIV > or < SPAN > or any other element with closing tag. mkText is not a pure Maker function though; due to its type signature, flip has to be applied to it.

One important passive widget not based on a HTML element is nowidget. It may be used as a placeholder for any passive widget, and does not produce any kind of effects.

Containers

HTML elements with closing tags contain other elements in between. To reflect this, HsWTK defines another function, container. This function, applied to a Maker function, produces a widget capable of nesting other widgets.

Composition combinators

For the purpose of sequencing widgets within a container, or nesting widgets in containers, HsWTK defines combinators +++, <<, |<<, and ++|. Please refer to the appropriate section of the Graphics.UI.HsWTK module documentation.

The +++ combinator sequences two widgets inside a container. Widgets (a +++ b) appear second (b) at the right of the first (a). Result of such composition is also a widget, and it may be sequenced with other widgets. (a +++ b) +++ c is same as a +++ b +++ c.

The << combinator nests a widget (or composition of widgets) in a container.

So, the following fragment of code creates a widget consisting of a < DIV > with a text inside:

mkTextFl = flip mkText
container mkDiv << passive (mkTextFl "Hello World")

To simplity the code, HsWTK defines these two functions:

  • textP which is equivalent to passive (flip mkText txt)
  • |<< which is defined as c |<< d = container c << d, that is the word container may be omitted.

Document body

The toplevel widget (one that is not nested in any other widget) has to be inserted into the HTML document body. This is acieved by applying the function docBodyC to the toplevel widget. This application often becomes the main function of a Web application. Please note that document body is not a Widget.

Code example - Hello Web

At this point, we are able to code our first HsWTK example. By tradition, this is a Hello ... program. Paste the code below into Yhc Web Service New Entry Form and press the Submit button (don't forget to fill out the Author and Title field).

-- Begin Pasteable Code --
module TutEx1 where

import DOM.Level2.HTMLSpanElement
import Graphics.UI.HsWTK

-- The Main Function

main = docBodyC mainW

-- The Toplevel Widget

mainW = (mkSpan |<< (textP "Hello " +++ textP "Web"))
-- End   Pasteable Code --

After the compilation is finished, load the generated Web page. Haskell says Hello to the new environment it just has started to explore.

The example shows all the facilities of HsWTK we recently discussed:

  • widgets sequencing (+++ combines two text elements one after another)
  • creation of a HTML Element based widget (mkSpan)
  • nesting composition of widgets in a container (|<<)
  • inserting the toplevel widget into the document body (docBodyC)

Decorators

Decorators are not Widgets: they are tools to change properties of a widget they are applied to, at the moment of that widget creation.

Earlier we discussed setters defined for HTML Elements' writable attributes. HsWTK defines a function decorate which when applied to a setter, produces a decorator. An example of such a decorator is withTitle defined as shown below:

withTitle :: (CHTMLElement b) => ((a -> ((b -> (CPS c b)) -> d)) -> (String -> (a -> d)))
withTitle = decorate set'title

The set'title function is a setter for the title attribute of HTMLElement.

Decorators are binary functions taking the Widget to decorate as the first argument, and the value used to decorate as the second. In our case, this looks like this:

... mkDiv `withTitle` "This div has a title" |<< textP "titled div"

HsWTK defines some frequently used decorators, such as withClass to specify the class attribute of an element used in a widget, or withSrc to use with an < IMG > element to specify image source.

Inline style

A special decorator, withStyle, represents a more complicated case. It does not alter attributes/properties of a widget element it is used with; instead it affects inline style properties of the widget element.

While arttribute-based decorators take simple values (strings, less often numbers) to decorate widget elements, withStyle takes a list of name-value pairs. Both names and values are strings, and should conform to the Cascading Style Sheets Specification.

Property names and values are paired using the := data constructor. The latter is just a binary infix data constructor, and it is used just to improve the code appearance, so CSS property assignments look more natural.

Our next pasteable examples deal with widget elements' inline style manipulations. The following example displays a centered white bold text on green background spanning over 45% of browser window width floating to the right side of browser window.

-- Begin Pasteable Code --
module TutEx2 where

import DOM.Level2.HTMLDivElement
import Graphics.UI.HsWTK

main = docBodyC mainW

mainW = mkDiv `withStyle` ["display" := "inline"
                          ,"float" := "right"
                          ,"width" := "45%"
                          ,"text-align" := "center"
                          ,"background-color" := "green"
                          ,"color" := "white"
                          ,"font-weight" := "bold"] |<< textP "Hello Web"
-- End   Pasteable Code --

Our next example is more contrived. It displays a line of text with each character colored differently, and colors are taken from an infinitely repeating sequence. Note the use of nowidget: it is used with foldr as a "starting value".

-- Begin Pasteable Code --
module TutEx2a where

import DOM.Level2.HTMLSpanElement
import Graphics.UI.HsWTK

-- Main function

main = docBodyC mainW

-- Text to display

txt = "Changing Colors of World Wide Web"

-- Make an infinite list of colors for each character to display

fgcs = cycle ["red", "blue", "green", "cyan", "magenta"]

-- Sequence as many spans as needed for colored characters

mainW = foldr (+++) nowidget (zipWith spanc fgcs txt)

-- Color a single character by creating a span properly styled

spanc f c = mkSpan `withStyle` ["color" := f] |<< textP [c]
-- End   Pasteable Code --

Activators

At this point, we are able to create static layout of Widgets. No way has been shown yet how to make GUI elements interact.

Activators serve exactly this purpose. Activators are functions, usually endlessly looped which are executed each in its own thread. These functions repeatedly receive messages from Message Boxes, and also intercept events induced by user. Activators also are able to modify on-the-fly properties of Widgets to which they are "attached". Some Activators also perform data exchange over XMLHTTP.

Method of inter-widget communication described here is derived from one discussed in the following paper:

Gadgets: Lazy Functional Components for Graphical User Interfaces (1995) by Rob Noble, Colin Runciman.

HsWTK defines a type for these functions:

type ACTF = THTMLElement -> Bool

This type has one thing in common with the Widget type: a THTMLElement is one of function's arguments.

HsWTK also defines a function active which being applied to an Activator turns it into a Widget, that is, an Activator may be nested within a container: that's what was meant above for an Activator "attached" to a Widget.

Our next example consists of two <INPUT> elements: when something is typed in the left one, it is repeated in the right one:

module TutEx3 where

import Graphics.UI.HsWTK
import Control.Concurrent.JSThreads

main = docBodyC mainW

mainW = msgBox $ \ibx2 ->
        msgBox $ \dummy ->
        inputI |<< active (evtBCastA "keyup" rtgt [ibx2])
    +++ inputI |<< active (fwdValueA ibx2 dummy)

rtgt e = readTargetU e FwdUpdSet

Let's go line by line. As new things are introduced, they will be discussed in appropriate sections.

Message boxes and activators

Message boxes were discussed earlier as means for inter-thread communications. Each Activator is represented by a separate thread. Unlike previous code examples, the main Widget code contains two calls to the msgBox function. The msgBox function passes reference to newly created Message box to its continuation. Thus, after the following code:

msgBox $ \ibx2 ->
msgBox $ \dummy ->

is executed, two Message boxes are created.

Wiring the static layout

The following code of the main Widget would have produced the same static layout of two input elements:

mainW = inputI |<< nowidget
    +++ inputI |<< nowidget

Note the use of nowidget here: the inputI function produces an <INPUT> element, and the |<< combinator assumes that the <INPUT> element is a container, that is, should have something nested.

This approach may be used during Web GUI design: make Widgets containers where necessary, but nest nowidget's instead of Activators.

Compare the code of mainW above with the code from our example:

mainW = ...
        inputI |<< active (evtBCastA "keyup" rtgt [ibx2])
    +++ inputI |<< active (fwdValueA ibx2 dummy)

Each <INPUT> element got an Activator. As it may be guessable, Activator attached to the first declared (showing at the left of Web page) <INPUT> element, transmits its value (whatever is typed in), and Activator attached to the <INPUT> element declared second (showing right of the first <INPUT>) receives the value.

Mapping and broadcasting events

HsWTK defines the following Activator function: evtBCastA:

evtBCastA :: CEvent e => String -> (e -> CPS Bool v) -> [MSGBOX Bool v] -> ACTF

The first argument of String type is the type of event this Activator responds to. Only one event type may be specified. Event types are derived from on- attribute names, e. g. "keyup" corresponds to onkeyup event, etc.

The second argument is a CPS-style function mapping an event to some value of type v. Such a function may retrieve certain parameters of an event (such as code of a key pressed), or event produce some side effects, although this is not recommended.

The third argument is list of Message boxes where the mapped value will be broadcast over. Broadcast will be performed using the sendMsg_ function, so there is possibility of message non-delivery.

HsWTK defines two functions that can be used as the second argument of evtBCastA:

  • evt2ConstU: maps any event to the given constant value
  • readTargetU: maps any event to the value (always of type String) retrieved from its target element. The target element must support the value property.

The latter function is used in our example. Basically the Activator attached to the left <INPUT> element intercepts each onkeyup event, retrieves event target value (that is, the <INPUT> element it is attached to), maps it to the value forwarding message (see below), and sends to the Message box that other <INPUT> element may be listening to by means of its Activator.

Value forwarding protocol

Value forwarding protocol is a convention set by HsWTK regarding the way how Widgets values may be set externally, or queried. A conforming Widget should have an Activator parameterized with two Message boxes. The first Message Box is for receiving messages of type FwdValueMsg. The second Message Box is for sending messages of type String.

The Activator should act upon the receipt of FwdValueMsg as follows:

  • FwdCurr: forward the current value, not changing it
  • FwdCurrSet s: forward the current value to the default Message Box, update with new value s
  • FwdUpdSet s: update element's value with new value s, forward the new value to the default Message Box
  • FwdCurrTo m: like FwdCurr but to a specified Message Box m
  • FwdCurrSetTo m s: like FwdCurrSet but to a specified Message Box m
  • FwdUpdSetTo m s: like FwdUpdSet but to a specified Message Box m

Messages FwdCurrTo, FwdCurSetTo, FwdUpdSetTo cause the value of the Widget to be forwarded to a Message Box different from one the Activator is parameterized with.

In our code example, the second <INPUT> element has an Activator fwdValueA:

... inputI |<< active (fwdValueA ibx2 dummy)

This is a "standard" Activator provided by HsWTK for Widgets based on HTML elements with attribute value defined. The first Message Box is the same where the first <INPUT> element's Activator broadcasts the value upon each key release.

The second Message Box is not used in any way, but it is there since fwdValueA requires it.

Now, looking at the event mapping function of the first <INPUT> element:

rtgt e = readTargetU e FwdUpdSet

which means that the constructor FwdUpdSet is applied to the value retrieved from the event target element (that is, the first <INPUT>), yielding the message per Value forwarding protocol. This value will be received by the second <INPUT> element's Activator, and will subsequently show in the element.

More complex widgets

Our next example shows a Widget which has some functionality encapsulated, while externally this is just an <INPUT> element. The example features an input field which validates its value (as it is typed in) against a regular expression, and changes its border color to green when validation passes, and to red otherwise.

-- Begin Pasteable Code --
module TutEx4 where

import Data.JRegex
import CDOM.Level2.DomUtils
import Graphics.UI.HsWTK
import DOM.Level2.HTMLSpanElement
import Control.Concurrent.JSThreads

main = docBodyC mainW

mainW = msgBox $ \valmb ->
        textP "Version (X.Y.Z) etc.:"
    +++ valInput (JRegex "^[0-9]+(\\.[0-9]+)*$") ("green", "red") valmb

valInput rgx coltp mb = 
  msgBox $ \dummy ->
  inputI |<< (active (evtBCastA "keyup" (valrx rgx coltp) [])
          +++ active (fwdValueA mb dummy))

valrx rgx (ct, cf) e k = readTargetU e (jrxTest rgx "") $ \bv ->
  targetElement e 
    (set'style ["border-color" := if bv then ct else cf]) $ \_ -> k True
-- End   Pasteable Code --

Regular expression in this example matches numbers separated by dots (like 1.2.3). Readers are encouraged to try other regular expressions as well.

Understanding of how this code works is left as reader's excercise. Hint: evtBCastA is called with empty list of Message Boxes. All event processing work is done on the single HTML element (event target).

Display-only widgets

Below is an example of code similar to the example with two <INPUT> elements except that user's input is displayed in a non-editable (display-only) Widget.

-- Begin Pasteable Code --
module TutEx5 where

import Graphics.UI.HsWTK
import DOM.Level2.HTMLDivElement
import DOM.Level2.HTMLSpanElement
import Control.Concurrent.JSThreads

main = docBodyC mainW

fleft = mkDiv `withStyle` ["float" := "left"]
fclear = mkDiv `withStyle` ["clear" := "both"] |<< nowidget

mainW = msgBox $ \ibx2 ->
        mkDiv |<< (fleft |<< inputI |<< active (evtBCastA "keyup" rtgt [ibx2])
               +++ fleft |<< mkDiv `withStyle` 
                                     ["border" := "1px solid gray"
                                     ,"width" := "100px"
                                     ,"padding" := "3px"
                                     ,"text-align" := "right"
                                     ,"overflow" := "hidden"] 
                               |<< (textP "\160" 
                                +++ mkSpan |<< active (updMapA "" unFwd ibx2))
               +++ fclear)

rtgt e = readTargetU e FwdUpdSet

unFwd (FwdUpdSet s) = s
unFwd _ = ""
-- End   Pasteable Code --

In this example, both <INPUT> and <DIV> elements are enclosed within left-floating <DIV>'s for proper placement. The character with code 160 (that is, &nbsp) is inserted within a framed <DIV> to make sure the frame has full height when nothing is displayed. Finally, a <SPAN> element is nested within the framed <DIV>. The special Activator, updMapA is attached to the latter. This activator is parameterized with one Message Box to receive messages of any type. Another parameter of updMapA is a function that maps input messages to Strings. In this example, the message sent by the <INPUT> element to be displayed, is expected to be wrapped into the FwdUpdSet constructor. Please note that this is not a full emulation of Value forwarding protocol as nothing would be sent in response to messages like FwdCurrTo. Please note also that when building a display-only element, avoid nesting anything other than the appopriate Activator within the element that performs actual display. The updMapA Activator is based on the updateU function which replaces the first child of given node with given String value. Other children remain unchanged. With this logic, some interesting effects may be achieved, but this feature should be used with caution.

Conclusion: all together

In conclusion, let's finally develop a program that does something useful. As another "classical" example, this will be a RPN calculator.

-- Begin Pasteable Code --
module TutEx6 where

import CPS
import Data.Char
import Graphics.UI.HsWTK
import DOM.Level2.Event
import DOM.Level2.Events
import DOM.Level2.KeyEvent
import DOM.Level2.HTMLDivElement
import DOM.Level2.HTMLSpanElement
import Control.Concurrent.JSThreads

main = docBodyC mainW

mainW = msgBox $ \calcmb ->
        msgBox $ \dispmb ->
        mkDiv `withStyle` ["border" := "1px solid black"
                          ,"width"  := "200px"
                          ,"height" := "150px"
                          ,"text-align" := "center"]
          |<< (mkDiv `withStyle` ["height" := "20%"
                                 ,"text-align" := "right"
                                 ,"vertical-align" := "middle"
                                 ,"overflow" := "hidden"]
                 |<< (textP "\160" +++ textP "\160"
                  +++ active (updMapA "0" id dispmb))
           +++ foldr (+++) nowidget (map (cbtn calcmb) btxt)
           +++ active (passMapStateA ci calc (show . acc) calcmb dispmb)
           +++ active (evtBCastA "keydown" clkey [calcmb])
           +++ active (tabIndexA 0))

clkey :: TKeyEvent -> CPS Bool Char

clkey e k = preventDefault e $ \_ -> get'keyCode e $ \c -> k $ case c of
  38 -> '^'
  107 -> '+'
  61 -> '+'
  109 -> '-'
  106 -> '*'
  191 -> '/'
  111 -> '/'
  59 -> '/'
  _ -> chr c

data CalcST = CalcST {acc :: Int, stack :: [Int], rst :: Int}

ci = CalcST {acc = 0, stack = [], rst = 0}

calc :: CalcST -> Char -> CalcST

calc st c = case c of
  'C' -> ci
  d | isDigit d -> let acc' = rst st * acc st * 10 + ord d - ord '0' 
                   in  st {acc = acc', rst = 1}
  '^' -> st {rst = 0, stack = (acc st) : (stack st)}
  o | o `elem` ['+', '-', '*', '/'] -> 
      let op '+' = (+)
          op '-' = (-)
          op '*' = (*)
          op '/' = div
      in  if null (stack st) 
            then st
            else  let acc' = op o (head $ stack st) (acc st)
                  in  st {rst = 0, 
                          stack = acc' : tail (stack st), 
                          acc = acc'}
  _   -> st

btxt = ['1', '2', '3', '+',
        '4', '5', '6', '-',
        '7', '8', '9', '*',
        'C', '0', '^', '/']

cbtn mb txt = mkDiv `withStyle` ["float" := "left"
                                ,"width" := "25%"
                                ,"height" := "20%"
                                ,"margin" := "0px"
                                ,"vertical-align" := "middle"
                                ,"text-align" := "center"]
                |<< buttonI `withStyle` ["width" := "80%"
                                        ,"height" := "80%"
                                        ,"font-size" := "80%"] 
                      |<< (textP [txt]
                       +++ active (evtBCastA "click" (evt2ConstU txt) [mb]))

-- End   Pasteable Code --

The main Widget, mainW consists of the following pieces:

  • Two Message Boxes. One (calcmb) will be used to transmit keystrokes and mouse clicks received from the browser's input facilities. Another (dispmb) will be used to update the calculator's display element.
  • A <DIV> element with visible border: it encloses all other elements of the calculator. It is also responsible for receiving keyboard input.

The following elements are nested within the above mentioned <DIV>:

  • A <DIV> element that contains the calculator's display.
  • 16 buttons for mouse input. Note the use of foldr and map. All buttons use the same Message Box calcmb, so it is passed to each button's creation function. Each button uses its own character taken from the btxt list: button creation function is mapped over this list. Finally, the resulting list is folded with +++ to sequence all buttons properly.
  • Activator which implements the internal (stateful) logic of the calculator. It is based on passMapStateA which receives messages from its input Message Box, maintains internal state transitions based on what is received, and maps internal state to messages sent to the output Message Box. That's how the two parts (user input and result display) are wired together.
  • Activator based on evtBCastA to catch keystrokes and route them to the same Message Box where mouse clicks go.
  • Activator based on tabIndexA. Although DOM does not define the tabIndex property for most HTML elements, according to this (last comment), it is necessary to initialize this property in order to be able to receive keystrokes on <DIV> elements.

The clkey function performs proper mapping of keystrokes to simulate mouse clicks on buttons. It extracts the value of keyCode property from the event received, and remaps certain codes, finally passing a character to the continuation.

The CalcST defines the internal state of the calculator. It includes the accumulator (where the user input goes), the stack (a list of numbers), and the reset flag which helps update the display properly when entry of a new number begins.

Internal logic of the calculator (calc) is pretty straighforward: numbers typed in are pushed down the stack when "^" button is clicked, or the "up arrow" key is pressed. Operation buttons/keys perform binary operations between the accumulator and the topmost stack element. Finally copy of the result is pushed back onto the stack, so next number typed in may be used for the next computation.

The btxt list of characters defines what shows on buttons.

The button creation function (cbtn) defines a <DIV> element nesting a <BUTTON> element. Each button has an Activator based on evtBCastA that maps each click to the character showing on the button. Note the float: left style and percentage width defined for <DIV>s: no matrix layout logic is necessary; buttons fill the <DIV> with borders with correct placement.