A brief introduction to Haskell

From HaskellWiki
Revision as of 13:46, 29 October 2011 by Gtirloni (talk | contribs) (fixed dead links. hbc's presence vanished from the internet (even tarballs can't be found in haskell.org))
Jump to navigation Jump to search


Haskell is:

  • A language developed by the programming languages research community.
  • Is a lazy, purely functional language (that also has imperative features such as side effects and mutable state, along with strict evaluation)
  • Born as an open source vehicle for programming language research
  • One of the youngest children of ML and Lisp
  • Particularly useful for programs that manipulate data structures (such as compilers and interpreters), and for concurrent/parallel programming

Inspired by the article Introduction to OCaml, and translated from the OCaml by Don Stewart.

Background

History:

  • 1990. Haskell 1.0
  • 1991. Haskell 1.1
  • 1993. Haskell 1.2
  • 1996. Haskell 1.3
  • 1997. Haskell 1.4
  • 1998. Haskell 98
  • 2000-2006. Period of rapid language and community growth
  • ~2007. Haskell Prime
  • 2009. Haskell 2010

Implementations:

Haskell features

Has some novel features relative to Java (and C++).

  • Immutable variables by default (mutable state programmed via monads)
  • Pure by default (side effects are programmed via monads)
  • Lazy evaluation: results are only computed if they're required (strictness optional)
  • Everything is an expression
  • First-class functions: functions can be defined anywhere, passed as arguments, and returned as values.
  • Both compiled and interpreted implementations available
  • Full type inference -- type declarations optional
  • Pattern matching on data structures -- data structures are first class!
  • Parametric polymorphism
  • Bounded parametric polymorphism

These are all conceptually more advanced ideas.

Compared to similar functional languages, Haskell differs in that it has support for:

  • Lazy evaluation
  • Pure functions by default
  • Monadic side effects
  • Type classes
  • Syntax based on layout

The GHC Haskell compiler, in particular, provides some interesting extensions:

  • Generalised algebraic data types
  • Impredicative types system
  • Software transactional memory
  • Parallel, SMP runtime system

The Basics

Read the language definition to supplement these notes. For more depth and examples see the Haskell wiki.

Interacting with the language

Haskell is both compiled and interpreted. For exploration purposes, we'll consider interacting with Haskell via the GHCi interpreter:

  • expressions are entered at the prompt
  • newline signals end of input

Here is a GHCi session, starting from a UNIX prompt.

   $ ghci
      ___         ___ _
     / _ \ /\  /\/ __(_)
    / /_\// /_/ / /  | |      GHC Interactive, version 6.4.2, for Haskell 98.
   / /_\\/ __  / /___| |      http://www.haskell.org/ghc/
   \____/\/ /_/\____/|_|      Type :? for help.
   Loading package base-1.0 ... linking ... done.

Here the incredibly simple Haskell program let x = 3+4 is compiled and loaded, and available via the variable x.

Prelude> let x = 3 + 4

We can ask the system what type it automaticaly inferred for our variable. x :: Integer means that the variable x "has type" Integer, the type of unbounded integer values.

Prelude> :t x
x :: Integer

A variable evaluates to its value.

Prelude> x
7

The variable x is in scope, so we can reuse it in later expressions.

Prelude> x + 4
11

Local variables may be bound using let, which declares a new binding for a variable with local scope.

Prelude> let x = 4 in x + 3
7

Alternatively, declarations typed in at the top level are like an open-ended let:

Prelude> let x = 4
Prelude> let y = x + 3
Prelude> x * x
16

Prelude> :t x
x :: Integer
Prelude> :t y
y :: Integer
Prelude> :t x * x
x * x :: Integer

Notice that type inference infers the correct type for all the expressions, without us having to ever specify the type explicitly.

Basic types

There is a range of basic types, defined in the language Prelude.

Int         -- bounded, word-sized integers
Integer     -- unbounded integers
Double      -- floating point values
Char        -- characters
String      -- strings
()          -- the unit type
Bool        -- booleans
[a]         -- lists
(a,b)       -- tuples / product types
Either a b  -- sum types
Maybe a     -- optional values

For example:

7
12312412412412321
3.1415
'x'
"haskell"
()
True, False
[1,2,3,4,5]
('x', 42)
Left True, Right "string"
Nothing, Just True

These types have all the usual operations on them, in the standard libraries.

