My Haskell notes based on Learn You A Haskell For Great Good
These notes will be in literate programming style. All code will be compiled and executed using GHC.
Haskell is picky about spacing vs tabs; by extension, it is also indentation sensitive. One can run into weirdness pretty quickly. Here are some links to clear that up:
- Good Haskell Style
- Haskell Indentation
- Why you shouldn’t mix tabs and spaces in Haskell?
- Haskell Style Guide
I’m not big on religious debates in programming; my philosophy is use the tool that works best for the job so in a lot of such scenarios, my answers is “it depends”. Not surprisingly, one can easily extend this to other logical discussions.
In Haskell though, some of these things matter and one might think why the Haskell folks went one way over the other. In that context, here is a good discussion on tabs vs spaces in general. Here’s another one from Silicon Valley :)
Now let’s get to the real stuff.
Simple arithmetic
5 + 2
7
10 + 14.5
24.5
Default type for numbers is floating point:
7 / 2
3.5
Be careful with negative numbers:
5 * -2
<interactive>:10:1: Precedence parsing error cannot mix `*' [infixl 7] and prefix `-' [infixl 6] in the same infix expression
Better to surround negative numbers with parens:
5 * (-2)
-10
Parens
Alright, parens are important to explicitly tell the compiler your precendence:
50 * (100 - 4999)
-244950
Otherwise, regular operator precedence rules will apply:
50 * 100 - 4999
1
Boolean algebra
Let’s look at these keywords and operators: TRUE
, FALSE
, not
, logical AND &&
, logical OR ||
True && False
False
True && True
True
False || True
True
not False
True
not (True && True)
False
Equality operators
9 == 9
True
9 == 8
False
/
means not in the context of equality operators:
9 /= 9
False
9 /= 8
True
We can compare strings as well:
"yo" == "yo"
True
"yo" == "no"
False
Syntax for functions:
min 8 9
8
So it’s the function name followed by input arguments. Another example:
succ 19
20
Calling a function takes highest precedence:
succ 5 + max 2 3 + 1
10
The above is equivalent to:
(succ 5) + (max 2 3) + 1
10
Above functions are of type prefix
i.e. function name comes before the arguments.
Another syntax for writing functions in haskell is infix
:
5 * 4
20
Wait, *
is an operator, right? Everything in haskell is a function, even operators.
Anyways, infix
means the name is at the center of the two arguments. Yes, infix
is
only valid for 2 arguments.
Any function that takes two arguments can always be represented using infix
syntax:
87 `div` 10
8
Okay, that’s how functions are called. They are defined in a similar way:
let doubleUs x y = x*2 + y*2
doubleUs 1 2
6
The let
here is just to provide the definition to the haskell interpreter. If we had a script that we were
compiling, we won’t need that. To load that script though, we’d need to say :l funcName
So we saw the syntax is function name followed by input arguments followed by = followed by an expression that calculates the output.
Haskell functions are pure, more about that later.
Haskell functions also can not begin with a capital letter. We’ll see why later.
Alright, this is how we write conditionals:
let doubleSmallNumber x = if x > 100 then x else 2*x
doubleSmallNumber 40
80
doubleSmallNumber 500
500
Note that conditionals always need an else. This is because in haskell, an if statement is an expression meaning that it has to return a value, or in other words, evaluate to something.
Lists in haskell are actually implemented as singly linked lists. Infact, they are as simple as:
data MyList a = Nil | Cons a (MyList a)
Haskell has a lot of tricks in its bag when it comes to list manipulation. Also, because of laziness, lists are used as iterators and they give acceptable performance. Examples later would help demonstrate this.
Lists is a homogenous
data structure in haskell i.e. it only stores elements of the same type.
As an example, String in haskell is just a list of characters.
There are many commands in this section, so let’s just look at code and hopefully that should be self-explanatory:
let myList = [4,77,17,23,55]
myList
4 | 77 | 17 | 23 | 55 |
myList ++ [1,2,3]
4 | 77 | 17 | 23 | 55 | 1 | 2 | 3 |
99 : myList
99 | 4 | 77 | 17 | 23 | 55 |
'C' : "AN JOIN BECAUSE STRINGS ARE LIST OF CHARS!"
CAN JOIN BECAUSE STRINGS ARE LIST OF CHARS!
myList !! 3
23
head [1,2,3]
1
tail [1,2,3]
2 | 3 |
init [1,2,3]
1 | 2 |
last [1,2,3]
3
null [1,2,3]
False
reverse [1,2,3]
3 | 2 | 1 |
Again, let’s go through some code which should be self-explanatory:
[1..10]
1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | 10 |
[1,2..10]
1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | 10 |
[10,9..1]
10 | 9 | 8 | 7 | 6 | 5 | 4 | 3 | 2 | 1 |
[1,3..10]
1 | 3 | 5 | 7 | 9 |
[2,4..20]
2 | 4 | 6 | 8 | 10 | 12 | 14 | 16 | 18 | 20 |
Floating point stepping can be funky, so better not go there:
[0.1,0.3..1]
0.1 | 0.3 | 0.5 | 0.7 | 0.8999999999999999 | 1.0999999999999999 |
['a'..'z']
abcdefghijklmnopqrstuvwxyz
You can also step by 2 letters (pretty cool, ‘an?):
['a','c'..'z']
acegikmoqsuwy
['S'..'Z']
STUVWXYZ
[13,26..7*13]
13 | 26 | 39 | 52 | 65 | 78 | 91 |
Another way using take
function:
take 7 [13,26..]
13 | 26 | 39 | 52 | 65 | 78 | 91 |
Wait, we can have infinite lists !? Well, yes:
[1,2,..]
But don’t try to execute it. Haskell is lazy but once we try to evaluate this expression, it’ll
want to calculate all numbers to infinity. That takes infinite time then, which clearly we don’t have.
The earlier example worked because take
took 7 as an argument so haskell knows we need only 7
elements of the infinite list, atleast for now. This is why laziness is really powerful!
take 10 (cycle [1,2,3])
1 | 2 | 3 | 1 | 2 | 3 | 1 | 2 | 3 | 1 |
cycle
function just repeats the list to produce an infinite list. This example worked
because we used the take
function again, which tells haskell we only need 10 elements of
this infinite list.
Similar to cycle
function is repeat
which is like cycle
but with one element only:
take 10 (repeat 5)
5 | 5 | 5 | 5 | 5 | 5 | 5 | 5 | 5 | 5 |
Can also use replicate
:
replicate 3 10
10 | 10 | 10 |
List comprehensions are one of the reasons haskell has concise and expressive syntax.
List comprehensions are very similar to Set Comprehensions in math.
List comprehensions essentially are used to form a subset of a list from a another list by operations and filters.
Let’s look at a list comprehension:
[x*2 | x <- [1..10]]
2 | 4 | 6 | 8 | 10 | 12 | 14 | 16 | 18 | 20 |
This is how the above code expression would read:
x
is drawn from the list [1..10]
and for every element in this list, multiply
it by 2 or x*2
. The final result is a list again.
Note that in haskell, x <- [1..10]
means [1..10]
is bound to x
.
Let’s go one step further; we can apply filters or predicates:
[x*2 | x <- [1..10], x*2 > 13]
14 | 16 | 18 | 20 |
This now says the same thing as before, but now, after the result is evaulated,
we filter them using the x*2 > 13
predicate before the list is finalized.
We can also have multiple predicates:
[x*2 | x <- [1..10], x*2 > 13, x*2 < 17]
14 | 16 |
Note that the two predicates here have an and relationship i.e. both must be met before the elements can go into the final list.
We can draw from multiple lists as well:
[x*y | x <- [2,5,10], y <- [8,10,11]]
16 | 20 | 22 | 40 | 50 | 55 | 80 | 100 | 110 |
Without filters, the length is 3*3
or 9
as expected.
Let’s apply a filter now:
[x*y | x <- [2,5,10], y <- [8,10,11], x*y>50]
55 | 80 | 100 | 110 |
At first tuples may seem like lists, but there are two keys differences:
- Lists are homogenous i.e. all elements have to have the same type e.g. integer. Tuples on the other hand can have elements of different types.
- The type of a list is defined only by the type of its elements i.e.
[1,2,3]
is a list of ints. For tuples, however, the type is defined not only by the types of its elements but also by the number of elements i.e. a tuple with 2 ints is different from a tuple with 3 ints which is different from a tuple with 2 ints and 1 string.
Let’s take a look at a simple example:
(1,3,"string",'c',5.09)
1 | 3 | string | c | 5.09 |
A tuple with 2 elements is called a pair:
(8,11)
8 | 11 |
Haskell has functions just for pairs:
fst (8,11)
8
snd (8,11)
11
By extension, tuples with 3 elements are called triplets. After that, they are called 4-tuples, 5-tuples etc.
Tuples are more rigid; think of how we can make a list of 2-D vectors. One way is:
[ [1,2], [8,11], [4,5] ]
1 | 2 |
8 | 11 |
4 | 5 |
Well, this sort of works but now someone can do:
[ [1,2], [8,11,15], [4,5] ]
1 | 2 | |
8 | 11 | 15 |
4 | 5 |
This works but shouldn’t. Answer is unsurprisingly, tuples:
[ (1,2), (8,11), (4,5) ]
1 | 2 |
8 | 11 |
4 | 5 |
Now no one can do:
[ (1,2), (8,11,15), (4,5) ]
<interactive>:34:10: Couldn't match expected type `(t, t1)' with actual type `(Integer, Integer, Integer)' Relevant bindings include it :: [(t, t1)] (bound at <interactive>:34:1) In the expression: (8, 11, 15) In the expression: [(1, 2), (8, 11, 15), (4, 5)] In an equation for `it': it = [(1, 2), (8, 11, 15), (4, 5)]
Heck, they can’t even do this:
[ (1,2), (8,11), ("four",5) ]
<interactive>:36:4: Could not deduce (Num [Char]) arising from the literal `1' from the context (Num t) bound by the inferred type of it :: Num t => [([Char], t)] at <interactive>:36:1-29 In the expression: 1 In the expression: (1, 2) In the expression: [(1, 2), (8, 11), ("four", 5)]
This is because, as discussed earlier, type of tuples encodes both the type of all of its elements as well as the total number of elements.
Finally, let’s look at the very useful, zip
function:
zip [1..5] ['a'..'e']
1 | a |
2 | b |
3 | c |
4 | d |
5 | e |
As we see, it takes in two lists, and stiches them element-by-element forming a list of pairs. Note that if the lists have different lengths, it picks the minimum of the lengths:
zip [1..3] ['a'..'e']
1 | a |
2 | b |
3 | c |
Haskell has a static type system which means that when you compile your haskell code, the compiler will try to
know types of all expressions in the code. If all types can’t be found, the compiler will error out. Then the
question comes up on how Haskell calculates what type you are using. In some cases, the code explicitly states
the types e.g. in a function declaration. In other cases, Haskell tries to infer or deduce the type based on the
context. For example, when the compiler sees let a = 'p'
, it deduces the type of a
is char
. In general, Haskell
uses an extension of Hindley-Milner-style type inference.
Alright, now how do we ask Haskell what’s the type it has calculated? Here’s how:
Prelude> :t 'a'
'a' :: Char
Prelude> :t "a"
"a" :: [Char]
Prelude> :t "HELLO"
"HELLO" :: [Char]
Prelude> :t (True, 'a')
(True, 'a') :: (Bool, Char)
Prelude> :t (1, 'a')
(1, 'a') :: Num t => (t, Char)
Prelude> :t 4 == 5
4 == 5 :: Bool
So, when we say :t expression
, Haskell gives us the result in the format expression :: type
.
Let’s try this on functions ([Int] -> Int
is called a function declaration
where we explicitly state the function type):
let getListHead :: [Int] -> Int; getListHead list = list !! 0
:t getListHead
getListHead :: [Int] -> Int
By the way, remember that Haskell is lazy? So we can actually get the head of an infinite list:
let getListHead :: [Int] -> Int; getListHead list = list !! 0
getListHead [1,2..]
1
Alright, back to types. What if we don’t provide an explicit type declaration and let Haskell decide the type of the function:
let getListHead list = list !! 0
:t getListHead
getListHead :: [a] -> a
Now what’s a
? It’s not a type because types always start with upper case letters in Haskell.
It’s actually a type variable. It signifies that a
can be of any type. This is like generics in other languages.
Functions that have type variables in their types are called polymorphic functions in Haskell.
Let’s see the type of another pre-defined function in Haskell:
:t fst
fst :: (a, b) -> a
This says that the fst
function takes in a pair of type (a,b)
where a
and b
can be of any type themselves. The function
then returns a value of type a
. This makes sense since the fst
function returns the first element of a pair.
Note that a
and b
can be the same type. This is just like variables. Two variables can have the same value.
Let’s keep moving. What if we do:
:t (==)
(==) :: Eq a => a -> a -> Bool
Wait, what? What’s =>
now? What’s Eq
? Let’s back up a little, isn’t ==
an operator? No, remember in Haskell operators
are actually functions? We can call them whatever we want; the important thing is that operators in Haskell are no different
than other functions since they are functions and are implemented as such in the language.
Alright, so we were taking the type of a function. We can parse the part a -> a -> Bool
atleast. This says that the
function takes in two input arguments of the same type a
, which itself can be of any type. The function then
returns a value of type Bool
.
Good, what’s Eq
now? It’s a typeclass.
Typeclasses are like abstract classes in C++ that provide an interface. When we derive from the abstract class, we
are saying that the derived/child class is a kind of the abstract class. For example, an abstract class can be
Fruit
. Although that’s just an interface which we can’t instantiate in C++. We can derive from this class though,
to create Apple
, Orange
, Banana
etc. All these classes are now concrete classes that we can instantiate. Finally,
we can create instances of these classes. Like we can have 2 apples, 3 oranges, and 1 banana. We do this by making
objects of that class in C++.
So how can we compare the above with Typeclasses, types, and values? Well, Typeclasses are like interface, types are like concrete derived classes of that interface, and values are instances/objects of the derived classes.
What’s the motivation behind having Typeclasses? Well, if a type is part of a typeclass, that means that it supports and implements the behavior of the typeclass it describes.
What’s =>
then? It means class constraint, which by the way we can have more than one seperated by commas.
So in addition a -> a -> Bool
, we are also saying that type variable
a
now can not be of any type, but now it must be of a type that is of typeclass Eq
. All of this information
is encapsulated in (==) :: Eq a => a -> a -> Bool
.
Eq
typeclass provides an interface for testing for equality. Most types in Haskell are part of Eq
typeclass because in general, we should
be able to compare values of those types. By the way, types can part of multiple typeclasses as well.
Let’s look at the type of a very useful function in Haskell, fromIntegral
:
:t fromIntegral
fromIntegral :: (Integral a, Num b) => a -> b
This says that the fromIntegral
function takes in one input argument of type variable a
and returns a value of type variable
b
. b
can be of any type. However, a
type variable is restricted. a
must to be of Integral
and Num
typeclasses.
This function is useful because it takes an integral typed input argument and returns a more generic Num
typed value.
We can explicitly tell Haskell what type to use by using ::
as follows:
Prelude> let myFunction x = 2*x
Prelude> :t myFunction
myFunction :: Num a => a -> a
Prelude> let myFunction2 :: Int -> Int; myFunction2 x = 2*x
Prelude> :t myFunction2
myFunction2 :: Int -> Int
Prelude> let myVar = 5
Prelude> :t myVar
myVar :: Num a => a
Prelude> let myVar2 :: Int; myVar2 = 5
Prelude> :t myVar2
myVar2 :: Int
Prelude> :t read
read :: Read a => String -> a
Prelude> read "5"
*** Exception: Prelude.read: no parse
Prelude> read "5" :: Int
5
Prelude> read "5" :: Float
5.0
Prelude> (read "5" :: Float) * 4
20.0
Prelude> read "(3,'a')"
*** Exception: Prelude.read: no parse
Prelude> read "(3,'a')" :: (Int,Char)
(3,'a')
Sidenote: Variables in Haskell are just functions with no input arguments!
See this link for a summary of different types and typeclasses in Haskell.
This is how you declare and define a function in Haskell:
-- this is a function declaration
let myFunc :: [Int] -> Int
-- this is a function definition
let myFunc x = x !! 0
Note that if you skip the declaration, Haskell will try to infer (specifically the function type) it from the definition.
But functions in Haskell are much more powerful than what you have seen until now. Let’s cover some of the important features in functions.
When defining functions, you can define seperate function bodies for various patterns. You can pattern match on inputs with any data type. Let’s go through some examples.
let isAnswerToLife :: (Integral a) => a -> Bool
isAnswerToLife 42 = True
isAnswerToLife _ = False
isAnswerToLife 7
False
isAnswerToLife 42
True
Haskell goes through patterns from top to bottom; as soon as the pattern matches on the input, Haskell returns the corresponding expression value.
Let’s look at a simple recursive factorial example:
let factorial :: (Integral a) => a -> a
factorial 0 = 1
factorial n = n * factorial (n-1)
factorial 5
Prelude> 120
It’s a good idea for patterns to be exhaustive i.e. cover all possible input value based on the function input type in the function declaration. However, Haskell allows for patterns to be non-exhaustive. If you try to invoke the function with an input that doesn’t match a pattern, Haskell will let you know at run-time:
let charName :: Char -> String
charName 'a' = "Alex"
charName 'b' = "Bob"
charName 'c' = "Cat"
charName 'a'
Alex
charName 'c'
Cat
charName 'd'
"*** Exception: <interactive>:224:33-97: Non-exhaustive patterns in function charName
Let’s pattern match pairs:
let addVectors :: (Num a) => (a,a) -> (a,a) -> (a,a)
addVectors (x1,y1) (x2,y2) = (x1+x2, y1+y2)
addVectors (1,2) (3,4)
4 | 6 |
Pretty cool! Note that here we have only one pattern, which is already exhaustive, so we’re good!
Not only can we pattern match in functions, but we can do so in list comprehensions as well! Check this out:
let xs = [(2,3), (6,7), (1,2)]
[a+b | (a,b) <- xs]
5 | 13 | 3 |
So when we are drawing from the list variable (or function with 0 input arguments) xs
, we can draw the pairs
inside the list and match two variables a
and b
in that pair.
Alright, back to functions now. We can pattern match list inputs arguments as well. But before that, remember
that [1,2,3]
is just syntactic sugar for 1:2:3:[]
where []
is the empty list. So a pattern like
[x:xs]
would bind head of the list to x
and the rest to xs
. This is very useful in recursive functions.
However, note that patterns that have :
in them can only match against lists of length 1 or more.
By extension, we can also bind [1,2,3,4]
to a pattern like [x1:x2:xs]
. Here 1
will bind to x1
, 2
to x2
and [3,4]
to xs
.
Now let’s implement our own head
function:
let head' :: [a] -> a
head' [] = error "head' only takes non-empty lists."
head' (x:_) = x
head' [4,5,6]
4
Note that we always use parens ()
for pattern matching list inputs.
Here’s another example from the book:
tell :: (Show a) => [a] -> String
tell [] = "The list is empty"
tell (x:[]) = "The list has one element: " ++ show x
tell (x:y:[]) = "The list has two elements: " ++ show x ++ " and " ++ show y
tell (x:y:_) = "This list is long. The first two elements are: " ++ show x ++ " and " ++ show y
Prelude> tell []
"The list is empty"
Prelude> tell [1]
"The list has one element: 1"
Prelude> tell [2,3]
"The list has two elements: 2 and 3"
Prelude> tell [6,7,8]
"This list is long. The first two elements are: 6 and 7"
Prelude> tell [4,5,6,7,8,9]
"This list is long. The first two elements are: 4 and 5"
Concise, expressive, nifty!
To avoid losing the reference to the entire list while doing pattern matching, Haskell has something
called patterns, the syntax for which is @
. Here’s how it works:
let capital :: String -> String
capital "" = "Empty"
capital all@(x:xs) = "First character of " ++ all ++ " is " ++ [x]
capital "42 is the number to remember"
First letter of 42 is the number to remember is 4
Nice, so we avoid typing in [x:xs]
everytime and instead just say all
. Rest of the binding in matching works the same way.
Lastly, you can not use ++
in pattern matches. Details in the book.
I am reading the book as I write these notes. So in that order, one of the coolest features of Haskell I found was List Comprehsensions where we can create a subset of a list by applying filters and actions, just like we do in match. I think the next coolest feature would be pattern matching in Haskell functions.
Say you have code like this:
let myCompare :: (Ord a) => a -> a -> Ordering
a `myCompare` b = if a > b then GT
else if a == b then EQ
else LT
Instead you can write using |
or guards:
let myCompare :: (Ord a) => a -> a -> Ordering
a `myCompare` b
| a > b = GT
| a == b = EQ
| otherwise = LT
3 `myCompare` 2
GT
Side note:
- In this example, we used infix notation to define the function; this is allowed.
- We also used
Ord
typeclass,Ordering
type, andLT/EQ/GT
type values forOrdering
type.
We can use where
keyword after the guards to define names (variables) or functions that can be used across
guards i.e. their scope is local to the function. Let’s see an example from the book:
bmiTell :: (RealFloat a) => a -> a -> String
bmiTell weight height
| bmi <= skinny = "You're underweight, you emo, you!"
| bmi <= normal = "You're supposedly normal. Pffft, I bet you're ugly!"
| bmi <= fat = "You're fat! Lose some weight, fatty!"
| otherwise = "You're a whale, congratulations!"
where bmi = weight / height ^ 2
skinny = 18.5
normal = 25.0
fat = 30.0
We can say this as: 18.5
has been binded to skinny
. Again, since the scope is local, we can’t access these
where bindngs outide the function. If we want to share a name (variable), we need to define it as a global but
that is undersirable in general so let’s avoid discussing that for now.
We can also use where bindings to pattern match. Above example can be re-written as:
bmiTell :: (RealFloat a) => a -> a -> String
bmiTell weight height
| bmi <= skinny = "You're underweight, you emo, you!"
| bmi <= normal = "You're supposedly normal. Pffft, I bet you're ugly!"
| bmi <= fat = "You're fat! Lose some weight, fatty!"
| otherwise = "You're a whale, congratulations!"
where bmi = weight / height ^ 2
(skinny, normal, fat) = (18.5, 25.0, 30.0)
Another cool example from the book:
initials :: String -> String -> String
initials firstname lastname = [f] ++ ". " ++ [l] ++ "."
where (f:_) = firstname
(l:_) = lastname
We can also define function in where blocks; another example from the book:
calcBmis :: (RealFloat a) => [(a, a)] -> [a]
calcBmis xs = [bmi w h | (w, h) <- xs]
where bmi weight height = weight / height ^ 2
let is similar to where binding in the sense that it lets us bind expressions to names (variables) or functions at the end of the function. The difference is that the scope of let bindings don’t span across guards.
The syntax for using let is: let <bindings> in <expressions>
. Here’s the important bit: <bindings>
are expressions themselves.
Let’s look at some examples from the book:
cylinder :: (RealFloat a) => a -> a -> a
cylinder r h =
let sideArea = 2 * pi * r * h
topArea = pi * r ^2
in sideArea + 2 * topArea
let can be used outside of functons as well:
4 * (let a = 9 in a + 1) + 2
42
<bindings>
can be functions since they are expressions and in the <expression>
block, we can call the function.
[let square x = x * x in (square 5, square 3, square 2)]
25 | 9 | 4 |
Let’s bind more than one thing:
(let a = 100; b = 200; c = 300 in a*b*c, let foo="Hey "; bar = "there!" in foo ++ bar)
6000000 | Hey there! |
We can pattern match as well:
(let (a,b,c) = (1,2,3) in a+b+c) * 100
600
We can use them inside list comprehensions too:
calcBmis :: (RealFloat a) => [(a, a)] -> [a]
calcBmis xs = [bmi | (w, h) <- xs, let bmi = w / h ^ 2, bmi >= 25.0]
Note that here we can’t use bmi
in (w, h) <- xs
because we draw from the list at the very start
when bmi
is not available.
That was a lot of stuff to absorb! Let’s cover case expressions next and finish this chapter.
Just like if/else expressions and let bindings, case expressions, are well, expressions. They are similar to case expressions in C++ but in Haskell, we can do pattern matching as well in case expressions.
Here’s the syntax for that:
case expression of pattern -> result
pattern -> result
pattern -> result
...
In this syntax, expression
is matched against pattern
.
Here’s an example from the book:
head' :: [a] -> a
head' xs = case xs of [] -> error "No head for empty lists!"
(x:_) -> x
Case expressions can be used pretty much everywhere:
describeList :: [a] -> String
describeList xs = "The list is " ++ case xs of [] -> "empty."
[x] -> "a singleton list."
xs -> "a longer list."
Phew! That was a lot of new syntax. Personally, I don’t think there will another syntax heavy chapter like this in the book but time will tell.
This chapter doesn’t talk about Haskell much, but in general talks about what is recursion, how is it super useful and appropriate in Haskell, and then we see a bunch of examples. I won’t be taking notes for this but you can go here to read this chapter from the book.
We were told a lie before! What’s the type of the max
function?
max 4 5
5
:t max
max :: Ord a => a -> a -> a
It’s a -> a -> a
. What does it mean? Well, I thought it means max
takes in two input arguments
of type varible a
and returns a value of type variable a
.
That’s wrong! max
does not take two input arguments, only one! Let’s see:
max 4
<interactive>:19:1: No instance for (Show (a0 -> a0)) (maybe you haven't applied enough arguments to a function?) arising from a use of `print' In the first argument of `print', namely `it' In a stmt of an interactive GHCi command: print it
We get an error here but that just means that the resulted expression can not be shown. The
reason is that function types are not part of the Show
typeclass like most other things. The
interpreter displays all the things that are in Show
typeclass by applying show
function on them.
So, if it’s not wrong, then what did max 4
return? It returned a function. Now we’re getting into the concept
of higher order functions and currying or curried functions.
This is the truth:
f : x y = x+y is actually equivalent to: 1) f x = g where g : a = x+a 2) g y
It’s called currying because Haskell automatically made functions in a way that at each level of exection, it passes the additional input argument.
Let’s look at an example. In terms of type:
:t max
max :: Ord a => a -> a -> a is actually Ord a => a -> (a -> a)
This means that max
takes in an argument, returns a function. This returned function also takes in
an argument, takes the max of the argument and 4, and returns the final answer.
In terms of order of execution:
max 4 5 is actually (max 4) 5
This is roughly (in terms of execution):
max
is executed with argument 4max
returnsfcn
wherefcn
is defined as taking one argument and returning max of that argument and 4fcn
is executed on argument 5fcn
returns max of argument and 4 i.e. 5 and 4 i.e. 5
Interesting! Given this fact, we can deduce that from the code point of view, now we can pass less arguments to the functions. This is called partial application. This can be best seen in an example:
let myMult3 :: (Num a) => a->a->a->a; myMult3 x y z = x*y*z
let myMult3_Partial x = myMult3 x
let myMult2_with4 = myMult3 4
let myMult2_with8 = myMult3 8
myMult3_Partial 2 3 4
24
myMult2_with4 2 3
24
myMult2_with8 2 3
48
Let’s see another use of this:
let compareWithTen_v1 x = 10 `compare` x
compareWithTen_v1 5
GT
The above can also be written as:
let compareWithTen_partial = compare 10
compareWithTen_partial 5
GT
Note that this code:
let compareWithTen_v2 x = x `compare` 10
compareWithTen_v2 5
LT
Can not be written as compareWithTen_partial
because x is the first argument to compare
function.
Yet another use for this:
let divideByTen :: (Floating a) => a->a; divideByTen = (/10)
divideByTen 1024
102.4
Functions can also take other functions as inputs:
let applyTwice :: (a->a)->a->a; applyTwice f x = f (f x)
applyTwice (/10) 1024
10.24
Now that I think about it, currying looks a lot like implementation detail but knowing that Haskell implements
it internally, clients can use it for their advantage i.e. add to their bag of tricks. What do I mean by that?
Well, from a new haskell programmer point of view, for fcn: a->b->c
, he/she is passing a
and b
and getting
c
. It’s fine to think this way since thinking about it as fcn: a->(b->c)
won’t change the final result
ever; I am pretty sure we can even prove it formally. The thing is that Haskell implemented multiple input arguments
in a way that functions always take 1 input and return a function (a->(b->c)
) or a value (a->b
). There’s
no such thing as >1 inputs in the implementation but the client can think about it as multiple input arguments
because that’s what the implementation emulates. Other than just this being an implementation thing, the above
examples show partial application where it be useful.
Rest of the chapter talks about map
, filter
, foldl
, foldr
, scanl
, and scanr
functions which are really useful in the context
of higher order functions. You can read about them here.
Lambda are anonymous functions that are mostly created when we need some function only once. They are expressions.
Syntax for lambdas in Haskell is \
. Here’s an example:
(\x -> x + 1) 5
This lambda expression returns a function that adds one to it’s input
So, we can say:
applyTwice (\x -> x + 1) 5
7
$
let’s us break the typical left-associative nature of function execution:
f a b c === ((f a) b) c
Example:
sqrt 3+4+9
14.732050807568877
Well, that’s wrong! sqrt 16
is 4. This is because of left-associative function execition, Haskell does this:
sqrt 3+4+9 === sqrt 3+(4+9) === (sqrt 3) + (4+9) == 1.73 + 13 == 14.73
This sort of lines up with the idea in Haskell that functions take one input argument only.
Anyways, this is how we generally fix this:
sqrt (3+4+9)
4.0
Yes, we used parens. More keystrokes. Instead, we can do:
sqrt $ 3+4+9
4.0
This doens’t seem too useful in this example so let’s look at this one:
sum (filter (> 10) (map (*2) [2..10]))
80
Equivalent way of doing this:
sum $ filter (> 10) $ map (*2) [2..10]
80
Other than getting rid of parens, this is also useful like this:
map ($ 3) [(4+), (10*), (^2), sqrt]
7.0 | 30.0 | 9.0 | 1.7320508075688772 |
Yes, we used it as function application which it is.
Note that $
is right-associative.
In Math, composition is:
(f.g)(x) == f(g(x))
That is create new composite function (f.g
) by applying g
and then applying f
to the result of what g
returned.
In Haskell it’s pretty much the same and the syntax is, unsurprisingly, .
:
let myFunc = negate . (+ 3)
myFunc (-5)
2
Haskell pseudo-code to implement this via bootstrapping:
(.) :: (b -> c) -> (a -> b) -> a -> c
f . g = \x -> f (g x)
Note that to use certain features in Haskell, sometimes we need to bind functions to names.