Skip to content

Instantly share code, notes, and snippets.

@joneshf
Forked from paf31/24days.md
Last active March 3, 2019 09:28
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save joneshf/30bac9a426d18280cdca to your computer and use it in GitHub Desktop.
Save joneshf/30bac9a426d18280cdca to your computer and use it in GitHub Desktop.

24 Days of PureScript

day 1 introduction

day 2 purescript-foreign

day 3 purescript-easy-ffi and purescript-oo-ffi

day 4 purescript-canvas and purescript-free-canvas

day 5 purescript-rx

day 6 purescript-lens

day 7 pulp

day 8 purescript-machines

day 9 purescript-test-unit

day 10 purescript-webaudio

day 11 purescript-express

day 12 purescript-react

day 13 purescript-smolder

day 14 yesod-purescript

day 15 purescript-hatter

day 16 Editor integration

day 17 purescript-strongcheck

day 18 purescript-d3

day 19 purescript-signal

Day 1 - Introduction

Inspired by the excellent 24 Days of Hackage by Oliver Charles, I have decided to write a series of blog posts to highlight some of the wonderful work being done in the PureScript community.

Each day, I will choose one of the PureScript libraries written by the community, give a brief introduction, and (hopefully) provide practical code examples.

PureScript is still a young language, having recently celebrated the one year anniversary of its initial GitHub commit, but the community has grown very quickly. Hopefully, this series of blog posts will inspire you to try to write a library of your own - and we have no shortage of ideas for possible projects.

If you are interested in learning PureScript, please follow along with the posts, which will be added here each day, and check out the book and the new website.

Also, guest posts are more than welcome, so please get in touch in the comments!

Thanks!

-Phil Freeman.

Day 2 - purescript-foreign

To kick things off, I'm going to discuss the purescript-foreign library, one of the earliest PureScript community-driven libraries, written by Gary Burgess and other contributors.

purescript-foreign provides the means to interoperate with untrusted JavaScript code, which includes both parsing JSON data, and validating the types of untrusted data at runtime.

In what situations is this useful? Well, suppose we want to load application data from a web service which returns JSON data. Assuming the data is well-formed relative to some schema, we can simply give the action the appropriate (effectful) type, and use the data as it is returned, being sure to take things like exceptions and the HTTP status of the response into account. However, in reality, the returned data might be incorrectly formed according to our schema, or just plain invalid JSON. In this case, we have to resort to checking the data at runtime. purescript-foreign provides a way to perform that task in a structured manner.

A good example of this approach is the Pursuit application, which is tool for looking up functions by name in the PureScript standard library. Pursuit loads its data from a JSON file stored on the server, and uses purescript-foreign to turn that untrusted data into its internal, typed representation.

Pursuit's application data consists of an array of JSON objects, each with three String fields, name, module and detail:

[ 
  {
    "name": "flip",
    "module": "Prelude",
    "detail": "flip :: forall a b c. (a -> b -> c) -> b -> a -> c"
  },
  ...
]

The application defines a type Entry which respresents these objects:

data Entry = Entry String String String

To read these values from a JSON document using purescript-foreign, the application provides an instance of the IsForeign type class:

instance isForeignEntry :: IsForeign Entry where
  read entry = Entry <$> readProp "module" entry
                     <*> readProp "name"   entry
                     <*> readProp "detail" entry

Here, we use the Applicative combinators to build larger parsers from smaller parsers, just as we would do in Haskell libraries like Parsec or Aeson.

The IsForeign class provides a very simple interface:

type F = Either ForeignError

class IsForeign a where
  read :: Foreign -> F a

The polymorphic read function can be used to turn an untrusted value (represented by the Foreign type) into either a checked value with some known type, or an error.

With this instance, the application can load its data from its JSON configuration file:

readData :: String -> T.Trie Entry
readData json = case readJSON json of
  Left err -> error $ show err
  Right arr -> ...

The Foreign data type also solves another related problem: how do we give appropriate types to foreign functions which might return untrusted or unstructured data? The answer is that we can always use the Foreign type in a foreign function type in any place where we are uncertain of the structure of the data. This effectively forces the user to use the purescript-foreign API to turn the untrusted data into usable, checked data.

A simple example is when we want to interact with a JavaScript function which might return null or undefined. The Data.Foreign.NullOrUndefined module provides a newtype whose IsForeign instance handles these cases using the Maybe type constructor:

newtype NullOrUndefined a = NullOrUndefined (Maybe a)

runNullOrUndefined :: forall a. NullOrUndefined a -> Maybe a

Now, we can define our FFI in two steps. At the lower level, we can use Foreign to represent the untrusted data:

foreign import jsFunc :: String -> Foreign

In the module exports, however, we present a sanitised version of the function, which uses NullOrUndefined to represent the missing data:

jsFunc' :: String -> F (Maybe String)
jsFunc' s = runNullOrUndefined <$> read (jsFunc s)

For more information on the purescript-foreign library, check out the FFI chapter in the book, which uses the library to read application data from the browser's local storage.

Day 3 - purescript-easy-ffi and purescript-oo-ffi

Today, I'm going to look at two more libraries which help with the tricky problem of integrating with the untyped world of JavaScript. The first is purescript-easy-ffi, by @pelotom, and the second is purescript-oo-ffi, by @fresheyeball.

purescript-easy-ffi

PureScript's FFI is quite easy to explain, but not quite to easy to use in many cases. For example, suppose you want to wrap a JavaScript function of several arguments. Let's take the extended JSON.stringify function as a simple example. You have two options:

  1. Write a curried version of the function:

    foreign import stringify
      "function stringify(n) {\
      \  return function (x) {\
      \    return JSON.stringify(x, null, n);\
      \  };\
      \}" :: forall a. Number -> a -> String
  2. Use Data.Function to write a function of multiple arguments, and then wrap that function to provide a curried alternative:

    import Data.Function
    
    foreign import stringify 
      "function stringify(n, x) {\
      \  return JSON.stringify(x, null, n);\
      \}" :: forall a. Fn2 Number a String
      
    stringify' :: forall a. Number -> a -> String
    stringify' n x = runFn2 stringify n x

Both approaches involve quite a lot of boilerplate, either in JavaScript or in PureScript code. In many cases, especially for prototyping purposes, it would be preferable to define something quickly with minimal fuss. This is the problem which is solved by the purescript-easy-ffi library.

By importing the EasyFFI module, we can simply specify an array of function argument names, and the function body:

stringify :: forall a. Number -> a -> String
stringify = unsafeForeignFunction ["n", "x"] "JSON.stringify(x, null, n)"

Much better! The advantages quickly become clear when writing bindings to large JavaScript libraries. For applications where performance is important, one might like to revert to the Data.Function approach for production code, but for getting an FFI project off the ground, this approach often gives an excellent time-to-first-release.

purescript-easy-ffi also provides a way to write methods in the Eff monad.

Suppose we wanted to modify the original example to properly take account of exceptions. In vanilla PureScript, this would involve two extra lines:

foreign import stringify
  "function stringify(n) {\
  \  return function (x) {\
  \    return function () {\
  \      return JSON.stringify(x, null, n);\
  \    };\
  \  };\
  \}" :: forall a eff. Number -> a -> Eff (err :: Exception | eff) String