Libraries

  • The Prelude contains the core operations on basic types. It is imported by default into every Haskell module. For example;
+ - div mod && || not < > == /=

Learn the Prelude well. Less basic functions are found in the standard libraries. For data structures such as List, Array and finite maps.

To use functions from these modules you have to import them, or in GHCi, refer to the qualified name, for example to use the toUpper function on Chars:

Prelude> Char.toUpper 'x'
'X'

Prelude> :m + Char
Prelude Char> toUpper 'y'
'Y'

In a source file, you have to import the module explicitly:

import Char

Overloading

Haskell uses typeclasses to methodically allow overloading. A typeclass describes a set of functions, and any type which provides those functions can be made an instance of that type. This avoids the syntactic redundancy of languages like OCaml.

For example, the function * is a method of the typeclass Num, as we can see from its type:

Prelude> :t (*)
(*) :: (Num a) => a -> a -> a

Which can be read as "* is a polymorphic function, taking two values of some type 'a', and returning a result of the same type, where the type 'a' is a member of the class Num".

This means that it will operate on any type in the Num class, of which the following types are members: Double, Float, Int, Integer. Thus:

Prelude> 2.3 * 5.7
13.11

or on integers:

Prelude> 2 * 5
10

The type of the arguments determines which instance of * is used. Haskell also never performs implicit coercions, all coercions must be explicit. For example, if we try to multiply two different types, then the type check against * :: Num a => a -> a -> a will fail.

Prelude> (2.3 :: Double) * (5 :: Int)

<interactive>:1:19:
    Couldn't match `Double' against `Int'
      Expected type: Double
      Inferred type: Int
    In the expression: 5 :: Int
    In the second argument of `(*)', namely `(5 :: Int)'

To convert 5 to a Double we'd write:

Prelude> (2.3 :: Double) * fromIntegral (5 :: Int)
11.5

Why bother -- why not allow the system to implicitly coerce types? Implicit type conversions by the system are the source of innumerable hard to find bugs in languages that support them, and makes reasoning about a program harder, since you must apply not just the language's semantics, but an extra set of coercion rules.

Note that If we leave off the type signatures however, Haskell will helpfully infer the most general type:

Prelude> 2.3 * 5
11.5

Expressions

In Haskell, expressions are everything. There are no pure "statements" like in Java/C++. For instance, in Haskell, if-then-else is a kind of expression, and results in a value based on the condition part.

Prelude> (if 2 == 3 then 5 else 6) + 1
7
Prelude> (if 2 == 3 then 5 else 6.5) + 1
7.5

Local bindings

In Haskell let allows local declarations to be made in the context of a single expression.

let x = 1 + 2 in x + 3

is analogous to:

   {
   int x = 1 + 2;
   ... x + 3 ... ;
   }

in C, but the Haskell variable x is given a value that is immutable (can never change).

Allocation

When you declare a new variable, Haskell automatically allocates that value for you -- no need to explicitly manage memory. The garbage collector will then collect any unreachable values once they go out of scope.

Advanced users can also manage memory by hand using the foreign function interface.

Lists

Lists are ... lists of Haskell values. Defining a new list is trivial, easier than in Java.

Prelude> [2, 1+2, 4]
[2,3,4]

Prelude> :t [2, 1+2, 4]
[2, 1+2, 4] :: (Num a) => [a]

This automatically allocates space for the list and puts in the elements. Haskell is garbage-collected like Java so no explicit de-allocation is needed. The type of the list is inferred automatically. All elements of a list must be of the same type.

Prelude> ["e", concat ["f", "g"], "h"]
["e","fg","h"]

Notice how the function call concat ["f","g"] does not require parenthesis to delimit the function's arguments. Haskell uses whitespace, and not commas, and:

  • You don't need parentheses for function application in Haskell: sin 0.3
  • Multiple arguments can be passed in one at a time (curried) which means they can be separated by spaces: max 3 4.

Lists must be uniform in their type ("homogeneous").

Prelude> ['x', True]

