Take a step back in history with the archives of PragPub magazine. The Pragmatic Programmers hope you’ll find that learning about the past can help you make better decisions for the future.

FROM THE ARCHIVES OF PRAGPUB MAGAZINE DECEMBER 2012

Web Programming in Haskell: Part One

By Paul Callaghan

PragPub
The Pragmatic Programmers
26 min readMay 20, 2022

--

Paul returns with another rich article on the Haskell language, this one focusing on Web programming.

https://pragprog.com/newsletter/
https://pragprog.com/newsletter/

The next few articles in this series on the Haskell language will look at web programming via Haskell. Web programming is supported in various ways, from low-level libraries for the basic operations like communicating over http and creation of HTML documents, up to sophisticated frameworks for building apps and performant web servers for running the apps. January’s article will look at the frameworks, primarily Yesod. This article will look at Fay, which is a Haskell alternative to CoffeeScript.

Replicating the libraries and frameworks of other languages is not too difficult. The interesting question — following a key theme of this series of articles — is how we can use Haskell’s facilities to improve the experience of web programming. For example, less coding and better maintainability via more powerful abstractions, more safety through using the language style and type system to avoid certain problems, or even improved performance by supporting certain kinds of optimization behind the scenes. Even more interesting is to understand the cases and phenomena where Haskell isn’t enough and where more powerful techniques, like dependent types, might provide additional leverage.

Fay — Another JavaScript Alternative

Fay was started in early 2012 by Chris Done as a relatively straightforward way to support Haskell-style programming in browsers. It is one of several options in the Haskell-ish area (see this comparison for more details) but for now it seems the front-runner in terms of simplicity, usefulness, and active development.

One important point, though: Fay is very much a work in progress, and some examples may not work in all versions. It’s worthwhile installing a particular recent release and reviewing the test and example files for that version. I’m using version 0.10 in this article. Also remember that the examples are still in flux, too, and some could be rough early experiments rather than showing the current ideas and understanding of the developers.

There are several reasons for my wanting to cover Fay here. Firstly, there’s the pragmatic approach of deliberately piggy-backing on an existing language and its tools instead of inventing a new language and needing to develop tools to go with it — but without requiring the complexity of the full compiler. It also removes the need to learn a new language and its semantics. Secondly, I believe that Fay has many advantages over CoffeeScript that are worth considering, particularly if you need to do moderately complex programming and would benefit from Haskell features like more flexibility with new data structures and support from the type checker. For one thing, it’s easy to isolate the core business code from the the UI parts and check that the ghc-compiled version behaves as expected — and identically to the via-fay-and-node-etc. version.

Also, it’s an excuse to look through some fairly complex Haskell code (the Fay compiler itself) and discuss the techniques used. We also get to cover a few of the core implementation details behind Haskell, such as how laziness and pattern matching work. Finally, it gives me personally a great excuse to tinker and have fun — which in itself is a very important reason. May you find time to tinker as well this month!

Using and Installing Fay