With purescript-easy-ffi, only three extra characters are required:

stringify :: forall a eff. Number -> a -> Eff (err :: Exception | eff) String
stringify = unsafeForeignFunction ["n", "x", ""] "JSON.stringify(x, null, n)"

The inner function is represented by the empty string in the argument list.

purescript-oo-ffi

The purescript-oo-ffi library solves a similar problem which you might encounter when writing bindings to object-oriented JavaScript libraries. It provides FFI helpers which can be used to construct the building blocks of an object-oriented FFI binding: object instantiations, method calls, and property getters and setters.

As an example, consider the following JavaScript "class" definition:

function Greeting() {
  var self = this;
  
  self.holiday = "Christmas";
  self.beMerry = true;
  
  self.greet = function() {
    var prefix = self.beMerry ? "Merry " : "Happy ";
    console.log(prefix + self.holiday + "!");
  };
}

We might call use this class as follows:

new Greeting().greet();

Or if we are feeling less merry:

var greeting = new Greeting();
greeting.beMerry = false;
greeting.greet();

Our class is also holiday-seasons-polymorphic!

var greeting = new Greeting();
greeting.beMerry = false;
greeting.holiday = "Easter";
greeting.greet();

Now suppose we wanted to write a binding to this class in PureScript. This task would usually involve a lot of boilerplate involving the Eff monad. However, the purescript-oo-ffi library makes our job much simpler.

We can start by defining our own effect type, and a foreign type for the class itself:

foreign import data Greet :: !

foreign import data Greeting :: *

To wrap the constructor, we can use the instantiate0 function, specifying the class name:

newGreeting :: forall e. Eff (greet :: Greet | e) Greeting
newGreeting = instantiate0 "Greeting"

To wrap the greet method, we can use the method0Eff function:

greet :: forall e. Greeting -> Eff (greet :: Greet | e) Unit
greet = method0Eff "greet"

This is enough to recreate our first example:

example1 = do
  g <- newGreeting
  greet g

We can also provide wrappers for our two object properties, using the getter and setter functions:

getMerry :: Greeting -> Eff (greet :: Greet | e) Boolean
getMerry = getter "beMerry"

setMerry :: Greeting -> Boolean -> Eff (greet :: Greet | e) Unit
setMerry = setter "beMerry"

getHoliday :: Greeting -> Eff (greet :: Greet | e) String
getHoliday = getter "holiday"

setHoliday :: Greeting -> String -> Eff (greet :: Greet | e) Unit
setHoliday = setter "holiday"

And now we can recreate the other two examples:

example2 = do
  g <- newGreeting
  setMerry g false
  greet g
  
example3 = do
  g <- newGreeting
  setMerry g false
  setHoliday g "Easter"
  greet g

Conclusion

Hopefully, this post has shown that writing PureScript FFI bindings does not have to be a chore. These two packages make it possible to quickly write bindings to almost any existing Javascript library.

Try it out - the PureScript community has no end of suggestions for existing JavaScript libraries which could be wrapped and possibly extended in PureScript code. Join the conversation on the #purescript IRC, and we can provide plenty of guidance to get started.

Day 4 - purescript-canvas and purescript-free-canvas

Today, I'm going to show how to create an online Christmas card using the HTML5 Canvas API from PureScript. You can see the finished result here.

I started working on the purescript-canvas library not long after I started work on the compiler itself, and it has since seen contributions from a number of community members. The purescript-free-canvas library provides a free monad interface to the Canvas API, which hides the 2D graphics context object from the user.

At this point, both libraries provide quite a complete representation of the HTML5 API, but there are still some features missing. If you would like to help to flesh out the remaining calls, then check out the issues board.

To follow along, start a new project using grunt-init, and install the purescript-math and purescript-free-canvas libraries using Bower.

We can start by getting a reference to the canvas object and its graphics context:

module Main where

import Control.Monad.Eff

import Graphics.Canvas (getCanvasElementById, getContext2D)
import Graphics.Canvas.Free

main = do
  canvas <- getCanvasElementById "canvas"
  context <- getContext2D canvas

  runGraphics context $ do
    -- Canvas API calls will go here

The first step will be to fill the canvas background with a solid color:

    setFillStyle "#00FFFF"
    rect { x: 0, y: 0, w: 400, h: 600 }
    fill

Inside the call to runGraphics, our code runs in the Graphics (free) monad, so we don't need to worry about passing around the context object. We only do that once in the call to runGraphics itself.

Next, let's draw the tree. Start by setting the fill color to green, and adding a shadow:

    setFillStyle "#008000"
    setShadowColor "#00FF00"
    setShadowBlur 5

Note how similar this code looks to regular Canvas code written in JavaScript. However, we get all of the benefits of writing code in PureScript, including type checking!

To draw the tree, we will make use of a combinator called at, which translates a set of drawing commands across some vector:

at x y gfx = do
  save
  translate x y
  gfx
  restore

Note how at wraps our action in calls to save and restore, which means that the state of the graphics context is preserved after the call to at. This is a good example of the benefits of higher-order functions.

Here is the code for the body of the tree:

    at 200 175 do
      beginPath
      triangle
      at 0 50 triangle
      at 0 100 triangle
      closePath
      rect { x: (-40), y: 200, w: 80, h: 50 }
      fill

Three tree consists of a path made up of three triangles and a rectangle. The triangle action is defined as follows at the top-level:

triangle = do
  moveTo 0 (-100)
  lineTo 75 100
  lineTo (-75) 100

Next, let's add some baubles to the tree:

      setFillStyle "#FFFF00"
      at (-10) (-10) $ bauble 10
      at (-20)   50  $ bauble 10
      at    0   100  $ bauble 10
      at (-20)  140  $ bauble 10
      at   20   190  $ bauble 7
      at   30    50  $ bauble 7
      at (-50)   75  $ bauble 7
      at (-40)  180  $ bauble 7
      at   50   125  $ bauble 7
      at   40   175  $ bauble 7

Again, the bauble function is defined as a reusable helper:

bauble size = do
  beginPath
  arc { x: 0, y: 0, r: size, start: 0, end: Math.pi * 2 }
  fill

You can try rewriting this to specify the bauble positions in an array, using traverse to loop over the array.

Finally, to add the text at the top and bottom, we can use the fillText action, as follows:

    setFillStyle "#FF0000"
    setFont "48px Sans-Serif"
    fillText "Merry Christmas" 25 50
    fillText "From PureScript!" 20 480

And that's it! A PureScript Christmas card in under 70 lines of code. Try making your own, and tell your relatives that you made your Christmas cards with free monads!

Day 5 - purescript-rx

Today, I'm going to look at the purescript-rx library, by @anttih, which provides a PureScript binding to the RxJS library.

For me, this library is a wonderful example of the self-documenting nature of a well-designed functional library. While I have used Reactive Extensions quite a lot in C# in the past, I have never used RxJS itself. Nor have I used the purescript-rx library before this morning, but I was able to get up and running in under 20 minutes by applying my knowledge of well-defined abstractions like Monad and Applicative.