Couldn't match `Char' against `Bool'

Here we tried to build a list containing a Char and a Boolean, but the list constructor, [], has type:

Prelude> :t []
[] :: [a]

meaning that all elements must be of the same type, a. (For those wondering how to build a list of heterogeneous values, you would use a sum type):

Prelude> [Left 'x', Right True]
[Left 'x',Right True]

Prelude> :t [Left 'x', Right True]
[Left 'x', Right True] :: [Either Char Bool]

List operations are numerous, as can be seen in the Data.List library.

Prelude> let x = [2,3]
Prelude> let y = 1 : x  -- 'cons' the value 1 onto the list
Prelude> x              -- the list is immutable
[2,3]
Prelude> y
[1,2,3]
Prelude> x ++ y         -- joining lists
[2,3,1,2,3]
Prelude> head y         -- first element of the list is the 'head'
1
Prelude> tail y         -- the rest of the list is the 'tail'
[2,3]

Pattern matching

Haskell supports pattern matching on data structures. This is a powerful language feature, making code that manipulates data structures incredibly simple. The core language feature for pattern matching is the case expression:

Prelude> case x of h:t -> h
2

The case forces x (the scrutinee) to match pattern h:t, a list with head and tail, and then we extract the head, h. Tail is similar, and we can use a wildcard pattern to ignore the part of the pattern we don't care about:

Prelude> case x of _:t -> t
[3]

Tuples

Tuples are fixed length structures, whose fields may be of differing types ("heterogeneous"). They are known as product types in programming language theory.

Prelude> let x = (2, "hi")
Prelude> case x of (y,_) -> y
2

Unlike the ML family of languages, Haskell uses the same syntax for the value level as on the type level. So the type of the above tuple is:

Prelude> :t x
x :: (Integer, [Char])

All the data mentioned so far are immutable - it is impossible to change an entry in an existing list, tuple, or record without implicitly copying the data! Also, all variables are immutable. By default Haskell is a pure language. Side effects, such as mutation, are discussed later.

Functions

Here is a simple recursive factorial function definition.

Prelude> let fac n = if n == 0 then 1 else n * fac (n-1)

Prelude> :t fac
fac :: (Num a) => a -> a

Prelude> fac 42
1405006117752879898543142606244511569936384000000000

The function name is fac, and the argument is n. This function is recursive (and there is no need to specially tag it as such, as you would in the ML family of languages).

When you apply (or invoke) the fac function, you don't need any special parenthesis around the code. Note that there is no return statement; instead, the value of the whole body-expression is implicitly what gets returned.

Functions of more than one argument may be defined:

Prelude> let max a b = if a > b then a else b
Prelude> max 3 7
7

Other important aspects of Haskell functions:

  • Functions can be defined anywhere in the code via lambda abstractions:
Prelude> ((\x -> x + 1) 4) + 7
12

Or, identical to let f x = x + 1:

Prelude> let f = \x -> x + 1
Prelude> :t f
f :: Integer -> Integer

Anonymous functions like this can be very useful. Also, functions can be passed to and returned from functions. For example, the higher order function map, applies its function argument to each element of a list (like a for-loop):

Prelude> map (\x -> x ^ 2) [1..10]
[1,4,9,16,25,36,49,64,81,100]

In Haskell, we can use section syntax for more concise anonymous functions:

Prelude> map (^ 2) [1..10]
[1,4,9,16,25,36,49,64,81,100]

Here map takes two arguments, the function (^2) :: Integer -> Integer, and a list of numbers.

Currying

Currying is a method by which function arguments may be passed one at a time to a function, rather than passing all arguments in one go in a structure:

Prelude> let comb n m = if m == 0 || m == n then 1 else comb (n-1) m + comb (n-1) (m-1)

Prelude> comb 10 4
210

The type of comb, Num a => a -> a -> a, can be rewritten as Num a => a -> (a -> a). That is, it takes a single argument of some numeric type a, and returns a function that takes another argument of that type!

Indeed, we can give comb only one argument, in which case it returns a function that we can later use:

Prelude> let comb10 = comb 10
Prelude> comb10 4
210
Prelude> comb10 3
120

Mutually recursive functions may be defined in the same way as normal functions:

let take []      = []
         (x:xs)  = x : skip xs
    skip []      = []
         (_:ys)  = take ys

Prelude> :t take
take :: [a] -> [a]

Prelude> :t skip
skip :: [a] -> [a]

Prelude> take [1..10]
[1,3,5,7,9]

Prelude> skip [1..10]
[2,4,6,8,10]

This example also shows a pattern match with multiple cases, either empty list or nonempty list. More on patterns now.

Patterns

Patterns make function definitions much more succinct, as we just saw.

let rev []     = []
    rev (x:xs) = rev xs ++ [x]

In this function definition, [] and (x:xs) are patterns against which the value passed to the function is matched. The match occurs on the structure of the data -- that is, on its constructors.

Lists are defined as:

data [] a = [] | a : [a]

That is, a list of some type a has type [a], and it can be built two ways:

  • either the empty list, []
  • or an element consed onto a list, such as 1 : [] or 1 : 2 : 3 : [].
  • For the special case of lists, Haskell provides the syntax sugar: [1,2,3] to build the same data.

Thus, [] matches against the empty list constructor, and (x:xs), match against the cons constructor, binding variables x and xs to the head and tail components of the list.

Remember that case is the syntactic primitive for performing pattern matching (pattern matching in let bindings is sugar for case). Also, the first successful match is taken if more than one pattern matches:

case [1,2,3] of
    (x:y)   -> True
    (x:y:z) -> False
    []      -> True

Warning: Pattern match(es) are overlapped
         In a case alternative: (x : y : z) -> ...

True

Warnings will be generated at compile time if patterns don't cover all possibilities, or contain redundant branches.

Prelude> :set -Wall
Prelude> case [1,2,3] of (x:_) -> x

Warning: Pattern match(es) are non-exhaustive
         In a case alternative: Patterns not matched: []

1

An exception will be thrown at runtime if a pattern match fails:

Prelude> let myhead (x:_) = x

Warning: Pattern match(es) are non-exhaustive
         In a case alternative: Patterns not matched: []

Prelude> myhead []
*** Exception: <interactive>:1:16-36: Non-exhaustive patterns in case

As we have seen, patterns may be used in function definitions. For example, this looks like a function of two arguments, but its a function of one argument which matches a pair pattern.

Prelude> let add (x,y) = x + y
Prelude> add (2,3)
5

Immutable declarations

Immutable Declarations

  • Important feature of let-defined variable values in Haskell (and some other functional languages): they cannot change their value later.
  • Greatly helps in reasoning about programs---we know the variable's value is fixed.
  • Smalltalk also forces method arguments to be immutable; C++'s const and Java's final on fields has a similar effect.
let x = 5 in
    let f y = x + 1 in
        let x = 7 in f 0 -- f uses the particular x in lexical scope where it is defined 
6

Here's the one that will mess with your mind: the same thing as above but with the declarations typed into GHCi. (The GHCi environment conceptually an open-ended series of lets which never close).

Prelude> let x = 5
Prelude> let f y = x + 1
Prelude> f 0
6
Prelude> let x = 7  -- not an assignment, a new declaration
Prelude> f 0
6

Higher order functions

Haskell, like ML, makes wide use of higher-order functions: functions that either take other functions as argument or return functions as results, or both. Higher-order functions are an important component of a programmer's toolkit.

  • They allow "pluggable" programming by passing in and out chunks of code.
  • Many new programming design patterns are possible.
  • It greatly increases the reusability of code.
  • Higher-order + Polymorphic = Reusable

The classic example of a function that takes another function as argument is the map function on lists. It takes a list and a function and applies the function to every element of the list.

map :: (a -> b) -> [a] -> [b]
map _ []     = []
map f (x:xs) = f x : map f xs

The lower case variables in the type declaration of map are type variables, meaning that the function is polymorphic in that argument (can take any type).

Prelude> map (*10) [4,2,7]
[40,20,70]

Perhaps the simplest higher-order function is the composer, in mathematics expressed as g o f. it takes two functions and returns a new function which is their composition:

(.)   :: (b -> c) -> (a -> b) -> a -> c
(.) f g x = f (g x)

This function takes three arguments: two functions, f and g, and a value, x. It then applies g to x, before applying f to the result. For example:

Prelude> let plus3times2 = (*2) . (+3)
Prelude> plus3times2 10
26

As we have seen before, functions are just expressions so can also be immediately applied after being defined:

Prelude> ((*2) . (+3)) 10
26
Prelude> (.) (*2) (+3) 10
26

Note how Haskell allows the infix function . to be used in prefix form, when wrapped in parenthesis.

Currying

Currying is an important concept of functional programming; it is named after logician Haskell Curry, after which the languages Haskell and Curry are named! Multi-argument functions as defined thus far are curried, lets look at what is really happening.

Here is a two-argument function defined in our usual manner.

Prelude> let myadd x y = x + y
Prelude> myadd 3 4
7

Here is another completely equivalent way to define the same function:

Prelude> let myadd x = \y -> x + y
Prelude> :t myadd
myadd :: (Num a) => a -> a -> a

Prelude> myadd 3 4
7
Prelude> let inc3 = myadd 3
Prelude> inc3 4 
7

The main observation is myadd is a function returning a function, so the way we supply two arguments is

  • Invoke the function, get a function back
  • Then invoke the returned function passing the second argument.
  • Our final value is returned, victory.
  • (myadd 3) 4 is an inlined version of this where the function returned by myadd 3 is not put in any variable

Here is a third equivalent way to define myadd, as an anonymous function returning another anonymous function.

Prelude> let myadd = \x -> \y -> x + y
Prelude> :t myadd
myadd :: Integer -> Integer -> Integer

With currying, all functions "really" take exactly one argument. Currying also naturally arises when functions return functions, as in the map application above showed. Multiple-argument functions should always be written in curried form; all the library functions are curried.

Note thus far we have curried only two-argument functions; in general, n-argument currying is possible. Functions can also take pairs as arguments to achieve the effect of a two-argument function:

Prelude> let mypairadd (x,y) = x + y 
Prelude> mypairadd (2,3)
5

So, either we can curry or we can pass a pair. We can also write higher-order functions to switch back and forth between the two forms.

fst         :: (a,b) -> a
fst (x,_)   =  x

snd         :: (a,b) -> b
snd (_,y)   =  y

curry       :: ((a, b) -> c) -> a -> b -> c
curry f x y =  f (x, y)

uncurry     :: (a -> b -> c) -> ((a, b) -> c)
uncurry f p =  f (fst p) (snd p)

Prelude> :t uncurry myadd
uncurry myadd :: (Integer, Integer) -> Integer

Prelude> :t curry mypairadd
curry mypairadd :: Integer -> Integer -> Integer

Prelude> :t uncurry map
uncurry map :: (a -> b, [a]) -> [b]

Prelude> :t curry (uncurry myadd) -- a no-op
curry (uncurry myadd) :: Integer -> Integer -> Integer

Look at the types: these mappings in both directions in some sense "implement" the well-known isomorphism on sets: A * B -> C = A -> B -> C

A bigger example

Here is a more high-powered example of the use of currying.

foldr f []     y = y
foldr f (x:xs) y = f x (foldr f xs y)

*Main> :t foldr
foldr :: (a -> t -> t) -> [a] -> t -> t

*Main> let prod = foldr (\a x -> a * x)
*Main> :t prod
prod :: [Integer] -> Integer -> Integer

*Main> let prod0 = prod [1,2,3,4]
*Main> :t prod0
prod0 :: Integer -> Integer

*Main> (prod0 1, prod0 2)
(24,48)

Here is an analysis of this recursive function, for the arbitrary 2-element list [x1,x2], the call

foldr f [x1, x2] y

reduces to (by inlining the body of fold):

f x1 (foldr f [x2] y)

which in turn reduces to:

f x1 (f x2 (foldr f [] y)))

and then:

f x1 (f x2 y)

From this we can assert that the general result returned from foldr f [x1,x2,...,xn] y is f x1 (f x2 f ...(f xn y)...)))). Currying allows us to specialize foldr to a particular function f, as with prod above.

Proving program properties by induction

We should in fact be able to prove this property by induction. Its easier if we reverse the numbering of the list.

Lemma. foldr f [xn,...,x1] y evaluates to f xn (f xn-1 f ...(f x1 y)...))) for n greater than 0.

Proof. Proceed by induction on the length of the list [xn,..,x1].

Base Case n=1, i.e. the list is [x1]. The function reduces to f x1 (foldr f [] y) which reduces to f x1 y as hypothesized.

Induction Step. Assume

foldr f [xn,...,x1] y

reduces to

f xn (f xn-1  f ...(f x1 y)...)))

and show

foldr f [xn+1, xn,...,x1] y

reduces to

f xn+1 (f xn  f ...(f x1 y)...))))

Computing

foldr f [x1,x2,...,xn,xn+1] y

it matches the pattern with x being xn+1 and xs being [xn,...,x1]. Thus the recursive call is

foldr f [xn,...,x1] y

which by our inductive assumption reduces to

f xn (f xn-1  f ...(f x1 y)...)))

And, given this result for the recursive call, the whole function then returns

f xn+1 (...result of recursive call...)

which is

f xn+1 (f xn (f xn-1  f ...(f x1 y)...)))

which is what we needed to show. QED

The above implementation is inefficient in that f is explicitly passed to every recursive call. Here is a more efficient version with identical functionality.

foldr :: (a -> b -> b) -> b -> [a] -> b
foldr k z xs = go xs
  where
    go []     = z
    go (y:ys) = y `k` go ys

This function also illustrates how functions may be defined in a local scope, using where. Observe 'go' is defined locally but then exported since it is the return value of f.

Question: How does the return value 'go' know where to look for k when its called??

Prelude> let summate = foldr (+)
Prelude> summate [1,2,3,4] 0
10

summate is just go but somehow it "knows" that k is (+), even though k is undefined at the top level:

Prelude> k
<interactive>:1:0: Not in scope: `k'