The Fay web page contains several examples, showing both the Haskell code and the compiled result. There is also a web-based IDE for experimenting with Fay, which is itself written using Fay (see github.com/faylang/fay-server. The IDE allows creation and editing of user-supplied code, or modification of standard examples and libraries. Both of these pages rely on JavaScript that was compiled from Haskell via Fay, and the IDE page uses Ajax calls to a server that does the compilation. Later on, we’ll look at how these pages use Fay.

To install on your own machine, start by installing the Haskell platform to give you the GHC compilers, several standard 3rd-party libraries, and a few useful development tools. (The web page has instructions for the usual OS platforms.) Then, install the latest stable release of Fay via cabal (Haskell’s package manager, like Ruby’s gem or Node’s npm), with the following line. Assuming you’re running this in a non-root account, the line will download the latest release of Fay and any relevant dependencies, configure and compile them for your setup, and place the results in $HOME/.cabal. GHC will check these directories when compiling code.

cabal install fay

It’s probably useful to clone the Fay language repository and the IDE repository so you can look at the various tests and examples contained within — but ensure that you check out the branch relevant to the release you have installed. Further information, including how to run the tests, is on the main Fay web page.

A Simple Example: Laziness and Partial Application

This simple example shows the key ideas of the translation from Haskell to JavaScript. Remember that laziness is technically an implementation technique provided by most Haskell compilers, rather than a fixed part of the language — but for now I’ll wave my hands on such details. Given this code:

foo :: Double -> Double -> Double
foo x y = x * x + y

We want it to behave in various ways. One, that foo 3 is meaningful and so on, and can be applied to another number to get a result, that is, when fix_3 = foo 3 then fix_3 1 gives 10. Two, that foo 3 (1/0) won’t evaluate its arguments before the call (so it will find the division-by-zero problem only when it tries to do the addition in the function body, not before) —that is, that it is “lazy.”

This is what the current version of Fay will generate:

var BasicTwo$foo = function($p1) { 
return function($p2) {
return new $(function() {
var y = $p2;
var x = $p1;
return _(Fay$$add)(_((Fay$$mult)(_(x))(_(x))))(_(y));
});
};
};

Note: the example output in this article will typically be the result after the initial translation stage with some minor optimizations added, using constructs that keep the translation simple, rather than immediately generating optimal code. So there could be further simplifications to be made. Such improvements are not always best done inside the compiler, and usually there are specific tools that can do a much better job anyway! Fay users often run the generated code through tools like Google’s closure compiler to squeeze out extra performance.

Firstly, partial application is served by the outer two function constructs, thus taking its two arguments one at a time. This is straightforward and nicely supported by JavaScript of course. The laziness is supported by three constructs that work together:

  • function () { …BODY… } — which creates a thunk or suspended value.
  • new $( …THUNK… ) — which helps avoid repeat evaluation of a thunk.
  • _(val) — which forces evaluation of a thunk until it is a real value.

When the code has both arguments, the immediate result is a thunk that represents the suspended execution of the function body. This means that the computation isn’t done right away but is wrapped up in a new function that will only be called if the result is actually required. This use of a 0-arity function is a standard way to get lazy effects in a non-lazy context, well explored in Lisp and Scheme work (for example, see SICP section 3.5.1), and works by freezing the relevant values in the closure but not performing the computation until the function is called. (However, Haskell VMs are lazy by design and so do not require this technique: the laziness is implemented much more efficiently.)

The evaluation is forced by applying the _(…) function, which ensures it returns a real value rather than a thunked value. This forcing also shares the results of evaluations, so for uses like foo (1 + 2) 3, the addition on the first argument will be done at most once. Finally, the new $( … ) is part of a wrapping mechanism to indicate whether a value is ready for use or if evaluation is required.

Running the above code is simple. Here is the complete example.

{-# LANGUAGE NoImplicitPrelude #-}         -- 1 
module BasicTwo where -- 2
import Language.Fay.Prelude -- 3
foo :: Double -> Double -> Double -- 4
foo x y = x * x + y -- 5
main :: Fay () -- 6
main = putStrLn (show (foo 1.2 3)) -- 7

The important line is (7). Following convention, the entry point for the code is called main, and it just prints the result of a simple call. Lines (1) and (3) disable the standard Haskell Prelude in favor of a cut-down version that matches Fay’s default library and the facilities available from JavaScript (for example, just one numeric type). Line (2) is used to namespace the generated code. Notice that in line (7), Fay provides putStrLn to print strings on stdout, and show to convert certain values to string form (though this show is a special function provided by Fay rather than the class version — see the documentation for details). The compiled code for BasicTwo$main looks like this.

var BasicTwo$main = new $(function() { 
return _(Language$Fay$Stdlib$putStrLn)(
_(Language$Fay$Stdlib$show)(
_( _(BasicTwo$foo)(1.2) )(
3
)
)
);
});

Foreign Functions and the Fay Monad

How does putStrLn work in Fay?

The default implementation maps it to JavaScript’s console.log(…) method. This section explores how this mapping works and how it fits into the rest of Fay.

When working with other JavaScript libraries — jQuery is a prime example — we’ll need some flexibility in calling bits of JavaScript. Fay achieves this through its FFI — Foreign Function Interface. The ideas are similar to how several Haskell implementations link into underlying C libraries, but adjusted for the JavaScript setting.

putStrLn :: String -> Fay ()
putStrLn = ffi “(function(x) { if (console && console.log)
console.log(x) })(%1)”

Behind the scenes, the Fay compiler arranges for the input value to be mapped from a Haskell string to its JavaScript equivalent, then after the code has been executed, to collect any relevant return value and convert it back to Haskell. FFI calls can be used to execute any piece of JavaScript, though some calls will need to be done in a particular order. One example is printing several strings using putStrLn, and as in conventional Haskell, this order can be controlled simply and unobtrusively via monads. Hence Fay provides the type constructor Fay (as in the result type of putStrLn above) with the standard monad interface (return and (>>=)). The monadic framework is also useful when interacting with many JavaScript libraries. The following shows some simple operations via jQuery.

data jQuery
select :: String -> Fay jQuery
select = ffi “window[‘jQuery’](%1)”
getVal :: jQuery -> Fay String
getVal = ffi “%1[‘val’]()”
setVal :: String -> jQuery -> Fay jQuery
setVal = ffi “%2[‘val’](%1)”

So, select produces a result set, from which we can get a value (of the first item) with getVal or set the value (of the first item) with setVal. The type jQuery is used as a placeholder for a jQuery result set, partially ensuring that we use the API appropriately. It’s like an abstract type, in that we don’t have a direct way to build a value or take a value apart, but we can obtain one by calling select and use it in relevant operations. For example:

foo = do name <- select “input#name_field”
txt <- getVal name
setVal (txt ++ “ smith”) name

And it is easy enough to write a new shorthand operation for this combination, so we can just write: foo = chgVal (\s -> s ++ “ smith”) “input#name_field”.

chgVal :: (String -> String) -> String -> Fay () 
chgVal change_fn selector
= do elems <- select selector
txt <- getVal elems
setVal (change_fn txt) elems
return ()

The return () at the end just ensures that the return result from setVal is discarded and so the operation has the expected type. I’m assuming that we don’t want to chain from this operation.

As an interesting side note, observe that the definition of ready below is the same as select, but the types are different. select can only be used to filter on a string expression to return a jQuery result set, whereas ready can only be used to bind some imperative block of Fay actions to the ready event and should not return any useful value. Details like this can help to prevent silly mistakes (if only petrol pumps had a similar type system — it would have saved me from an expensive and embarrassing trip to the car dealership recently…).

ready :: Fay () -> Fay ()
ready = ffi “window[‘jQuery’](%1)”

This being Haskell, we can also let our imagination loose and play with other ways to use jQuery idioms and to use the type system. For example, we might find that setVal mostly needs to work on complex jQuery expressions, so we might prefer setVal_v2 as below, to allow code like setVal_v2 field_one (select “input#other” >>= getVal).

setVal_v2 :: jQuery -> Fay String -> Fay jQuery 
setVal_v2 result_set value_action
= do value <- value_action
setVal value result_set

Another possibility is to have a specialized version of the Fay monad reserved for jQuery that is used to protect against inadvertent mixing of jQuery code and other Fay IO code. Or perhaps to add more detail into the name of the jQuery type so that it reflects what is in the result set, say one thing or many, which might also help to weed out errors. For example, the result set after setVal will always contain just the modified item. We’re still experimenting to see what looks good!

An Example — the Fay Home Page

The Fay home page is generated from a Haskell script, and the interactive features are provided via a Fay script. The scripts are here and here, respectively. The Fay script currently does three jobs: passing the JavaScript code samples through a beautifier (js-beautify) and a highlighter (highlight.js), setting up the show/hide toggle on the code samples and setting the initial state depending on the example’s size, and building the TOC.

While noting the comment at line 10 (and the point about “still experimenting” with good ways to interact with jQuery), here’s the TOC code . It’s a sequence of actions via the jQuery library, written in monadic style. The first few lines create a div for the TOC and fill it with a heading and an unordered list, then insert it in the document after a certain title element. Next, loop through the h2 elements in the document using each on the result set. For each h2, the anchor is set from the element’s position in the list, then a link to this anchor is added in the unordered list. The final return True ensures that the monadic result matches the expected type, rather than whatever was returned by the previous action in the loop’s block.

setupTableOfContents :: Fay () 
setupTableOfContents = do
toc <- makeElement “<div class=’table-of-contents’>
<p>Table of Contents</p></div>”
query “.subheadline” >>= after toc
ul <- makeElement “<ul></ul>” >>= appendTo toc
headings <- query “h2”
each headings $ \i heading ->
let anchor = (“section-” ++ show i)
h = wrap heading
in do -- Make sure the anchor exists at the heading point.
attr h “id” anchor
-- Make the entry.
li <- makeElement “<li></li>” >>= appendTo ul
a <- makeElement “<a></a>” >>= appendTo li
getText h >>= setText a
-- Link up to an anchor.
attr a “href” (“#” ++ anchor
-- For the indentation.
getTagName heading >>= addClass li
return True

The type given to each elsewhere in the code is each :: jQuery -> (Double -> Element -> Fay Bool) -> Fay (), so it is a monadic action done only for its side effects (since it returns the boring value ()), and requires a result set (or so we hope — the typing doesn’t distinguish this yet) and a function that expects a number (JavaScript numbers are all double precision) and a DOM element, and returns a monadic action that will eventually produce a boolean value. The DOM element is converted to a result set with wrap :: Element -> jQuery, exactly like $(element) or jQuery(element) in plain JavaScript, and can then be used freely in jQuery calls. Interestingly, this wrap is typed as a pure function, not some monadic action. This is okay assuming that jQuery runs this without doing side effects, and it is convenient when working with existing elements in code, though there’s no harm in being safe and making it a monadic action either.

The style used with each applies to event handlers too: callbacks will take zero or more arguments and return a monadic value, hence an action (or sequence of actions) to be run when the event is triggered. A good example is the calculator from the Fay examples directory. It defines onClick :: Fay Bool-> jQuery -> Fay jQuery to bind the action in its first argument to the click event of elements in the second argument result set, which is covered in more detail below. Just pause a while to consider how monadic values are being used here: when the click occurs on some element, we want some actions to be executed, and the monadic framework provides excellent support for doing this clearly and safely.

Finally, a quick look at the Haskell script that generates the accompanying page. The first few lines arrange for certain JavaScript examples to be included in the document, and for the Fay script to be compiled before a deploy. I want to highlight the code starting around Line 71. It uses a Haskell library called Blaze as a DSL for HTML documents, very similar to Haml in Ruby. It uses a few tricks with monadic notation and overloading to provide a clean-looking DSL, using types to eliminate certain notational mistakes.

theheading = do 
div !. “head” $ do
img !. “head-logo” ! src “logo-large.png”
div !. “head-text” $ do
h1 “Fay programming language”
div !. “subheadline” $ “A proper subset of Haskell
that compiles to JavaScript”

The above example describes the document’s heading component. Monadic blocks (indented under a do) represent lists of HTML elements, for example, the .head-text block contains a h1 followed by a div. Nesting is provided by $ — the simple pipeline operator! — hence the final line indicates a div that has the tagline as its sole contents. The !. and ! operators are used here to set the class names and other attributes on the parent element, for example, the img line is rendered to:

<img class=”head-logo” src=”logo-large.png”>

We’ll return to this library next time, when we look at server-side web programming in Haskell. (Final thought: can types help to prevent people using tables for layout? Hmmmm.)

User-Defined Types and Pattern Matching

This (for me) is the killer feature of Fay — followed closely by Haskell’s clean syntax and type checking, of course. It is a key point of these articles that functional programming is about putting data first, and being able to add and use complex data structures flexibly and simply is a huge part of this. Alternatives like CoffeeScript or TypeScript just do not compete.

Fay supports all of the Haskell-98 forms of algebraic data types and some restricted cases of more complex types, hence any mixture of enumerations, union types, records, polymorphic types, recursive types, and nested types. For example, it supports the arbitrary-branching tree used for the search space in the word-chain kata two months ago.

data Tree a
= Node { rootLabel :: a, -- label value
subForest :: Forest a -- zero or more child trees
}
type Forest a = [Tree a]

And we can write standard Haskell to manipulate it:

val1 :: Tree String
val1 = Node “a” [Node “b” [Node “c” [], Node “d” []],
Node “e” []]
showT :: Tree String -> String
showT (Node s cs)
= unlines $ s : map (“ “++) (concat $ map (lines . showT) cs) main_t = putStrLn (showT val1)

When compiling this through Fay then executing via node or similar, the result is what we expect — a nested tree.

Notice that we’re using the list type and several standard Prelude operations. Fay supports Haskell lists as a primitive type, providing direct implementation of several basic operations. Some of the common Prelude operations are written in the Fay subset of Haskell and compiled into JavaScript on demand. You can see what Fay currently supports from the files here and here.

Compilation of these data types and pattern matching is simple but effective. Constructors in user-defined types are converted to objects, and provided with curried constructor functions. Where record types have field names (as in Tree above), accessor functions are generated with appropriate names, for example rootLabel:: Tree a -> a.

var $_Main$Node = function(rootLabel, subForest) { 
this.rootLabel = rootLabel;
this.subForest = subForest;
};
var Main$Node = function(rootLabel) {
return function(subForest) {
return new $(function() {
return new $_Main$Node(rootLabel, subForest);
});
};
};

Pattern matching is compiled into if-tests, using instanceof to test the constructor (that is, JavaScript function) that built the (forced) object being passed in. All Haskell constructors are mapped to such objects, hence the instanceof test is appropriate. Nested patterns will result in nested if-statements. When some pattern clause matches, the corresponding block of code is executed and should return an appropriate value. As the nested if-statement is navigated, names in the pattern are bound as JavaScript variables and the same names used directly in the appropriate right-hand side. If no pattern matches, then the code will fall through to the final exception line that reports a missing pattern or unhandled case.

var Main$showT = function($p1) { 
return new $(function() {
if (_($p1) instanceof $_Main$Node) {
var s = _($p1).rootLabel;
var cs = _($p1).subForest;
return // … big right-hand side
}
throw [“unhandled case in showT”, [$p1]];);
});
}

Another useful detail is that Fay can automatically add support for converting values from such user-defined types to and from JavaScript. This happens behind the scenes, but to be explicit about it, the following two lines are needed — the purpose being to keep the type checker happy. After all: we don’t want to — or need to — subvert type checking. With these two lines, we can now run putStrLn (show val1) directly. (Note that Fay doesn’t support full type classes yet, just a few special cases.)

instance Foreign a => Foreign (Tree a) 
instance Show a => Show (Tree a)

Finally, for the masochists, here’s the actual RHS from the example above. Try to spot the recursive call!

// unlines $ s : map (“ “++) (concat $ map (lines . showT) cs)
//
_(_(Language$Fay$Stdlib$$36$)
(Language$Fay$Stdlib$unlines))
(_(_(Fay$$cons)(s))
(_(_(Language$Fay$Stdlib$map)
(function($p1) {
var $gen_1 = $p1;
return _(_(Language$Fay$Stdlib$$43$$43$)
(Fay$$list(“ “)))
($gen_1);
}))
(_(_(Language$Fay$Stdlib$$36$)
(Language$Fay$Stdlib$concat))
(_(_(Language$Fay$Stdlib$map)
(_(_(Language$Fay$Stdlib$$46$)
(Language$Fay$Stdlib$lines))
(Main$showT)))
(cs)))));

On a technical note, full Haskell compilers use several techniques to make pattern matching much more efficient than cascaded if-statements. For example, a set of patterns can be compiled into a series of multi-way jump tables, much like case statements on a small set of N fixed values choosing a branch in one single step rather than needing N tests. Such techniques could be added to Fay too, if there was sufficient practical justification. Tagless approaches might also help, where the representation of the constructor becomes the code that performs pattern decisions directly.

A Bigger Example

The Fay repository contains several larger examples. Let’s look at the interesting details of a simple calculator that uses several other jQuery features. It’s using a monadic style to communicate with jQuery. The code first builds the HTML for the calculator using a table for layout, a process that is triggered on the document-ready event. The table is appended to the document body, and the first row is set to contain the display as a simple text box.

The remaining buttons are generated from a description in the buttons list, defined elsewhere. Each button has a label and an associated action. A button element is created for each, its text set to the label, and the click event bound to the action. The rest of the code creates these buttons inside rows of cells, using a nested loop.

ready $ do
body <- select “body”
table <- select “<table></table>” & appendTo body
dtr <- select “<tr></tr>” & appendTo table
display <- select “<input type=’text’ value=’’>”
select “<td colspan=’4'></td>” & appendTo dtr & append display
forM_ buttons $ \row -> do
tr <- select “<tr></tr>” & appendTo table
forM_ row $ \(text,action) -> do
td <- select “<td></td>” & appendTo tr
select “<input type=’button’ value=’’ style=’width:32px’>”
& setVal text
& appendTo td
& onClick (do action; return False)

The button information is quite simple — basically pairing a label with the various actions. buttons is a list of lists, hence easily mapped to rows of cells. enter is just a shorthand for (show n, add_number n).

buttons =
[[enter 7, enter 8, enter 9, (“/”,operator (/))]
,[enter 4, enter 5, enter 6, (“*”,operator (*))]
,[enter 1, enter 2, enter 3, (“-”,operator (-))]
,[(“C”,clear), enter 0,
(“=”,calculate), (“+”,operator (+))]]

Now, a calculator requires some kind of state. The display is one kind of state, holding the current value. But we’ll also need some way of holding the last number and current operation. Fay adopts the technique used for simple mutable values in Haskell’s IO system, whereby a reference may be created, read, and updated under monadic control. The interface is shown below. Behind the scenes the Ref is just a name for a JavaScript object. Notice that the three operations are all monadic, that is, can only be used in a monadic context. Quite right, too — we do need to get reads and writes in the right order, and the Fay monad provides for this.

data Ref a
instance Show (Ref a)
instance Foreign a => Foreign (Ref a)
newRef :: Foreign a => a ->
Fay (Ref a)
writeRef :: Foreign a => Ref a -> a -> Fay ()
readRef :: Foreign a > Ref a -> Fay a

The simplest operation is clearing the calculator state: set the display to show 0, forget any pending calculation, and then refresh.

clear = do
setVal “0” display
writeRef operation Nothing
calculate

Calculation, when the = button is clicked, first checks whether there’s a pending operation. Notice use of a Maybe value to distinguish between “nothing there” and “something useful, which is X” cases. If there’s nothing, do nothing yet. Otherwise, grab the operation and the number currently in the display and perform the pending operation. In good Haskell style, rather than recording the previous number and the previous operator as two pieces of data, we can store just one — the function that the two items actually represent. There’s no problem storing this as a JavaScript value either! For example, in 10 + 20, the stored operation will be (\x -> 10 + x), waiting for the 20 to be fed in. The resulting value is written to the display.

calculate = do
op <- readRef operation
case op of
Nothing -> return ()
Just maths -> do
num <- getInput
setVal (show (maths num)) display
return ()
writeRef operation Nothing

Notice the final line is only indented one step. This means that it (as written) must be done after whatever was executed in the case expression, that is, regardless of what happened before. We could safely move it into the Just branch because the Nothing branch ensures that the result left in that mutable variable is indeed already Nothing.

There’s one possible point of confusion here, on what the return () actions actually do. Beware — it’s not a return from the whole function, as you would expect in imperative languages. Some people prefer to rename return as the less loaded term wrap, and here is makes sense because we want the boring value () to be the result of the case statement, but wrapped up to fit in the monadic context.

And that’s as complex as the code gets! Some initial setup, a few monadic actions to perform the functionality of the calculator (using three state values), binding the actions to appropriate buttons. Go find a similar example in CoffeeScript, and compare!

How Fay Works

Here are some brief pointers to how Fay is implemented, if you fancy browsing a larger Haskell example.

Inside the repository, the src/ directory holds the main code. It’s divided into several namespaced modules, some of which are nested. The important one is Language.Fay — this contains the library definition and the compiler.

First, look at Types.hs, around line 219. These types specify the expected syntactic structure for JavaScript constructs, first for statements then for expressions, followed by various ways of representing names and the JavaScript type system. Print.hs contains code for converting those JavaScript syntax trees to a flat string.

The complex part of Fay is the compiler. Basically, it converts some Haskell syntax into some JavaScript syntax, mostly by transforming one tree into another. That’s basically what all compilers do! The fun starts around Line 326, with the code for translating data type declarations. You can see the conversion of expressions around Line 514.

Notice the type of the various compilation functions, for example, compilePat :: JsExp-> Pat -> [JsStmt] -> Compile [JsStmt]. The arguments are syntactic data (the JavaScript expression being scrutinized, the pattern in Haskell syntax, and the body of the clause as a list of JavaScript statements), and the core result is a list of JavaScript statements — which will be the body wrapped in the various tests required for matching the pattern. There’s also the Compile wrapped around the result list: this is a monad that is used to hide away various bits of compiler plumbing, in this case mutable state, error handling, and access to IO. You hardly notice this in the code, of course — that’s one of the reasons why we use monads.

Where does Fay get the Haskell syntax from? Conveniently, there’s an official Haskell parser with related types in a standard library. Fay thus works by parsing a set of modules using this parser, and then selectively translating parts of the resulting tree to JavaScript. It also runs GHC on your code to perform certain type checking operations. It seems there are plans to use other components of GHC as well.

If you’re interested in compiling other languages and using Haskell for it, you might enjoy looking at my MiniJava compiler. This transforms MiniJava (a basic subset) into C, and was written as a demonstration in an undergrad course on compilers. A key feature is that it saves full snapshots of key data structures at each main stage of the compiler pipeline.

Fay Does Async Too

A certain publisher has just released Asynchronous JavaScript by Trevor Burnham. The book covers the key ideas behind programming effectively with JavaScript in an asynchronous context, and it looks like a useful addition to available material.

However, something is missing: monads.

In a nutshell, the patterns of asynchronous programming used in JavaScript work via functions called “continuations” as a way of processing some result when and as it arrives. It’s a powerful concept, but can be tricky to use — the danger is that your code ends up like a mass of spaghetti. Some people like to describe lambda (that is, anonymous functions) as “the ultimate go-to” for such reasons. How to manage the complexity? It would be great if we could make the asynchronous program look like it was synchronous. One answer is to use a monadic framework — the structuring ideas of monads will help us hide the continuations plumbing away (for it is plumbing and not the real program!)

Burnham includes an example of finding the plain files in a directory and building the concatenation of the contents. We can write this example inside Fay too. (The full Fay example is here, and for brevity I just show the important details here.) The main block is this:

main = do all_entries <- readDir “.”
all_files <- filterM isFile
all_entries all_text <- sequence $ map readFile all_files
lift $ putStrLn $ concat all_text

Can you tell whether this is executed synchronously or asynchronously? Should it make a difference? And if we changed from one to the other, should the program have to change? Hopefully your answer is “no” on each. This is a big part of the power of good abstractions!

I’ll assume that the code above speaks for itself, and instead will sketch how we link to the underlying operations. Firstly, readdir is provided by the fs library and takes a directory name and a callback or continuation which says how to process the result — a list of strings — when the directory scan is ready. Now, the execution of JS calls needs to be done in sequence, so we’re going to work inside the Fay monad at low level, similar to what we did for jQuery. Hence, we can give readDir_ the following type and definition via the FFI.

readDir_ :: Foreign b => String -> ([String] -> Fay b) -> Fay b readDir_ = ffi “require(‘fs’).readdir(%1,function(_,s){ %2(s); })”

The pattern (a -> b) -> b is the hallmark of continuations. We can string together several continuation operations by manually building the functions, but we can do better — especially when the control flow gets a bit more complex. The key idea is to think of these continuations as computations that eventually produce some value, that is, to think of them in monad terms. Conceptually, we want the “do something when the result is ready” to be transformed to “do something and pass the result on”.

The magic step is to work out a definition of (>>=) (monadic then) that allows two continuations to be piped together. It might take a bit of hard staring (see the gist) but effectively you’re splicing the first continuation (yielding some a value) with something that expects such a value and should yield a b value, and then together they produce a new continuation which knows what to do with the b value. I’ll let you have the simpler half of the monad definition now: return a = \f -> f a.

Good news: the relevant transformation (from continuation to monad) is already part of the Fay distribution and likely to be moved to a standard library soon, so you don’t need to repeat or adapt the ideas. All you need to turn your continuation-using call into something monadic is just to wrap it in a constructor. The monad behavior is tied to this constructor and the resulting type, for example, with its definition of (>>=) unpacking the continuations and gluing them together. (Note my use of trailing underscore to mark the continuation code.)

readDir :: String -> ContinuationM [String] 
readDir s = ContT $ readDir_ s

Having wrapped up our basic continuation calls, we can then start programming with operations like readDir using standard monad techniques, like do-notation and sequence.

I’ve skipped over the details of error handling, but that can be slotted into the framework too. For example, our FFI code could be extended to take a callback that expects a nullable error value plus the return value — though for sanity we would map it to a single Either value! We can then extend the definition of (>>=) to do certain kinds of error handling, for example, an exception raise or storing handlers for certain kinds of error or… whatever you want. It’s just plumbing, and we can use monads to hide it away when we don’t need to see it.

There are already quite a few blog posts which discuss the use of monads in JavaScript, with and without asynchronous calls, and it’s worth a browse. I’ve also included some more explanation on the gist. We can of course rewrite the JavaScript example from the book to use monads, but I’ll leave that as an exercise for you. (But I will say, it’s a lot easier to do it via Fay, not least because of the type checker!)

Trampolines Not Required

One other detail that might tempt you to use Fay: it’s harder to run out of stack space.

Some people complain about JavaScript’s lack of support for tail recursion, that is, wanting the optimization where certain kinds of recursion can be converted to a loop and thus avoid using tons of stack. Space is short, but be aware that Fay — as a language with a lazy implementation — doesn’t suffer the same problems. First, direct recursion isn’t a problem because all function calls return a thunk (suspended computation). Recursive calls, if present, will only get executed when the thunk is forced, and this forcing only occurs after the first call has returned. (I think this has some similarity to how trampolining works, though I could be wrong.) You can still get into an infinite loop, of course, but it won’t blow the stack.

Second, some functions can generate their results lazily, like the code for fizz buzz a few months back, and you only execute as much as you need. Hence, some kinds of potentially infinite recursion are ok — and encouraged! Finally, the Fay developers are looking at adding tail call optimizations that provide more performance by bypassing the function call mechanism in favor of a loop, hence could lead to better performance. So: you can be recursive again!

Final Thoughts

So, Fay is a useful tool for compiling medium-complexity Haskell programs into JavaScript. It’s still a work in progress, but is stable enough, with sufficient features, for interesting experiments — such as different ways to use more powerful abstractions and types on top of common libraries, and looking to write more functionally complex code with fewer headaches. Also worth exploring is the interaction of Fay front-ends with server components written in Haskell. (We’ll look at the server side next time.) I’m really looking forward to using these toys more! Hope a few of you are tempted too.

About the Author

Dr. Paul Callaghan rides a big, fast motorbike, and suggests that this informs his programming style too. Some people say bike riding is too risky, but you can manage the risk in various ways. Defensive riding means looking ahead, anticipating problems, and actively minimizing risk by avoiding trouble. One can program like this too.

Paul also flies big traction kites and can often be seen being dragged around inelegantly on the beaches of North-east England, much to the amusement of his kids. He blogs at free-variable.org.

Cover from PragPub Magazine, December 2012
Cover from PragPub Magazine, December 2012

--

--

PragPub
The Pragmatic Programmers

The Pragmatic Programmers bring you archives from PragPub, a magazine on web and mobile development (by editor Michael Swaine, of Dr. Dobb’s Journal fame).