• Stars
    star
    109
  • Rank 319,077 (Top 7 %)
  • Language
  • Created almost 7 years ago
  • Updated about 4 years ago

Reviews

There are no reviews yet. Be the first to send feedback to the community and the maintainers!

Repository Details

What I Wish I Knew When Learning PureScript

What I Wish I Knew When Learning PureScript

Important

This documentation can be outdated. See Links for official documentation.

A concise overview of the PureScript language and ecosystem, in the same style as "What I Wish I Knew When Learning Haskell" by Stephen Diehl.

Table of Contents

Basics

Install PureScript and Spago

We will use NPM to install PureScript. If you want to install PureScript (and other NPM packages) into your home directory (rather than to the global system directories), you could set a prefix in your npmrc. On Linux you can do:

$ npm set prefix $HOME/.local

Then the following commands can be run as an ordinary user instead of as root:

$ npm install -g [email protected] spago

We only need to create a symlink to purs.bin. If you installed to the $HOME/.local prefix then you can do it as follows. Also, make sure that $HOME/.local/bin/ is in your path.

$ export PATH="$HOME/.local/bin/:$PATH"
$ cd ~/.local/bin/
$ ln -s ../lib/node_modules/purescript/purs.bin purs
$ purs --version
0.13.8
$ spago version
0.16.0

If you get something like the following error:

spago: error while loading shared libraries: libtinfo.so.5: cannot open shared object file: No such file or directory

I solved it on Fedora by installing the package ncurses-compat-libs. You could also create a symlink or install from source.

Starting a new project with Spago

Now we can use Spago (a package manager and build tool for PureScript) to create a new empty project.

$ mkdir purescript-hello
$ cd purescript-hello/
$ spago init

We are going to use it to install some additional dependencies. Do not include the purescript- prefix of the package when using Spago, so for example to install purescript-maybe:

$ spago install maybe

Spago adds the dependency to your project configuration file (spago.dhall). As the extension implies this is a file written in the Dhall configuration language (see this cheatsheet).

Spago uses package sets to ensure that all the libraries can be build together because there is only one version of each.

Note
You may need to add PureScript libraries to your local package set if they are on Bower but not part of the package set.

Run

Run your code with spago run:

$ spago run
[..snip..]
[info] Build succeeded.
🍝

PSCi

PSCi is the REPL for PureScript, you can use Spago to run it for you:

$ spago repl

Importing modules on the REPL uses the same syntax as in the source code. In PSCi you do not use let to bind variables (as of version 0.11). So, you can write:

> import Data.Maybe
> foo = Just 1

If you try to reassign an existing binding PSCi will complain. You either have to chose a new variable name or you can optionally :reload. Which will remove all bindings and reimports all your imported modules (compiling when necessary).

You can see the type of an expression with :t (or :type):

> :t Just 1
Maybe Int

Another handy feature is :paste mode, which allows you to paste multiple lines of code into PSCi, or to type a statement with multiple lines. You can finish input by pressing Ctrl-D while on the last empty line.

Documentation

You can build documentation for your project and all it’s dependencies in HTML format like so:

$ spago docs --open

This can be really useful when you don’t have continuous Internet access (and thus access to Pursuit).

Types

The built-in types are defined in the Prim module that is embedded in the PureScript compiler (this module is implicitly imported in every module).

Number

A double precision floating point number (IEEE 754).

> :t 42.0
Number

TODO: show all operators that work with Number

Int

A 32-bit signed integer.

> :t 42
Int

You can also use hexadecimal notation for Integer literals:

> 0xff
255

> :t 0xff
Int
Note
Note that you can’t mix Int and Number in expressions like add and div. Use toNumber from Data.Int (package purescript-integers) to convert an Int to a Number.

String

Strings are a built-in type in PureScript and correspond to the native string in JavaScript. So, unlike Haskell they’re not stored as a list of characters.

> :t "Hello world!"
String