go in fact knew the right k to call, so it must have been kept somewhere: in a closure. At function definition point, the current values of variables not local to the function definition are remembered in a structure called a closure. Function values in Haskell are thus really a pair consisting of the function (pointer) and the local environment, in a closure.

Without making a closure, higher-order functions will do awkward things (such as binding to whatever 'k' happens to be in scope). Java, C++, C can pass and return function (pointers), but all functions are defined at the top level so they have no closures.

Loading source from a file

You should never type large amounts of code directly into GHCi! Its impossible to fix errors. Instead, you should edit in a file. Usingg any editor, save each group of interlinked functions in a separate file, for example "A.hs". Then, from GHCi type:

Prelude> :l A.hs
*Main>

This will compile everything in the file.

Show

Haskell has the show function.

*Main> show 1
"1"
*Main> show (1,2,'x')
"(1,2,'x')"
*Main> show "haskell"
"\"haskell\""
*Main> show (Just ())
"Just ()"

It simply returns a string representation for its arguments.

Types

We have generally been ignoring the type system of Haskell up to now. Its time to focus on typing in more detail.

Type Declarations

Haskell infers types for you, but you can add explicit type declarations if you like.

let myadd :: Int -> Int -> Int
    myadd x y = x + y

*Main> :t myadd
myadd :: Int -> Int -> Int

