Index | Part 1 | Part 2 | Submit | Results | My status | Statistics | Login
by Joel Kaasinen (Nitor) and John Lång (University of Helsinki)
Beware! This is a preview of part 2 of the course. It contains lectures 9 to 13. Further lectures will be added before the course is ready. The material presented here is roughly ready, and shouldn’t change too much. However, you should know that:
Enjoy!
This lecture goes over the basic parts of Haskell introduced in part 1 of the course: types, values, pattern matching, functions and recursion.
Remember the primitive types of Haskell? Here they are:
Values | Type | Meaning |
---|---|---|
True , False |
Bool |
Truth values |
0 , 1 , 20 , -37 , … |
Int |
Whole numbers |
'A' , 'a' , '!' , … |
Char |
Characters |
"" , "abcd" , … |
String |
Strings, which are actually just lists of characters, [Char] |
0.0 , -3.2 , 12.3 , … |
Double |
Floating-point numbers |
() |
() |
The so called unit type with only one value |
It’s possible to combine these primitive types in various ways to form more complex types. Function types, tuple types and list types are examples of types that combine other types.
Values | Type | Meaning |
---|---|---|
(1,2) , (True,'c') , … |
(a, b) |
A pair of a value of type a and a value of type b |
(1,2,3) , (1,2,'c') , … |
(a, b, c) |
A triple of values (of types a , b and c ) |
[] , [1,2,3,4] , … |
[a] |
List of values of type a |
not , reverse , \x -> 1 , \x -> x , … |
a -> b |
Function from type a to type b |
There’s one more powerful mechanism for creating more types: Algebraic datatypes (ADTs). Some examples include:
-- Enumeration types
data Bool = True | False
data Color = Red | Green | Blue
-- Record types that contain fields
data Vector2d = MakeVector Double Double
data Person = Person Int String
-- Parameterized types. Note the type parameter `a`
data PairOf a = TwoValues a a
-- Recursive types
data IntList = Empty | Node Int IntList
-- Complex types which combine many of these features
data Maybe a = Nothing | Just a
data Either a b = Left a | Right b
data List a = Nil | Cons a (List a) -- This is equivalent to the built-in [a] type
data Tree a = Leaf a | Node a (Tree a) (Tree a)
data MultiTree a = MultiTree a [RoseTree a] -- Note the list
Values of these types include:
Values | Type |
---|---|
True , False |
Bool |
Red , Green , Blue |
Color |
MakeVector 1.5 3.2 |
Vector2d |
Person 13 "Bob" |
Person |
TwoValues 1 3 |
PairOf Int |
Empty , Node 3 (Node 4 Empty) |
IntList |
Nothing , Just 3 , Just 4 , … |
Maybe Int |
Nothing , Just 'c' , Just 'd' , … |
Maybe Char |
Left "foo" , Right 13 , … |
Either String Int |
Nil , Cons True Nil , Const True (Cons False Nil) … |
List Bool |
Leaf 7 , Node 1 (Leaf 0) (Leaf 2) , … |
Tree Int |
MultiTree 'a' [MultiTree 'b' [], MultiTree 'c' []]] , … |
MultiTree Char |
You can combine parameterized types in complex ways, for example with something like Either [String->String] (Maybe String, Int)
.
The names of concrete types start with capital letters. Lowercase letters are used for type variables which indicate parametric polymorphism: functions and values that can have multiple types. Here are some examples of polymorphic function types:
[a] -> [a] -- function from list of any type, to list of the same type
[a] -> a -- function from list of any type, to the element type
(a,b) -> [a] -- function from tuple to list
List literals can be written in using the familiar [x,y,z]
syntax. However, lists are actually built up of the list constructors []
and (:)
. These constructors are also used when pattern matching lists as we’ll see next. Here are some examples of lists:
Abbreviation | Full list | Type |
---|---|---|
[1,2,3] |
1:2:3:[] |
[Int] |
[[1],[2],[3]] |
(1:[]):(2:[]):(3:[]):[] |
[[Int]] |
"foo" |
'f':'o':'o':[] |
[Char] , also known as String |
There’s also a range syntax for lists:
Range | Result |
---|---|
['a' .. 'z'] |
"abcdefghijklmnopqrstuvwxyz" |
[0 .. 9] |
[0,1,2,3,4,5,6,7,8,9] |
[0, 5 .. 25] |
[0,5,10,15,20,25] |
[min .. max] |
everything from min to max |
[9 .. 3] |
[] |
[max, max-1 .. min] |
everything from max to min in decreasing order |
[9,8 .. 3] |
[9,8,7,6,5,4,3] |
List comprehensions are another way for create lists:
Comprehension | Result |
---|---|
[x^3 | x <- [1..3]] |
[1,8,27] |
[x^2 + y^2 | x <- [1..3], y <- [1..2]] |
[2,5,5,8,10,13] |
[y | x <- [1..10], let y = x^2, even x, y<50] |
[4,16,36] |
[c | c <- "Hello, World!", elem c ['a'..'z']] |
"elloorld" |
In general, [f x | x <- xs, p x]
is the same as map f (filter p xs)
. Also, [y | x <- xs, let y = f x]
is the same as [f x | x <- xs]
. Any combination of <-
, let
and [f x | ...]
is possible.
The basic form of function definition is:
For example:
Functions taking multiple arguments are defined in a similar manner. Note how the type of a multi-argument function looks like.
Functions can be polymorphic, can take multiple arguments, and can even take functions as arguments. Here are more examples:
id :: a -> a
id x = x
const :: a -> b -> a
const x y = x
flip :: (a -> b -> c) -> b -> a -> c
flip f x y = f y x
More sophisticated functions can be defined using pattern matching. We can pattern match on the constructors of algebraic datatypes like Nothing
, []
and (:)
.
swap :: (a,b) -> (b,a)
swap (x,y) = (y,x)
maybe :: b -> (a -> b) -> Maybe a -> b
maybe def _ Nothing = def
maybe _ f (Just x) = Just (f x)
safeHead :: [a] -> Maybe a
safeHead [] = Nothing
safeHead (x:_) = Just x
Yet more sophistication can be achieved with guards. Guards let you define a function case-by-case based on tests of type Bool
. Guards are useful in situations where pattern matching can’t be used. Of course, guards can also be combined with pattern matching:
myAbs :: Int -> Int
myAbs x
| x < 0 = -x
| otherwise = x
safeDiv :: Double -> Double -> Maybe Double
safeDiv x y
| y == 0 = Nothing
| otherwise = Just (x / y)
buy :: String -> Double -> String
buy "Banana" money
| money < 3.2 = "You don't have enough money for a banana"
| otherwise = "You bought a banana"
buy product _ = "No such product: " ++ product
Case expressions let us pattern match inside functions. They are useful in situations where the result of one function depends on the result of another and we want to match the pattern on the output of the other function:
divDefault :: Double -> Double -> Double -> Double
divDefault x y def = case safeDiv x y of
Nothing -> def
Just w -> w
Let-expressions enable local definitions. Where-clauses work similarly to let
s. For example:
circleArea :: Double -> Double
circleArea r = let pi = 3.1415926
square x = x * x
in pi * square r
circleArea' :: Double -> Double
circleArea' r = pi * square r
where pi = 3.1415926
square x = x * x
Lambda expressions are another occasionally useful syntax for defining functions. Lambda expressions represent anonymous (unnamed) functions. They can be used for defining local functions that are typically used only once.
Note that f x = y
is the same thing as f = \x -> y
.
Finally, binary operators have sections. Sections are partially applied operators. The section of an operator is obtained by writing the operator and one of its arguments in parentheses. For example, (*2)
multiplies its argument by 2
from the right, e.g. (*2) 5 ==> 5 * 2
. A fractional number (e.g. a Double
) can be inverted with the section (1/)
, e.g. (1/) 2 ==> 0.5
.
Haskell is a functional programming language, which means that functions can be passed in as arguments and returned from functions. As a programming paradigm, functional programming aims to build programs by combining simple functions together to form larger and larger ones.
The most often presented example of functional programming is functional list manipulation using higher-order functions (functions that take functions as arguments) like map
and filter
. Here’s one example from part 1:
-- a predicate that checks if a string is a palindrome
palindrome :: String -> Bool
palindrome str = str == reverse str
-- palindromes n takes all numbers from 1 to n, converts them to
-- strings using show, and keeps only palindromes
palindromes :: Int -> [String]
palindromes n = filter palindrome (map show [1..n])
palindromes 150
==> ["1","2","3","4","5","6","7","8","9",
"11","22","33","44","55","66","77","88","99",
"101","111","121","131","141"]
We also encountered other functional programming patterns in part 1, like partial application:
Also, function composition:
(map reverse . filter (/="Smith")) ["Jones","Smith","White"]
==> ["senoJ","etihW"]
map (negate . sum) [[1,2,3],[5]]
==> [-6,-5]
And finally, folds:
To implement a function that uses repetition in Haskell, you need recursion. Haskell has no loops like other programming languages. Here are some simple recursive functions in Haskell:
repeatString :: String -> Int -> String
repeatString 0 s = ""
repeatString n s = s ++ repeatString (n-1) s
times :: Int -> Int -> Int
times 0 n = n
times 1 n = n
times m n = n * times (m - 1) n
safeLast :: [a] -> Maybe a
safeLast [] = Nothing
safeLast [x] = Just x
safeLast (x:xs) = safeLast xs
To consume or produce a list you often need recursion. Here are the implementations of map
and filter
as examples of recursive list processing:
map :: (a -> b) -> [a] -> [b]
map _ [] = []
map f (x:xs) = f x : map f xs
filter :: (a -> Bool) -> [a] -> [a]
filter _ [] = []
filter pred (x:xs)
| pred x = x : filter pred xs
| otherwise = filter pred xs
Sometimes, a recursive helper function is needed in case you need to keep track of multiple pieces of data.
sumNumbers :: [Int] -> Int
sumNumbers xs = go 0 xs
where go sum [] = sum
go sum (x:xs) = go (sum+x) xs
Here’s a final example utilizing guards, pattern matching, a helper function and recursion:
-- split a string into pieces at the given character
mySplit :: Char -> String -> [String]
mySplit c xs = helper [] xs
where helper piece [] = [piece]
helper piece (y:ys)
| c == y = piece : helper [] ys
| otherwise = helper (piece++[y]) ys
The following functions are parametrically polymorphic:
Parametrically polymorphic functions always work the same way, no matter what types we’re working with. This means that we can’t define a special implementation of id
just for the Int
type, or fst
for the type (Bool, String)
.
By contrast, ad hoc polymorphism allows different types to have different implementations of the same function. Ad hoc polymorphism in Haskell can be achieved by defining a type class and then declaring instances of that type class for various types. Ad hoc polymorphism is a handy way for expressing a common set of operations, even when the implementation of the operations depends on the type they’re acting on.
Functions that use ad hoc polymorphism have a class constraint in their types. Here are some examples:
A type like Num a => a -> a
means: for any type X
that’s a member of the Num
class, this function has type X -> X
. In ther words, we can invoke negate
on any number type, but not on other types:
Prelude> negate 1
-1
Prelude> negate 1.0
-1.0
Prelude> negate True
<interactive>:3:1: error:
• No instance for (Num Bool) arising from a use of ‘negate’
Here’s a summary of some useful type classes from the standard library.
Eq
is for equality comparison. It contains the ==
operatorOrd
is for order comparison. It contains the ordered comparison operators like <
and =>
, and functions like max
and min
.Num
is for all number types. It contains +
, -
, *
and negate
.Integral
is for whole number types. Most notably, it contains integer division div
.Fractional
is for number types that support division, /
Show
contains the function show :: Show a => a -> String
that converts values to stringsRead
contains the function read :: Read a => String -> a
that is the inverse of show
Sometimes, multiple class constraints are needed. For instance here:
Now that we’ve seen some classes and types, let’s look at the syntax of declaring classes and instances. Here are two class definitions:
class Sized a where
empty :: a -- a thing with size 0
size :: a -> Int
class Eq a where
(==) :: a -> a -> Bool
Consider the following data structures:
data Numbers = None | One Int | Two Int Int
data IntList = Nil | ListNode Int IntList
data Tree a = Leaf | Node a (Tree a) (Tree a)
All of these have sizes that we can count, but we need to perform the operation differently:
instance Sized Numbers where
empty = None
size None = 0
size (One _) = 1
size (Two _ _) = 2
instance Sized IntList where
empty = Nil
size Nil = 0
size (ListNode _ list) = 1 + size list
instance Sized (Tree a) where
empty = Leaf
size Leaf = 0
size (Node _ left right) = 1 + size left + size right
We can also easily declare Eq
instances for Numbers
and IntList
:
instance Eq Numbers where
None == None = True
(One x) == (One y) = x==y
(Two x y) == (Two z w) = x==z && y==w
_ == _ = False -- to handle cases like None == One 1
instance Eq IntList where
Nil == Nil = True
(ListNode x xs) == (ListNode y ys) = x == y && xs == ys
_ == _ = False
However, since the Tree
datatype is parameterized over the element type a
, we need an Eq a
instance in order to have an Eq (Tree a)
instance. This is achieved by adding a class constraint to the instance declaration. This is called an instance hierarchy.
instance Eq a => Eq (Tree a) where
Leaf == Leaf = True
(Node x l r) == (Node x' l' r') = x == x' && l == l' && r == r'
_ == _ = False
Some standard type classes, most notably Show
, Read
, Eq
and Ord
can be derived, that is, you can ask the compiler to generate automatic instances for you. For example we could have derived all of these classes for our earlier Numbers
example.
None == One 1 ==> False
Two 1 2 == Two 1 2 ==> True
None < Two 1 2 ==> True
Two 1 3 < Two 1 2 ==> False
show (Two 1 3) ==> "Two 1 3"
What is the type of ('c',not)
[Char]
[Bool]
(Char,Bool -> Bool)
(Char,Bool)
What is the type of ['c',not]
[Char]
[Bool]
(Char,Bool -> Bool)
(Char,Bool)
Which of these is a value of the following type?
X "foo"
Y "foo"
Z (X 1)
X (Z 1)
What is the type of this function?
Maybe a -> a
[Maybe a] -> a
[Maybe a] -> Bool
[Maybe Bool] -> Bool
What is the type of this function?
Num a => a -> a -> Bool
Eq a => a -> a -> Bool
a -> a -> Bool
Purity and laziness were mentioned as key features of Haskell in the beginning of part 1. Let’s take a closer look at them.
Haskell is a pure functional language. This means that the value f x y
is always the same if the values x
and y
are the same. This property is also called referential transparency.
Purity also means that there are no side effects: you can’t have the evaluation of f x y
read a line from the user - the line would be different on different invocations of f
and would affect the return value, breaking referential transparency! Obviously you need side effects to actually get something done. We’ll get back to how Haskell handles side effects later.
Haskell is a lazy language. This means that a value is not evaluated if it is not needed. An example illustrates this best. Consider these two functions:
Evaluating f 1
does not halt due to the infinite recursion. However, this works:
Laziness is not a problem because Haskell is pure. Only the result of the function matters, not the side effects. So if the result of a function is not used, we can simply not evaluate it without changing the meaning (semantics) of a program. Well okay, sometimes we get a terminating program instead of one that goes on for ever, but adding laziness never makes a functioning Haskell program break.
If you’re interested in the theory behind this, check out the Church-Rosser theorem or the Haskell Wiki article Lazy vs. non-strict.
Referential transparency, the feature that an expression always returns the same value for the same inputs, is a very powerful property that we can leverage to reason about programs.
In a C-style language, we might write a procedure that may not always return the same value for the same arguments:
int c = 0;
int funny(int x) {
return x + c++;
}
The expression c++
increments the value of c
and returns the old value of c
. The next time it is evaluated, the value of c
has increased by one. This means that depending on the current value of c
, funny(0)
might return 0
, 1
, 2
, or any other integer value. (It might even return negative values if c
overflows!)
In some situations this kind of behaviour with side-effects may be useful, but there are also times when it is more important to be able to reason about the code easily. The advantage of pure functions is that they can be analyzed using basic mathematical techniques. Sometimes applying math to our functions can even reveal simplifications or optimisations we otherwise wouldn’t have thought about.
Consider the following expression:
This expression can be simplified to just reverse
. We begin by establishing some helpful facts (or lemmas). First, suppose that we know
map id === id
map f . map g === map (f.g)
reverse . map f === map f . reverse
The fourth fact that we’re going to need is the following:
(+1) . (-1) === id
We can prove fact 4 by reasoning about how (+1) . (-1)
behaves for an arbitrary input x
:
Because we didn’t assume anything about x
, we may conclude that the above chain of equations holds for all x
s. Thus,
For those who are familiar with the technique of proof by induction, it is a fun exercise to prove the first three facts also. This course doesn’t discuss induction proofs, though, so don’t sweat if you don’t know induction.
Now, from facts 1-4 it follows that
map (+1) . reverse . map (-1)
=== map (+1) . (reverse . map (-1)) -- By associativity of (.)
=== map (+1) . (map (-1) . reverse) -- By fact 3
=== (map (+1) . map (-1)) . reverse -- By associativity of (.)
=== map ((+1) . (-1)) . reverse -- By fact 2
=== map id . reverse -- By fact 4
=== id . reverse -- By fact 1
=== reverse -- By the definition of id
This course won’t go into detail about proving things about programs, but it’s good to know that pure functional programming is very compatible with analysis like this.
The benefits of laziness are best demonstrated with some examples involving infinite lists. Let’s start with repeat 1
, which generates an infinite list of 1
s. If we try to tell GHCi to print the value repeat 1
, it will just keep printing 1
s for ever until we interrupt it using Control-C:
However, due to laziness, we can work with infinite lists and write computations that end. We just need to use a finite number of elements from the infinite list. Here are some examples:
Prelude> take 10 $ repeat 1
[1,1,1,1,1,1,1,1,1,1]
Prelude> take 20 $ repeat 1
[1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1]
Prelude> repeat 1 !! 13337
1
An infinite list that just repeats one element can sometimes be necessary, but it’s kind of pointless. Let’s look at some more useful infinite lists next. You can use the [n..]
syntax to generate an infinite list of numbers, starting from n
:
Prelude> take 20 [0..]
[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19]
Prelude> take 10 . map (2^) $ [0..]
[1,2,4,8,16,32,64,128,256,512]
The function cycle
repeats elements from the given list over and over again. It can be useful when dealing with rotations or cycles.
Prelude> take 21 $ cycle "asdf"
"asdfasdfasdfasdfasdfa"
Prelude> take 4 . map (take 4) . tails $ cycle "asdf"
["asdf","sdfa","dfas","fasd"]
As a more concrete example of how cycle
is useful, let’s look at computing the check digit of Finnish bank transfer transaction numbers (viitenumero). A transaction number consists of any number of digits, followed by a single check digit. The check digit is checked by multiplying the digits (from right to left) with the numbers 7, 3, 1, 7, 3, 1 and so on, and summing the results. If the result of the sum plus the check digit is divisible by 10, the number is valid.
Here’s a concrete example. 116127
is a valid transaction number. The computation goes like this:
digits: 1 1 6 1 2
* * * * *
multipliers: 3 7 1 3 7
3+ 7+ 6+ 3+14 = 33
check digit is 7, 33+7=40 is divisible by 10, valid
Here’s the Haskell code for a transaction number checker. Note how we use use the infinite list cycle [7,3,1]
for the multipliers.
viitenumeroCheck :: [Int] -> Bool
viitenumeroCheck allDigits = mod (checksum+checkDigit) 10 == 0
where (checkDigit:digits) = reverse allDigits
multipliers = cycle [7,3,1]
checksum = sum $ zipWith (*) multipliers digits
Finally, here’s how you would find the first power of 3 that’s larger than 100.
Let’s go through how this works step by step. Note how map and filter are processing the list lazily, one element at a time, as needed. This is similar to how generators or iterators work in languages like Python or Java.
head (filter (>100) (map (3^) [0..]))
==> head (filter (>100) (map (3^) (0:[1..]))) -- evaluate first element of the lazy list
==> head (filter (>100) (1 : map (3^) [1..])) -- map processes the element
==> head (filter (>100) (map (3^) [1..])) -- filter drops the element
==> head (filter (>100) (map (3^) (1:[2..]))) -- evaluate second element of the lazy list
==> head (filter (>100) (3 : map (3^) [2..])) -- map processes the element
==> head (filter (>100) (map (3^) [2..])) -- filter drops the element
-- let's take bigger steps now
==> head (filter (>100) (9 : map (3^) [3..])) -- map processes, filter will drop
==> head (filter (>100) (27 : map (3^) [4..])) -- map processes, filter will drop
==> head (filter (>100) (81 : map (3^) [5..])) -- map processes, filter will drop
==> head (filter (>100) (243 : map (3^) [6..])) -- map processes
==> head (243 : filter (>100) (map (3^) [6..])) -- filter lets the value through
==> 243 -- head returns the result
Laziness will probably feel a bit magical to you right now. You might wonder how it can be implemented. Haskell evaluation is remarkably simple, it’s just different than what you might be used to. Let’s dig in.
In most other programming languages (like Java, C or Python), evaluation proceeds inside-out. Arguments to functions are evaluated before the function.
Haskell evaluation proceeds outside-in instead of inside-out. The definition of the outermost function in an expression is applied without evaluating any arguments. Here’s a concrete example with toy functions f
and g
:
Inside-out (normal) evaluation:
f 1 (1234*1234) 2
-- evaluate arguments to f
==> f 1 1522756 2
-- evaluate f
==> g (1*1000) 2
-- evaluate arguments to g
==> g 1000 2
-- evaluate g
==> 2+1
==> 3
Haskell outside-in evaluation:
f 1 (1234*1234) 2
-- evaluate f without evaluating arguments
==> g (1*1000) 2
-- evaluate g without evaluating arguments
==> 2+1
==> 3
Note how the unused calculations 1234*1234
and 1*1000
didn’t get evaluated. This is why laziness is often helpful.
Let’s look at a more involved example, with pattern matching and more complex data (lists). Pattern matching drives Haskell evaluation in a very concrete way, as we’ll see. Here are some functions that we’ll use. They’re familiar from the Prelude, but I’ll give them simple definitions.
not True = False
not False = True
map f [] = []
map f (x:xs) = f x : map f xs
length [] = 0
length (x:xs) = 1+length xs
Here’s the inside-out evaluation of an expression:
length (map not (True:False:[]))
==> length (not True : not False : []) -- evaluate call to map
==> length (False:True:[]) -- evaluate calls to not
==> 2
Here’s how the evaluation proceeds in Haskell. Note how it’s not strictly outside-in, since we sometimes need to evaluate inside arguments to be able to know which pattern is matched.
length (map not (True:False:[]))
-- We can't evaluate length since we don't know which equation of length applies,
-- so we look at length's argument. We can apply the second equation of map, so we do.
==> length (not True : map not (False:[]))
-- Now the argument of length has a (:) we can pattern match on, so we apply the
-- second equation of length
==> 1 + length (map not (False:[]))
-- The outermost function is now +, but it can't do anything unless both arguments
-- are numbers. So we need to evaluate length. In order to pick an equation, we need
-- to evaluate the argument of length again. We apply the second equation of map
==> 1 + length (not False : map not ([]))
-- Now we can apply the second equation of length again.
==> 1 + (1 + length (map not []))
-- The outermost + needs a number to be evaluated. The second + also needs a number.
-- We need to evaluate length again, which means we need to pick an equation for length,
-- which means we need to evaluate its argument. This time it is the first equation for
-- map that applies.
==> 1 + (1 + length [])
-- Now we can apply the first equation for length
==> 1 + (1 + 0)
-- The outermost + still can't be evaluated, but the inner one can
==> 1 + 1
-- Finally we evaluate the outer +
==> 2
Note that we didn’t need to evaluate any of the not
applications.
Let’s introduce some terminology. We say that pattern matching forces evaluation. When Haskell evaluates something, it evaluates it to something called weak head normal form (WHNF). WHNF basically means a value that can be pattern matched on. An expression is in WHNF if it can’t be evaluated on its top level. This means it either:
1
False
, Just (1+1)
, 0:filter f xs
(\x -> 1+x)
The most notable class of expressions that is not in WHNF is function applications. If an expression consists of a function (that is not a constructor), applied to some arguments, it is not in WHNF. We must evaluate it in order to get something pattern matchable.
In the previous example we couldn’t evaluate length (map not (False:[]))
at the top level because the argument to length
wasn’t in WHNF. When we apply the second equation of map
, we get length (not False : map not [])
, and now the argument to length is in WHNF since there is a constructor, (:)
, at the top level. This is a bit more evident if we switch from infix to prefix notation and write the argument to length
as (:) (not False) (map not [])
.
In practice, pattern matching is not the only thing that forces evaluation. Primitives like (+)
also force their arguments.
Instead of forcing, some sources talk about strictness, we can say for instance that (+)
is strict in both arguments.
There’s one more thing about Haskell evaluation. Any time you give a value a name, it gets shared. This means that every occurrence of the name points at the same (potentially unevaluated) expression. When the expression gets evaluated, all occurrences of the name see the result.
Let’s look at a very simple example.
Based on the previous sections, you might imagine evaluation works like the following. The evaluation is first represented textually, and then visually, as an expression tree.
square (2+2)
==> (2+2) * (2+2) -- definition of square
==> 4 * (2+2) -- (*) forces left argument
==> 4 * 4 -- (*) forces right argument
==> 16 -- definition of (*)
However, what really happens is that the expression 2+2
named by the variable x
is only computed once. The result of the evaluation is then shared between the two occurrences of x
inside square
. So here’s the correct evaluation, first textually, and then visually. Note how now instead of an expression tree, we have an expression graph. This is why Haskell evaluation is sometimes called graph reduction.
As another example, consider the function f
below and its evaluation.
_______shared________
| |
f (1+1) ==> if (1+1)>10 then 10 else (1+1)
==> if 2>10 then 10 else 2
==> if False then 10 else 2
==> 2
Haskell does not compute 1+1
twice because it was named, and the name was used twice. We can contrast this with another function that takes two arguments:
______no sharing_____
| |
g (1+1) (1+1) ==> if (1+1)>10 then 10 else (1+1)
==> if 2>10 then 10 else (1+1)
==> if False then 10 else (1+1)
==> (1+1)
==> 2
Here we have two different names for equivalent expressions, and Haskell doesn’t magically share them. Automatically sharing equivalent expressions is an optimization called Common Subexpression Elimination (CSE). You can learn a bit more CSE and Haskell here.
You can name things via
let ... in ...
where
Combined with laziness, sharing means that a name gets evaluated at most once.
You’ll find below a slightly contrived recursive definition of the function even
. It will illustrate the concepts of forcing and sharing.
not :: Bool -> Bool
not True = False
not False = True
(||) :: Bool -> Bool -> Bool
True || _ = True
_ || x = x
even :: Int -> Bool
even x = x == 0 || not (even (x-1))
Firstly, note that ||
forces its left argument, but not its right argument. (In other words, ||
is strict in its left argument.) This is because we only need to evaluate the left argument of ||
in order to know which equation applies. This means by extension that even
forces its first argument:
||
forces x==0
x==0
forces x
Now let’s evaluate the expression even 2
to WHNF.
even 2
==> 2 == 0 || not (even (2-1)) -- apply definition of even
==> False || not (even (2-1)) -- || forces its first argument
==> not (even (2-1)) -- second equation of ||
==> not ((2-1) == 0 || not (even ((2-1)-1))) -- not forces its argument: apply definition of even
==> not ( 1 == 0 || not (even ( 1 -1))) -- note sharing!
==> not ( False || not (even (1-1)))
==> not (not (even (1-1)))
==> not (not ((1-1) == 0 || not (even ((1-1)-1))))
==> not (not ( 0 == 0 || not (even ( 0 -1)))) -- (sharing)
==> not (not ( True || not (even (0-1))))
==> not (not True)
==> not False
==> True
Note that with this alternate definition even
would not have worked. Can you tell why?
Now we can really understand what’s going on in the infinite list example from earlier. Let’s use these definitions:
head (x:_) = x
head [] = -1
filter p [] = []
filter p (x:xs) = if p x
then x : filter p xs
else filter p xs
map f [] = []
map f (x:xs) = f x : map f xs
-- [0..] is syntax sugar for enumFrom 0
enumFrom n = n : enumFrom (n+1)
And here we go:
head (filter (>100) (map (3^) [0..]))
=== head (filter (>100) (map (3^) (enumFrom 0)))
-- head forces filter, which forces map, which forces enumFrom. We apply the definition of enumFrom.
==> head (filter (>100) (map (3^) (0:[1..])))
-- head forces filter, which forces map. We apply the second equation of map.
==> head (filter (>100) ((3^0) : map (3^) [1..]))
-- head forces filter. We apply the second equation of filter
==> head (if ((3^0)>100)
then (3^0) : filter (>100) (map (3^) [1..])
else filter (>100) (map (3^) [1..]))
-- head forces if, if forces >, > forces ^. Note sharing!
==> head (if (1>100)
then 1 : filter (>100) (map (3^) [1..])
else filter (>100) (map (3^) [1..]))
-- head forces if, if forces >
==> head (if False
then 1 : filter (>100) (map (3^) [1..])
else filter (>100) (map (3^) [1..]))
-- apply definition of if
==> head (filter (>100) (map (3^) [1..]))
-- let's take slightly bigger steps now
==> head (filter (>100) (map (3^) (1:[2..])))
==> head (filter (>100) ((3^1) : map (3^) [2..]))
==> head (filter (>100) (3 : map (3^) [2..]))
==> head (filter (>100) (map (3^) [2..]))
-- and even bigger steps now
==> head (filter (>100) (9 : map (3^) [3..]))
==> head (filter (>100) (27 : map (3^) [4..]))
==> head (filter (>100) (81 : map (3^) [5..]))
==> head (filter (>100) (243 : map (3^) [6..]))
==> head (243 : filter (>100) (map (3^) [6..]))
==> 243
Whew.
Functions that work with lists often have the best performance when they’re written in such a way that they utilize laziness. One way to try to accomplish this is to write list-handling functions that work well with infinite lists.
To write a function that transforms an infinite list, you need to write a function that only looks at a limited prefix of the input list, then outputs a (:)
constructor, and then recurses. Here’s a first example.
A good heuristic for writing functions that work well with infinite lists is: can the head
of the result be evaluated cheaply? Here are two examples of functions that don’t work with infinite inputs. In the case of mapTailRecursive
, the problem is that it needs to process the whole input before being in WHNF. In the case of myDrop
, the problem is that it uses the function length
, doesn’t work for infinite lists since it tries to iterate until the end of the list.
map :: (a -> b) -> [a] -> [b]
map _ [] = []
map f (x:xs) = f x : map x xs
mapTailRecursive :: (a -> b) -> [a] -> [b]
mapTailRecursive f xs = go xs []
where go (x:xs) res = go xs (res++[f x])
go [] res = res
head (map inc [0..]) ==> head (inc 0 : map inc [1..]) ==> inc 0 ==> 1
head (mapTailRecursive inc [0..])
==> head (go [0..] [])
==> head (go [1..] ([]++[inc 0]))
==> head (go [2..] ([]++[inc 0]++[inc 1]))
==> head (go [3..] ([]++[inc 0]++[inc 1]++[inc 2]))
-- never terminates
drop :: Int -> [a] -> [a]
drop 0 xs = xs
drop _ [] = []
drop n (x:xs) = drop (n-1) xs
myDrop :: Int -> [a] -> [a]
myDrop 0 xs = xs
myDrop n xs = if n > length xs then [] else myDrop (n-1) (tail xs)
head (drop 2 [0..]) ==> head (drop 1 [1..]) ==> head (drop 0 [2..]) ==> head [2..] ==> 2
head (myDrop 2 [0..])
==> head (if n > length [0..] then [] else myDrop (n-1) (tail [0..]))
==> head (if n > 1+length [1..] then [] else myDrop (n-1) (tail [0..]))
==> head (if n > 1+1+length [2..] then [] else myDrop (n-1) (tail [0..]))
==> head (if n > 1+1+1+length [3..] then [] else myDrop (n-1) (tail [0..]))
-- never terminates
Pretty much all the list functions in the standard library are written in this form, for example:
head (takeWhile (>=0) [0..]) ==> 0
head (concat (repeat [1,2,3])) ==> 1
head (zip [0..] [2..]) ==> (0,2)
head (filter even [3..]) ==> 4
Remember foldr
from part 1? Let’s have a look at its cousin foldl
. Here’s the definition of foldl
for lists (it’s actually part of the Foldable
typeclass and so works for various other types too). While foldr
processes a list right-to-left, foldl
processes a list left-to-right. To be a bit more exact, foldr
associates to the right while foldl
associates to the left. Note the difference in the next example:
Here are the definitions of foldl
and foldr
:
As foldr f y (x:xs) ==> f x (foldr f y xs)
, it enables lazy evaluation to focus on f
on the second step. Hence, foldr
works nicely with lazy or short-circuiting operations:
head (foldr (++) [] ["Hello","World","lorem","ipsum"])
==> head ("Hello" ++ (foldr (++) [] ["World","lorem","ipsum"]))
==> head ('H':("ello" ++ (foldr (++) [] ["World","lorem","ipsum"])))
==> 'H'
However foldl
needs to process the whole list in order to produce a (WHNF) value. The reason is that foldl
remains in the leftmost-outermost position for as long as its list argument remains non-empty. This makes foldl
the priority for lazy evaluation. Only after the list becomes empty does the evaluation proceed into simplifying the folded values.
foldl (&&) True [False,False,False]
==> foldl (&&) (True&&False) [False,False]
==> foldl (&&) ((True&&False)&&False) [False]
==> foldl (&&) (((True&&False)&&False)&&False) []
==> ((True&&False)&&False)&&False
==> ( False &&False)&&False
==> False &&False
==> False
head (foldl (++) [] ["Hello","World","lorem","ipsum"])
==> head (foldl (++) ([]++"Hello") ["World","lorem","ipsum"])
==> head (foldl (++) (([]++"Hello")++"World") ["lorem","ipsum"])
==> head (foldl (++) ((([]++"Hello")++"World")++"lorem") ["ipsum"])
==> head (foldl (++) (((([]++"Hello")++"World")++"lorem")++"ipsum") [])
==> head (((([]++"Hello")++"World")++"lorem")++"ipsum")
-- head forces the last ++, which forces the next-to-last ++, and so on
==> head ((("Hello"++"World")++"lorem")++"ipsum")
-- same happens again
==> head ((('H':("ello"++"World"))++"lorem")++"ipsum")
-- for clarity, let's drop the "ello"++"World" expression which isn't needed
==> head ((('H':__)++"lorem")++"ipsum")
-- now the next-to-last ++ can operate
==> head (('H':(__++"lorem"))++"ipsum")
-- let's drop the __++"lorem" expression
==> head (('H':__)++"ipsum")
-- now the last ++ can operate
==> head ('H':(__++"ipsum"))
==> 'H'
So why use foldl
at all? Let’s return to our first fold example again. Now, since +
is a strict operation, both types of fold need to build up an expression with lots of +
s. The Haskell implementation needs to track this expression in memory, which is why a problem like this is called a space leak.
foldr (+) 0 [1,2,3]
==> 1 + foldr (+) 0 [2,3]
==> 1 + (2 + foldr (+) 0 [3])
==> 1 + (2 + (3 + foldr (+) 0 []))
==> 1 + (2 + (3 + 0))
==> 1 + (2 + 3)
==> 1 + 5
==> 6
foldl (+) 0 [1,2,3]
==> foldl (+) (0+1) [2,3]
==> foldl (+) ((0+1)+2) [3]
==> foldl (+) (((0+1)+2)+3) []
==> ((0+1)+2)+3
==> ( 1 +2)+3
==> 3 +3
==> 6
Now let’s instead look at what happens when we use foldl'
, a version of foldl
that forces its second argument!
foldl' (+) 0 [1,2,3]
==> foldl' (+) (0+1) [2,3]
-- force second argument
==> foldl' (+) 1 [2,3]
==> foldl' (+) (1+2) [3]
-- force second argument
==> foldl' (+) 3 [3]
==> foldl' (+) (3+3) []
-- force second argument
==> foldl' (+) 6 []
==> 6
Now the work is performed incrementally while scanning the list. No space leak! Sometimes too much laziness can cause space leaks, and a bit of strictness can fix them.
You can find foldl'
in the Data.List
module, and it works just like this. But how could one implement foldl'
? We certainly know by now how to do it for a specific type, say Int
. We just add a pattern match on the second argument that doesn’t change the semantics of the function.
foldl'Int :: (Int -> Int -> Int) -> Int -> [Int] -> Int
foldl'Int f z [] = z
foldl'Int f 0 (x:xs) = foldl'Int f (f 0 x) xs
foldl'Int f z (x:xs) = foldl'Int f (f z x) xs
foldl'Int (+) 0 [1,2,3]
==> foldl'Int (+) (0+1) [2,3]
-- to be able to pick between the second and third equations, (0+1) is forced
==> foldl'Int (+) 1 [2,3]
-- the third equation applies
==> foldl'Int (+) (1+2) [3]
-- again, we need to pick between the second and third equations
==> foldl'Int (+) 3 [3]
==> foldl'Int (+) (3+3) []
==> 3+3
==> 6
To write a generic implementation of foldl'
we need to introduce a new built-in function, seq
. The call seq a b
evaluates to b
but forces a
into WHNF. Here are some examples of using seq
in GHCi. To demonstrate what gets evaluated, we use the special value undefined
, which causes an error if something tries to evaluate it into WHNF.
Prelude> seq (not True) 3
3
Prelude> seq undefined 3
*** Exception: Prelude.undefined
Prelude> (seq (not True) 3) + 7
10
Prelude> (seq undefined 3) + 7
*** Exception: Prelude.undefined
Prelude> let f x = f x in seq (f 3) 3
-- ...infinite recursion
As an example of using seq
in a function, here’s a version of head
that doesn’t work for infinite lists (since it evaluates the last element of the list):
Let’s play around with it in GHCi:
Prelude> head [1,2,3]
1
Prelude> strictHead [1,2,3]
1
Prelude> head (1:2:undefined)
1
Prelude> strictHead (1:2:undefined)
*** Exception: Prelude.undefined
Prelude> head [1..]
1
Prelude> strictHead [1..]
-- ...infinite recursion
Finally, here’s a definition for foldl'
. Note how we need to introduce sharing of a new variable, z'
, to be able to make seq
evaluate the new value and then use it in a recursive call. The new definition is also used in a more detailed evaluation of foldl' (+) 0 [1,2,3]
below.
foldl' :: (a -> b -> a) -> a -> [b] -> a
foldl' f z [] = z
foldl' f z (x:xs) = let z' = f z x
in seq z' (foldl f z' xs)
foldl' (+) 0 [1,2,3]
==> seq (0+1) (foldl' (+) (0+1) [2,3]) -- seq forces first argument
| |
+-----sharing-----'
| |
==> seq 1 (foldl' (+) 1 [2,3]) -- first argument to seq in WHNF, seq disappears
==> foldl' (+) 1 [2,3]
==> seq (1+2) (foldl' (+) (1+2) [3])
==> seq 3 (foldl' (+) 3 [3])
==> foldl' (+) 3 [3]
==> seq (3+3) (foldl' (+) (3+3) [])
==> seq 6 (foldl' (+) 6 [])
==> foldl' (+) 6 []
==> 6
We won’t dive deeper into this subject on this course, but it’s important that you’re aware that seq
exists. You can find more about seq
on the Haskell Wiki and learn more about when it is necessary to add strictness in Real World Haskell. Often it’s nicer to use bang patterns instead of seq
, as discussed by FPComplete and Real World Haskell.
Recall lecture 7. Sometimes we need boxed types. There’s a special keyword newtype
that can be used instead of data
when a boxed type is needed. newtype
expects exactly one constructor, with exactly one field. For instance,
However, the following won’t work, you need data
:
-- the compiler won't accept these!
newtype Currency = Dollars Int | Euros Int
newtype Money = Money Int Int
So what’s the difference? In terms of writing code, nothing. You work with a newtype
exactly as you would with a data
. However, the memory layout is different. Using data
introduces an indirection layer (the constructor), but using newtype
doesn’t. The indirection for data
is necessary to support multiple constructors and multiple fields. An illustration:
code: memory:
data Money = Cents Int x --> Cents --> 100
x = Cents 100
newtype Money = Cents Int x --> 100
x = Cents 100
This difference has many repercussions. First of all, newtype
is more efficient: the type can be said to “disappear” when compiling. The type is still checked though, so you get type safety without any performance impact. Secondly, newtypes are strict. Concretely, this means that Money x
is in weak head normal form only if x
is in WHNF. This can be witnessed in GHCi:
-- if we use data, Cents undefined is in WHNF
Prelude> data Money = Cents Int
Prelude> seq (Cents undefined) True
True
-- if we use newtype, Cents undefined isn't in WHNF, and trying
-- to make it so trips up in undefined
Prelude> newtype Money = Cents Int
Prelude> seq (Cents undefined) True
*** Exception: Prelude.undefined
So when should you use newtype
? In general it’s best to use newtype
whenever you have a single-field single-constructor datatype. However nothing will go catastrophically wrong if you always use data
. The newtype
pattern is also often used when you need to define a different type class instance for a type. Here’s an example that defines a number type with an inverted ordering
newtype Inverted = Inverted Int
deriving (Show, Eq)
instance Ord Inverted where
compare (Inverted i) (Inverted j) = compare j i
Prelude Data.List> sort [1,2,3]
[1,2,3]
Prelude Data.List> sort [Inverted 1,Inverted 2,Inverted 3]
[Inverted 3,Inverted 2,Inverted 1]
Now that we know about sharing and path copying, we can make our own cyclic datastructures. Remember the cycle
examples from the list lecture?
This is what it looks like in memory:
Earlier it was said that Haskell data forms directed graphs in memory. This is an example of a directed graph with a cycle.
How can we define structures like this? We just give a value a name, and refer to that name in the value itself. That is, the value is recursive or self-referential. This trick is known as tying the knot. A simple example:
Note how we use the name xs
inside the definition of xs
. When we make a recursive definition like this, sharing causes it to turn into a cyclic structure in memory.
A more fun example: a simple adventure game where the world is a self-referential structure. Note how the cyclic structure is built with local definitions that refer to each other.
data Room = Room String [(String,Room)]
describe :: Room -> String
describe (Room s _) = s
move :: Room -> String -> Maybe Room
move (Room _ directions) direction = lookup direction directions
world :: Room
world = meadow
where
meadow = Room "It's a flowery meadow next to a cliff." [("Stay",meadow),("Enter cave",cave)]
cave = Room "You are in a cave" [("Exit",meadow),("Go deeper",tunnel)]
tunnel = Room "This is a very dark tunnel. It seems you can either go left or right."
[("Go back",cave),("Go left",pit),("Go right",treasure)]
pit = Room "You fall into a pit. There is no way out." []
treasure = Room "A green light from a terminal fills the room. The terminal says <<loop>>."
[("Go back",tunnel)]
play :: Room -> [String] -> [String]
play room [] = [describe room]
play room (d:ds) = case move room d of Nothing -> [describe room]
Just r -> describe room : play r ds
Prelude> play world ["Stay","Enter cave","Go deeper","Go back","Go deeper","Go right"]
["It's a flowery meadow next to a cliff.",
"It's a flowery meadow next to a cliff.",
"You are in a cave",
"This is a very dark tunnel. It seems you can either go left or right.",
"You are in a cave",
"This is a very dark tunnel. It seems you can either go left or right.",
"A green light from a computer terminal floods the room. The terminal says <<loop>>."]
Here’s what the world
of the game looks like in memory:
,-----------------,
v |
+-----------------------|-----------------+
meadow-->|Room "It's..." ["Stay" o, "Enter cave" o]|
+---------------------------------------|-+
^ v
+--------------------------|----------------+
cave---->|Room "You are..." ["Exit" o, "Go deeper" o]|
+-----------------------------------------|-+
^ v
+-----------------------------|----------------------------+
tunnel-->|Room "This is..." ["Go back" o, "Go left" o, "Go right" o]|<--------,
+------------------------------------------|-------------|-+ |
| | |
,------------------------------' | |
v v |
+---------------------+ +-----------------------------|-+
pit----->|Room "You fall..." []| treasure--->|Room "A green..." ["Go back" o]|
+---------------------+ +-------------------------------+
We’ve now seen three types of recursion. Recursive functions call themselves. Recursive types allow us to express arbitarily large structures. Recursive values are one way to implement infinite structures.
Even though Haskell is a pure programming language, we can sometimes gain insights by sprinkling in a bit of impurity.
We can use the function trace :: String -> a -> a
from the module Debug.Trace
to peek into Haskell evaluation. The expression trace "message" x
is the same as x
, but prints message
when it is evaluated (forced). We can use trace
to witness the laziness of the ||
operator:
Prelude> import Debug.Trace
Prelude Debug.Trace> trace "a" True
a
True
Prelude Debug.Trace> trace "a" False || trace "b" True
a
b
True
Prelude Debug.Trace> trace "a" True || trace "b" True
a
True
We can also have a look at when list elements are evaluated. Note how length
doesn’t need to evaluate the elements of the list, and sum
needs to evaluate all of them. (To be precise, head xs
doesn’t actually evaluate the first element of xs
, but returns it to GHCi, which evaluates it in order to show it.)
Prelude Debug.Trace> head [trace "first" 1, trace "second" 2, trace "third" 3]
first
1
Prelude Debug.Trace> last [trace "first" 1, trace "second" 2, trace "third" 3]
third
3
Prelude Debug.Trace> length [trace "first" 1, trace "second" 2, trace "third" 3]
3
Prelude Debug.Trace> sum [trace "first" 1, trace "second" 2, trace "third" 3]
third
second
first
6
Debug.Trace
also offers useful variants of trace
. A notable one is traceShowId x
which prints show x
and evaluates to x
. Let’s verify the evaluation of our previous head-filter-map example using traceShowId
. Note how even though we map traceShowId
over the infinite list [0..]
, only 6 values are actually evaluated. The last 243 is the returned value, not a trace print.
Debug.Trace
is especially useful when you have an infinite recursion bug. Here’s an example:
-- computes sums like 7+5+3+1
sumEverySecond :: Int -> Int
sumEverySecond 0 = 0
sumEverySecond n = n + sumEverySecond (n-2)
We can debug this by adding a trace
to wrap the whole recursive case.
sumEverySecond :: Int -> Int
sumEverySecond 0 = 0
sumEverySecond n = trace ("sumEverySecond "++show n) (n + sumEverySecond (n-2))
Prelude Debug.Trace> sumEverySecond 6
sumEverySecond 6
sumEverySecond 4
sumEverySecond 2
12
Prelude Debug.Trace> sumEverySecond 7
sumEverySecond 7
sumEverySecond 5
sumEverySecond 3
sumEverySecond 1
sumEverySecond -1
sumEverySecond -3
sumEverySecond -5
-- and so on
A ha! The problem is that our recursion base case of sumEverySecond 0
is not enough to stop the recursion.
Finally, a word of caution. Using trace
, and especially traceShowId
, can cause things that would not otherwise get evaluated to get evaluated. For example:
Prelude Debug.Trace> let traceHead xs = head (traceShowId xs)
Prelude Debug.Trace> traceHead [0..]
-- never terminates since it's trying to show an infinite list
So feel free to use Debug.Trace
when working on the exercises, but try to leave trace
calls out of your final answers. Some exercise sets check your imports and disallow Debug.Trace
.
We’ll see a more principled way of dealing with side effects in the next lecture!
Which of these statements is true?
reverse . reverse . reverse === reverse
reverse . reverse === reverse
reverse . id === reverse
Which of these is an infinite list that starts with [0,1,2,1,2,1,2...]
?
cycle [0,1,2]
0:repeat [1,2]
0:cycle [1,2]
0:[1,2..]
What’s the next step when evaluating this expression?
head (False : True : [])
head (not True)
head (False : map not (False:[]))
head (not True : map not (False:[]))
Which of these values is not in weak head normal form?
map
f 1 : map f (2 : [])
Just (not False)
(\x -> x) True
Which of these statements about the following function is true?
f
is strict in its left argument
f
is strict in its right argument
f
forces both of its arguments
Does this function work with infinite lists as input? Why?
[]
case, which is never reached.
map
, which evaluates the whole list.
map
, which works with infinite lists.
What about this one?
map
, which evaluates the whole list.
head
of the result needs the whole input list.
[]
case
map
, which works with infinite lists.
RealWorld -> (a,RealWorld)
Forget what we talked about functional programming and purity. Actually, Haskell is the world’s best imperative programming language! Let’s start:
Reading input and writing output was easy enough. We can also read stuff over the network. Here’s a complete Haskell program that fetches a some words from a URL using HTTP and prints them.
import Network.HTTP
import Control.Monad
main = do
rsp <- simpleHTTP (getRequest "http://httpbin.org/base64/aGFza2VsbCBmb3IgZXZlcgo=")
body <- getResponseBody rsp
forM_ (words body) $ \w -> do
putStr "word: "
putStrLn w
You can find this program in the course repository as exercises/Examples/FetchWords.hs
, and you can run it like this:
$ cd exercises/Examples
$ stack runhaskell FetchWords.hs
word: haskell
word: for
word: ever
What’s going on here? Let’s look at the types:
A value of type IO a
is an operation that produces a value of type a
. So getLine
is an IO operation that produces a string. The ()
type is the so called unit type, its only value is ()
. It’s mostly used when an IO operation doesn’t return anything (but rather just has side effects).
A comparison with Java (method) types might help:
Haskell type | Java type |
---|---|
doIt :: IO () |
void doIt() |
getSomething :: IO Int |
int getSomething() |
force :: a -> b -> IO () |
void force(a arg0, b arg1) |
mogrify :: c -> IO d |
d mogrify(c arg) |
IO operations can be combined into bigger operations using do-notation.
do operation
operation arg
variable <- operationThatReturnsStuff
let var2 = expression
operationThatProducesTheResult var2
You can find useful IO operations in the standard library modules Prelude and System.IO
Here’s an IO operation that asks the user for a string, and prints out the length of the string.
query :: IO ()
query = do
putStrLn "Write something!" -- run an operation, ignore produced value
s <- getLine -- run an operation, capture produced value
let n = length s -- run a pure function
putStrLn ("You wrote "++show n++" characters") -- run an operation, passing on the produced value
The value produced by the last line of a do
block is the value produced by the whole block. Note how askForALine
has the same type as getLine
, IO String
:
In addition to IO operations like query
you can also run IO operations that produce values, like askForALine
, in GHCi. You can use <-
to capture the result of the operation into a variable if you want.
Prelude> askForALine
Please give me a line
this is a line
"this is a line"
Prelude> line <- askForALine
Please give me a line
this is a line
Prelude> :t line
line :: String
Prelude> line
"this is a line"
If you need to give your operation parameters, you can just make a function that returns an operation. Note how ask
has a function type with a ->
, just like a normal function. We also use normal function definition syntax to give the parameter the name question
.
Prelude> ask "What is love?"
What is love?
Baby don't hurt me!
"Baby don't hurt me!"
Prelude> response <- ask "Who are you?"
Who are you?
The programmer.
Prelude> response
"The programmer."
Prelude> :t response
response :: String
Prelude> :t ask
ask :: String -> IO String
Prelude> :t ask "Who are you?"
ask "Who are you?" :: IO String
return
The Haskell function return
is named a bit misleadingly. In other languages return
is a built-in keyword, but in Haskell it’s just a function. The return :: a -> IO a
function takes a value and turns it into an operation, that produces the value.
produceThree :: IO Int
produceThree = return 3
printThree :: IO ()
printThree = do
three <- produceThree
putStrLn (show three)
That doesn’t sound very useful does it? Combined with do-notation it is. Here we return a boolean according to whether the user answered Y
or N
:
yesNoQuestion :: String -> IO Bool
yesNoQuestion question = do
putStrLn question
s <- getLine
return (s == "Y")
Prelude> yesNoQuestion "Fire the missiles?"
Fire the missiles?
Y
True
Prelude> answer <- yesNoQuestion "Are you sure?"
Are you sure?
N
Prelude> :t answer
answer :: Bool
Prelude> answer
False
Note! This means that return does not stop execution of an operation (unlike return in Java or C). Remember that in do-blocks, the last line decides which value to produce. This means that this operation produces 2
:
Let’s look at this another way. The do
notation allows us to cause a sequence of side-effects, and finally to produce a value.
produceThree = do putStrLn "1" -- side effect, produces (), which is ignored
return 2 -- no side effect, produces 2, which is ignored
getLine -- side effect, produces a String, which is ignored
return 3 -- no side effect, produces 3, which is passed on
Prelude> final <- produceThree
1
this line is ignored
Prelude> final
3
Also note that these are the same operation:
Since return
is a function, you should remember to parenthesize any complex expressions:
do
and TypesLet’s look at the typing of do-notation in more detail. A do-block builds a value of type IO <something>
. For example in
The lastOp
must be of type IO X
(for some X
). The type of foo
will also be IO X
. Let’s look at an example with parameters next:
The lastOp
must be of type Y -> IO X
(so that lastOp arg
has type IO X
). The type of bar
will be A -> B -> IO X
(and inside bar
we’ll have x :: A
and y :: B
).
If we use return
:
The function quux
will have type A -> IO B
, where x :: A
and value :: B
.
Let’s look at the typing of <-
next. If op :: IO X
and you have var <- op
, var
will have type X
. We’ve seen this in many GHCi examples.
The last line of a do
cannot be foo <- bar
. The last line determines what the whole operation produces, so it must be an operation (for example, return something
).
Here’s a worked example:
alwaysFine :: IO Bool
alwaysFine = do
putStrLn "What?" -- :: IO ()
return 2 -- :: IO Int, produced value is discarded
s <- getLine -- getLine :: IO String, thus s :: String
putStrLn s -- putStrLn :: String -> IO (), thus putStrLn s :: IO ()
let b = True -- b :: Bool
return b -- :: IO Bool
-- Thus, alwaysFine :: IO Bool
The typing rules guarantee that you can not “escape” IO
. Even though <-
gives you an X
from an IO X
, you can only use <-
inside do
. However a do
always means a value of type IO Y
. In other words: you can temporarily open the IO
box, but you must return into it. “What happens in IO, stays in IO.”
We’ll talk more about what this means later. For now, it’s enough to know that if you have a function with a non-IO type, like for example myFunction :: Int -> [String] -> String
, the function can not have IO happening inside it. It is a pure function.
For the following examples, we’ll need two new operations.
print :: Show a => a -> IO () -- print a value using the show function
readLn :: Read a => IO a -- get a line and convert it to a value using the read function
The usual tools of recursion, guards and if-then-else also work in the IO
world. Here’s an IO operation that’s defined using a guard:
printDescription :: Int -> IO ()
printDescription n
| even n = putStrLn "even"
| n==3 = putStrLn "three"
| otherwise = print n
Here’s an operation that prints all numbers in a list using recursion and pattern matching:
printList :: [Int] -> IO ()
printList [] = return () -- do nothing
printList (x:xs) = do print x
printList xs -- recursion
Here are two slightly more complicated examples of recursive IO operations. They use the value produced by the recursive call. The operation readAndSum n
reads n
numbers from the user and prints their sum. The operation ask questions
shows each string in questions
to the user, reads a response, and returns a list of all the responses.
readAndSum :: Int -> IO Int
readAndSum 0 = return 0
readAndSum n = do
i <- readLn -- read one number
s <- readAndSum (n-1) -- recursion: read and sum rest of numbers
return (i+s) -- produce result
ask :: [String] -> IO [String]
ask [] = return []
ask (question:questions) = do
putStr question
putStrLn "?"
answer <- getLine -- get one answer
answers <- ask questions -- recursion: get rest of answers
return (answer:answers) -- produce result
Prelude> replies <- ask ["What is your name","How old are you"]
What is your name?
Yog-Sothoth
How old are you?
The question is meaningless
Prelude> replies
["Yog-Sothoth","The question is meaningless"]
Additionally, we have some IO
-specific control structures, or rather, functions. These come from the module Control.Monad
.
-- when b op performs op if b is true
when :: Bool -> IO () -> IO ()
-- unless b op performs op if b is false
unless :: Bool -> IO () -> IO ()
-- do something many times, collect results
replicateM :: Int -> IO a -> IO [a]
-- do something many times, throw away the results
replicateM_ :: Int -> IO a -> IO ()
-- do something for every list element
mapM :: (a -> IO b) -> [a] -> IO [b]
-- do something for every list element, throw away the results
mapM_ :: (a -> IO b) -> [a] -> IO ()
-- the same, but arguments flipped
forM :: [a] -> (a -> IO b) -> IO [b]
forM_ :: [a] -> (a -> IO b) -> IO ()
Using these, we can rewrite our earlier examples:
ask :: [String] -> IO [String]
ask questions = do
forM questions askOne
askOne :: String -> IO String
askOne question = do
putStr question
putStrLn "?"
getLine
do
and IndentationIt’s easy to run into weird indentation problems when using do-notation. Here are some rules of thumb to help you get it right.
The most important rule of do and indentation is all operations in a do-block must start in the same column.
Some examples of this rule:
-- This is not OK, putStrLn is way too left
foo = do y <- getLine
putStrLn y
-- This is not OK either
foo = do y <- getLine
putStrLn y
-- This is OK
foo = do y <- getLine
putStrLn y
-- This is also OK: putting a line break after do
foo = do
y <- getLine
putStrLn y
A related rule is when an operation goes over multiple lines, indent the follow-up lines. If you don’t indent, it’ll look like a new operation!
-- This is not OK, the string starts a new operation
quux = do putStrLn
"this long string"
print 1
-- This is OK
quux = do putStrLn
"this long string"
print 1
Here’s one more example, with nested do-blocks, and two different valid indentations.
-- This is OK
foo x = do quux
y <- blorg
when y (do thing
otherThing)
return 3
-- This is also OK: starting putting a line break after do, using $
foo x = do
quux
y <- blorg
when y $ do
thing
otherThing
return 3
After all these short one-off examples, let’s turn to something a bit longer. Let’s write a program to fetch all type annotations from all .hs
files. We use IO operations like readFile
and listDirectory
to read and find files, but also pure code like map
and filter
to do the actual processing. First off, here’s a recap of the library operations we’re using:
-- split string into lines
lines :: String -> [String]
-- `isSuffixOf suf list` is true if list ends in suf
Data.List.isSuffixOf :: Eq a => [a] -> [a] -> Bool
-- `isInfixOf inf list` is true if inf occurs inside list
Data.List.isInfixOf :: Eq a => [a] -> [a] -> Bool
-- FilePath is just an alias for String
type FilePath = String
-- get entire contents of file
readFile :: FilePath -> IO String
-- list files in directory
System.Directory.listDirectory :: FilePath -> IO [FilePath]
-- is the given file a directory?
System.Directory.doesDirectoryExist :: FilePath -> IO Bool
And here’s the program itself. You can also find it in the course repository as exercises/Examples/ReadTypes.hs
.
module Examples.ReadTypes where
import Control.Monad (forM)
import Data.List (isInfixOf, isSuffixOf)
import System.Directory (listDirectory, doesDirectoryExist)
-- a line is a type signature if it contains :: but does not contain =
isTypeSignature :: String -> Bool
isTypeSignature s = not (isInfixOf "=" s) && isInfixOf "::" s
-- return list of types for a .hs file
readTypesFile :: FilePath -> IO [String]
readTypesFile file
| isSuffixOf ".hs" file = do content <- readFile file
let ls = lines content
return (filter isTypeSignature ls)
| otherwise = return []
-- list children of directory, prepend directory name
qualifiedChildren :: String -> IO [String]
qualifiedChildren path = do childs <- listDirectory path
return (map (\name -> path++"/"++name) childs)
-- get type signatures for all entries in given directory
-- note mutual recursion with readTypes
readTypesDir :: String -> IO [String]
readTypesDir path = do childs <- qualifiedChildren path
typess <- forM childs readTypes
return (concat typess)
-- recursively read types contained in a file or directory
-- note mutual recursion with readTypesDir
readTypes :: String -> IO [String]
readTypes path = do isDir <- doesDirectoryExist path
if isDir then readTypesDir path else readTypesFile path
-- main is the IO action that gets run when you run the program
main :: IO ()
main = do ts <- readTypes "."
mapM_ putStrLn ts
We can run this program by going to the directory exercises/Examples
and running:
$ stack runhaskell ReadTypes.hs
deposit :: String -> Int -> Bank -> Bank
withdraw :: String -> Int -> Bank -> (Int,Bank)
runBankOp :: BankOp a -> Bank -> (a,Bank)
... and so on
The exact output will vary according to the contents of the directory, of course.
Let’s return to the functional world. How can we reconcile IO operations with Haskell being a pure and lazy language? Something like putStrLn :: String -> IO ()
is a pure function that returns an operation. How is it pure? putStrLn x
is the same when x
is the same. In other words: an operation is a pure description of a chain of side effects. Only executing the operation causes those side effects. When a Haskell program is run, only one operation is executed - it’s called main :: IO ()
. Other operations can be run only by linking them up to main
.
When in GHCi, if an expression you type in evaluates to an operation, GHCi runs that operation for you. Here’s a demonstration of the purity of print
:
Prelude> let x = print 1 -- creates operation, doesn't run it
Prelude> x -- runs the operation
1
Prelude> x -- runs it again!
1
Operations are values just like numbers, lists and functions. We can write code that operates on operations. This function takes two operations, a
and b
, and returns an operation that asks the user which one he’d like to run.
choice :: IO x -> IO x -> IO x
choice a b =
do putStr "a or b? "
x <- getLine
case x of "a" -> a
"b" -> b
_ -> do putStrLn "Wrong!"
choice a b
Using operations specified as parameters lets us write functions like mapM_
, which we met earlier. The implementation is a recursive IO operation that takes another IO operation as a parameter. Conceptually complicated, but simple when you read the code:
mapM_ :: (a -> IO b) -> [a] -> IO ()
mapM_ op [] = return () -- do nothing for an empty list
mapM_ op (x:xs) = do op x -- run operation on first element
mapM_ op xs -- run operation on rest of list, recursively
So far the only side-effects we’ve been able to produce in IO have been terminal (getLine
, print
) and file (readFile
, listDirectory
) IO. Imperative programs written in Java, Python or C have other types of side effects too that we can’t express in pure Haskell. One of these is mutable (i.e. changeable) state. A pure function can not read mutable state, because otherwise two invocations of the same function might not return the same value.
The Haskell type IORef a
from the module Data.IORef
is a mutable reference to a value of type a
newIORef :: a -> IO (IORef a) -- create a new IORef containing a value
readIORef :: IORef a -> IO a -- produce value contained in IORef
writeIORef :: IORef a -> a -> IO () -- set value in IORef
modifyIORef :: IORef a -> (a -> a) -> IO () -- modify value contained in IORef with a pure function
Here are some examples of using an IORef in GHCi:
Prelude> :m +Data.IORef
Prelude Data.IORef> myRef <- newIORef "banana"
Prelude Data.IORef> readIORef myRef
"banana"
Prelude Data.IORef> writeIORef myRef "apple"
Prelude Data.IORef> readIORef myRef
"apple"
Prelude Data.IORef> modifyIORef myRef reverse
Prelude Data.IORef> readIORef myRef
"elppa"
Here’s an example of using an IORef
to sum the values in a list. Note the similarity with an imperative loop.
sumList :: [Int] -> IO Int
sumList xs = do r <- newIORef 0 -- initialize r to 0
forM_ xs (\x -> modifyIORef r (x+)) -- for every xs, add it to r
readIORef r -- get last value of r
Using IORef
isn’t necessary most of the time. Haskell style prefers recursion, arguments and return values. However real world programs might need one or two IORefs occasionally.
A value of type IO X
is an IO operation that produces a value of type X when run. Operations are pure values. Only running the operation causes the side effects.
IO operations can combined together using do
-notation:
op :: X -> IO Y
op arg = do operation -- run operation
operation2 arg -- run operation with argument
result <- operation3 arg -- run operation with argument, store result
let something = f result -- run a pure function f, store result
finalOperation -- last operation produces the the return value
The return x
operation is an operation that always produces value x
. When x :: a
, return x :: IO a
.
Useful IO operations:
-- printing & reading
putStr :: String -> IO ()
putStrLn :: String -> IO ()
print :: Show a => a -> IO ()
getLine :: IO String
readLn :: Read a => IO a
-- control structures from Control.Monad
when :: Bool -> IO () -> IO () -- when b op performs op if b is true
unless :: Bool -> IO () -> IO () -- unless b op performs op if b is false
replicateM :: Int -> IO a -> IO [a] -- do something many times, collect results
replicateM_ :: Int -> IO a -> IO () -- do something many times, throw away the results
mapM :: (a -> IO b) -> [a] -> IO [b] -- do something for every list element
mapM_ :: (a -> IO b) -> [a] -> IO () -- do something for every list element, throw away the results
forM :: [a] -> (a -> IO b) -> IO [b] -- the same, but arguments flipped
forM_ :: [a] -> (a -> IO b) -> IO ()
-- files
readFile :: FilePath -> IO String
What is the type of this IO operation?
String -> IO String
IO Int
String -> IO Int
IO String -> IO Int
Which of these lines could be used in place of ????
q <- getLine
return (y++z)
return [q]
ans <- return [y,z]
What values does blorg [1,2,3]
print?
1
, 2
, 3
1
, 2
, 3
, 6
3
, 2
, 1
3
, 2
, 1
, 6
Which of these can a function of type Int -> IO Int
do?
Which of these can a function of type IO Int -> Int
do?
Remember the map
function for lists? Here’s the definition again:
It applies a function g :: a -> b
to each element of a list of type [a]
, returning a list of type [b]
. Another way to express the type of map
would be (a -> b) -> ([a] -> [b])
. This is the same type because ->
associates to right. The extra parentheses emphasize the fact that map
converts the function g :: a -> b
into a function map g :: [a] -> [b]
. This means that map
is a higher-order function that transforms functions to functions.
As map
is parametrically polymorphic, its definition doesn’t depend on the type of values stored in the list. Thus, every function of type a -> b
is converted into a function of type [a] -> [b]
using exactly the same logic. Using the definition above, we can see that:
map (|| True) [True, True, False]
==> [True || True, True || True, False || True]
==> [True, True, True]
map (+1) [1,2,3]
==> [1 + 1, 2 + 1, 3 + 1]
==> [2, 3, 4]
map (++"1") ["1", "2", "3"]
==> ["1" ++ "1", "2" ++ "1", "3" ++ "1"]
==> ["11", "21", "31"]
What’s notable here is that map
preserves the structure of a list. The length of the list and the relative positions of the elements are the same. The general idea is demonstrated in the picture below.
Let’s see if we can find other similar functions. A value of type Maybe a
is kind of like a list of length at most 1. Let’s map over a Maybe
! Can you see the similarity with the definition of map
?
mapMaybe :: (a -> b) -> Maybe a -> Maybe b
mapMaybe f Nothing = Nothing
mapMaybe f (Just x) = Just (f x)
Here too, the structure of the value is preserved. A Nothing
turns into a Nothing
, and a Just
turns into a Just
. Here too, we can think of the type as (a -> b) -> (Maybe a -> Maybe b)
, converting (or “lifting”) a normal function into a function that works on Maybes.
One more example: consider binary trees.
data Tree a = Leaf | Node a (Tree a) (Tree a)
mapTree :: (a -> b) -> Tree a -> Tree b
mapTree f Leaf = Leaf
mapTree f (Node val left right) = Node (f x) (mapTree f left) (mapTree f right)
A binary tree might look like this:
After mapTree f
the tree would looke like this:
Functor
ClassNow we have three different structure-preserving mapping functions. Three similar operations over different types. Could we write a type class to capture this similarity?
map :: (a -> b) -> [a] -> [b]
mapMaybe :: (a -> b) -> Maybe a -> Maybe b
mapTree :: (a -> b) -> Tree a -> Tree b
A naive attempt at writing a type class runs into problems. If we try to abstract over Maybe c
, we can’t seem to write the right type for the map operation. We’d need to be able to change the type parameter c
somehow.
class Mappable m where
mapThing :: (a -> b) -> m -> m
instance Mappable (Maybe c) where
mapThing :: (a -> b) -> Maybe c -> Maybe c
mapThing = ...
Luckily Haskell type classes have a feature we haven’t covered before. You can write classes for type constructors in addition to types. What does this mean? Let’s just have a look at the standard type class Functor
that does what we tried to do with our Mappable
.
Note how the type parameter f
is a type constructor: it’s being passed a
and b
arguments in different parts of the type of fmap
. Now let’s see the instance for Maybe
.
instance Functor Maybe where
fmap :: (a -> b) -> Maybe a -> Maybe b
fmap f Nothing = Nothing
fmap f (Just x) = Just (f x)
Now fmap
has the right type and we can implement it like mapMaybe
! Note how we’ve declared instance Functor Maybe
instead of instance Functor (Maybe a)
. The type Maybe a
isn’t a functor, the type constructor Maybe
is.
The type constructor for lists is written []
. It’s special syntax, just like other list syntax. However if the type [a]
was written List a
, the type constructor []
would mean List
.
Here’s the final of our examples, as a Functor
instance.
data Tree a = Leaf | Node a (Tree a) (Tree a)
instance Functor Tree where
fmap _ Leaf = Leaf
fmap f (Node val left right) = Node (f val) (fmap f left) (fmap f right)
Sidenote: the term functor comes originally from a branch of mathematics called category theory. However, to work with Haskell you don’t need to know any category theory. When you see functor, you can just think “something I can map over”, or perhaps “a container”.
Let’s zoom out a bit. When we have an instance Functor MyFun
we know that we can map a type X
into a new type MyFun X
(since MyFun
is a type constructor), but also that we can lift a function f
that takes an X
argument into a function fmap f
that takes a MyFun X
argument! So you could say we’re mapping both on the type level and the value level.
Oh right, one more thing. Once you’ve gotten the hang of fmap
you might find yourself using it quite a bit. For code that uses fmap
heavily it can be nice to use its infix alias, <$>
. Consider the symmetry between $
and <$>
in these examples:
(+1) <$> [1,2,3] ==> [2,3,4]
not <$> Just False ==> Just True
reverse . tail $ "hello" ==> "olle"
reverse . tail <$> Just "hello" ==> Just "olle"
-- which is the same as
fmap (reverse . tail) (Just "hello") ==> Just "olle"
What is this “preserving of the structure” that was mentioned above exactly? The following two functor laws are expected to hold for any Functor
instance f
(though unfortunately Haskell compilers can’t enforce them):
fmap id === id
fmap (f . g) === fmap f . fmap g
Don’t worry if that sounded abstract! The first law says that a functor maps id :: a -> a
into id :: f a -> f a
. (id
is the identity function, meaning that id x = x
.) Let’s be concrete and see how it works for the list [1,2,3]
:
fmap id [1,2,3] ==> map id [1,2,3]
==> map id (1:[2,3])
==> id 1 : map id [2,3]
==> 1 : map id [2,3]
==> 1 : id 2 : map id [3]
==> 1 : 2 : id 3 : map id []
==> 1 : 2 : 3 : []
=== [1,2,3]
On the other hand,
Hence, the result of fmap id [1,2,3]
was the same as the result of id [1,2,3]
, so the first functor law holds in this case. It’s not hard to show that the first functor law holds for any list whatsoever.
The first functor law is really a very simple proposition if you think about it. It just says that you can either fmap id
or just apply id
directly without a noticeable difference.
How about the second functor law? For lists, consider what happens if we fmap
the function negate.(*2)
(remember, negate
maps x
to -x
and (*2)
multiplies its argument by 2
):
fmap (negate.(*2)) [1,2,3] ==> map (negate.(*2)) [1,2,3]
==> (negate.(*2)) 1 : map (negate.(*2)) [2,3]
==> negate (1 * 2) : map (negate.(*2)) [2,3]
==> -2 : map (negate.(*2)) [2,3]
==> -2 : (negate.(*2)) 2 : map (negate.(*2)) [3]
==> -2 : -4 : map (negate.(*2)) [3]
==> -2 : -4 : (negate.(*2)) 3 : map (negate.(*2)) []
==> -2 : -4 : -6 : []
==> [-2,-4,-6]
Let’s consider the right-hand side of the second functor law in this case:
(fmap negate . fmap (*2)) [1,2,3] ==> (map negate . map (*2)) [1,2,3]
==> map negate (map (*2) [1,2,3])
==> map negate [2,4,6]
==> [-2,-4,-6]
The second functor law turns out to hold in this particular case. In fact, it holds in all cases (exercise!).
Remember that Functor
was a class for type constructors. If we try to define an instance of Functor
for a type, we get an error:
Prelude> instance Functor Int where
<interactive>:1:18: error:
• Expected kind ‘* -> *’, but ‘Int’ has kind ‘*’
• In the first argument of ‘Functor’, namely ‘Int’
In the instance declaration for ‘Functor Int’
The error message talks about kinds. Kinds are types of types. A type like Int
, Bool
or Maybe Int
that can contain values has kind *
. A type constructor has a kind that looks like a function, for example, Maybe
has kind * -> *
. This means that the Maybe
type constructor must be applied to a type of kind *
to get a type of kind *
.
We can ask GHCi for the kinds of types:
Prelude> :kind Int
Int :: *
Prelude> :kind Maybe
Maybe :: * -> *
Prelude> :kind Maybe Int
Maybe Int :: *
If we ask GHCi for info about the Functor
class, it tells us that instances of Functor
must have kind * -> *
:
Here are some examples of even more complex kinds.
-- multiple type parameters
Prelude> :kind Either
Either :: * -> * -> *
Prelude> data Either3 a b c = Left a | Middle b | Right c
Prelude> :kind Either3
Either3 :: * -> * -> * -> *
-- a type parameter of kind *->*
Prelude> data IntInside f = IntInside (f Int)
Prelude> :kind IntInside
IntInside :: (* -> *) -> *
You won’t bump into kinds that much in Haskell programming, but sometimes you’ll see error messages that talk about kinds, so it’s good to know what they are.
Foldable
, AgainWe briefly covered the class Foldable
, which occurs in many type signatures of basic functions, in part 1. For example:
length :: Foldable t => t a -> Int
sum :: (Foldable t, Num a) => t a -> a
minimum :: (Foldable t, Ord a) => t a -> a
foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m
From these type signatures we can see that Foldable
, just like Functor
, is a class for type constructors (things of kind * -> *
). The essence of Foldable
is to be a class for things you can fold over. The class definition could be as simple as
However, for performance reasons, the class contains many methods (you can see them yourself by checking :info Foldable
in GHCi!), but when we’re defining an instance for Foldable
it’s enought to define just foldr
.
Another way of thinking of the Foldable
class is processing elements left-to-right, in other words, if Functor
was the class for containers, Foldable
is the class for ordered containers.
As an example, let’s implement Functor
and Foldable
for our own pair type.
data Pair a = Pair a a
deriving Show
instance Functor Pair where
-- fmap f applies f to all values
fmap f (Pair x y) = Pair (f x) (f y)
instance Foldable Pair where
-- just like applying foldr over a list of length 2
foldr f initialValue (Pair x y) = f x (f y initialValue)
-- an example function that uses both instances
doubleAndCount :: (Functor f, Foldable f) => f Int -> Int
doubleAndCount = sum . fmap (*2)
Now, we can use Pair
almost wherever we can use a list:
fmap (+1) (Pair 3 6) ==> Pair 4 7
fmap (+1) [3,6] ==> [4,7]
foldr (*) 1 (Pair 3 6) ==> 18
foldr (*) 1 (Pair 3 6) ==> 18
length (Pair 3 6) ==> 2
length [3,6] ==> 2
minimum (Pair 3 6) ==> 3
minimum [3,6] ==> 3
doubleAndCount (Pair 3 6) ==> 18
doubleAndCount [3,6] ==> 18
Other types we’ve met that are Foldable
include Data.Map
and Data.Array
.
So, to summarize, a functor is a type constructor f
and the corresponding Functor f
instance such that fmap
satisfies the two functor laws. These laws assert that fmap
must preserve the identity function and distribute over function composition. More informally, fmap
lifts a function g :: a -> b
operating on values to one operating on containers: fmap g :: f a -> f b
. Basically all well-behaving data structures in Haskell are functors.
What’s the type of fmap
?
a -> b -> f a -> f b
(a -> b) -> f a -> f b
Functor f => a -> b -> f a -> f b
Functor f => (a -> b) -> f a -> f b
Which code snippet completes the next Functor
instance?
fmap (Things x ys) = Things (f x) [f x]
fmap (Things x ys) = Things (f x) (map f ys)
fmap (Things x ys) = Things (f x) ys
fmap (Things x ys) = f (Things x ys)
What’s the kind of [a]
?
*
* -> *
[a]
What’s the kind of Foo
?
*
* -> *
Foo
What is the value of foldr (-) 1 (Just 2)
?
Which code snippet completes the next Functor
instance?
foldr f z (Things x ys) = f x z
foldr f z (Things x ys) = foldr f x ys
foldr f z (Things x ys) = f x (foldr f z ys)
foldr f z (Things x ys) = foldr f z (x:ys)
In this lecture we’ll build up to the concept of a monad using a number of examples. By now you should be familiar with all the Haskell features needed for understanding monads.
Monads are a famously hard topic in programming, which is partly due to weird terminology, partly due to bad tutorials, and partly due to trying to understand monads too early when learning Haskell. Monads are introduced this late in the course in an attempt to make understanding them easier.
If you find this lecture hard, don’t despair, many others have found the topic hard as well. There are many many productive Haskell programmers who have managed to understand monads, so the task is not hopeless.
One final word of caution: monads, like functors, are a concept originally from a branch of mathematics called Category Theory. However, and I can’t stress this enough, you do not need to know anything or even care about category theory to understand monads in Haskell programming. Just like one can work with object-oriented programming or functional programming without knowing the theory of objects or functions, one can work with monads without understanding the math associated with them.
When working with many Maybe
values, the code tends to become a bit messy. Let’s look at some examples. First, we combine some functions returning Maybe String
. Note the nested case
we need in stealSecret
: not fun to write.
-- Try to login with a password. `Just username` on success, `Nothing` otherwise.
login :: String -> Maybe String
login "f4bulous!" = Just "unicorn73"
login "swordfish" = Just "megahacker"
login _ = Nothing
-- Get a secret associated with a user. Not all users have secrets.
secret :: String -> Maybe String
secret "megahacker" = Just "I like roses"
secret _ = Nothing
-- Login and return the user's secret, if any
stealSecret :: String -> Maybe String
stealSecret password =
case login password of
Nothing -> Nothing
Just user -> case secret user of
Nothing -> Nothing
Just s -> Just ("Stole secret: "++s)
stealSecret "swordfish" ==> Just "Stole secret: I like roses"
stealSecret "f4bulous!" ==> Nothing
stealSecret "wrong_password" ==> Nothing
Next up, we modify a list of pairs. We use the Maybe
-returning function lookup
from the Prelude. Here we have an if inside a case instead of a nested case.
-- Get the value corresponding to a key from a key-value list.
lookup :: (Eq a) => a -> [(a, b)] -> Maybe b
-- Set the value of key to val in the given key-value list,
-- but only if val is larger than the current value!
increase :: Eq a => a -> Int -> [(a,Int)] -> Maybe [(a,Int)]
increase key val assocs =
case lookup key assocs
of Nothing -> Nothing
Just x -> if (val < x)
then Nothing
else Just ((key,val) : delete (key,x) assocs)
This type of code is pretty common, and usually repeats the same pattern: if any intermediate result is Nothing
, the whole result is Nothing
. Let’s try to make writing code like this easier by defining a chaining operator ?>
. The chaining operator takes a result and the next step of computation, and only runs the next step if the result was a Just
value.
(?>) :: Maybe a -> (a -> Maybe b) -> Maybe b
Nothing ?> _ = Nothing -- if we failed, don't even bother running the next step
Just x ?> f = f x -- otherwise run the next step
The chaining operator streamlines our examples nicely. Note how we can define simple helper functions that take care of one step of the computation instead of writing one big expression.
stealSecret :: String -> Maybe String
stealSecret password =
login password ?>
secret ?>
decorate
where decorate s = Just ("Stole secret: "++s)
increase :: Eq a => a -> Int -> [(a,Int)] -> Maybe [(a,Int)]
increase key val assocs =
lookup key assocs ?>
check ?>
buildResult
where check x
| x < val = Nothing
| otherwise = Just x
buildResult x = Just ((key,val) : delete (key,x) assocs)
Here’s another example: safe list indexing built from safeHead
and safeTail
:
safeHead :: [a] -> Maybe a
safeHead [] = Nothing
safeHead (x:xs) = Just x
safeTail :: [a] -> Maybe [a]
safeTail [] = Nothing
safeTail (x:xs) = Just xs
safeThird :: [a] -> Maybe a
safeThird xs = safeTail xs ?> safeTail ?> safeHead
safeNth :: Int -> [a] -> Maybe a
safeNth 0 xs = safeHead xs
safeNth n xs = safeTail xs ?> safeNth (n-1)
safeThird [1,2,3,4]
==> Just 3
safeThird [1,2]
==> Nothing
safeNth 5 [1..10]
==> Just 6
safeNth 11 [1..10]
==> Nothing
PS. note that ?>
associates to the left as is the default in Haskell. That means that op ?> f ?> g
means (op ?> f) ?> g
. The alternative, op ?> (f ?> g)
would not even type check!
Let’s explore the concept of chaining with another example: logging. The type Logger
represents a value plus a list of log messages (produced by the computation that produced the value).
-- Logger definition
data Logger a = Logger [String] a deriving Show
getVal :: Logger a -> a
getVal (Logger _ a) = a
getLog :: Logger a -> [String]
getLog (Logger s _) = s
-- Primitive operations:
nomsg :: a -> Logger a
nomsg x = Logger [] x -- a value, no message
annotate :: String -> a -> Logger a
annotate s x = Logger [s] x -- a value and a message
msg :: String -> Logger ()
msg s = Logger [s] () -- just a message
Here’s a login
function that logs some details about the usernames and passwords it processes. Note how we run into complicated code in login
when we need to handle multiple Logger
values.
validateUser :: String -> Logger Bool
validateUser "paul.atreides" = annotate "Valid user" True
validateUser "ninja" = nomsg True
validateUser u = annotate ("Invalid user: "++u) False
checkPassword :: String -> String -> Logger Bool
checkPassword "paul.atreides" "muad'dib" = annotate "Password ok" True
checkPassword "ninja" "" = annotate "Password ok" True
checkPassword _ pass = annotate ("Password wrong: "++pass) False
login :: String -> String -> Logger Bool
login user password =
let validation = validateUser user
in if (getVal validation)
then let check = checkPassword user password
in Logger (getLog validation ++ getLog check) (getVal check)
else validation
login "paul.atreides" "muad'dib"
==> Logger ["Valid user","Password ok"] True
login "paul.atreides" "arrakis"
==> Logger ["Valid user","Password wrong: arrakis"] False
login "ninja" ""
==> Logger ["Password ok"] True
login "leto.atreides" "paul"
==> Logger ["Invalid user: leto.atreides"] False
Let’s try to streamline this code by defining a chaining operator for Logger
. The important thing when doing multiple Logger
operations is to preserve all the logs. Here’s a chaining operator, #>
, and an example of how it can be used to log some arithmetic computations.
(#>) :: Logger a -> (a -> Logger b) -> Logger b
Logger la a #> f = let Logger lb b = f a -- feed value to next step
in Logger (la++lb) b -- bundle result with all messages
-- square a number and log a message about it
square :: Int -> Logger Int
square val = annotate (show val ++ "^2") (val^2)
-- add 1 to a number and log a message about it
add :: Int -> Logger Int
add val = annotate (show val ++ "+1") (val+1)
-- double a number and log a message about it
double :: Int -> Logger Int
double val = annotate (show val ++ "*2") (val*2)
-- compute the expression 2*(x^2+1) with logging
compute :: Int -> Logger Int
compute x =
square x
#> add
#> double
We can streamline login
quite a bit by using #>
. Note how we don’t need to worry about combining logs together. Also note how we use a lambda expression instead of defining a helper function.
login :: String -> String -> Logger Bool
login user password =
validateUser user
#>
\valid -> if valid then checkPassword user password
else nomsg False
To ramp things up a bit, let’s use Logger
in a recursive list processing function. Here’s a logging version of filter
. Note how the code chains a log message before the recursive call in order to keep the order of log entries nice.
-- sometimes you don't need the previous value:
(##>) :: Logger a -> Logger b -> Logger b
Logger la _ ##> Logger lb b = Logger (la++lb) b
filterLog :: (Eq a, Show a) => (a -> Bool) -> [a] -> Logger [a]
filterLog f [] = nomsg []
filterLog f (x:xs)
| f x = msg ("keeping "++show x) ##> filterLog f xs #> (\xs' -> nomsg (x:xs'))
| otherwise = msg ("dropping "++show x) ##> filterLog f xs
filterLog (>0) [1,-2,3,-4,0]
==> Logger ["keeping 1","dropping -2","keeping 3","dropping -4","dropping 0"] [1,3]
In the previous example we just wrote some state (the log). Sometimes we need computations that change some sort of shared state. Let’s look at accounts in a small bank. We’ll first define a datatype for the state of the bank: the balances of all accounts, as a map from account name to balance.
Here’s how we can deposit some money to an account. We use the function adjust
from Data.Map
to modify the map.
-- Apply a function to one value in a map
Map.adjust :: Ord k => (a -> a) -> k -> Map.Map k a -> Map.Map k a
deposit :: String -> Int -> Bank -> Bank
deposit accountName amount (Bank accounts) =
Bank (Map.adjust (\x -> x+amount) accountName accounts)
Withdrawing money is a bit more complicated, since we want to handle some special cases like the account not existing, or the account not having enough money. We use the library function findWithDefault
to help us along.
-- Fetch the value corresponding to a key from a map, or a default value
-- in case the key does not exist
Map.findWithDefault :: Ord k => a -> k -> Map.Map k a -> a
withdraw :: String -> Int -> Bank -> (Int,Bank)
withdraw accountName amount (Bank accounts) =
let balance = Map.findWithDefault 0 accountName accounts -- balance is 0 for a nonexistant account
withdrawal = min amount balance -- can't withdraw over balance
newAccounts = Map.adjust (\x -> x-withdrawal) accountName accounts
in (withdrawal, Bank newAccounts)
Finally, let’s write a function that takes at most 100 money from one account, splits the money in half, and deposits it in two accounts. Pay attention to how we need to carefully thread the different versions of the bank, bank
, bank1
, bank2
and bank3
to make sure all transactions happen in the right order.
share :: String -> String -> String -> Bank -> Bank
share from to1 to2 bank =
let (amount,bank1) = withdraw from 100 bank
half = div amount 2
rest = amount-half -- carefully preserve all money, even if amount was an odd number
bank2 = deposit to1 half bank1
bank3 = deposit to2 rest bank2
in bank3
share "wotan" "siegfried" "brunhilde"
(Bank (Map.fromList [("brunhilde",0),("siegfried",0),("wotan",1000)]))
==> Bank (Map.fromList [("brunhilde",50),("siegfried",50),("wotan",900)])
share "wotan" "siegfried" "brunhilde"
(Bank (Map.fromList [("brunhilde",0),("siegfried",0),("wotan",91)]))
==> Bank (Map.fromList [("brunhilde",46),("siegfried",45),("wotan",0)])
Code like this turns up often in Haskell when you’re doing serial updates to one value, while also performing some other computations on the side. It’s easy to make a mistake, and the type system won’t help you if you e.g. reuse the bank1
value. Let’s rewrite share
so that we don’t need to refer to the bank itself. We can again use the same chaining idea to accomplish this.
-- `BankOp a` is an operation that transforms a Bank value, while returning a value of type `a`
data BankOp a = BankOp (Bank -> (a,Bank))
-- running a BankOp on a Bank
runBankOp :: BankOp a -> Bank -> (a,Bank)
runBankOp (BankOp f) bank = f bank
-- Running one BankOp after another
(+>>) :: BankOp a -> BankOp b -> BankOp b
op1 +>> op2 = BankOp combined
where combined bank = let (_,bank1) = runBankOp op1 bank
in runBankOp op2 bank1
-- Running a parameterized BankOp, using the value returned by a previous BankOp
-- The implementation is a bit tricky but it's enough to understand how +> is used for now.
(+>) :: BankOp a -> (a -> BankOp b) -> BankOp b
op +> parameterized = BankOp combined
where combined bank = let (a,bank1) = runBankOp op bank
in runBankOp (parameterized a) bank1
-- Make a BankOp out of deposit. There is no return value so we use ().
depositOp :: String -> Int -> BankOp ()
depositOp accountName amount = BankOp depositHelper
where depositHelper bank = ((), deposit accountName amount bank)
-- Make a BankOp out of withdraw. Note how
-- withdraw accountName amount :: Bank -> (Int,Bank)
-- is almost a BankOp already!
withdrawOp :: String -> Int -> BankOp Int
withdrawOp accountName amount = BankOp (withdraw accountName amount)
Let’s see how chaining works with these bank operations.
Prelude> let bank = Bank (Map.fromList [("edsger",10),("grace",50)])
-- Running a number of operations using +>>
Prelude> runBankOp (depositOp "edsger" 1) bank
((),Bank (fromList [("edsger",11),("grace",50)]))
Prelude> runBankOp (depositOp "edsger" 1 +>> depositOp "grace" 1) bank
((),Bank (fromList [("edsger",11),("grace",51)]))
Prelude> runBankOp (depositOp "edsger" 1 +>> depositOp "grace" 1 +>> withdrawOp "edsger" 11) bank
(11,Bank (fromList [("edsger",0),("grace",51)]))
-- Using +> to implement a transfer from one account to the other:
Prelude> runBankOp (withdrawOp "edsger" 5 +> depositOp "grace") bank
((),Bank (fromList [("edsger",5),("grace",55)]))
Prelude> runBankOp (withdrawOp "edsger" 100 +> depositOp "grace") bank
((),Bank (fromList [("edsger",0),("grace",60)]))
Note how a value of type BankOp
represents a process that transforms the bank. The initial state of the bank must be supplied using runBankOp
. This makes sense because BankOp
transformations can be composed, unlike Bank
states. Having to use runBankOp
makes the distinction between defining operations and executing them clearer.
Now that we’re familiar with manipulating BankOp
values, we can implement share
as a BankOp
. We implement a helper distributeOp
to make the code a bit neater.
-- distribute amount to two accounts
distributeOp :: String -> String -> Int -> BankOp ()
distributeOp to1 to2 amount =
depositOp to1 half
+>>
depositOp to2 rest
where half = div amount 2
rest = amount - half
shareOp :: String -> String -> String -> BankOp ()
shareOp from to1 to2 =
withdrawOp from 100
+>
distributeOp to1 to2
runBankOp (shareOp "wotan" "siegfried" "brunhilde")
(Bank (Map.fromList [("brunhilde",0),("siegfried",0),("wotan",1000)]))
==> ((),Bank (Map.fromList [("brunhilde",50),("siegfried",50),("wotan",900)]))
runBankOp (shareOp "wotan" "siegfried" "brunhilde")
(Bank (Map.fromList [("brunhilde",0),("siegfried",0),("wotan",91)]))
==> ((),Bank (Map.fromList [("brunhilde",46),("siegfried",45),("wotan",0)]))
That was pretty clean wasn’t it? We don’t need to mention the bank at all, we can almost program as if in an imperative language while staying completely pure.
You can find all of this code in the course repository under exercises/Examples/Bank.hs
.
We’ve now seen three different types with a chaining operation:
(?>) :: Maybe a -> (a -> Maybe b) -> Maybe b
(#>) :: Logger a -> (a -> Logger b) -> Logger b
(+>) :: BankOp a -> (a -> BankOp b) -> BankOp b
Just like previously with map
and Functor
, there is a type class that captures this pattern. Note that Monad
is a class for type constructors, just like Functor
.
There are some additional operations in Monad
too:
-- lift a normal value into the monad
return :: a -> m a
-- simpler chaining (like our ##>)
(>>) :: m a -> m b -> m b
a >> b = a >>= \_ -> b -- remember: _ means ignored argument
Recall that the Functor
class was about a generic map
operation. Similarly, the Monad
class is just about a generic chaining operation.
The expression operation >>= next
takes a monadic operation operation :: m a
, and does some further computation with the value that it produces using next :: a -> m b
. If this feels too abstract, just recall how chaining works for Maybe
:
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
Nothing >>= _ = Nothing -- if we failed, don't even bother running the next step
Just x >>= f = f x -- otherwise run the next step
Here’s the full Monad
instance for Maybe
and some examples.
instance Monad Maybe where
(Just x) >>= k = k x
Nothing >>= _ = Nothing
(Just _) >> k = k
Nothing >> _ = Nothing
return x = Just x
Just 1 >>= \x -> return (x+1)
==> Just 2
Just "HELLO" >>= (\x -> return (length x)) >>= (\x -> return (x+1))
==> Just 6
Just "HELLO" >>= \x -> Nothing
==> Nothing
Just "HELLO" >> Just 2
==> Just 2
Just 2 >> Nothing
==> Nothing
Here are the stealSecret
and increase
examples rewritten with monad operations. The changes are ?>
to >>=
and Just
to return
.
stealSecret :: String -> Maybe String
stealSecret password =
login password >>=
secret >>=
decorate
where decorate s = return ("Stole secret: "++s)
-- Set the value of key to val in the given key-value list,
-- but only if val is larger than the current value!
increase :: Eq a => a -> Int -> [(a,Int)] -> Maybe [(a,Int)]
increase key val assocs =
lookup key assocs >>=
check >>=
buildResult
where check x
| val < x = Nothing
| otherwise = return x
buildResult x = return ((key,val) : delete (key,x) assocs)
do
Here’s an example of what a complex monad operation might look like.
Let’s see what happens when we transform this code a bit. First off, let’s inline the definitions.
Due to lambda expressions continuing to the end of the expression, we can omit the parentheses. Let’s also indent differently.
Now we can notice the similarity with do
notation. The do
block below is actually the same code!
To clarify, do
notation is just a nicer syntax for the monad operations (>>=
and >>
) and lambdas. Here’s how do notation gets transformed into monad operations. Note! the definition is recursive.
Here’s safeNth
using do notation:
safeHead :: [a] -> Maybe a
safeHead [] = Nothing
safeHead (x:xs) = Just x
safeTail :: [a] -> Maybe [a]
safeTail [] = Nothing
safeTail (x:xs) = Just xs
safeNth :: Int -> [a] -> Maybe a
safeNth 0 xs = safeHead xs
safeNth n xs = do t <- safeTail xs
safeNth (n-1) t
Here is increase
one last time, now with do notation
-- Set the value of key to val in the given key-value list,
-- but only if val is larger than the current value!
increase :: Eq a => a -> Int -> [(a,Int)] -> Maybe [(a,Int)]
increase key val assocs =
do oldVal <- lookup key assocs
check oldVal
return ((key,val) : delete (key,oldVal) assocs)
where check x
| val < x = Nothing
| otherwise = return x
We should be able to write a Monad
instance for Logger
ourselves, by setting >>=
to #>
. However, due to recent changes in the Haskell language we must implement Functor
and Applicative
instances to be allowed to implement the Monad
instance. Functor
we’ve already met, but what’s Applicative
? We’ll find out later. Let’s implement the instances:
import Control.Monad
data Logger a = Logger [String] a deriving Show
msg :: String -> Logger ()
msg s = Logger [s] ()
-- The Functor instance just maps over the stored value
instance Functor Logger where
fmap f (Logger log x) = Logger log (f x)
-- This is an Applicative instance that works for any monad, you
-- can just ignore it for now. We'll get back to Applicative later.
instance Applicative Logger where
pure = return
(<*>) = ap
-- Finally, the Monad instance
instance Monad Logger where
return x = Logger [] x
Logger la a >>= f = Logger (la++lb) b
where Logger lb b = f a
We don’t need the nomsg
operation any more since it’s just return
. We can also reimplement the annotate
operation using monad operations.
nomsg :: a -> Logger a
nomsg x = return x
annotate :: String -> a -> Logger a
annotate s x = msg s >> return x
Here are the compute
and filterLog
examples rewritten using do-notation. Note how nice filterLog
is with do-notation.
compute x = do
a <- annotate "^2" (x*x)
b <- annotate "+1" (a+1)
annotate "*2" (b*2)
filterLog :: (Show a) => (a -> Bool) -> [a] -> Logger [a]
filterLog f [] = return []
filterLog f (x:xs)
| f x = do msg ("keeping "++show x)
xs' <- filterLog f xs
return (x:xs')
| otherwise = do msg ("dropping "++show x)
filterLog f xs
compute 3
==> Logger ["^2","+1","*2"] 20
filterLog (>0) [1,-2,3,-4,0]
==> Logger ["keeping 1","dropping -2","keeping 3","dropping -4","dropping 0"] [1,3]
Haskell’s State
monad is a generalized version of our BankOp
type. The State
type is parameterized by two types, the first being the type of the state, and the second the type of the value produced. State Bank a
would be equivalent to our BankOp a
. You can find the State
monad in the module Control.Monad.Trans.State
of the transformers
package. Here’s a simplified implementation of State
.
data State s a = State (s -> (a,s))
runState (State f) s = f s
-- operation that overwrites the state (and produces ())
put :: s -> State s ()
put state = State (\oldState -> ((),state))
-- operation that produces the current state
get :: State s s
get = State (\state -> (state,state))
-- operation that modifies the current state with a function (and produces ())
modify :: (s -> s) -> State s ()
modify f = State (\state -> ((), f state))
-- Functor and Applicative instances skipped
instance Monad (State s) where
return x = State (\s -> (x,s))
op >>= f = State h
where h state0 = let (val,state1) = runState op state0
op2 = f val
in runState op2 state1
Note how we declare an instance Monad (State s)
. We’re using a partially-applied type constructor because instances of Monad
can only be declared for type constructors that take one more type parameter. This might be a bit clearer if you look at how m
, Maybe
and State
occur in the type of >>=
below.
class Monad m where
(>>=) :: m a -> (a -> m b) -> m b
instance Monad Maybe where
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
instance Monad (State s) where
(>>=) :: State s a -> (a -> State s b) -> State s b
Let’s look at some examples of working with State
. To start off, let’s consider computations of type State Int a
, which represent working with a single counter.
example :: State Int Int
example = do add 3 -- increment state by 3
value <- get -- value is current state, i.e. initial+3
add 1000 -- increment state by 1000
put (value + 1) -- overwrite state with value+1, i.e. initial+4
return value -- produce value, i.e. intial+3
Note how a value of type State s a
represents a process that transforms the state (just like BankOp
). The initial state must be supplied using runState
. Again, having to use runState
makes the distinction between defining operations and executing them clearer.
A state can replace an accumulator parameter when processing a list. Here are two examples: finding the largest element of a list, and finding values in a list that occur directly after a 0
.
findLargest :: Ord a => [a] -> State a ()
findLargest [] = return ()
findLargest (x:xs) = do
modify (\y -> max x y) -- update state with max of current value and previous largest value
findLargest xs -- process rest of list
-- store the given value in the state list
remember :: a -> State [a] ()
remember x = modify (x:)
valuesAfterZero :: [Int] -> [Int]
valuesAfterZero xs = runState (go xs) []
where go :: [a] -> State [a] ()
go (0:y:xs) = do remember y
go (y:xs)
go (x:xs) = go xs
go [] = return ()
mapM
The control structures from the IO lecture work in all monads. Here are their real types.
when :: Monad m => Bool -> m () -> m () -- conditional operation
unless :: Monad m => Bool -> m () -> m () -- same, but condition is flipped
replicateM :: Monad m => Int -> m a -> m [a] -- do something many times
replicateM_ :: Monad m => Int -> m a -> m () -- same, but ignore the results
mapM :: Monad m => (a -> m b) -> [a] -> m [b] -- do something on a list's elements
mapM_ :: Monad m => (a -> m b) -> [a] -> m () -- same, but ignore the results
forM :: Monad m => [a] -> (a -> m b) -> m [b] -- mapM but arguments reversed
forM_ :: Monad m => [a] -> (a -> m b) -> m () -- same, but ignore the results
As we can see here, we can use mapM
over all of the monads we’ve met so far:
mapM (\x -> if (x>0) then Just (x-1) else Nothing) [1,2,3] ==> Just [0,1,2]
mapM (\x -> if (x>0) then Just (x-1) else Nothing) [1,0,3] ==> Nothing
mapM (\x -> msg "increment" >> msg (show x) >> return (x+1)) [1,2,3]
==> Logger ["increment","1","increment","2","increment","3"] [2,3,4]
runState (mapM (\x -> modify (x+) >> return (x+1)) [1,2,3]) 0
==> ([2,3,4],6)
Some more examples:
safeHead :: [a] -> Maybe a
safeHead [] = Nothing
safeHead (x:xs) = Just x
firsts :: [[a]] -> Maybe [a]
firsts xs = forM xs safeHead
-- an abbreviated version of an example from the last section
findLargest :: Ord a => [a] -> State a ()
findLargest xs = mapM_ update xs
where update x = modify (\y -> max x y)
Here’s filter
reimplemented using the State
monad:
rememberElements :: (a -> Bool) -> [a] -> State [a] ()
rememberElements f xs = mapM_ maybePut xs
where maybePut x = when (f x) (modify (++[x]))
sfilter :: (a -> Bool) -> [a] -> [a]
sfilter f xs = finalState
where (_, finalState) = runState (rememberElements f xs) []
We can write our own operations that work for all monads. This is made possible by type classes, as we’ve seen before. If you only use monad operations like return
and do-notation, the type system will infer a generic type for your function.
mywhen b op = if b then op else return ()
mymapM_ op [] = return ()
mymapM_ op (x:xs) = do op x
mymapM_ op xs
*Main> :t mywhen
mywhen :: (Monad m) => Bool -> m () -> m ()
*Main> :t mymapM_
mymapM_ :: (Monad m) => (t -> m a) -> [t] -> m ()
We can use these generic operations in each of our example monads:
search :: (Show a, Eq a) => a -> [a] -> Logger ()
search x ys = mymapM_ look ys
where look y = mywhen (x==y) (msg ("Found "++show y))
sumPositive :: [Int] -> State Int ()
sumPositive xs = mymapM_ f xs
where f x = when (x>0) (modify (x+))
One useful operation hasn’t yet been introduced: liftM
.
The liftM
operation makes it easy to write code with pure and monadic parts.
liftM negate (Just 3)
==> Just (-3)
liftM sort $ firsts [[4,6],[2,1,0],[3,3,3]]
==> Just [2,3,4]
runState (liftM negate get) 3
==> (-3,3)
Does the type of liftM
look familiar? It’s just like the type of fmap
! In fact, it’s easy to define a functor instance for a monad: just set fmap = liftM
. Since every Monad
needs to be a Functor
these days, modern Haskell style prefers fmap
over liftM
.
fmap negate (Just 3)
==> Just (-3)
fmap sort $ firsts [[4,6],[2,1,0],[3,3,3]]
==> Just [2,3,4]
runState (fmap negate get) 3
==> (-3,3)
The list monad (that is, the Monad
instance for []
) represents computations with multiple return values. It’s useful for searching through alternatives. Here’s a first example. For every x
we produce both x
and -x
:
We can filter out unsuitable values by produing an empty list:
If we’re using do-notation the list monad starts to look more like a looping construct:
do word <- ["Blue", "Green"]
number <- [1,2,3]
return (word ++ show number)
==> ["Blue1","Blue2","Blue3","Green1","Green2","Green3"]
More interesting example: find all the pairs in a list that sum to k
findSum :: [Int] -> Int -> [(Int,Int)]
findSum xs k = do a <- xs
b <- xs
if (a+b==k) then [(a,b)] else []
A final, more complex example. We find all palindromes from a string using the list monad, and then find the longest one.
import Data.List (sortBy)
substrings :: String -> [String]
substrings xs = do start <- [0..length xs - 1]
end <- [start+1..length xs - 1]
return $ drop start $ take end $ xs
palindromesIn :: String -> [String]
palindromesIn xs = do s <- substrings xs
if (s==reverse s) then return s else []
longestPalindrome xs = head . sortBy f $ palindromesIn xs
where f s s' = compare (length s') (length s) -- longer is smaller
palindromesIn "aabbacddcaca"
==> ["a","aa","a","abba","b","bb","b","a","acddca","c","cddc","d","dd","d","c","cac","a","c"]
longestPalindrome "aabbacddcaca"
==> "acddca"
Here’s the surprisingly simple implementation of the list monad:
instance Monad [] where
return x = [x] -- an operation that produces one value
lis >>= f = concat (map f lis) -- compute f for all values, combine the results
We’ve actually seen the list monad previously in the guise of list comprehensions. Compare this reimplementation of findSum
to the earlier one that uses do
-notation.
As you’ve probably guessed by now, IO
is a monad. However the implementations of the IO
type and instance Monad IO
are compiler built-ins. You couldn’t implement the IO monad just using standard Haskell, unlike Maybe
monad, State
monad and other monads we’ve seen.
However, true side effects fit the monad pattern just like State
and Maybe
. Just like with other monads, we’re separating the pure definitions of operations from the process of running the operations. As a bonus, you can use all the generic monad operations (mapM
and friends) with IO.
Here are some examples of writing IO using monad operations.
printTwoThings :: IO ()
printTwoThings = putStrLn "One!" >> print 2
echo :: IO ()
echo = getLine >>= putStrLn
verboseEcho :: IO ()
verboseEcho = getLine >>= \s -> putStrLn ("You wrote: " ++ s)
query :: String -> IO String
query question = putStrLn question >> getLine
confirm :: String -> IO Bool
confirm question = putStrLn question >> fmap interpret getLine
where interpret "Y" = True
interpret _ = False
Prelude> printTwoThings
One!
2
Prelude> verboseEcho
The Iliad
You wrote: The Iliad
Prelude> answer <- query "Why am I here?"
Why am I here?
Good question!
Prelude> answer
"Good question!"
Prelude> b <- confirm "Fire warheads?"
Fire warheads?
no no no no
Prelude> b
False
Prelude> b <- confirm "Make love, not war?"
Make love, not war?
Y
Prelude> b
True
Once you’ve gotten familiar with the concept of a monad, you’ll start seeing monadlike things in other languages too. The most well-known examples of this are Option types, Java Streams and JavaScript promises . If you know these languages or concepts from before, you might find this section illuminating. If you don’t, feel free to skip this.
Many langages have an option type. This type is called Optional<T>
in Java, std::optional<T>
in C++, Nullable<T>
in C#, and so on. These types often have behaviour resembling the Haskell Maybe
monad, for example:
Optional.flatMap
corresponds to >>=
: it lets you apply a Function<T,<Optional<U>>
to an Optional<T>
and get an Optional<U>
.Nullable
types. For example, a + null
becomes null
.Java Streams have a monadlike API too. Streams are about producing many values incrementally. Just like with Optional, the method Stream.flatMap
lets us take a Stream<T>
, combine it with a Function<T,Stream<U>>
and get a Stream<U>
.
As an example, if lines
is a Stream<String>
, words
takes a String
and returns a Stream<String>
and readInt
takes a String
and returns an Integer
, we can write:
This corresponds to the following Haskell list monad code:
There is much disagreement about whether Promises in JavaScript really are monads or not. However, some similarities are obvious.
First, consider the similarities between Promise.then
and >>=
. Both take an operation (promise or monadic operation), and combine it with a function that returns a new operation.
function concatPromises(promise1, promise2) {
return promise1.then(value1 => promise2.then(value2 => value1+value2));
}
concatMonadic :: Monad m => m String -> m String -> m String
concatMonadic op1 op2 = op1 >>= (\value1 -> op2 >>= (\value2 -> return (value1++value2)))
Next, let’s consider the similarities between async/await and do-notation. Both are nicer syntaxes for working with the raw Promise.then
or >>=
mechanisms. We reimplement concatPromises
using async/await, and concatMonadic
using do-notation. Their behaviour stays the same.
async function concatPromises(promise1, promise2) {
let value1 = await promise1;
let value2 = await promise2;
return value1+value2;
}
concatMonadic :: Monad m => m String -> m String -> m String
concatMonadic op1 op2 = do
value1 <- op1
value2 <- op2
return (value1++value2)
Monad
type class is a way to represent different ways of executing recipes
Maybe
)Monad
class operations (>>=
, >>
) directlydo
-notationM
is a monad, values of type M a
are operations that produce a result of type a
mapM
etc)
State
operation is easier than deciphering a complicated recursion with stateThis and the previous lecture have covered many parts where the GHC version of Haskell differs from standard Haskell 2010. Here’s a short list of the changes GHC has made, just so you know:
length
, sum
, foldr
etc. generalized to work on Foldable
instead of just listsFunctor
and Applicative
are superclasses of Monad
fail
method has been moved from the Monad
type class to its own MonadFail
classWhat is the expression equivalent to the following do block?
z >> \y -> s y >> return (f y)
z >>= \y -> s y >> return (f y)
z >> \y -> s y >>= return (f y)
What is the type of \x xs -> return (x : xs)
?
Monad m => a -> [a] -> m [a]
Monad m => a -> [m a] -> [m a]
a -> [a] -> Monad [a]
What is the type of \x xs -> return x : xs
?
Monad m => a -> [a] -> m [a]
Monad m => a -> [m a] -> [m a]
a -> [a] -> Monad [a]
What is the type of (\x xs -> return x) : xs
?
Monad m => a -> [a] -> m [a]
Monad m => a -> [m a] -> [m a]
a -> [a] -> Monad [a]