Multi-line string literals are also supported with triple quotes ("""):

> :paste  -- paste mode allows us to type multi-line statements in PSCi
> multiline = """Hello
… world!"""-- press Ctrl-D now to stop paste mode
> multiline
"Hello\nworld!"

String utility functions can be found in purescript-strings. It also contains functions for the Char type.

Char

A single character (UTF-16 code unit). The JavaScript representation is a normal String, which is guaranteed by the PureScript type system to contain one code unit.

> :t 'a'
Char

Boolean

Either true or false.

Note
Note that the values are written in lowercase like in JavaScript, in contrast with Haskell where they are written capitalized. Also, the type is called Boolean instead of Bool as in Haskell.
> true == false  -- equal
false

> true /= false  -- not equal
true

> true || false  -- or
true

> true && false  -- and
false

> not true       -- negation
false

Array

Arrays are implemented using Javascript arrays, but must be homogeneous (all elements must be of the same type). They support efficient random access. The Data.Array module from purescript-arrays provides many functions for working with arrays.

> import Data.Array
> xs = [1, 2, 3, 4, 5]
> :t xs
Array Int
> head xs  -- head is a total function in PS
Just 1
Note
you cannot pattern match on arrays as you can in Haskell with lists.

Records

Records correspond to JavaScript’s objects, and record literals (values) have the same syntax as JavaScript’s object literals:

> lang = { title: "PureScript", strictEval: true, pure: true }
> lang.title
"PureScript"

Pattern matching

We can perform pattern matching on records like this:

TODO

Record puns

The functionality {..} does not exist in PS?

Note
These are sometimes called object puns

Polymorphic records

TODO

List

Linked lists are not a built-in type in PureScript, but are provided by the library purescript-lists. There are lazy and strict versions available.

import Data.List (List(..), (:), fromFoldable, range)

someList :: List Int
someList = 1 : 2 : 3 : Nil

listFromArray :: List Int
listFromArray = fromFoldable [1, 2, 3]

listUsingRange :: List Int
listUsingRange = range 1 3
Note
There is no special syntax to write the type of a list (i.e. [String] or [Int] as in Haskell), it’s just List String.

Unit

PureScript has a type Unit used in place of Haskell’s (). The Prelude module provides a value unit that inhabits this type.

Modules

Defining a module

A source file must contain exactly one module. A module declaration looks like this:

module Main where

import Prelude

Module names do not need to match the filename, but it’s recommended. Module names should be unique within a project.

Prelude

In PureScript the Prelude libraries are not bundled with the compiler. You need to install the purescript-prelude library. Also, the prelude is not imported automatically, just add the following line to the top of your module.

import Prelude

Main

The function main in the module with the name Main is the entry point of a script.

module Main where

import Effect.Console (log)

main :: Effect Unit
main = log "Hello world!"

As you can see here in the type of main, PureScript has a type Unit used in place of Haskell’s (). The Prelude module provides a value unit that inhabits this type.

Importing modules

Imports must appear before other declarations in a module.

To open import a module:

import Prelude

PureScript allows one open import per module. Usually this is Prelude.

To import a specific set of members:

import Prelude (head, tail)

Import one data constructor of a given type constructor:

import Data.Maybe (Maybe(Just))

Importing all data constructors for a given type constructor:

import Data.Maybe (Maybe(..))

Importing type classes:

import Prelude (class Show)

Importing qualified:

import Data.Maybe as Data.Maybe
Note
Note that PureScript does not have the qualified keyword as Haskell. An import is always qualified with as.

Only names that have been imported into a module can be referenced, and you can only reference things exactly as you imported them.

Some examples:

Import statement Exposed members

import X

A, f

import X as Y

Y.A, Y.f

import X (A)

A

import X (A) as Y

Y.A

import X hiding (f)

A

import Y hiding (f) as Y

Y.A

Exporting modules

Export only a set of it’s members:

module A (runFoo, Foo(..)) where

Export a type class:

module A (class B) where

Re-export a module in it’s entirety:

module A (module B) where
import B

Re-export the module itself in it’s entirety:

module A (module A, module B) where
import B
data ...

Re-export a restricted set of members:

module A (module ExportB) where
import B (foo, bar) as ExportB

Functions

Function composition

In PureScript function composition is done with the (<<<) operator:

> import Data.String (toLower, trim)
> clean = toLower <<< trim
> clean " Matthias "
"matthias"

Operator Sections

PureScript, like Haskell, supports operator sections, or partial application on infix operators, however the syntax is different: you need to put an underscore in the place of the newly created function’s argument. For example:

> import Data.Array ((..))  -- Import the `range` operator from Data.Array
> map (2 * _) (1..10)
[2,4,6,8,10,12,14,16,18,20]

> prependHello = ("Hello " <> _)
> prependHello "World"
"Hello World"

> (_ <> "!") (prependHello "World")
"Hello World!"

Typeclasses

Create a type class

We can define a type class using the class keyword:

class Show a where
  show :: a -> String

Create an instance

We can manually create an instance for a type class like this:

data Colour = Red | White | Blue

instance eqColour :: Eq Colour where
  eq Red   Red   = true
  eq White White = true
  eq Blue  Blue  = true
  eq _     _     = false

instance showColour :: Show Colour where
  show Red   = "Red"
  show White = "White"
  show Blue  = "Blue"

Instance deriving

Of course this may become tedious, that’s why the PureScript compiler supports automatic deriving for a number of type classes:

data Colour = Red | White | Blue

derive instance eqColour :: Eq Colour

Currently, the following type classes can be automatically derived by the compiler:

  • Data.Eq (class Eq)

  • Data.Ord (class Ord)

  • Data.Functor (class Functor)

  • Data.Newtype (class Newtype)

  • Data.Generic.Rep (class Generic)

Newtype deriving

In Haskell it’s common to define a newtype using record syntax to automatically create an unwrap function. In PureScript the Newtype type class provides unwrap. The compiler can derive instances of Newtype automatically:

newtype EmailAddress = EmailAddress String

derive instance newtypeEmailAddress :: Newtype EmailAddress _

main = do
  let email = EmailAddress "[email protected]"
  log $ unwrap email

This requires the purescript-newtype package.

Generic deriving

Generic deriving allows data-type generic programming (inspired by GHC’s Generics). This technique allows us for example to easily create serialization/deserialization code for our own data types (as done by Argonaut). The basic functionality is provided by the purescript-generics-rep package.

For example we can use a function genericShow that works on all types that have an instance for the Generic typeclass:

import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)

data Colour = Red | White | Blue

derive instance genericColour :: Generic Colour _

instance showColour :: Show Colour where
  show = genericShow

Deriving instances for records

If you want to create instances for records, you need to wrap the record in a newtype first (or use data to declare your type). Like this:

import Prelude
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Data.Generic.Rep.Ord (genericCompare)

newtype Person = Person { firstName :: String, lastName :: String }

derive instance genericPerson :: Generic Person _

-- This is equivalent to:
-- `derive instance eqPerson :: Eq Person`
instance eqPerson :: Eq Person where
  eq = genericEq

-- This is equivalent to:
-- `derive instance ordPerson :: Ord Person`
instance ordPerson :: Ord Person where
  compare = genericCompare

instance showPerson :: Show Person where
  show = genericShow

Common type classes

Relationships

g?digraph%20G%20{%22Semigroupoid%22%20 %3E%20%22Category%22%22Functor%22%20 %3E%20%22Apply%22%22Apply%22%20 %3E%20%22Applicative%22%22Semigroup%22%20 %3E%20%22Monoid%22%22Monoid%22%20 %3E%20%22Foldable%22%20

Semigroupoid (purescript-prelude)

A Semigroupoid is similar to a Category but does not require an identity element, just composable morphisms.

class Semigroupoid a where
  compose :: forall b c d. a c d -> a b c -> a b d
Note
(<<<) is an alias for compose. (>>>) is an alias for flip compose. So, function composition is done with the (<<<) operator unlike (.) in Haskell. The . is used for record field access in PureScript.

Category (purescript-prelude)

`Category`s consist of objects and composable morphisms between them, and as such are `Semigroupoid`s, but unlike `Semigroupoid`s must have an identity element.

class (Semigroupoid a) <= Category a where
  identity :: forall t. a t t
Note
Per version 4.0.0 of the Prelude id has been renamed to identity.

Semigroup (purescript-prelude)

The Semigroup type class identifies those types which support an append operation to combine two values.

class Semigroup a where
  append :: a -> a -> a
Note
(<>) is an alias for append. The (++) operator as an alias for append is removed in PureScript 0.9.1.

Monoid (purescript-monoid)

The Monoid type class extends the Semigroup type class with the concept of an empty value, called mempty.

class Semigroup m <= Monoid m where
  mempty :: m

Functor (purescript-prelude)

The map function allows a function to be “lifted” over a data structure.

class Functor f where
  map :: forall a b. (a -> b) -> f a -> f b
Note
(<$>) is an alias for map. (<#>) is an alias for map with its arguments reversed. NOTE: PureScript uses map instead of Haskell’s fmap.

Foldable (purescript-foldable-traversable)

If the Monoid type class identifies those types which act as the result of a fold, then the Foldable type class identifies those type constructors which can be used as the source of a fold.

class Foldable f where
  foldr :: forall a b. (a -> b -> b) -> b -> f a -> b
  foldl :: forall a b. (b -> a -> b) -> b -> f a -> b
  foldMap :: forall a m. Monoid m => (a -> m) -> f a -> m

Apply (purescript-prelude)

The Apply type class is a subclass of Functor, and defines an additional function apply. The difference between map and apply is that map takes a function as an argument, whereas the first argument to apply is wrapped in the type constructor f.

class Functor f <= Apply f where
  apply :: forall a b. f (a -> b) -> f a -> f b
Note
(<*>) is an alias for apply.

Applicative (purescript-prelude)

Applicative is a subclass of Apply and defines the pure function. pure takes a value and returns a value whose type has been wrapped with the type constructor f.

class Apply f <= Applicative f where
  pure :: forall a. a -> f a

Traversable (purescript-foldable-traversable)

A traversable functor provides the ability to combine a collection of side-effects which depend on its structure.

class (Functor t, Foldable t) <= Traversable t where
  traverse :: forall a b f. Applicative f => (a -> f b) -> t a -> f (t b)
  sequence :: forall a f. Applicative f => t (f a) -> f (t a)

Monad (purescript-prelude)

class Apply m <= Bind m where
  bind :: forall a b. m a -> (a -> m b) -> m b

class (Applicative m, Bind m) <= Monad m
Note
(>>=) is an alias for bind. PureScript does not have return as an alias for pure.

Function types

Function application

($)   :: forall a b.                    (a -> b) ->   a ->   b
(<$>) :: forall a b f. (Functor f) =>   (a -> b) -> f a -> f b
(<*>) :: forall a b f. (Apply f)   => f (a -> b) -> f a -> f b
(=<<) :: forall m a b. (Bind m)    => (a -> m b) -> m a -> m b
(>>=) :: forall a b m. (Bind m)    => m a -> (a -> m b) -> m b
traverse :: forall a b m t. (Traversable t, Applicative m) => (a -> m b) -> t a -> m (t b)
foldMap  :: forall a m f.   (Foldable f, Monoid m)         => (a -> m)   -> f a -> m
Note
In PureScript map can be used instead of liftA or liftM in Haskell, and traverse replaces mapM.

Composition

(<<<) :: forall b c d a. (Semigroupoid a) => a c d -> a b c -> a b d
(>>>) :: forall a b c d. (Semigroupoid a) => a b c -> a c d -> a b d
(<=<) :: forall a b c m. (Bind m) => (b -> m c) -> (a -> m b) -> a -> m c
(>=>) :: forall a b c m. (Bind m) => (a -> m b) -> (b -> m c) -> a -> m c

Discarding one of two values

const :: forall a b.                    a ->   b ->   a
(<$)  :: forall f a b. (Functor f) =>   a -> f b -> f a
($>)  :: forall f a b. (Functor f) => f a ->   b -> f b
(<*)  :: forall a b f. (Apply f)   => f a -> f b -> f a
(*>)  :: forall a b f. (Apply f)   => f a -> f b -> f b
Note
Purescript does not have the operators (>>) or (<<) as Apply is a superclass of Monad (i.e. use (*>) and (<*) respectively).

Restructuring

sequence :: forall a m t. (Traversable t, Applicative m) => t (m a) -> m (t a)
join     :: forall a m.   (Bind m)                       => m (m a) -> m a

Identity

identity :: forall t a. (Category a)    => a t t
pure     :: forall a f. (Applicative f) => a -> f a