*Main> :set -fglasgow-exts
let myadd (x :: Int) (y :: Int) = x + y

*Main> :t myadd
myadd :: Int -> Int -> Int

You can in fact put type assertions on any variable in an expression to clarify what type the variable has:

*Main> let myadd (x :: Int) (y :: Int) = (x :: Int) + y
*Main> :t myadd
myadd :: Int -> Int -> Int

Type synonyms

You can also make up your own name for any type. To do this, you must work in a separate file and load it into GHCi using the ":load A.hs" command.

type IntPair = (Int,Int)

f :: IntPair -> Int
f (l,r) = l + r

Working from GHCi:

f :: IntPair -> Int
*Main> :l A.hs
*Main> :t f
f :: IntPair -> Int
*Main> f (2,3)
5

Polymorphic Types and Type Inference

*Main> let id x = x
*Main> :t id
id :: forall t. t -> t
*Main> id 3
3
*Main> id True
True

Since id was not used as any type in particular, the type of the function is polymorphic ("many forms").

  • t is a type variable, meaning it stands for some arbitrary type.
  • Polymorphism is really needed with type inference -- inferring Int -> Int would not be completely general.

Parametric polymorphism

The form of polymorphism in Haskell is to be precise, parametric polymorphism. The type above is parametric in t: what comes out is the same type as what came in. Generics is another term for parametric polymorphism used in some communities.

  • Java has no parametric polymorphism, but does have object polymorphism (unfortunately this is often just called polymorphism by some writers) in that a subclass object can fit into a superclass-declared variable.
  • When you want parametric polymorphism in Java you declare the variable to be of type Object, but you have to cast when you get it out which requires a run-time check.
  • The Java JDK version 1.5 will have parametrically polymorphic types in it.