Using bower install git@github.com:anttih/purescript-rx.git will conveniently install the rxjs, jquery and rxjs-jquery libraries under bower_components directory, which we can then include in our page as follows:

<script type="text/javascript" src="../bower_components/jquery/dist/jquery.js"></script> 
<script type="text/javascript" src="../bower_components/rxjs/dist/rx.all.js"></script> 
<script type="text/javascript" src="../bower_components/rxjs-jquery/rx.jquery.js"></script> 

My example will consist of two colored squares, and I will attempt to detect various gestures by using RxJS to combine event streams. Here is the HTML:

<div style="width: 100px; height: 100px; background-color: green; float: left" id="green"></div>
<div style="width: 100px; height: 100px; background-color: red; float: left" id="red"></div>
<pre style="clear: left;" id="output"></pre>

The imports list is straightforward:

module Main where

import Control.Monad.Eff

import Rx.JQuery
import Rx.Observable

import Control.Monad.JQuery

The first task is to get a reference to the three DOM elements, using the purescript-jquery library:

main = do
  red <- select "#red"
  green <- select "#green"
  output <- select "#output"

Next, let's use the Rx.JQuery module to turn the mouseover, mousemove and mousedown event streams into Observable streams:

  redOver <- "mouseover" `onAsObservable` red
  redMove <- "mousemove" `onAsObservable` red
  redOut  <- "mouseout"  `onAsObservable` red
  
  greenOver <- "mouseover" `onAsObservable` green
  greenMove <- "mousemove" `onAsObservable` green
  greenOut  <- "mouseout"  `onAsObservable` green

We can subscribe to these event streams directly, by using the subscribe action:

  redOver `subscribe` \_ -> void $ "red mouseover" `setText` output
  redMove `subscribe` \_ -> void $ "red mousemove" `setText` output
  redOut  `subscribe` \_ -> void $ "red mouseout"  `setText` output

  greenOver `subscribe` \_ -> void $ "green mouseover" `setText` output
  greenMove `subscribe` \_ -> void $ "green mousemove" `setText` output
  greenOut  `subscribe` \_ -> void $ "green mouseout"  `setText` output

However, these examples are not particularly interesting.

The documentation for purescript-rx helpfully notes that Observable is an instance of several common type classes: Semigroup, Applicative, Monad and their respective superclasses. We can use these instances to build more interesting gesture recognizers.

Here's a simple example. Suppose we wanted to detect when the user moved the mouse from the left to the right, from the red square and onto the green square. Or the other way, from the green square onto the red square.

Ordinarily, this would involve a mess of callback handlers, but with RxJS, we can use the flatMap function to combine dependent event streams in this way. In purescript-rx, this function defines the >>= function of the Observable type constructor's Monad instance, so we can just define our gestures using regular do notation!

  let gestureLeft = do redOver
                       redOut
                       greenOver
                       greenOut
                       return "Swipe left"
  let gestureRight = do greenOver
                        greenOut
                        redOver
                        redOut
                        return "Swipe right"

Here, we could even use <- to extract data from the various events, but let's keep things simple for now.

We can subscribe to these combined events, and display the recognized gesture on the screen:

  (gestureLeft `merge` gestureRight) `subscribe` \msg ->
    void $ msg `setText` output

The finished demo can be seen here.

This is just one example of the ways in which purescript-rx and RxJS can be used to combine event streams. I haven't covered the Applicative or Semigroup instances here, which are interesting in their own right. Fortunately, the library is very simple to install, so fork the demo repository and give it a try for yourself.

Later in the month, I will show another approach to combining event streams in PureScript, so stay tuned!

Day 6 - purescript-lens

Today I will give a very basic introduction to the purescript-lens library, written by @joneshf.

purescript-lens is a partial port of Edward Kmett's lens library from Haskell to PureScript.

lens is an impressive library which solves a number of problems in vastly more generality than I am about to present, but hopefully the following should whet your appetite.

Let's demonstrate the most simple functionality of the purescript-lens library - using lenses to update a part of a nested data structure. I should add that I have not used lens or purescript-lens before today, and my experience so far is that the types are somewhat complicated, but that following the examples is a good way to get started.

Suppose we have the following data structures, representing an address book (I think these Christmas analogies are getting more convoluted ...):

data Person = Person { name :: String
                     , addr :: Address
                     , type :: PersonType
                     }

data Address = Address { street :: String
                       , city :: String
                       }

data PersonType = Naughty | Nice

Here, a Person contains a name, an Address and a PersonType. We can create an example Person:

examplePerson :: Person
examplePerson = 
  Person { name: "John Smith"
         , addr: Address { street: "123 Fake St."
                         , city: "Los Angeles"
                         }
         , type: Naughty      
         }

Now suppose we want to update the city property of the addr property. This requires nested record updates, and the problem gets worse if our data structures use more levels of nesting.

purescript-lens provides one solution. For each of our properties, we can define a Lens, using the lens function to specify getters and setters:

name :: LensP Person String
name = lens (\(Person p) -> p.name) (\(Person p) name -> Person (p { name = name }))

address :: LensP Person Address
address = lens (\(Person p) -> p.addr) (\(Person p) addr -> Person (p { addr = addr }))

_type :: LensP Person PersonType
_type = lens (\(Person p) -> p.type) (\(Person p) ty -> Person (p { type = ty }))

street :: LensP Address String
street = lens (\(Address a) -> a.street) (\(Address a) street -> Address (a { street = street }))

city :: LensP Address String
city = lens (\(Address a) -> a.city) (\(Address a) city -> Address (a { city = city }))

In psci, we can update various parts of the structure using the .~ operator:

> :i Optic.Core

> examplePerson
(Person "John Smith" (Address "123 Fake St." "Los Angeles") Naughty)

> examplePerson # _type.~ Nice
(Person "John Smith" (Address "123 Fake St." "Los Angeles") Nice)

> examplePerson # address..city.~ "San Diego"
(Person "John Smith" (Address "123 Fake St." "San Diego") Naughty)

Note that purescript-lens provides the .. operator as a synonym for function composition (<<<), which makes the code easier to read.

We can also use the ^. operator to read nested properties from our structure:

> examplePerson ^. _type
Naughty

> examplePerson ^. address..street
"123 Fake St."

The purescript-lens library (and the associated refractor and optic libraries) provide a great deal more functionality than I have presented here, but I spent most of my time today getting up to speed with the basics. I, for one, will certainly be spending more time getting familiar with this excellent library, and I encorage you to try it for yourself.

Day 7 - pulp

Today I will show how to use Bodil Stokke's pulp tool to get up and running quickly with PureScript.

pulp is a command line tool which automates a number of common PureScript tasks, such as creating a new project, pulling Bower dependencies, and generating Javascript and documentation. It assumes a number of simple conventions, which enable a very simple command line interface.

Get started by initializing a new pulp project on the command line:

$ pulp init
* Generating project skeleton in purescript/pulp-test

At this point, the current directory will contain a src directory, for source files, a test directory for tests, and a bower.json file, where you can specify your PureScript library dependencies.

To see the list of commands available, type pulp with no command at the shell:

$ pulp
No command specified.

