Difference between revisions of "Yhc/Javascript/Programmers guide"

From HaskellWiki
Jump to navigation Jump to search
(prog for web browser 1)
(Better implementation of send w/o forkAfter)
 
(57 intermediate revisions by 2 users not shown)
Line 1: Line 1:
==Up from the Ground==
+
==Up from the ground==
This part of the Programmers Guide is a collection of notes taken during the development of the first Haskell-in-Browser demo, a program that accepts users' input using a HTML input element, and repeats whatever the user typed upon pressing <code>Enter</code>. Additionally, Roman numeral conversion will occur if user's input is a decimal or a Roman numeral that can be converted. A timer is provided to measure code performance.
+
This part of the Programmers Guide is a collection of notes taken during the development of the first Haskell-in-Browser demo, a program that accepts users' input using a HTML input element, and repeats whatever the user typed upon pressing <code>Enter</code>. Additionally, Roman numeral conversion will occur if user's input is a decimal or a Roman numeral that can be converted. A timer is provided to measure code performance. [http://www.haskell.org/haskellwiki/Yhc/Javascript/Programmers_guide/Up_from_the_ground More...]
   
  +
==DOM framework==
===Programming for Web Browser===
 
   
  +
In this section of the Yhc/Javascript Programmers Guide, the implementation of [http://www.w3c.org/DOM Document Object Model] in Haskell is described. Continuation Passing Style usage is discussed. The section provides details on conversion of DOM specifications from Interface Definition Language to Haskell, and related issues and features. Finally, examples of Haskell programming with DOM are provided.
A Javascript program running in a web browser faces environment different from "traditional": there is no input/output operations as we are used to them, no file system, and no sequential flow of execution.
 
  +
===Continuation passing style===
   
  +
====Rationale====
===The [[Yhc/Javascript/Programmers_guide/Echo_demo_source|Echo]] Demo Program===
 
  +
Unlike the previous Echo example, the DOM framework uses [[Continuation passing style|CPS]] rather than monads to provide proper sequence of Haskell expressions evaluation. The choice of CPS is dictated by the internal structure of Fudget kernels which use CPS. An original Fudget (built on top of the X11 protocol and related I/O) sends a message to Fudlogue each time an input/output action is needed (even one not involving waiting for any asyncronous input, such as opening a window). With DOM interface implemented in CPS style, all synchronous operations (such as creating a DOM node, and basically all operations not involving event handling) can be performed without such message exchange, which significantly reduces execution overhead.
   
  +
<small>'''Note:''' Fudgets (stream processors) unfortunately did not make it into web browser because of terrible memory leaks (almost 500k browser size increase on each user action like mouse click). there is however another rationale to use CPS, that is to simulate cooperative threads via scheduling further execution of continuations, see the new [[#Threads_and_events|Threads and events]] section.</small>
===The <code>main</code> function===
 
   
===A Simple Monad===
+
====Wrapper functions====
  +
A function conforming the Continuation Passing Style always has as its last argument, continuation, which will take the result of this function's application to its other arguments, as an argument. Any non-CPS expression may be converted into a CPS one by applying a wrapper which transforms the expression into a function with one argument:
   
  +
<haskell>
===Calling Javascript from Haskell: <code>unsafeJS</code>===
 
  +
toCPS x = \k -> k x
The <code>unsafeJS</code> function is not a function per se: it is rather a macro, or a compilation directive. Its purpose is to provide a Haskell-accessible wrapper with proper type signature for an arbitrary Javascript code which obeys certain coding rules.
 
  +
</haskell>
   
  +
where <hask>x</hask> is an expression to convert. The expression will be passed to the continuation unevaluated.
The function has a type signature:
 
  +
  +
A variant of this wrapper:
  +
  +
<haskell>
  +
toCPE x = \k -> x `seq` (k x)
  +
</haskell>
  +
  +
forces evaluation of the expression before passing it to the continuation.
  +
  +
Consider obtaining a current date and time from the browser. Browser provides a Javascript function <code>new Date().getTime()</code> for this purpose. So, at the first look the following might be enough:
  +
  +
<haskell>
  +
getTimeStamp' a = unsafeJS "return new Date().getTime();"
  +
</haskell>
  +
  +
The dummy parameter <hask>a</hask> is necessary to prevent creation of a CAF, that is, every time the function is called with any value of this parameter, evaluation will take place.
  +
  +
To convert this expression, e. g. <hask>getTimeStamp' 0</hask> in CPS, it needs to be given a parameter representing continuation which will use its result, that is, the current time. This may be written as:
  +
  +
<haskell>
  +
getTimeStamp k = k `seq` (getTimeStamp' 0)
  +
</haskell>
  +
  +
where <hask>k</hask> is a continuation which will be given the current time. The <hask>seq</hask> combinator ensures that the continuation will get an evaluated expression.
  +
  +
So, in a larger example:
  +
  +
<haskell>
  +
main = getTimeStamp $ \t1 ->
  +
foo $ \_ ->
  +
bar $ \_ ->
  +
getTimeStamp $ \t2 ->
  +
putLine ("Time interval: " ++ show (t2 - t1) ++ " ms") $ id
  +
</haskell>
  +
  +
two time stamps will be obtained, before and after the two computations <hask>foo</hask> and <hask>bar</hask> (whose results are not of interest) are performed. The result will be output with some imaginary function <hask>putLine</hask>.
  +
  +
The <hask>id</hask> call after <hask>putLine</hask> is necessary to "close" the chain of continuations: the value that <hask>putLine</hask> returns, becomes return value of <hask>main</hask>. If however it is necessary to return something else, say, the length of the time interval measured, the last row might look like:
  +
  +
<haskell>
  +
putLine ("Time interval: " ++ show (t2 - t1) ++ " ms") $ \_ ->
  +
(t2 - t1)
  +
</haskell>
  +
  +
In general, the example above gives some idea how Haskell programs using DOM in CPS style look like.
  +
  +
The <hask>CPS</hask> module should be imported by any Haskell module using the Continuation Passing Style constructs and the DOM framework. The <hask>CPS</hask> type itself is defined as:
  +
  +
<haskell>
  +
type CPS c a = (a -> c) -> c
  +
</haskell>
  +
  +
So, if a function has the return type <hask>CPS x y</hask>, this means that its continuation would accept a value of type <hask>y</hask> and return a value of type <hask>x</hask>
  +
  +
====Unsafe interfaces with CPS====
  +
Usage of <hask>unsafeJS</hask> has not changed from one described above. This is still a pseudo-function accepting a string literal with Javascript code as an argument. The Javascript code supplied will be wrapped into a Haskell-callable function.
  +
  +
To access properties of Javascript objects, the following CPS-aware functions are provided:
  +
  +
<haskell>
  +
unsafeGetProperty :: String -> b -> CPS d c
  +
  +
unsafeSetProperty :: String -> b -> c -> CPS d c
  +
  +
unsafeCheckProperty :: String -> b -> CPS d Bool
  +
</haskell>
  +
  +
The first function accepts Javascript property name as its first argument, and a reference to a Javascript object as the second. It passes the value of the property retrieved (in type-agnostic manner) to its continuation.
  +
  +
The second function accepts Javascript property name as its first argument, the value to set the property to as the second argument, and a reference to a Javascript object as the third. The continuation gets the reference to the Javascript object with updated property (that is, the update occurs in-place).
  +
  +
The third function checks whether the given property is set to <code>null</code>, and passes <hask>True</hask> to the continuation if it is not <code>null</code>, and <hask>False</hask> otherwise.
  +
  +
All three functions evaluate their arguments.
  +
  +
To unsafely convert Javascript values to Haskell <hask>Num</hask> and <hask>String</hask> values, the following two functions are provided:
  +
  +
<haskell>
  +
unsafeToNum :: (Num b) => a -> CPS c b
  +
  +
unsafeToString :: a -> CPS c String
  +
</haskell>
  +
  +
The first function calls the <code>Number</code> Javascript constructor on the argument's value, the second calls the <code>String</code> Javascript constructor on its argument. Both functions evaluate their argument first.
  +
  +
To catch exceptions, the following function is provided:
  +
  +
<haskell>
  +
catchJS :: a -> (b -> a) -> a
  +
</haskell>
  +
  +
This function takes its first argument and evaluates it. If an error occurs (Javascript exception is thrown), it is passed as an argument to the function specified as <hask>catchJS</hask>'s second argument. The function handling an exception should either return a value of the same type as the failed expression does, or to (re)throw an exception. The <hask>error</hask> function from the Standard Prelude is implemented using the Javascript <code>throw</code> statement.
  +
  +
====Programming examples====
  +
The [[Yhc/Javascript/Programmers_guide/EchoCPS_demo_source|EchoCPS]] Wiki page contains an example of a working Echo demo program written using the DOM Level1 interfaces.
  +
  +
The [[Yhc/Javascript/Programmers_guide/EchoCPS2_demo_source|EchoCPS2]] Wiki page contains an example of a working Echo demo program written using the DOM Level2 interfaces which have been added to the Javascript backend. The only major difference between these two example programs is better typing of event handlers based on the definitions that appeared only in DOM Level2 specifications.
  +
  +
===DOM and the Web Consortium===
  +
The Document Object Model (DOM) is the base interface to access the content and structure of documents in a web browser. The Web Consortium has a [http://www.w3.org/DOM/ page] dedicated to DOM.
  +
  +
This Programmers Guide is based on the [http://www.w3.org/TR/2000/WD-DOM-Level-1-20000929 Document Object Model (DOM) Level 1 Specification (Second Edition)] provided by the Web Consortium. This version of DOM, although not very new, can serve as the greatest common denominator for many types of web browsers available these days.
  +
  +
===DOM and Interface Definition Language (IDL)===
  +
====General information====
  +
The Web Consortium uses a subset of the [http://en.wikipedia.org/wiki/Interface_description_language Interface Definition Language] proposed by the [http://www.omg.org Object Management Group] ([http://www.omg.org/gettingstarted/omg_idl.htm OMG IDL]) to describe the [http://www.w3.org/TR/2000/WD-DOM-Level-1-20000929/idl-definitions.html abstract interface] to the Document Object Model, so it may be implemented in various programming languages. These definitions cover basic operations to create and delete document nodes, manipulate their attributes and contents, and insert/remove nodes within the document loaded into the browser.
  +
  +
====Conversion to Haskell====
  +
In accordance with the [http://www.w3.org/TR/2000/WD-DOM-Level-1-20000929/copyright-notice.html Web Consortium Copyright Notice], IDL files provided by the Web Consortium may be freely redistributed by anybody. So, copy of these files is included with the Yhc Javascript Backend. A modified version of the [http://www.haskell.org/hdirect/ HaskellDirect] (trimmed down to only OMG IDL code symtax recognition, and with different model of Haskell code generation) is also included. This HaskellDirect-based utility runs automatically when the Javascript Backend is being installed, so the installation includes Haskell code autogenerated from the IDL files. Developers who define new interfaces on the browser side to be used with the Javascript Backend are encouraged to write their own IDL files, and use the same utility to produce Haskell interface code.
  +
  +
====Technical details of IDL to Haskell conversion====
  +
This section gives general details of correspondence between IDL definitions and generated Haskell code. Deeper details related to programming will be discussed in next sections.
  +
  +
Consider this IDL definition (from the [http://www.w3.org/TR/2000/WD-DOM-Level-1-20000929/idl/dom.idl DOM section] of the definitions):
   
 
<code>
 
<code>
  +
interface Attr : Node {
foreign import primitive unsafeJS :: String -> a
 
  +
readonly attribute DOMString name;
  +
readonly attribute boolean specified;
  +
// Modified in DOM Level 1:
  +
attribute DOMString value;
  +
// raises(DOMException) on setting
  +
  +
};
 
</code>
 
</code>
   
  +
One interface definition in IDL results in creation of one Haskell module with the same name as the interface has. Module name will be prefixed with <hask>DOM.Level1</hask>, that is, the <code>#pragma prefix "w3c.org"
Which means that it takes a string. Type of the return value does not matter: the function itself is never executed. Its applications are detected by '''ycr2js''' at the time of Javascript generation.
 
  +
</code> in the beginning of the file is ignored.
   
  +
The Haskell translation is:
The <code>unsafeJS</code> function should be called with a string literal. Neither explicitly coded (with <code>(:)</code>) list of characters nor concatenation of two or more strings will work. The converter will report an error in this situation.
 
   
  +
<haskell>
A valid example of using unsafeJS is shown below:
 
  +
module DOM.Level1.Attr
  +
(get'name, get'specified, set'value, get'value) where
  +
import DOM.Level1.Dom
  +
import CPS
  +
import UnsafeJS
  +
import DOM.Level1.Document (createElement)
  +
  +
get'name :: (CAttr this) => this -> CPS c String
  +
get'name = unsafeGetProperty "name"
  +
  +
get'specified :: (CAttr this) => this -> CPS c Bool
  +
get'specified = unsafeGetProperty "specified"
  +
  +
set'value :: (CAttr zz) => String -> zz -> CPS c zz
  +
set'value = unsafeSetProperty "value"
  +
  +
get'value :: (CAttr this) => this -> CPS c String
  +
get'value = unsafeGetProperty "value"
  +
</haskell>
  +
  +
Additionally, in the <hask>DOM.Level1.Dom</hask> module, the following is defined (comments added):
  +
  +
<haskell>
  +
data TAttr = TAttr -- phantom type for the interface
  +
class (CNode a) => CAttr a -- class reflecting inheritance from Node
  +
instance CAttr TAttr -- interfaces of Attr are implemented
  +
instance CNode TAttr -- interfaces of Node are implemented
  +
</haskell>
  +
  +
Attributes that have <code>readonly</code> in their definitions only have getter methods (e. g. <hask>get'name</hask>). The rest of attributes also have setter methods (e. g. <hask>get'value</hask>, <hask>set'value</hask>). Getter and setter names are produced by prefixing IDL attribute name with <hask>get'</hask> and <hask>set'</hask> respectively.
  +
  +
The <code>Attr</code> interface does not have methods, only attributes. The following interface illustrates how methods are represented:
   
 
<code>
 
<code>
  +
interface NodeList {
  +
Node item(in unsigned long index);
  +
readonly attribute unsigned long length;
  +
};
  +
</code>
   
  +
<haskell>
global_YHC'_Primitive'_primIntSignum :: Int -> Int
 
  +
module DOM.Level1.NodeList (item, get'length) where
  +
import DOM.Level1.Dom
  +
import CPS
  +
import UnsafeJS
  +
import DOM.Level1.Document (createElement)
 
 
  +
item :: (CNodeList this, CNode zz) => this -> Int -> CPS c zz
global_YHC'_Primitive'_primIntSignum a = unsafeJS
 
  +
item a b = toCPE (item' a b)
"var ea = exprEval(a); if (ea>0) return 1; else if (ea<0) return -1; else return 0;"
 
  +
item' a b = unsafeJS "return((exprEval(a)).item(exprEval(b)));"
</code>
 
  +
  +
get'length :: (CNodeList this) => this -> CPS c Int
  +
get'length = unsafeGetProperty "length"
  +
</haskell>
   
  +
There also are related lines of code in the <hask>DOM.Level1.Dom</hask> module (not shown as they are logically identical to already reviewed).
This is a Javascript overlay (in the sense that it overlays the default Prelude definition of the <code>signum</code> function) of a function that returns sign of an <code>Int</code> value.
 
   
  +
The <hask>item</hask> method, as implemented in Haskell, takes the reference to the DOM element (<code>NodeList</code>) as the first argument, <hask>this</hask>. The second argument is the index of a node in the <code>NodeList</code>, corresponding to the <code>in unsigned long index</code> in the IDL definition. The last argument is the continuation. Type constraints <hask>(CNodeList this, CNode zz) =></hask> state that the method operates on instances of the <hask>CNodeList</hask> class, and values passed to the continuation are instances of the <hask>CNode</hask> class.
The string literal <code>unsafeJS</code> is applied to is the Javascript code to be wrapped.
 
   
  +
Body of the method contains a type-aware wrapper over the unsafe code calling appropriate <code>item</code> method on the Javascript object implementing the <code>NodeList</code> interface.
Below is the Javascript representation of this function found in the <code>Echo</code> page source.
 
   
  +
====Known omissions====
<code>
 
  +
* Exception information (<code>raises...</code>) is completely ignored by the converter. If an exception in Javascript code occurs, it should be treated as described above, in the [[#Unsafe_interfaces_with_CPS|Unsafe interfaces with CPS]] section.
strIdx["F_hy"] = "YHC.Primitive.primIntSignum";
 
   
  +
* The converter makes no distinction between <code>in</code> and <code>out</code> arguments.
  +
  +
* The converter does not tolerate multiple methods with the same name, but different number of arguments, within a single interface. It is however possible to have methods with the same name (regardless of number of arguments) in different interfaces. The <hask>focus</hask> and <hask>blur</hask> methods serve as a good example: they appear in at least two HTML elements: <input> and <textarea>. Developers are recommended to use <hask>import qualified</hask> statement for importing modules with conflicting method names, and use qualified names to resolve ambiguities.
  +
  +
===Haskell DOM vs. Javascript DOM===
  +
====Haskell phantom types vs. Javascript object types====
  +
A phantom type is created for every interface defined in OMG IDL files provided by the Web Consortium. Examples above illustrated this. So, this is important that all interface names were unique across all IDL files that are processed by the converter at once (both toplevel and include). More examples of such phantom types:
  +
  +
<haskell>
  +
data TDOMImplementation = TDOMImplementation
  +
data TNode = TNode
  +
data TNodeList = TNodeList
  +
data TNamedNodeMap = TNamedNodeMap
  +
data TCharacterData = TCharacterData
  +
data TAttr = TAttr
  +
data TElement = TElement
  +
data TText = TText
  +
data TComment = TComment
  +
data TCDATASection = TCDATASection
  +
data TDocumentType = TDocumentType
  +
</haskell>
  +
  +
Names of these types are derived from interface names by adding the capital letter "T" at the beginning.
  +
  +
====Haskell type classes reflect interfaces inheritance====
  +
IDL, like many other object-oriented languages, features inheritance between interfaces defined. This means that an object implementing an interface <code>X</code> funcitonality, also implements functionality of interface <code>Y</code>, as well as all ancestors of <code>Y</code> if declared as
  +
  +
<code>
  +
interface X : Y {
 
...
 
...
  +
}
  +
</code>
   
  +
Let's trace a chain of inheritance of the <hask>HTMLButtonElement</hask> which represents a <button> tag:
var F_hy=new HSFun("F_hy", 1, function(a){
 
  +
var ea = exprEval(a); if (ea>0) return 1; else if (ea<0) return -1; else return 0;});
 
  +
<code>
  +
interface HTMLButtonElement : HTMLElement
  +
interface HTMLElement : Element
  +
interface Element : Node
  +
interface Node
 
</code>
 
</code>
   
  +
which basically means that all methods and properties of <hask>Node</hask> are expected to be implemented in <hask>HTMLButtonElement</hask>.
Here are the rules that govern the usage of <code>unsafeJS</code>:
 
   
  +
To tell this to the Haskell compiler, the type constraints mechanism is involved:
* The <code>unsafeJS</code> function is contained in the <code>UnsafeJS</code> module and should be imported from there
 
* Its argument must be a string literal, and nothing else
 
* Its argument should be written entirely on a single line
 
* Formal parameter names visible to Javascript are <code>a</code>, <code>b</code>, <code>c</code>, etc. that is single lowercase letters
 
* Number of formal parameters should match the Haskell type signature
 
* It is recommended to name the function's formal parameters in Haskell declaration in the same way they are visible to Javascript, i. e. <code>a</code>, <code>b</code>, <code>c</code>, etc.
 
* Haskell values are passed to Javascript functions unevaluated: use <code>exprEval</code> to evaluate
 
* Javascript code passed to <code>unsafeJS</code> should not contain outermost Javascript function declaration and curly braces: '''ycr2js''' will provide those
 
* Javascript code is not limited in what it may contain<sup>*</sup>; common sense must be observed not to code in unsafe way when not really necessary: for instance it is possible to change fields of a Haskell data object from Javascript, but it is strongly discouraged: create a modified copy of the object and leave the original unchanged, like a Haskell program would do.
 
* <b>Javascript code must return a value</b>
 
   
  +
<haskell>
So, in the <code>signum</code> function above, first thing done is evaluation of the argument <code>a</code>. Because of the proper Haskell type signature provided, it is safe to expect a numeric value as result of the evaluation.
 
  +
class (CHTMLElement a) => CHTMLButtonElement a
  +
class (CElement a) => CHTMLElement a
  +
class (CNode a) => CElement a
  +
class CNode a
  +
</haskell>
   
  +
The correspondence between these two examples is clear. Names of classes are derived from interface names by adding the capital letter "C" at the beginning.
Next, usual comparisons with zero are performed, to determine the sign of the argument. Results are returned.
 
   
  +
To enable the desired functionality on the correct (phantom) data types, instance declarations are added:
----
 
  +
<sup>*</sup> For instance, inner function declaration may be used, as in this more complex example below (implementation of integer division via modulus):
 
  +
<haskell>
  +
data THTMLButtonElement = THTMLButtonElement
  +
  +
instance CHTMLButtonElement THTMLButtonElement
  +
instance CHTMLElement THTMLButtonElement
  +
instance CElement THTMLButtonElement
  +
instance CNode THTMLButtonElement
  +
</haskell>
  +
  +
So, if we have a function that operates on Nodes (and therefore has <hask>(Cnode a ...) =></hask> in its type signature), it will accept values of the <hask>THTMLButtonElement</hask> type because of the above instance declarations, but not a <hask>TNodeList</hask> values because declaration for <code>NodeList</code> was:
   
 
<code>
 
<code>
  +
interface NodeList {
global_YHC'_Primitive'_primIntegerQuot :: Integer -> Integer -> Integer
 
  +
Node item(in unsigned long index);
  +
readonly attribute unsigned long length;
  +
};
  +
</code>
   
  +
so <code>NodeList</code> does not inherit from <code>Node</code>. It is worth saying that Javascript code (which is type-agnostic) would likely accept passing a <code>NodeList</code> value to a function operating on Nodes. At best, a run-time exception would occur; at worst, some hard to find problems might be introduced diring the execution of such a function. Haskell compiler would catch this at the compilation stage.
global_YHC'_Primitive'_primIntegerQuot a b = unsafeJS
 
  +
"(function(x,y){return (x - (x % y))/y;})(exprEval(a),exprEval(b));"
 
  +
====The <code>this</code> object reference in Haskell code====
  +
In Javascript, methods of some object have an implicit argument, <code>this</code>. When a method is executed, the argument holds a reference to the object the method was invoked upon. Thus, if we had a DOM object implementing the <code>NodeList</code> interface, and wanted to extract a <code>n</code>th item of it, we would write:
  +
  +
<code>
  +
var itm;
  +
var nl = /* obtain the NodeList reference here */;
  +
itm = nl.item(n); /* item is a (only) NodeList's method taking a number */
 
</code>
 
</code>
   
  +
Haskell does not allow to have such an implicit argument to a function. Instead, <hask>this</hask> is defined explicitly:
The purpose of having an inner function declaration is to reuse evaluated arguments <code>a</code> and <code>b</code>: even though every expression is evaluated only once, extra call to <code>exprEval</code> may be avoided this way.
 
  +
  +
<haskell>
  +
item :: (CNodeList this, CNode zz) => this -> Int -> CPS c zz
  +
</haskell>
  +
  +
Equivalent Haskell code to retrieve a <code>n</code>th item would be:
  +
  +
<haskell>
  +
{-- obtain the NodeList reference here --} $ \nl ->
  +
item nl n $ \itm ->
  +
{-- itm may be used further on in the code --}
  +
</haskell>
  +
  +
==Threads and events==
  +
  +
===Cooperative threads===
  +
Execution of Javascript by a web browser is always single-threaded. Scripts running when the page is being loaded cannot be interrupted by event handlers, and event handlers themselves cannot be interrupted by another event handlers.
  +
  +
There is however a Javascript function <code>[http://developer.mozilla.org/en/docs/DOM:window.setTimeout window.setTimeout]</code> which may be used, in combination with [[Continuation_passing_style|CPS]], to simulate cooperative threads. Combining this technique with run-once auto-cleaning event handlers allows to utilize an event-driven programming model with cooperative threads (similar to what was used in MS-DOS based versions of Windows).
  +
  +
The <code>setTimeout</code> function takes a timeout length (in milliseconds), and (in the most common case) a string representing the Javascript code to evaluate after the timeout expires. Browser may potentially execute a pending event handler within the timeout specified.
  +
  +
===Haskell primitives===
  +
In Haskell terms, there are three things to deal with: a timeout (an integer number), an expression to evaluate after the timeout expires ("child" thread), and an expression to evaluate right after the timeout has been set ("parent" thread).
  +
  +
The basic threading primitive (defined in the <hask>UnsafeJS</hask> module):
  +
  +
<haskell>
  +
-- Fork execution for certain amount of time (including 0) by setting timeout
  +
-- and passing a value to be evaluated then (b) and right now (c).
  +
  +
forkAfter :: Int -> b -> c -> c
  +
  +
forkAfter a b c = (fork' a b) `seq` c
  +
  +
fork' a b = unsafeJS
  +
"var t=contNum++;var s='exprEval(delCont['+t+']);delCont['+t+']=null;';
  +
delCont[t]=b;window.setTimeout(s,exprEval(a)); return 0;"
  +
</haskell>
  +
  +
The <code>contNum</code> and <code>delCont</code> objects are global Javascript variables defined in <code>Runtime.js</code>. The former provides unique number for each delayed continuation, and the latter acts as a storage of references to continuations.
  +
  +
<small>'''Note:''' One thing to be added here: after some number of forks, the <code>delCont</code> object should be cleaned from nullified references to continuations that executed in the past; this requires trivial changes in <code>Runtime.js</code>.</small>
  +
  +
Javascript event handlers may be used similarly, considering that an event handler may execute a delayed continuation, thus allowing a thread to wait for event. An event handler should nullify itself at its target (that is, if a <code>onclick</code> handler is executed, its target object should get its <code>onclick</code> attribute set to <code>null</code> before the handler exits. Another convention: if an object already has an event handler installed for certain event type, it cannot be replaced with another handler, thus guaranteeing that one thread will not recapture events that another thread is waiting for.
  +
  +
The basic event primitive (defined in <hask>CDOM.Level2.Events</hask>module):
  +
  +
<haskell>
  +
-- Wait for an event from an element. Execution of the continuation given
  +
-- is resumed as the event has been received. True is returned if the element
  +
-- was not waiting for another event, False otherwise.
  +
  +
waitFor :: (CEvent e, CElement c) => c -> String -> (e -> Bool) -> Bool
  +
  +
waitFor elt evid k =
  +
unsafeCheckProperty ("on" ++ evid) elt $ \h -> case h of
  +
True -> False
  +
False -> secl evid k elt $ \_ -> True
  +
</haskell>
  +
  +
The <hask>secl</hask> function used by this primitive installs a self-clearing event handler for a specified type of events. Once executed, the handler removes itself from its target.
  +
  +
===Usage examples===
  +
  +
This piece of code sets focus on an input element (referred to by <code>inp</code> and starts the main event loop which will receive information from this input element for further processing):
  +
  +
<haskell>
  +
focus inp $ \_ ->
  +
forkAfter 0 (mainY inp) $
  +
-- the rest of the program
  +
</haskell>
  +
  +
This piece of code reads each character input from <code>inp</code>, and when <code>Enter</code> is pressed, passes the whole string to its continuation:
  +
  +
<haskell>
  +
readChar :: THTMLInputElement -> CPS Bool Int
  +
  +
readChar inp k = waitFor inp "keypress" $ \e ->
  +
get'keyCode (e :: TKeyEvent) $ \c -> k c
  +
  +
readLine inp k = readChar inp $ \kci ->
  +
if kci == cDOM_VK_ENTER
  +
then get'value inp $ \s -> k s
  +
else readLine inp k
  +
</haskell>
  +
  +
This piece of code reads the whole line, and performs some actions (omitted in this example) depending on the length of input:
  +
  +
<haskell>
  +
mainY inp = readLine inp $ \v ->
  +
if length v > 0
  +
then
  +
-- some actions
  +
mainY inp
  +
else
  +
-- other actions
  +
mainY inp
  +
</haskell>
  +
  +
The function loops infinitely, so everything a user types will be processed.
  +
  +
===Message boxes===
  +
  +
Message boxes provide a way for pseudo-threads to communicate with each other. Programmatically, a message box is a mutable memory cell holding a continuation that a message sent is to be passed to. Objects of type <hask>Data.JSRef</hask> are used for this purpose.
  +
  +
A simpliest message box that is capable of holding a single message, rejects any messages that arrive while the receiver thread is not expecting a message, and provides a synchronous <hask>send</hask> operation (sender thread will not be resumed until the receiver thread begins to wait again for a message on the message box), may be implemented like shown below:
  +
  +
<haskell>
  +
  +
-- A continuation which is stored in the message box when no thread is waiting
  +
-- for a message: any message sent via this message box will be rejected
  +
-- (discarded).
  +
  +
ignore = \_ -> False
  +
  +
-- Message box constructor: initializes the JSRef object with
  +
-- ignore-everything continuation.
  +
  +
mkMsgBox k = newJSRef ignore $ \mb -> k mb
  +
  +
-- Send a message: obtain the continuation stored in the message box,
  +
-- construct a thunk (res) to pass the message to the continuation,
  +
-- evaluate res, and finally, resume our own continuation (k) when
  +
-- the receiver evaluates the message, getting the evaluation result.
  +
-- Thus, synchronicity of send is achieved.
  +
  +
send mb msg k = readJSRef mb $ \cont ->
  +
let res = cont msg
  +
in res `seq` (k res)
   
  +
-- Receive a message: store our continuation (k) in the message box,
===Calling Haskell from Javascript===
 
  +
-- once called, restore what was in the message box before (thus ignoring
  +
-- any messages that may arrive before we wait for a message again),
  +
-- evaluate our continuation with the message received.
   
  +
recv mb k = readJSRef mb $ \prev ->
===Passing Primitive Values===
 
  +
writeJSRef mb (writeJSRef mb prev $ \_ -> k ) $ \_ -> True
  +
</haskell>
   
  +
An example of two threads using a message box this way: the sender thread is associated with an input (select) element whose updated value may be obtained by handling an "onchange" event; the receiver thread is associated with some display element whose contents may be updated.
===Passing Strings===
 
   
  +
<haskell>
===Passing Arrays===
 
   
  +
-- Sender thread:
===Passing Objects===
 
  +
-- mb: message box to use
  +
-- par: abstract select element whose value is to be sent
   
  +
acts mb par = (waitFor par "change" :: CPS Bool TEvent) $ \e ->
===Type Coercions===
 
  +
(unsafeToSelf par :: CPS Bool THTMLSelectElement) $ \sel ->
  +
get'value sel $ \v ->
  +
send mb v $ \_ -> acts mb par
   
  +
-- Receiver thread:
===Getting/Setting Properties===
 
  +
-- mb: message box to use
  +
-- par: abstract display element whose visible contents may be updated
  +
-- updateD: a function to update the display element
   
  +
actu mb par = recv mb $ \s ->
===Running Methods===
 
  +
updateD par s $ \_ ->
  +
actu mb par
  +
</haskell>
   
  +
<small>
==DOM Framework==
 
  +
'''Note:''' Just for the sake of giving proper credit: one might find this method of inter-thread communication very similar to one described in [http://citeseer.ist.psu.edu/noble95gadgets.html Gadgets: Lazy Functional Components for Graphical User Interfaces (1995) by Rob Noble, Colin Runciman]. In fact, this paper was studied along with the Fudgets Thesis, and gave some inspiration to this developer.
<once we have one...>
 
  +
</small>

Latest revision as of 01:58, 17 November 2007

Up from the ground

This part of the Programmers Guide is a collection of notes taken during the development of the first Haskell-in-Browser demo, a program that accepts users' input using a HTML input element, and repeats whatever the user typed upon pressing Enter. Additionally, Roman numeral conversion will occur if user's input is a decimal or a Roman numeral that can be converted. A timer is provided to measure code performance. More...

DOM framework

In this section of the Yhc/Javascript Programmers Guide, the implementation of Document Object Model in Haskell is described. Continuation Passing Style usage is discussed. The section provides details on conversion of DOM specifications from Interface Definition Language to Haskell, and related issues and features. Finally, examples of Haskell programming with DOM are provided.

Continuation passing style

Rationale

Unlike the previous Echo example, the DOM framework uses CPS rather than monads to provide proper sequence of Haskell expressions evaluation. The choice of CPS is dictated by the internal structure of Fudget kernels which use CPS. An original Fudget (built on top of the X11 protocol and related I/O) sends a message to Fudlogue each time an input/output action is needed (even one not involving waiting for any asyncronous input, such as opening a window). With DOM interface implemented in CPS style, all synchronous operations (such as creating a DOM node, and basically all operations not involving event handling) can be performed without such message exchange, which significantly reduces execution overhead.

Note: Fudgets (stream processors) unfortunately did not make it into web browser because of terrible memory leaks (almost 500k browser size increase on each user action like mouse click). there is however another rationale to use CPS, that is to simulate cooperative threads via scheduling further execution of continuations, see the new Threads and events section.

Wrapper functions

A function conforming the Continuation Passing Style always has as its last argument, continuation, which will take the result of this function's application to its other arguments, as an argument. Any non-CPS expression may be converted into a CPS one by applying a wrapper which transforms the expression into a function with one argument:

toCPS x = \k -> k x

where x is an expression to convert. The expression will be passed to the continuation unevaluated.

A variant of this wrapper:

toCPE x = \k -> x `seq` (k x)

forces evaluation of the expression before passing it to the continuation.

Consider obtaining a current date and time from the browser. Browser provides a Javascript function new Date().getTime() for this purpose. So, at the first look the following might be enough:

getTimeStamp' a = unsafeJS "return new Date().getTime();"

The dummy parameter a is necessary to prevent creation of a CAF, that is, every time the function is called with any value of this parameter, evaluation will take place.

To convert this expression, e. g. getTimeStamp' 0 in CPS, it needs to be given a parameter representing continuation which will use its result, that is, the current time. This may be written as:

getTimeStamp k = k `seq` (getTimeStamp' 0)

where k is a continuation which will be given the current time. The seq combinator ensures that the continuation will get an evaluated expression.

So, in a larger example:

main = getTimeStamp $ \t1 ->
       foo $ \_ ->
       bar $ \_ ->
       getTimeStamp $ \t2 ->
       putLine ("Time interval: " ++ show (t2 - t1) ++ " ms") $ id

two time stamps will be obtained, before and after the two computations foo and bar (whose results are not of interest) are performed. The result will be output with some imaginary function putLine.

The id call after putLine is necessary to "close" the chain of continuations: the value that putLine returns, becomes return value of main. If however it is necessary to return something else, say, the length of the time interval measured, the last row might look like:

       putLine ("Time interval: " ++ show (t2 - t1) ++ " ms") $ \_ ->
       (t2 - t1)

In general, the example above gives some idea how Haskell programs using DOM in CPS style look like.

The CPS module should be imported by any Haskell module using the Continuation Passing Style constructs and the DOM framework. The CPS type itself is defined as:

type CPS c a = (a -> c) -> c

So, if a function has the return type CPS x y, this means that its continuation would accept a value of type y and return a value of type x

Unsafe interfaces with CPS

Usage of unsafeJS has not changed from one described above. This is still a pseudo-function accepting a string literal with Javascript code as an argument. The Javascript code supplied will be wrapped into a Haskell-callable function.

To access properties of Javascript objects, the following CPS-aware functions are provided:

unsafeGetProperty :: String -> b -> CPS d c

unsafeSetProperty :: String -> b -> c -> CPS d c

unsafeCheckProperty :: String -> b -> CPS d Bool

The first function accepts Javascript property name as its first argument, and a reference to a Javascript object as the second. It passes the value of the property retrieved (in type-agnostic manner) to its continuation.

The second function accepts Javascript property name as its first argument, the value to set the property to as the second argument, and a reference to a Javascript object as the third. The continuation gets the reference to the Javascript object with updated property (that is, the update occurs in-place).

The third function checks whether the given property is set to null, and passes True to the continuation if it is not null, and False otherwise.

All three functions evaluate their arguments.

To unsafely convert Javascript values to Haskell Num and String values, the following two functions are provided:

unsafeToNum :: (Num b) => a -> CPS c b

unsafeToString :: a -> CPS c String

The first function calls the Number Javascript constructor on the argument's value, the second calls the String Javascript constructor on its argument. Both functions evaluate their argument first.

To catch exceptions, the following function is provided:

catchJS :: a -> (b -> a) -> a

This function takes its first argument and evaluates it. If an error occurs (Javascript exception is thrown), it is passed as an argument to the function specified as catchJS's second argument. The function handling an exception should either return a value of the same type as the failed expression does, or to (re)throw an exception. The error function from the Standard Prelude is implemented using the Javascript throw statement.

Programming examples

The EchoCPS Wiki page contains an example of a working Echo demo program written using the DOM Level1 interfaces.

The EchoCPS2 Wiki page contains an example of a working Echo demo program written using the DOM Level2 interfaces which have been added to the Javascript backend. The only major difference between these two example programs is better typing of event handlers based on the definitions that appeared only in DOM Level2 specifications.

DOM and the Web Consortium

The Document Object Model (DOM) is the base interface to access the content and structure of documents in a web browser. The Web Consortium has a page dedicated to DOM.

This Programmers Guide is based on the Document Object Model (DOM) Level 1 Specification (Second Edition) provided by the Web Consortium. This version of DOM, although not very new, can serve as the greatest common denominator for many types of web browsers available these days.

DOM and Interface Definition Language (IDL)

General information

The Web Consortium uses a subset of the Interface Definition Language proposed by the Object Management Group (OMG IDL) to describe the abstract interface to the Document Object Model, so it may be implemented in various programming languages. These definitions cover basic operations to create and delete document nodes, manipulate their attributes and contents, and insert/remove nodes within the document loaded into the browser.

Conversion to Haskell

In accordance with the Web Consortium Copyright Notice, IDL files provided by the Web Consortium may be freely redistributed by anybody. So, copy of these files is included with the Yhc Javascript Backend. A modified version of the HaskellDirect (trimmed down to only OMG IDL code symtax recognition, and with different model of Haskell code generation) is also included. This HaskellDirect-based utility runs automatically when the Javascript Backend is being installed, so the installation includes Haskell code autogenerated from the IDL files. Developers who define new interfaces on the browser side to be used with the Javascript Backend are encouraged to write their own IDL files, and use the same utility to produce Haskell interface code.

Technical details of IDL to Haskell conversion

This section gives general details of correspondence between IDL definitions and generated Haskell code. Deeper details related to programming will be discussed in next sections.

Consider this IDL definition (from the DOM section of the definitions):

 interface Attr : Node {
   readonly attribute DOMString        name;
   readonly attribute boolean          specified;
   // Modified in DOM Level 1:
            attribute DOMString        value;
                                       // raises(DOMException) on setting
 };

One interface definition in IDL results in creation of one Haskell module with the same name as the interface has. Module name will be prefixed with DOM.Level1, that is, the #pragma prefix "w3c.org" in the beginning of the file is ignored.

The Haskell translation is:

module DOM.Level1.Attr
       (get'name, get'specified, set'value, get'value) where
import DOM.Level1.Dom
import CPS
import UnsafeJS
import DOM.Level1.Document (createElement)
 
get'name :: (CAttr this) => this -> CPS c String
get'name = unsafeGetProperty "name"
 
get'specified :: (CAttr this) => this -> CPS c Bool
get'specified = unsafeGetProperty "specified"
 
set'value :: (CAttr zz) => String -> zz -> CPS c zz
set'value = unsafeSetProperty "value"
 
get'value :: (CAttr this) => this -> CPS c String
get'value = unsafeGetProperty "value"

Additionally, in the DOM.Level1.Dom module, the following is defined (comments added):

data TAttr = TAttr               -- phantom type for the interface
class (CNode a) => CAttr a       -- class reflecting inheritance from Node
instance CAttr TAttr             -- interfaces of Attr are implemented
instance CNode TAttr             -- interfaces of Node are implemented

Attributes that have readonly in their definitions only have getter methods (e. g. get'name). The rest of attributes also have setter methods (e. g. get'value, set'value). Getter and setter names are produced by prefixing IDL attribute name with get' and set' respectively.

The Attr interface does not have methods, only attributes. The following interface illustrates how methods are represented:

 interface NodeList {
   Node               item(in unsigned long index);
   readonly attribute unsigned long    length;
 };

module DOM.Level1.NodeList (item, get'length) where
import DOM.Level1.Dom
import CPS
import UnsafeJS
import DOM.Level1.Document (createElement)
 
item :: (CNodeList this, CNode zz) => this -> Int -> CPS c zz
item a b = toCPE (item' a b)
item' a b = unsafeJS "return((exprEval(a)).item(exprEval(b)));"
 
get'length :: (CNodeList this) => this -> CPS c Int
get'length = unsafeGetProperty "length"

There also are related lines of code in the DOM.Level1.Dom module (not shown as they are logically identical to already reviewed).

The item method, as implemented in Haskell, takes the reference to the DOM element (NodeList) as the first argument, this. The second argument is the index of a node in the NodeList, corresponding to the in unsigned long index in the IDL definition. The last argument is the continuation. Type constraints (CNodeList this, CNode zz) => state that the method operates on instances of the CNodeList class, and values passed to the continuation are instances of the CNode class.

Body of the method contains a type-aware wrapper over the unsafe code calling appropriate item method on the Javascript object implementing the NodeList interface.

Known omissions

  • Exception information (raises...) is completely ignored by the converter. If an exception in Javascript code occurs, it should be treated as described above, in the Unsafe interfaces with CPS section.
  • The converter makes no distinction between in and out arguments.
  • The converter does not tolerate multiple methods with the same name, but different number of arguments, within a single interface. It is however possible to have methods with the same name (regardless of number of arguments) in different interfaces. The focus and blur methods serve as a good example: they appear in at least two HTML elements: <input> and <textarea>. Developers are recommended to use import qualified statement for importing modules with conflicting method names, and use qualified names to resolve ambiguities.

Haskell DOM vs. Javascript DOM

Haskell phantom types vs. Javascript object types

A phantom type is created for every interface defined in OMG IDL files provided by the Web Consortium. Examples above illustrated this. So, this is important that all interface names were unique across all IDL files that are processed by the converter at once (both toplevel and include). More examples of such phantom types:

data TDOMImplementation = TDOMImplementation
data TNode = TNode
data TNodeList = TNodeList
data TNamedNodeMap = TNamedNodeMap
data TCharacterData = TCharacterData
data TAttr = TAttr
data TElement = TElement
data TText = TText
data TComment = TComment
data TCDATASection = TCDATASection
data TDocumentType = TDocumentType

Names of these types are derived from interface names by adding the capital letter "T" at the beginning.

Haskell type classes reflect interfaces inheritance

IDL, like many other object-oriented languages, features inheritance between interfaces defined. This means that an object implementing an interface X funcitonality, also implements functionality of interface Y, as well as all ancestors of Y if declared as

interface X : Y {
...

}

Let's trace a chain of inheritance of the HTMLButtonElement which represents a <button> tag:

interface HTMLButtonElement : HTMLElement
interface HTMLElement : Element
interface Element : Node
interface Node 

which basically means that all methods and properties of Node are expected to be implemented in HTMLButtonElement.

To tell this to the Haskell compiler, the type constraints mechanism is involved:

class (CHTMLElement a) => CHTMLButtonElement a
class (CElement a) => CHTMLElement a
class (CNode a) => CElement a
class CNode a

The correspondence between these two examples is clear. Names of classes are derived from interface names by adding the capital letter "C" at the beginning.

To enable the desired functionality on the correct (phantom) data types, instance declarations are added:

data THTMLButtonElement = THTMLButtonElement

instance CHTMLButtonElement THTMLButtonElement
instance CHTMLElement THTMLButtonElement
instance CElement THTMLButtonElement
instance CNode THTMLButtonElement

So, if we have a function that operates on Nodes (and therefore has (Cnode a ...) => in its type signature), it will accept values of the THTMLButtonElement type because of the above instance declarations, but not a TNodeList values because declaration for NodeList was:

 interface NodeList {
   Node               item(in unsigned long index);
   readonly attribute unsigned long    length;
 };

so NodeList does not inherit from Node. It is worth saying that Javascript code (which is type-agnostic) would likely accept passing a NodeList value to a function operating on Nodes. At best, a run-time exception would occur; at worst, some hard to find problems might be introduced diring the execution of such a function. Haskell compiler would catch this at the compilation stage.

The this object reference in Haskell code

In Javascript, methods of some object have an implicit argument, this. When a method is executed, the argument holds a reference to the object the method was invoked upon. Thus, if we had a DOM object implementing the NodeList interface, and wanted to extract a nth item of it, we would write:

 var itm;
 var nl = /* obtain the NodeList reference here */;
 itm = nl.item(n); /* item is a (only) NodeList's method taking a number */

Haskell does not allow to have such an implicit argument to a function. Instead, this is defined explicitly:

item :: (CNodeList this, CNode zz) => this -> Int -> CPS c zz

Equivalent Haskell code to retrieve a nth item would be:

{-- obtain the NodeList reference here --} $ \nl ->
item nl n $ \itm ->
{-- itm may be used further on in the code --}

Threads and events

Cooperative threads

Execution of Javascript by a web browser is always single-threaded. Scripts running when the page is being loaded cannot be interrupted by event handlers, and event handlers themselves cannot be interrupted by another event handlers.

There is however a Javascript function window.setTimeout which may be used, in combination with CPS, to simulate cooperative threads. Combining this technique with run-once auto-cleaning event handlers allows to utilize an event-driven programming model with cooperative threads (similar to what was used in MS-DOS based versions of Windows).

The setTimeout function takes a timeout length (in milliseconds), and (in the most common case) a string representing the Javascript code to evaluate after the timeout expires. Browser may potentially execute a pending event handler within the timeout specified.

Haskell primitives

In Haskell terms, there are three things to deal with: a timeout (an integer number), an expression to evaluate after the timeout expires ("child" thread), and an expression to evaluate right after the timeout has been set ("parent" thread).

The basic threading primitive (defined in the UnsafeJS module):

-- Fork execution for certain amount of time (including 0) by setting timeout
-- and passing a value to be evaluated then (b) and right now (c).

forkAfter :: Int -> b -> c -> c

forkAfter a b c = (fork' a b) `seq` c

fork' a b = unsafeJS
  "var t=contNum++;var s='exprEval(delCont['+t+']);delCont['+t+']=null;';
delCont[t]=b;window.setTimeout(s,exprEval(a)); return 0;"

The contNum and delCont objects are global Javascript variables defined in Runtime.js. The former provides unique number for each delayed continuation, and the latter acts as a storage of references to continuations.

Note: One thing to be added here: after some number of forks, the delCont object should be cleaned from nullified references to continuations that executed in the past; this requires trivial changes in Runtime.js.

Javascript event handlers may be used similarly, considering that an event handler may execute a delayed continuation, thus allowing a thread to wait for event. An event handler should nullify itself at its target (that is, if a onclick handler is executed, its target object should get its onclick attribute set to null before the handler exits. Another convention: if an object already has an event handler installed for certain event type, it cannot be replaced with another handler, thus guaranteeing that one thread will not recapture events that another thread is waiting for.

The basic event primitive (defined in CDOM.Level2.Eventsmodule):

-- Wait for an event from an element. Execution of the continuation given
-- is resumed as the event has been received. True is returned if the element
-- was not waiting for another event, False otherwise.

waitFor :: (CEvent e, CElement c) => c -> String -> (e -> Bool) -> Bool

waitFor elt evid k = 
  unsafeCheckProperty ("on" ++ evid) elt $ \h -> case h of
    True -> False
    False -> secl evid k elt $ \_ -> True

The secl function used by this primitive installs a self-clearing event handler for a specified type of events. Once executed, the handler removes itself from its target.

Usage examples

This piece of code sets focus on an input element (referred to by inp and starts the main event loop which will receive information from this input element for further processing):

focus inp $ \_ ->
forkAfter 0 (mainY inp) $
-- the rest of the program

This piece of code reads each character input from inp, and when Enter is pressed, passes the whole string to its continuation:

readChar :: THTMLInputElement -> CPS Bool Int

readChar inp k = waitFor inp "keypress" $ \e ->
  get'keyCode (e :: TKeyEvent) $ \c -> k c
  
readLine inp k = readChar inp $ \kci ->
  if kci == cDOM_VK_ENTER 
    then get'value inp $ \s -> k s
    else readLine inp k

This piece of code reads the whole line, and performs some actions (omitted in this example) depending on the length of input:

mainY inp = readLine inp $ \v ->
            if length v > 0
            then
-- some actions
              mainY inp
            else  
-- other actions
              mainY inp

The function loops infinitely, so everything a user types will be processed.

Message boxes

Message boxes provide a way for pseudo-threads to communicate with each other. Programmatically, a message box is a mutable memory cell holding a continuation that a message sent is to be passed to. Objects of type Data.JSRef are used for this purpose.

A simpliest message box that is capable of holding a single message, rejects any messages that arrive while the receiver thread is not expecting a message, and provides a synchronous send operation (sender thread will not be resumed until the receiver thread begins to wait again for a message on the message box), may be implemented like shown below:

-- A continuation which is stored in the message box when no thread is waiting
-- for a message: any message sent via this message box will be rejected
-- (discarded).

ignore = \_ -> False

-- Message box constructor: initializes the JSRef object with 
-- ignore-everything continuation.

mkMsgBox k = newJSRef ignore $ \mb -> k mb

-- Send a message: obtain the continuation stored in the message box,
-- construct a thunk (res) to pass the message to the continuation,
-- evaluate res, and finally, resume our own continuation (k) when 
-- the receiver evaluates the message, getting the evaluation result. 
-- Thus, synchronicity of send is achieved.

send mb msg k = readJSRef mb $ \cont ->
  let res = cont msg
  in  res `seq` (k res)

-- Receive a message: store our continuation (k) in the message box,
-- once called, restore what was in the message box before (thus ignoring
-- any messages that may arrive before we wait for a message again),
-- evaluate our continuation with the message received.

recv mb k = readJSRef mb $ \prev ->
  writeJSRef mb (writeJSRef mb prev $ \_ -> k ) $ \_ -> True

An example of two threads using a message box this way: the sender thread is associated with an input (select) element whose updated value may be obtained by handling an "onchange" event; the receiver thread is associated with some display element whose contents may be updated.

-- Sender thread:
-- mb: message box to use
-- par: abstract select element whose value is to be sent

acts mb par = (waitFor par "change" :: CPS Bool TEvent) $ \e ->
  (unsafeToSelf par :: CPS Bool THTMLSelectElement) $ \sel ->
  get'value sel $ \v ->
  send mb v $ \_ -> acts mb par

-- Receiver thread:
-- mb: message box to use
-- par: abstract display element whose visible contents may be updated
-- updateD: a function to update the display element

actu mb par = recv mb $ \s ->
  updateD par s $ \_ ->
  actu mb par

Note: Just for the sake of giving proper credit: one might find this method of inter-thread communication very similar to one described in Gadgets: Lazy Functional Components for Graphical User Interfaces (1995) by Rob Noble, Colin Runciman. In fact, this paper was studied along with the Fudgets Thesis, and gave some inspiration to this developer.