The general intuition to have about the type inference algorithm is everything starts out as having arbitrary types, t, u, etc, but then the use of functions on values generates constraints that "this thing has the same type as that thing".

Use of type-specific operators obviously restricts polymorphism:

*Main> let doublenegate x = not (not x)
*Main> :t doublenegate
doublenegate :: Bool -> Bool

When a function is defined via let to have polymorphic type, every use can be at a different type:

let id x = x
in case id True of
        True  -> id 3
        False -> id 4
3

Algebraic Data Types

Algebraic data types in Haskell are the analogue of union/variant types in C/Pascal. Following in the Haskell tradition of lists and tuples, they are not mutable. Haskell data types must be declared. Here is a really simple algebraic data type declaration to get warmed up, remember to write this in a separate file, and load it in to HHCi:

data Height = Tall | Medium | Short

Three constructors have been defined. These are now official constants. Constructors must be capitalized, and variables must be lower-case in Haskell.

*Main> :l A.hs
*Main> :t Tall
Tall :: Height
*Main> Tall

Top level:
    No instance for (Show Height)

So we can type check them, but can't show them yet. Let's derive the typeclass Show for our data type, which generates a 'show' function for our data type, which GHCi can then use to display the value.

data Height = Tall | Medium | Short
    deriving Show

*Main> :reload
*Main> Tall
Tall

