Yhc/Javascript/Programmers guide

From HaskellWiki
< Yhc‎ | Javascript
Revision as of 19:21, 14 June 2007 by DimitryGolubovsky (talk | contribs) (Added IDL section)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

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.

At the moment this demo program is being written, there is no programming paradigm decided upon, no GUI framework for Haskell to use in web browser, no supporting libraries, nothing. Only the browser itself plus a small runtime support library. Just like programming in machine codes on "bare iron": that's how first programs were created.

This Programmers Guide shows how Haskell can be used to interact with web browser at the lowest possible level. Before one starts developing a programming paradigm, or a GUI framework, this area of low-level programming needs to be explored.

Programming for Web Browser

A Haskell program converted into Javascript and running in a web browser faces environment different from "traditional": there are no input/output devices and operations as we are used to them, no file system, and no sequential flow of execution. Instead, there is the DOM tree of objects; some of them perform interaction with user input and provide visual output, and program execution is event-driven.

This Programmers Guide, using the demo Echo program as a basis, will describe programming approaches and paradigms suitable for such environment.

The Echo Demo Program

The Echo demo program demonstrates primitive interaction with user input, dynamic modification of the DOM structure to show output, and integration with third-party Haskell code (Roman conversion module). It also demonstrates how Javascript exceptions can be handled, and how to measure time intervals when running in a web browser. The link in the section header points to a syntax-colored source of the demo program.

The main function

The demo program discussed in this Programmers Guide has a main function which is called when the page is loaded into a browser. It is important to mention that in general, such a program may have more than one "entry point", and none of them called main. For example, a program consisting of event handlers only, with handlers being attached statically to page elements using HTML.

It is necessary to remember that all "entry points" must be specified on the converter's command line as reachability roots.

Type signature of the main function depends only of the framework used. This demo program uses simple monadic framework, therefore the main function returns a monadic value. It may or may not have arguments, again, this is dependent of conventions used when building a web page to place the program on.

In this demo program, the only purpose of the main function is to create the initial page layout and define an event handler for the input element. All interaction with user is performed by the event handler.

A Simple Monad

One of possible ways to guarantee proper sequence of actions is to define a monad, and perform all actions that require execution ordering within. Here is an example of such monad:

data JS a = JS a

instance Monad JS where
  (JS a) >>= fn = fn a
  (JS a) >> fn = fn
  return a = a `seq` (JS a)

This monad is sufficient to guarantee proper order of execution of Javascript code. Note that all of its operations force evaluation of their arguments. That is, the RHS expression of bind will not start executing until the LHS expression is completely evaluated. The same applies to return: control will not be passed furter until the returned expression is completely evaluated.

If this monadic framework is used, the main function has return type JS ().

Calling Javascript from Haskell: unsafeJS

The unsafeJS 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.

The function has a type signature:

foreign import primitive unsafeJS :: String -> a

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.

The unsafeJS function should be called with a string literal. Neither explicitly coded (with (:)) list of characters nor concatenation of two or more strings will work. The converter will report an error in this situation.

A valid example of using unsafeJS is shown below:

global_YHC'_Primitive'_primIntSignum :: Int -> Int

global_YHC'_Primitive'_primIntSignum a = unsafeJS
  "var ea = exprEval(a); if (ea>0) return 1; else if (ea<0) return -1; else return 0;"

This is a Javascript overlay (in the sense that it overlays the default Prelude definition of the signum function) of a function that returns sign of an Int value.

The string literal unsafeJS is applied to is the Javascript code to be wrapped.

Below is the Javascript representation of this function found in the Echo page source.

strIdx["F_hy"] = "YHC.Primitive.primIntSignum";
...
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;});

Here are the rules that govern the usage of unsafeJS:

  • The unsafeJS function is contained in the UnsafeJS 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 a, b, c, 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. a, b, c, etc.
  • Haskell values are passed to Javascript functions unevaluated: use exprEval to evaluate
  • Javascript code passed to unsafeJS should not contain outermost Javascript function declaration and curly braces: ycr2js will provide those
  • Javascript code is not limited in what it may contain*; 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.
  • Javascript code must return a value

So, in the signum function above, first thing done is evaluation of the argument a. Because of the proper Haskell type signature provided, it is safe to expect a numeric value as result of the evaluation.

Next, usual comparisons with zero are performed, to determine the sign of the argument. Results are returned.


* For instance, inner function declaration may be used, as in this more complex example below (implementation of integer division via modulus):

global_YHC'_Primitive'_primIntegerQuot :: Integer -> Integer -> Integer
global_YHC'_Primitive'_primIntegerQuot a b = unsafeJS 
  "(function(x,y){return (x - (x % y))/y;})(exprEval(a),exprEval(b));"

The purpose of having an inner function declaration is to reuse evaluated arguments a and b: even though every expression is evaluated only once, extra call to exprEval may be avoided this way.

Calling Haskell from Javascript