Available commands:

  init  - Generate an example PureScript project
  install   - Download and install project dependencies
  build     - Build the project
  test  - Run project tests
  browserify    - Produce a deployable bundle using Browserify
  run   - Compile and run the project
  docgen    - Generate project documentation
  psci  - Launch a PureScript REPL configured for the project

Try building the project in its default state:

$ pulp build
* Building project in purescript/pulp-test
* Build successful.

The source modules will be compiled and placed in the output directory. We also have the option of running the tool in watch mode, by using pulp build -w. This will cause the project to be rebuilt when the sources change. In fact, all of the pulp commands can be run in watch mode by using the -w flag.

Now try running the compiled sources, by using pulp run:

$ pulp run
* Building project in purescript/pulp-test
* Build successful.
Hello sailor!

We can also compile and run the tests using pulp test:

$ pulp test
* Building project in purescript/pulp-test
* Build successful. Running tests...
You should add some tests.
* Tests OK.

Other options include the browserify command, which will generate JavaScript for the browser, and the pulp command which will load your sources into psci.

Let's add some code to src/Main.purs, and use pulp psci to test our library:

module Main where

import Debug.Trace

greet :: Boolean -> String -> String
greet beMerry holiday
  | beMerry   = "Merry " <> holiday <> "!"
  | otherwise = "Happy " <> holiday <> "."

main = do
  trace $ greet true "Christmas"

Using pulp run should generate a season-appropriate greeting on the command line, or we can use pulp psci to test our function in isolation in psci:

$ pulp psci
 ____                 ____            _       _   
|  _ \ _   _ _ __ ___/ ___|  ___ _ __(_)_ __ | |_ 
| |_) | | | | '__/ _ \___ \ / __| '__| | '_ \| __|
|  __/| |_| | | |  __/___) | (__| |  | | |_) | |_ 
|_|    \__,_|_|  \___|____/ \___|_|  |_| .__/ \__|
                                       |_|        

:? shows help

Expressions are terminated using Ctrl+D
> Main.greet false "Easter"

"Happy Easter."

Hopefully, this has shown that pulp is a great tool which can help you to get up and running with PureScript very quickly. In a future post, I will show we might get started with pulp test, by using one of PureScript's testing libraries to modify test/Main.purs.

Day 8 - purescript-machines

Today, I'm going to look at the purescript-machines library by @jdegoes, which can be used to create finite state machines in PureScript.

The purecript-machines library provides an implementation of Mealy machines, which we can use to separate our code into components which are responsible for either producing or consuming data (or both). Our machines can act over any Monad, which as we will see, is very helpful when we need to deal with asynchronous data sources in a non-blocking way.

Here is a very simple example to get started:

module Main where

import Data.Machine.Mealy
import Control.Monad.Eff
import Debug.Trace

main = runMealy machine
  where
  machine = take 100 (loop (return "Merry Christmas!")) >>> sink trace

Here, we can factor our code into a source and a sink:

main = runMealy machine
  where
  machine = greetings >>> printer
  greetings = take 100 (loop (return "Merry Christmas!"))
  printer = sink trace

Note that the usual function composition operator >>> is being used here in its more polymorphic form, taken from the Category type class. The purescript-machines library provides a rich array of standard type class implementations for its MealyT type constructor, which can be used to build complex state machines.

Now suppose that we want to ask for the user's name before offering them a more personalized greeting. We can write a function which uses the continuation monad to represent a call to the readline module, to read a string from standard input. I won't reproduce the code here, but the function will have the following type signature:

type AppC = ContT Unit App

questionC :: String -> AppC String

With that, we can modify our greetings and printer machines accordingly:

greetings :: Source AppC String
greetings = take 5 $ loop $ source $ questionC "What is your name? "

printer :: Sink AppC String
printer = do
  name <- id
  wrapEffect $ lift $ trace $ "Merry Christmas, " <> name

Note that the printer machine uses a trick here to get hold of the upstream value: the polymorphic type of id gets instantiated to the type MealyT f a a, which means that the result type of our computation is actually the type of the source. We can then use wrapEffect to wrap the effectful code which prints the greeting to the screen.

In our main function, we simply need to call runContT in order to run the final asynchronous computation:

main = flip runContT return $
         runMealy $
           greetings >>> printer

We can run the compiled code using node, and see how the two machines interact:

What is your name? Phil
Merry Christmas, Phil
What is your name? John
Merry Christmas, John
What is your name? Mary
Merry Christmas, Mary
What is your name? ...

This has really only covered the basics of the purescript-machines library. The Data.Machine.Mealy module provides a lot more functionality, which is well worth exploring.

Day 9 - purescript-test-unit

Two days ago, I promised to show how we might utilize the tests folder in Bodil Stokke's pulp tool. There are actually multiple options, and I hope to cover more of them in future posts, but today I will take a look at another library from @bodil called purescript-test-unit.

purescript-test-unit aims to bring conventional unit testing to PureScript, with support for asynchronous tests.

Let's create a new project using pulp, add some sample code, and write some tests.

$ pulp init

Santa's software development division have created a web service to respond to inventory requests for Christmas gifts, and helpfully provided a mock service which simulates server latency. Here is their code, which we can place into src/ServiceMock.purs:

module ServiceMock where

import Control.Monad.Eff

foreign import data HTTP :: !

foreign import checkInventory 
  "function checkInventory(item) {\
  \  return function(k) {\
  \    return function() {\
  \      setTimeout(function() {\
  \        switch (item) {\
  \          case 'Nutcracker':\
  \          case 'Spinning Top':\
  \            k(true)();\
  \            break;\
  \          default:\
  \            k(false)();\
  \        }\
  \      }, 500);\
  \    };\
  \  }\
  \}" :: forall eff. String -> 
                     (Boolean -> Eff (http :: HTTP | eff) Unit) ->
                     Eff (http :: HTTP | eff) Unit

Now, we can test this mock service implementation (and any code which depends on it), by placing our tests in test/Main.purs:

module Test.Main where

import Test.Unit
import ServiceMock

main = runTest do
  test "Service Tests" do
    assertFn "Nutcracker is missing from inventory" $
      checkInventory "Nutcracker"
    assertFn "Spinning Top is missing from inventory" $
      checkInventory "Spinning Top"

Here, runTest runs a test suite, printing a test report onto the console. test introduces a named test group, and assertFn can be used to run an asynchronous test, by taking a callback as an argument.

We can run our test suite on the command line:

$ pulp test
* Building project in purescript/pulp-test
* Build successful. Running tests...
→ Running: Service Tests
  ✓ Passed: Service Tests
* Tests OK.

If we modify our tests to make a false assertion, we will see an error in the test report:

$ pulp test
* Building project in purescript/pulp-test
* Build successful. Running tests...
→ Running: Service Tests
  ☠ Failed: Service Tests because Bicycle is in inventory
* ERROR: Subcommand terminated with error code 1

purescript-test-unit supports other test functions, such as assert and assertFalse, which can be used to build pure tests, and timeout which can be used to ensure that an asynchronous function returns in a fixed amount of time.

Later in the series, I'll take a look at some complementary testing libraries, which can be used alongside purescript-test-unit to provide different types of tests.

Until next time...

Day 10 - purescript-webaudio