The previous type is only an enumerated type. Much more interesting data types can be defined. Remember the (recursive) list type:

data [] a = [] | a : [a]

*Main> (:) 3 ((:) (3+1) [])
[3,4]
*Main> 3 : 3+1 : []
[3,4]

This form of type has several new features:

  • As in C/Pascal, the data types can have values and they can be recursively defined, plus,
  • Polymorphic data types can be defined; a here is a type argument.
  • Note how there is no need to use pointers in defining recursive variant types. The compiler does all that mucking around for you.
  • Also note how (:), the constructor, can be used as a function.

We can define trees rather simply:

data Tree a = Empty | Node a (Tree a) (Tree a)

Patterns automatically work for new data types.

Record Declarations

Records are data types with labels on fields. They are very similar to structs of C/C++. Their types are declared just like normal data types, and can be used in pattern matches.

data OneTwo = OneTwo { one :: Int, two :: String }
    deriving Show

*Main> let x = OneTwo { one = 2 , two = "ni" }
*Main> one x
2
*Main> case x of OneTwo { one = x, two = s } -> x
2

Imperative Programming

Haskell and OCaml differ on imperative programming: OCaml mixes pure and impure code, while Haskell separates them statically.

The expressions and functions for I/O, mutable states, and other side effects have a special type. They enjoy a distinguished status: they are I/O instructions, and the entry point of each complete program must be one of them. The following honours this distinction by using the word command for them (another popular name is action), though they are also expressions, values, functions.

Commands have types of the form IO a, which says it takes no parameter and it gives an answer of type a. (I will carefully avoid saying it “returns” type a, since “return” is too overloaded.) There are also functions of type b -> IO a, and I will abuse terminology and call this a command needing a parameter of type b, even though the correct description should be: a function from b to commands.

I/O

The command for writing a line to Standard Output is

putStrLn :: String -> IO ()

It outputs the string parameter, plus linebreak. And since there is no answer to give, the answer type is the most boring ().

At first, using output commands at the prompt is as easy as using expressions.

Prelude> putStrLn "Hello world"
Hello world

You can also write a compound command with the >> operator.

Prelude> putStrLn "Hello" >> putStrLn "world"
Hello
world

The fun begins when you also take input. The command for reading one line from Standard Input is:

getLine :: IO String

Note that the type is not String or ()->String. In a purely functional language, such types promise that all calls using the same parameter yield the exactly same string. This is of course what an input command cannot promise. If you read two lines, they are very likely to be different. The type IO String does not promise to give the same string all the time. (It only promises to be the same command all the time—a rather "duh" one.) But this poses a question: how do we get at the line it reads?

A non-solution is to expect an operation stripIO :: IO a -> a. What's wrong with this strip-that-IO mentality is that it asks to convert a command, which gives different answers at different calls, into a pure function, which gives the same answer at different calls. Contradiction!

But you can ask for a weaker operation: how to pass the answer on to subsequent commands (e.g., output commands) so they can use it. A moment of thought reveals that this is all you ever need. The operator sought is

(>>=) :: IO a -> (a -> IO b) -> IO b

It builds a compound command from two commands, the first one of which takes no parameter and gives an answer of type a, and the second of which needs a parameter of type a. You guessed it: this operator extracts the answer from the first command and passes it to the second. Now you have some way to use the answer!