To call a Haskell function from within Javascript code, one has to construct application of this function to argument(s), and evaluate the application (may be done later, or not done at all in Javascript code).

Every Haskell expression visible to Javascript is represented by an object of type HSFun or HSDly. See Structure of Javascript Objects for more details about these objects' methods and properties.

Application of a function to its arguments is constructed by calling the _ap method of an object representing a function. The _ap method takes an array of values as its only argument.

So, if objf is a Javascript object representing a Haskell function, and p1...pn are the arguments, application is constructed like this:

objf._ap([p1,p2,...pn])

Construction of an application does not force the function to evaluate its code and return a value. In order to do this, a function from the Runtime support library should be called:

var v = exprEval(objf._ap([p1,p2,...pn]));

Then v will be assigned a value returned by the function referred to by objf.

Value for objf mey be obtained either from the Haskell code which calls a Javascript function or from the index of function names.

Names of functions that were used in Haskell source code are not preserved in the generated Javascript code. They are replaced with meaningless sequences of letters and numbers. For instance, Echo.main function is renamed to F_cj. It cannot be known in advance, what will function names look like after renaming.

To be able to locate a renamed function by its name, the global object named funIdx exists. It is essentially a hash table mapping function names used in Haskell source to their names used in Javascript code. This hashtable contains only names of functions specified in the converter's command line as reachability roots.

To obtain name of a function after renaming, the following expression needs to be constructed: funIdx['Echo.main'] (quotes may be double as well) for the Echo.main function. Function names should be qualified.

Result of function name lookup points to an object that may be used to call the function as it was described above.

An example of function name index usage is specifying the Javascript expression to be executed when web browser loads the page:

 <body onload="exprEval(funIdx['Echo.main'])">

Passing Primitive Values

  • Numeric values are passed from Haskell to Javascript and from Javascript to Haskell without any special wrappers.
  • Boolean values are passed from Javascript to Haskell without wrappers, but passing from Haskell to Javascript requires evaluation and extracting value of the _t property.

That is, if Javascript code expects a Boolean value as its argument a, the following expression exprEval(a)._t extracts the primitive value of true or false.

Passing Strings

Passing strings in both directions does not need any wrapping. When passed from Javascript to Haskell, strings are lazily converted into lists of characters. When passing from Haskell to Javascript, method toString overloaded in HSCons forces evaluation of every expression the list is built of, and finally, a string that Javascript can use is created.

Passing Arrays

Javascript arrays when passed to Haskell code are lazily converted to lists of values. To convert a Haskell list reference to a Javascript array, one has to call the _toArray method on that reference.

An example of the latter can be seen in the runMethod function implementation. This function receives arguments of the method to be run as an array.

runMethod :: JSObject -> String -> a -> JS JSObject runMethod a b c = unsafeJS "var a1=exprEval(a); return new HSData(conIdx['Echo.JS'],[cbrApply(a1[exprEval(b).toString()],a1,c._toArray())]);"

Note that the b argument is evaluated, and toString is called upon it, and c._toArray make sure that the c argument will be visible to Javascript as an Array. Note that this might be a better idea to call exprEval on c too.

Passing Objects

Javascript objects may be passed to Haskell by reference. For this purpose, an opaque type may be defined:

newtype JSObject = JSObject ()

No values of this type will be directly created by Haskell code. But when it is necessary to pass to, or return from Javascript a reference to an object whose structure is not accessed by Haskell code, this is where it helps.

For example, the function to get the document interface of the web page currently loaded in the browser, one may define a function:

getDocument :: JS JSObject getDocument = unsafeJS "return new HSData(conIdx['Echo.JS'],[document]);"

In this case, it is only needed to get a reference to the document object itself; nothing about its internal structure is known. Further in this Guide, it will be shown how individual properties of Javascript objects may be accessedm and methods run.

Another aspect of passing objects is ability to access internal structure and to create Haskell objects in Javascript code. Haskell data objects are visible to Javascript code as objects of type HSData. See Structure of Javascript Objects for more details about this object's methods and properties.

In general, constructor tag index is accessible as the _t property, and data fields as the _f property which is an Array. Order of fields in this array is same as it was declared in Haskell code.

The most widespread usage of the _t property of HSData objects is in Haskell case statements translated to Javascript when pattern matching is done by constructor tag.

In the example above, a monadic value of document object reference is constructed by calling the HSData constructor function with Echo.JS tag index (obtained via the conIdx lookup object), and a singleton Array consisting of the reference to the document.

If a Haskell data object belongs to a type declared as a "regular" data type, i. e. not with a record-style declaration, the only way to access individual fields is to use indexed (0-based) access to the _f property of a HSData object. For objects whose type was declared in the record style, it is potentially possible to use selector functions for individual fields, but the following needs to be remembered:

  • It is necessary to obtain a function index (via funIdx lookup) for each selector function, therefore qualified name of the function must be specified as a root of reachability on the ycr2js command line
  • It is therefore necessary to know exactly which module contains declaration for a particular data type to get a qualified name for the selector function.