Today, we're going to create purely functional Christmas Carols, using @waterson's excellent purescript-webaudio library.

If you're interested in seeing this library in action, you should check out the Asteroids demo, by the same author.

To begin, pull down a copy of the library into a new project using Bower:

$ bower install https://github.com/waterson/purescript-webaudio

I worked from the examples projects in the purescript-webaudio repo, and used the following imports:

module Main where

import Control.Bind
import Control.Monad.Eff

import Data.DOM.Simple.Types
import Data.DOM.Simple.Window

import Audio.WebAudio.Types
import Audio.WebAudio.AudioContext
import Audio.WebAudio.AudioParam
import Audio.WebAudio.OscillatorNode
import Audio.WebAudio.DestinationNode

The web audio API defines different types of nodes which can be connected to form networks. We will only be interested in the oscillator node in this post. The network can then be connected to a destination node on an audio context, which results in sound being generated.

We can start by creating a new audio context:

main :: forall eff. (Eff (wau :: WebAudio, dom :: DOM | eff) Unit)
main = do
  ctx <- makeAudioContext

Next, we can create an oscillator node which will produce a sine wave:

  osc <- createOscillator ctx
  setOscillatorType Sine osc
  startOscillator 0.0 osc

Now, we connect the oscillator node to the destination node on the audio context:

  connect osc =<< destination ctx

And finally, we delegate to a helper function, play, which is responsible for playing our song, passing the context and oscillator nodes as arguments.

  play ctx osc

The play function is very simple. It sets up a timer on the window object to update the oscillator every 10 milliseconds:

play :: forall eff. AudioContext -> OscillatorNode -> Eff (wau :: WebAudio, dom :: DOM | eff) Unit
play ctx osc = void $ setInterval globalWindow 10 update

The update function uses the setValue action from purescript-webaudio to change the frequency of the oscillator, based on the time:

  where
  update = do
    t <- currentTime ctx
    frequency osc >>= setValue (freqAt t)
    return unit

The particular melody which is played depends on the freqAt function. Try some different functions - you might find a table of notes and frequencies to be helpful.

Here is an example, which oscillates between two octaves, producing an alarm-like sound:

freqAt t | t < 1 = 440
         | t < 2 = 880
         | otherwise = freqAt $ t - 2

However, in the spirit of the season, let's write a function which will render a popular Christmas carol. Here are the first four bars of Jingle Bells, in the form of a pure function:

freqAt :: Number -> Number
freqAt t | t <  4.50 = 164.81 * 2.0
         | t <  5.00 = 196.00 * 2.0
         | t <  5.75 = 130.81 * 2.0
         | t <  6.00 = 146.83 * 2.0
         | t <  8.00 = 164.81 * 2.0
         | t < 10.50 = 174.61 * 2.0
         | t < 12.00 = 164.81 * 2.0
         | t < 13.00 = 196.00 * 2.0
         | t < 13.50 = 174.61 * 2.0
         | t < 14.00 = 146.83 * 2.0
         | t < 16.00 = 130.81 * 2.0
         | otherwise = freqAt $ t - 16

Try it out, and see what other melodies you can produce by varying the freqAt function. You may also be interested to try out some of the different node types provided by the purescript-webaudio library.

I'm particularly interested to see what might be done with this library in conjunction with an FRP library, like purescript-signal or purescript-behaviors, using functions of multiple arguments to represent various node parameters.

Day 11 - purescript-express

Today, I tried out the purescript-express library for the first time. This library, by @dancingrobot84, provides a wrapper for the Express web framework. If you are interested in seeing this library in use in a real project, you should check out Beta Reduction Online, by the same author.

Let me start by saying that I was amazed by how simple it was to get started with this library. I was able to get up and running in a matter of a few minutes. Here is a console transcript and a few lines of code which should suffice to get started:

$ pulp init
$ npm install express
$ bower install purescript-express
$ ... modify src/Main.purs ...
$ pulp run

Here is the code which I wrote for my first test, based on the example from the project repository:

module Main where

import Node.Express.Types
import Node.Express.App
import Node.Express.Handler

handler :: Handler
handler = sendJson { greeting: "Merry Christmas!" }

app :: App
app = get "/" handler

main = listen app 8080 \_ -> return unit

This application will listen on port 8080, and you can open your browser to http://localhost:8080 to see the result.

Let's modify our routes to match a parameter. Start by changing the route pattern in app, as follows:

app :: App
app = get "/greet/:name" handler

Next, add an import for Data.Maybe, and change the handler to read the value of the parameter:

handler :: Handler
handler = do
  Just name <- getParam "name"
  sendJson { greeting: "Merry Christmas, " <> name <> "!" }

This time, when you visit, for example, http://localhost:8080/greet/Charlie%20Brown, you should see a more personalized greeting.

purescript-express provides much more functionality. As one final example, let's implement a (very unsafe) file server.

handler :: Handler
handler = do
  m <- getQueryParam "file"
  case m of
    Just file -> download file
    Nothing -> do
      setStatus 400
      sendJson { error: "Please specify the file parameter" }

app :: App
app = get "/file" handler

This example demonstrates a few other functions:

  • setStatus can be used to send an error (or success) code in the HTTP response.
  • download can be used to download a file given its filename.
  • getQueryParam can be used to read a value from the query string.

Now, we can download files by navigating to, for example, http://localhost:8080/file?file=/etc/hosts. Obviously, this is very unsafe, and such a service should not be made publically (or probably even locally) available, but it demonstrates how quickly it is possible to write useful services with this great library.

Day 12 - purescript-react

Today, I'm going to take a look at one of the earliest, most developed, and most discussed PureScript contributor libraries - purescript-react, originally created by @andreypopp, which provides an interface to the React UI library.

On the face of it, React is a wonderful match for PureScript, emphasizing isolation of mutable state, and separation of concerns in the UI. However, while the philosophy of React seems like a great match, the actual implementation is another matter. It is somewhat challenging to provide an API for React's idiomatic JavaScript, in PureScript (or for that matter, in any pure functional language).

For that reason, I see purescript-react as a triumph in its use of PureScript's flexible FFI. Also, I think it provides a great example of the trade-offs one can choose to make when writing FFI bindings, between type safety, and usability.

Other libraries such as virtual-dom seem to take more cues from pure functional programming, and I look forward to seeing what will be done using those libraries from PureScript.

Let's get started. I created a new project, with a HTML file, and installed both react and purescript-react using Bower.

I created the following Main.purs file, based on the example in the purescript-react repository:

module Main where

import Control.Monad.Eff

import React
import React.DOM

ui = mkUI spec { getInitialState = pure initialState } $
       view <$> readState
  where
  initialState = { name: "World" }
  
  view st =
    p [] [ text "Merry Christmas, "
         , text name
         , text "!"
         ]

main =
  let
    component = div [] [ ui {} ]
  in renderToBody component

This is enough to get started - compile the code and open index.html, and you will see the greeting "Merry Christmas, World!".

The code requires a little explanation.

The mkUI function can be used to build a UI component. We pass the initial state object, and a function which can render the view from the current state. The React.DOM library provides a collection of smart constructors which can be used to build views simply.

Finally, in main, the renderToBody function is used to render the UI component to the DOM body.