Here is the first example. Why don't we read a line and immediately display it? getLine answers a string, and putStrLn wants a string. Perfect match!

Prelude> getLine >>= putStrLn
Good morning
Good morning

But more often you want to output something derived from the input, rather than the input itself verbatim. To do this, you customize the second command to smuggle in the derivation. The trick of anonymous functions is very useful for this:

Prelude> getLine >>= \s -> putStrLn ("You entered: " ++ s)
Good morning
You entered: Good morning

You will also want to give derived answers, especially if you write subroutines to be called from other code. This is facilitated by the command that takes a parameter and simply gives it as the answer (it is curiously named return):

return :: a -> IO a

For example here is a routine that reads a line and answers a derived string, with a sample usage:

Prelude> let mycmd = getLine >>= \s -> return ("You entered: " ++ s)
Prelude> mycmd >>= putStrLn
Good morning
You entered: Good morning

Some programmers never use Standard Input. Reading files is more common. One command for this is:

readFile :: String -> IO String

The parameter specifies the file path. Let us read a file and print out its first 10 characters (wherever available). Of course please change the filename to refer to some file you actually possess.

Prelude> readFile "file.txt" >>= \s -> putStrLn (take 10 s)
abcdefghij

Do not worry about slurping up the whole file into memory; readFile performs a magic of pay-as-you-go reading.

A while ago I showed the >> operator for compound commands without elaboration. I can now elaborate it: it merely uses >>= in a way that throws away the first answer:

    putStrLn "x" >> putStrLn "y"
  = putStrLn "x" >>= \_ -> putStrLn "y"

do-Notation

To bring imperative code closer to imperative look, Haskell provides the do-notation, which hides the >>= operator and the anonymous functions. An example illustrates this notation well, and it should be easy to generalize:

  cmd0 >>= \x -> cmd1 >>= \_ -> cmd2 >>= \z -> cmd3
= do { x <- cmd0; cmd1; z <- cmd2; cmd3 }

(cmd1, cmd2, and cmd3 may use x as a parameter; similarly, cmd3 may use z as a parameter. At the end, between cmd3 and }, you may choose to insert or omit semicolons; similarly right after { at the beginning.)

Below we re-express examples in the previous section in the do-notation.

Prelude> do { putStrLn "Hello"; putStrLn "world" }
Hello
world

Prelude> do { s <- getLine; putStrLn s }
Good morning
Good morning

Prelude> do { s <- getLine; putStrLn ("You entered: " ++ s) }
Good morning
You entered: Good morning

Prelude> let mycmd = do { s <- getLine; return ("You entered: " ++ s) }
Prelude> do { s <- mycmd; putStrLn s }
Good morning
You entered: Good morning

Prelude> do { s <- readFile "file.txt"; putStrLn (take 10 s) }
abcdefghij

At the prompt it is necessary to write one-liners. In a source code file it is more common to use multiple lines, one line for one command, as per tradition. In this case, layout rules allow omitting {;} in favour of indentation. Thus, here are two valid ways of writing the same do-block in a source code file, one with {;} and the other with layout.

foo = do { name <- getLine;         foo = do name <- getLine
           s <- readFile name;               s <- readFile name
           putStrLn (take 10 s)              putStrLn (take 10 s)
         }

Mutable variables

Data.IORef Data.Array.MArray Data.Array.IO

Exceptions

Control.Exception

Concurrency

Control.Concurrent Control.Concurrent.MVar

Monads

Mutable variables

Data.STRef Data.Array.MArray Data.Array.ST

State

The State monad

Monad transformers

Compilation

You can easily compile your Haskell modules to standalone executables. For example, write this in a file "A.hs":

main = putStrLn "Hello, World!"

In general, main is the entry point, and you must define it to be whatever you want run. (TODO: once the monad/IO section is done, this place should also say more about main and IO.)

The compiler, on unix systems, is ghc. For example "A.hs" can be compiled and run as:

   $ ghc A.hs
   $ ./a.out 
   Hello, World!

For multiple modules, use the --make flag to GHC. Example: write these two modules:

B.hs:

import M1
main = putStrLn s

M1.hs:

module M1 where
s = "Hi, Everyone!"

To compile and run (this will automatically look for M1.hs):

   $ ghc --make B.hs
   $ ./a.out
   Hi, Everyone!

In general, one and only one file must define main. In general, for all other files, the filename must match the module name.