This makes Javascript access to data fields of Haskell data objects something to avoid without extreme need. Indeed, it needs to be borne in mind that on the Javascript side, primitive values are better to process, and manipulation by Haskell-specific objects is better to perform on the Haskell side.

Type Coercions

This section of the Guide discusses methods to coerce values contained in Javascript objects returned from Javascript code (JSObject) to values that Haskell understands. Internal representation of Javascript values does not contain explicit type information: based on the context where values are used, they may be treated differently, e. g. a number may be treated as a string (containing numeric value converted to a string). Haskell programs need type of every value to be specified at compile time.

Usually, to coerce a Javascript value to certain type some constructor or method must be called upon that Javascript value. After that, the value may be returned as if it had the required Haskell type. If the value cannot be coerced as required, Javascript code may throw an exception, or return an undefined value, or behave in some other way.

For example, a Javascript object that is expected to contain a numeric value, may be coerced from an abstract type JSObject to Int:

asInt :: JSObject -> JS Int asInt a = unsafeJS "return new HSData(conIdx['Echo.JS'],[new Number(exprEval(a))]);"

That is, there will be an attempt to create a numeric value out of the object. If unsuccessful, certain reaction will follow (see the Javascript documentation for details), but if successful, it is a numeric value that is returned.

Similarly, a stringified representation of a Javascript object may be obtained:

asString :: JSObject -> JS String asString a = unsafeJS "return new HSData(conIdx['Echo.JS'],[new String(exprEval(a))]);"

In the latter example, the String constructor function obtains string representation of an object (that is, whatever its toString overloaded method returns).

Thus, if a key code from an event object is expected to be an integer number, one may write:

kcs <- getProperty e "keyCode" >>= asInt

and if a value entered into an input element is to be treated as a string, one writes:

v <- getProperty o "value" >>= asString

Here, e refers to an event Javascript object, and o refers to a DOM object associated with the HTML <input> element.

Getting/Setting Properties

Javascript objects' properties may be accessed both using the dot-notation (object.property) and associative array notation (object["property"]) both for setting and getting properties' values.

The second method is more convenient because string passed to unsafeJS may only be a literal and cannot be parameterized.

A pair of functions below (names self-explanatory) gives an example how Javascript objects' properties may be accessed from Haskell.

getProperty :: JSObject -> String -> JS JSObject getProperty a b = unsafeJS "return new HSData(conIdx['Echo.JS'],[exprEval(a)[exprEval(b).toString()]]);" setProperty :: JSObject -> String -> a -> JS () setProperty a b c = unsafeJS "exprEval(a)[exprEval(b).toString()]=exprEval(c);return new HSData(conIdx['Echo.JS'],[]);"

These examples also feature wrapping of returning values into a monadic type.

Note that the b argument containing property name is evaluated before getting its string value. This argument may pass a concatenation of several strings, or an expression computing a string therefore its evaluation needs to be forced.

Also note that type of property value returned by getProperty is JS JSObject, and value a property is set to may be of any type. This is a consequence of Javascript's untypedness: no assumption can be made what is the actual type of property value. Use coercion functions to cast property values to types needed in each case.

Running Methods

Similarly, methods of Javascript objects may be run from a Haskell program. The following function can be used to provide this functionality:

runMethod :: JSObject -> String -> a -> JS JSObject runMethod a b c = unsafeJS "var a1=exprEval(a); return new HSData(conIdx['Echo.JS'],[cbrApply(a1[exprEval(b).toString()],a1,exprEval(c)._toArray())]);"

This function constructs a Haskell data object of type JS JSObject containing value returned from the method. Note that method's arguments are passed in a list.

This function calls the cbrApply function to apply the method to its arguments. This function provided by the Javascript Runtime Support library congains workaround for MSIE whose DOM methods do not have the apply method.

Handling Exceptions

In certain situations, Javascript code may throw an exception. One possible usage of exceptions is implementation of the Prelude.error function which just throws an exception containing among other things the string given to Prelude.error as an argument.

To handle an exception (and thus make result of calling Prelude.error non-fatal for the program) a handler should be installed which is achieved by using try-catch blocks.

The function code below shows an example how to handle exceptions in a monadic framework. Its type signature is similar to one of the Prelude.catch:

catchJS :: JS a -> (JSObject -> JS a) -> JS a catchJS a b = unsafeJS "try {return exprEval(a);} catch(_e) {return exprEval(b)._ap([_e]);}"

The function installs an exception handler, evaluates the expression given as the first argument, and if exception is caught, passes it as a parameter to the expression given as the second argument.

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.

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

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).

Both 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 interfaces.

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

Haskell DOM vs. Javascript DOM

Haskell Phantom Types vs. Javascript Object Types

Haskell Type Classes Reflect Inheritance

The "Defaulting " Problem and DOM Utility Functions

Programming Examples

Fudgets On Web

(once we implement that)