Now let's extend our application by allowing the user to modify the state object. We will add a text box to let the user enter their name.

First, modify the view function to add the text box:

  view st =
    div [] [ p [] [ text "Your name: "
                  , input [ onChange updateName ] []
                  ]
           , case st.name of
               "" -> p [] [ text "Please enter your name." ]
               name -> p [] [ text "Merry Christmas, "
                            , text name
                            , text "!"
                            ]
           ]

Here, the onChange function adds an event handler to the UI component. We can provide the updateName handler, which sets the state to the entered text:

  updateName :: Event -> EventHandlerContext _ _ _ _ _
  updateName e = writeState { name: getValue e }

Here, I need to specify a type signature to avoid a type error due to purescript-react's use of rank-N types. However, notice that the new type wildcards feature allows us to only specify what is necessary.

The getValue function needs to be provided as an FFI import:

foreign import getValue
  "function getValue (e) {\
  \  return e.target.value;\
  \}" :: Event -> String

If you would like to see the finished application, it is available online here.

Day 13 - purescript-smolder

Today, I'm going to take a look at purescript-smolder, which is the third (but not final) PureScript library to be covered in this series, which is written by @bodil.

purescript-smolder is a domain-specific language for the problem of creating and applying DOM templates, inspired by Haskell's blaze-html library.

To celebrate having just completed twelve days of this mini-blog series, I'm going to use the library to create a page which lists the lyrics to the song "the twelve days of Christmas" in a structured form.

For anyone who just wants to see the finished result, you can do so here.

My demo uses the following imports from the purescript-smolder library:

import Text.Smolder.HTML (h1, p, ul, li)
import Text.Smolder.HTML.Attributes (name, content)
import Text.Smolder.Markup (Markup(), text)
import Text.Smolder.Renderer.String (render)

The Text.Smolder.HTML and Text.Smolder.Attributes modules contain typed representations of HTML elements and attributes respectively.

The Text.Smolder.Markup defines the text function which, as we will see, is used to embed plain text into a document.

Finally, the Text.Smolder.Renderer.String module defines one of two renderers provided by the library, which renders the HTML to a string.

To start, let's define a list of gifts which my true love gave to me:

gifts :: [String]
gifts = [ "partridge in a pear tree"
        , "turtle doves"
        , "french hens"
        , "calling birds"
        , "golden rings"
        , "geese a-laying"
        , "swans a-swimming"
        , "maids a-milking"
        , "ladies dancing"
        , "lords a-leaping"
        , "pipers piping"
        , "drummers drumming"
        ]

We're also going to need the following helper function:

th :: Number -> String
th 1 = "st"
th 2 = "nd"
th 3 = "rd"
th _ = "th"

Now, let's define a model for a single verse of the song:

type Model = [Tuple Number String]

day :: Number -> Model
day n = reverse (take n (zip (1..12) gifts))

To determine the model for a given day, we simply take that number of days from the list and reverse it.

Now, we can use purescript-smolder to render our view:

view :: Markup
view = do
  h1 $ text "The twelve days of Christmas"
  for_ (1..12) $ \n -> do
    p $ do
      text "On the "
      text $ show n
      text $ th n
      text " day of Christmas, my true love gave to me:"
    ul $ do
      for_ (day n) $ \(Tuple count gift) -> li do
        text $ show count
        text " "
        text gift

There are a few things to notice here:

  • Elements are just functions like h1 and ul.
  • Text content is created using the text function.
  • We can use do notation, and functions like for_ to structure our code, since Markup is monadic.

Finally, we can use the render function to turn our Markup into a HTML string:

main = asBody $ render view

Here, the asBody function is defined using a foreign import:

foreign import asBody 
  "function asBody(html) {\
  \  return function() {\
  \    onload = function() {\
  \      document.body.innerHTML = html;\
  \    };\
  \  };\
  \}" :: forall eff. String -> Eff (dom :: DOM | eff) Unit

One other neat thing about purescript-smolder is that it also provides a renderer which makes use of the virtual-dom library, in the Text.Smolder.Renderer.VTree module. This means that you would be able to render two values of type Markup to virtual DOM elements, and patch the DOM by applying the differences. This approach can result in some remarkable speed improvements in DOM-heavy applications.

Day 14 - yesod-purescript

Today, I've been looking at the yesod-purescript library, which allows PureScript code to be compiled as part of a Yesod website.

yesod-purescript is created by @mpietrzak, who has done a wonderful job of documenting the library, including a getting started guide in the README file, and even a fully-worked example project. I have not done a great deal of work with Yesod in the past, but I was able to get up and running in 30 minutes (not including the time to cabal install the necessary libraries).

I started by using cabal init to create a new Cabal project in a sandbox, followed by cabal installing yesod-core and yesod-purescript (from the cloned repository). From there, I created an empty Yesod website in Main.hs, using the name Greeting for my site's foundation type:

{-# LANGUAGE TemplateHaskell #-} 
{-# LANGUAGE QuasiQuotes #-} 
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}

module Main where

import qualified Yesod.Core as Y

data Greeting = Greeting

Y.mkYesod "Greeting" [Y.parseRoutesNoCheck|
/     Home  
|]

instance Y.Yesod Greeting

handleHome :: Handler ()
handleHome = return ()

main = Y.warp 8080 Greeting 

This project should compile and run, opening a web server on port 8080. The site will serve an empty page at the root /.

From there, I simply followed the instructions in the yesod-purescript README file:

  1. I added an import for the Yesod.PureScript module:

    import qualified Yesod.PureScript as Y
  2. I modified my site's foundation type to include a value of type PureScriptSite, and added an instance for the YesodPureScript type class:

    data Greeting = Greeting { getPureScriptSite :: Y.PureScriptSite }
    
    instance Y.YesodPureScript Greeting
  3. I updated my routing table to route /purs to my new subsite:

    Y.mkYesod "Greeting" [Y.parseRoutesNoCheck|
    /     Home  
    /purs PureScript Y.PureScriptSite getPureScriptSite
    |]
  4. I updated main to create the subsite using createYesodPureScriptSite:

    main = do
      purs <- Y.createYesodPureScriptSite def
      Y.warp 8080 $ Greeting purs

At this point, if you compile and run the project, you should be able to open your browser to localhost:8080/purs and see the yesod-purescript status page, which lists PureScript modules and their compilation status.

However, we don't have any PureScript modules yet, so let's create one.

Create purs/ and bower_components/ directories in your project's root directory, and copy the Prelude files from your PureScript distribution's share directory into purs/. Also create a purs/Main.purs file, for example:

module Main where
  
import Control.Monad.Eff

foreign import data Alert :: !

foreign import alert 
  "function alert(s) {\
  \  return function() {\
  \    window.alert(s);\
  \  };\
  \}" :: forall eff. String -> Eff (alert :: Alert | eff) Unit

main = alert "Merry Christmas!"

Finally, we need to update our home page route to include the compiled PureScript code:

handleHome :: Handler Y.Html
handleHome = do
  Y.defaultLayout $ do
    Y.setTitle "Merry Christmas from PureScript!"
    Y.addScript $ PureScript $ Y.getPureScriptRoute ["Main"]

Now, if you recompile and refresh the page at localhost:8080/purs, you will hopefully see a list of successfully compiled modules. If you open the browser to the home page at localhost:8080/, the compiled JavaScript code will be run, resulting in a call to window.alert.

The neat thing about yesod-purescript is that you can develop your PureScript code in the purs/ directory without needing to recompile or even restart your Yesod application. If your PureScript modules change, they will be recompiled on the next page load.

I think that yesod-purescript is a great way to get started with any project which uses a Haskell backend and a PureScript frontend, and I hope to make use of it in an upcoming project.

My complete project code is available here.

Until tomorrow...

Day 15 - purescript-hatter

Today, I have been looking at the purescript-hatter DOM templating library by @mechairoi.

Hatter is a very interesting library, because it solves a problem which would normally be solved using something like Template Haskell (which does not yet exist for PureScript, but which is planned): compile-time code generation.

The purescript-hatter library itself contains a parser and code generator, but also comes with a set of companion libraries: gulp-purescript-hatter which embeds the code generation capability into the build process using the Gulp build automation tool, and purescript-hatter-runtime, which contains the runtime needed to support the generated code.

Hatter targets the virtual-dom library using the purescript-virtual-dom-typed bindings, which means that the generated templates should generally be very fast, and support partial updates.

Here, I'm just going to give a very brief overview of the functionality.

I created a new project using pulp, and installed purescript-hatter and purescript-virtual-dom-typed using Bower. My Main module uses the following imports from Hatter:

import Text.Hatter
import Text.Hatter.Parser

Based on the example in the repository, I came up with the following template:

input :: String
input = 
  "greet :: String -> VirtualDOM.VTree.VTree\n\
  \greet name =\n\
  \<p style='color: red'>\n\
  \  Merry Christmas,\n\
  \  <span style='font-weight: bold'>\n\
  \    <% VirtualDOM.VTree.vtext name %>\n\
  \  </span>\n\
  \</p>"

Hopefully, when Template PureScript is functional, it will be possible to embed code like this directly into a quasiquoter.

Notice how Hatter allows us to embed HTML directly into PureScript code. After code generation, this means that our HTML will benefit from type checking, while keeping all the performance benefits of a statically-defined template.

The <% ... %> brackets also allow us to embed virtual-dom elements back into the HTML structure. From what I can tell, attributes and text content can also be templated in this way.

Here is my main function:

main =
  case hatter "Greeting" ["VirtualDOM.VTree"] input of
    Left err -> print err
    Right purs -> trace purs

I specified the module name Greeting, and my imports list, and this was enough to get Hatter to generate some PureScript code for my template. This code can then be built as part of your application.

I had a little trouble with versions of various Bower packages, but many of these bindings are new, and hopefully we will see them stabilize along with the upstream packages like purescript-virtual-dom.

That's it for my brief overview, but I urge you to try this excellent library out for yourselves. I think that virtual-dom is a great match for PureScript, and I look forward to seeing more interesting integrations like this.

Day 16 - Editor integration

Today, I'm going to take a break from talking about libraries, to briefly highlight some of the options available for working with PureScript in various popular text editors.

Vim

Vim is my terminal text editor of choice, so I can say the most about it here. I use the purescript-vim plugin by [@raichoo], which provides two neat features:

  • Syntax highlighting
  • Automatic indentation

The indentation levels can be configured to your liking. Also, to my knowledge, the purescript-vim syntax highlighter is the only one which currently correctly identifies triple-quoted string literals (although I might be wrong).

Installation is simple - install Pathogen if you don't have it installed already, and then clone the purescript-vim repository under ~/.vim/bundle/.

Emacs

Emacs users can enjoy a collection of PureScript-related plugins, thanks to the excellent work done by various contributors:

Alejandro Cabrera has written some useful information about his Emacs setup here.

Other Editors

Support is available for other editors to various degrees:

Did I miss any?

Future Plans

One of the prioritized items for the compiler is the so-called "compiler-as-a-service", which should make it possible to build richer editor integrations: type-checking on save, getting the type of the expression at the cursor, searching for possible implementation a la Hoogle, etc.

Generally, this is an area where the community can use a lot of help. Good editor integration is exactly the sort of thing which will enable PureScript to succeed, so please join the #purescript IRC channel and share your ideas.

Day 17 - purescript-strongcheck

Today, I'm going to look at the purescript-strongcheck library by @jdegoes. Strongcheck is an "industrial-strength" version of the purescript-quickcheck library, providing additional combinators for building more powerful tests, and new testing strategies entirely, such as statistical testing and exhaustive testing. In fact, Strongcheck actually comprises what could make up several smaller interesting libraries.

New Generators

Suppose we write a library to verify Christmas gift wishlists. The library is designed to ensure that the list is not too long, and does not contain duplicate gift requests:

module Wishlist where

import Data.Array (length, nub)

type Gift = String

newtype Wishlist = Wishlist [Gift]

verify :: Wishlist -> Boolean
verify (Wishlist wl) 
  | length wl > 5 = false
  | length (nub wl) /= length wl = false
  | otherwise = true

We can test this library in psci:

$ pulp psci

> Wishlist.verify ["foo", "bar", "bar"]
false

> Wishlist.verify ["foo", "bar", "baz", "bam", "bux"]
true

> Wishlist.verify ["foo", "bar", "baz", "bam", "bux", "xyz"]
false

And we could use purescript-quickcheck to generate arbitrary Wishlists and verify their properties. The problem is that it is tricky to generate arbitrary Wishlists which satisfy the criteria described by the verify function.

Strongcheck provides additional functions for generating random input data, which makes this job easier. In this case, we can use two additional functions, chooseInt and nChooseK to generate valid Wishlists from a pool of 20 mock "gifts":

gifts :: [Gift]
gifts = toGift <$> (1 .. 20)
  where
  toGift :: Number -> Gift
  toGift n = "Gift " ++ show n

instance arbWishlist :: Arbitrary Wishlist where
  arbitrary = do
    n <- chooseInt 0 5
    Wishlist <$> nChooseK n gifts

Then we can use the quickCheck function to validate 100 random Wishlists:

main = do
  quickCheck Wishlist.verify

The chooseInt generator chooses an integer from a range, and the nChooseK generator will generate arrays of a given size without duplicates. We can use these two functions to generate randomly-selected valid Wishlists.

Strongcheck provides many interesting new generators like these ones. This is possible because Strongcheck's Gen type is built on the purescript-machines library, and can support more interesting ways of generating of pseudo-random data.

smallCheck and statCheck

Strongcheck also provides two new test types in the form of the smallCheck and statCheck functions.

smallCheck can be used to test properties exhaustively. In fact, if we want to modify our test to verify all valid Wishlists instead of a random sample, it is as simple as changing quickCheck to smallCheck:

main = do
  smallCheck Wishlist.verify

statCheck is used when you want to verify that a property holds with some probability, but cannot guarantee that it holds with certainty for any random sample.

For example, we would expect that a random sampling of Wishlists generated as above would contain any given gift from the list of 20 mock gifts, about a quarter of the time. We can express this with statCheck as follows:

main = do
  statCheck (1/4) $ \(Wishlist wl) -> "Gift 1" `elem` wl

Strongcheck contains some other impressive features, like the ability to resize and perturb randomly generated values to generate more meaningful test failures, but I won't cover those here.

I urge you to check out this feature-packed library. If purescript-strongcheck doesn't meet your needs for generative testing, I would be surprised!

If you would like to see the code for this example, it is available here.

Day 18 - purescript-d3

Today I spent some time looking at the purescript-d3 library, written by @pelotom. purescript-d3 provides a set of bindings to the D3 diagrams library.

I have not used D3 before, but I started by creating a new project, installing purescript-d3 using Bower, and following the excellent examples.

The data science division of Santa and co. is preparing its annual report and has decided to use D3 to create its charts. Here is their data in the form of an array:

array = [ { label: "Nice"
          , count: 92
          }
        , { label: "Naughty"
          , count: 8
          }
        ]

I will show how to plot this as a simple bar chart, with vertical bars.

I created a HTML file, based on the example, which looked like this:

<html>
  <head>
    <style>
    .chart rect {
      fill: green;
    }
    .chart text {
      font: 10px sans-serif;
    }
    </style>
  </head>
  <body>
    <svg class="chart"></svg>
    <script src="../bower_components/d3/d3.min.js"></script>
    <script src="index.js"></script>
  </body>
</html>

and a PureScript file in src/Main.purs, with the following imports:

module Main where

import Graphics.D3.Util
import Graphics.D3.Selection

purescript-d3 provides a monadic interface to D3, based on the Eff monad. D3's fluent interface is captured by the bind operation of the Eff monad, but purescript-d3 provides a helpful .. operator as a synonum for >>=, making the code more readable.

In the first part of the code, I obtain a reference to the <svg> element on the page, and bind the data in array to a list of <g> subnodes of that element:

main = do
  g <- rootSelect ".chart"
    .. selectAll "g"
    .. bind array  
    .. enter
      .. append "g"

The result is that we create one <g> element for each entry in our array. g is bound to this selection, and we can use this reference to append different nodes to each element.

Let's start by adding a rectangle to represent each bar:

  g # append "rect"
    .. attr'' "x"      (\_ i -> i * 100)
    .. attr'  "y"      (\o -> 100 - o.count)
    .. attr   "width"  98
    .. attr'  "height" (\o -> o.count)

    .. style  "stroke-width" "1"
    .. style  "stroke"       "rgb(0,255,0)"

Here we are essentially only using two functions to modify the rectangle, attr and style. The attr' and attr'' modifiers are variants of the attr function, which provide access to the current element of the array, and its index in the array respectively, as function arguments.

Next, we can append a text node for each array element, to label the corresponding bar, as follows:

  g # append "text"
    .. attr'' "x"  (\_ i -> i * 100 + 20)
    .. attr   "y"  120
    .. text'       (\o -> o.label ++ " (" ++ show o.count ++ "%)")

And that's it! The finished product can be seen here.

purescript-d3 provides much more functionality, including transitions, interpolation, and the ability to read data from TSV files. I don't have time to cover these here, but they are well worth checking out on GitHub.

Day 19 - purescript-signal

Today, I've been looking at @bodil's purescript-signal library, which is a PureScript port of part of Elm's signal implementation. You might be familiar with this library already from Bodil's excellent Strange Loop 2014 talk. I'm going to try to make a very minimal Christmas-themed game using the library.

I started by creating a new project with pulp init, and using Bower to install purescript-signal. I found an image of Rudolf the red-nosed reindeer online and copied it into the images/ directory, and created this simple HTML page:

<html>
  <head>
    <style>
      #rudolf {
        position: absolute;
        background-image: url('../images/rudolf.png');
        background-size: contain;
        width: 268px;
        height: 355px;
        margin-left: -134px;
        margin-top: -177px;
      }
    </style>
  </head>
  <body>
    <div id="rudolf"></div>
    <script src="index.js"></script>
  </body>
