Difference between revisions of "Haskell in web browser/Haskell web toolkit"

From HaskellWiki
Jump to navigation Jump to search
(ACtivators)
(Activators example)
Line 206: Line 206:
   
 
''HsWTK'' also defines a function <code>[http://www.golubovsky.org:5984/_utils/yhcws/Graphics-UI-HsWTK.html#v%3Aactive active]</code> which being applied to an ''Activator'' turns it into a ''Widget'', that is, an ''Activator'' may be nested within a [[#Containers|container]]: that's what was meant above for an ''Activator'' "attached" to a ''Widget''.
 
''HsWTK'' also defines a function <code>[http://www.golubovsky.org:5984/_utils/yhcws/Graphics-UI-HsWTK.html#v%3Aactive active]</code> which being applied to an ''Activator'' turns it into a ''Widget'', that is, an ''Activator'' may be nested within a [[#Containers|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:
  +
  +
<div style="border: 1px solid gray">
  +
<haskell>
  +
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
  +
</haskell>
  +
</div>
  +
  +
Let's go line by line. As new things are introduced, they will be discussed in appropriate sections.

Revision as of 02:37, 21 March 2008

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 exchange information among themselves.

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.

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.