</html>

The goal will be to animate the rudolf element by using signals to change its position based on things like the mouse position.

My first attempt was very simple - I had the element simply follow the cursor. I started with a foreign import which would set the left and top properties on the div, as follows:

import Control.Monad.Eff

import DOM

import Signal
import Signal.DOM

foreign import render
  "function render(pos) {\
  \  return function() {\
  \    var rudolf = document.getElementById('rudolf');\
  \    rudolf.style.left = pos.x + 'px';\
  \    rudolf.style.top  = pos.y + 'px';\
  \  };\
  \}" :: forall eff. CoordinatePair -> Eff (dom :: DOM | eff) Unit

With that, my main action was very simple:

main = do
  mouse <- mousePos
  runSignal (render <~ rudolf mouse)
  where
  rudolf :: Signal CoordinatePair -> Signal CoordinatePair
  rudolf mouse = mouse

The main abstraction in the purescript-signal library is the Signal type constructor, which represents time-varying values. Here, I only use the mousePos action to get a Signal which represents the current mouse position. I then use the <~ operator, which is a synonym for the Functor's fmap function, to map the render function over the generated coordinates. Finally, I use runSignal to listen for changes to the signal's value, and run the wrapped effects.

I can compile this file with pulp browserify and save the resulting JavaScript in html/index.js, and see in the browser that Rudolf does indeed follow the mouse cursor. However, to make things more interesting, let's try to make Rudolf avoid the cursor, and the aim of the game can be to try to catch him.

Let's start by making our own Signal which will reflect the size of the window. To keep things simple, I'll just check the size of the window each second, but you might like to try using the FFI to implement this using an event handler instead:

type Dimensions = { w :: Number, h :: Number }

foreign import dimensions
  "function dimensions() {\
  \  return { w: document.body.offsetWidth\
  \         , h: document.body.offsetHeight\
  \         };\
  \};" :: forall eff. Eff (dom :: DOM | eff) Dimensions

dimensionsS :: forall eff. Eff (dom :: DOM, timer :: Timer | eff) (Signal Dimensions)
dimensionsS = unwrap $ every second ~> \_ -> dimensions

I've used the every signal to generate a tick every second, and the unwrap function, which turns a signal of effectful computations like dimensions into a regular signal.

Here is my new main method:

main = do
  mouse <- mousePos
  dims  <- dimensionsS
  runSignal (render <~ rudolf mouse dims)
  where
  rudolf :: Signal CoordinatePair -> Signal Dimensions -> Signal CoordinatePair
  rudolf = zip position 

  position :: CoordinatePair -> Dimensions -> CoordinatePair
  position o d = { x: d.w - o.x, y: d.h - o.y }

I've used the zip combinator to combine my two signals into a single signal by applying the two-argument function position. Now Rudolf avoids the mouse cursor, unless the mouse is in the center of the screen.

My final version of the game has Rudolf move at a velocity which depends on his distance to the cursor, and in a direction away from the cursor. In addition, if the user manages to catch Rudolf, then he will jump to another position.

The code for the final version can be found here. It uses the sampleOn combinator to sample the relevant events every 20 milliseconds, and then uses the foldp combinator to modify the game state (Rudolf's position) based on these events.

The final game can be played here.

Programming with signals is a lot of fun, especially when designing interactive web pages or games like these. I suggest you try it out!

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment