Haskell

Table of Contents

1. Sources

Textbook

  1. "Programming in Haskell" by Graham Hutton

Online

  1. Learn you a Haskell for Great Good! abbreviated in this set of notes as LYAHFGG.
  2. A "Gentle" Introduction to Haskell

2. Introduction

Haskell is a

  1. statically scoped
  2. statically typed
  3. non-strict by default (lazy evaluation)
  4. functional language (functions are first-class)
  5. with Automatic type inference

Haskell is in many ways, the most sophisticated programming language available today. Its power in practical situations comes from its powerful type system.

In comparison to Oz, Haskell does not have

  1. data flow variables
  2. Partial values
  3. Concurrency (debatable?)

In addition, as in the declarative part of Oz, there are no side-effects. An appropriate xkcd cartoon.

3. Installation

From https://www.haskell.org/downloads/. The full Haskell platform is recommended. I will use the ghc (Glasgow Haskell Compiler) in the course, and the interactive shell ghci.

ghc, the compiler will compile files with a .hs files.

4. Values

4.1. Expressions and types

All computations are done by evaluating expressions. The result of an evaluation is a value.

\x -> x+1

is an anonymous function. 3 is a number, [1,2,3] is a list. Note that a Haskell list has entries separated by commas.

Every value has a type. Try the following in the interactive shell ghci.

:t 3
:t [1 2 3]
:t (\l x -> x+1)

4.2. Numeric types

4.3. Lists, List comprehensions

4.3.1. Definition and examples

Haskell lists are arbitrary length collections with objects of the same type. (different from Oz). The list is specified within square brackets, and the elements are separated by commas. For example, the following are lists.

[1,2,3]
[succ, add2]

On the other hand, [succ, add] will not be a valid list. This is because the functions have different types.

4.3.2. some elementary list functions

  1. ++ : append lists
  2. head: first element of a non-nil list
  3. tail: for a non-nil list, all elements but the head. For a nil list, this is nil.
  4. length: number of elements in the list
  5. !! : get an element from a list. The first index is 0. [1,2,3] !! 0 yields 1.
  6. <,<=,>,>=,==,!= : lexicographic comparison of lists.

4.3.3. pattern matching on lists

Example:

case [1,2,3] of [] -> 0; (x:xs) -> 1;

4.3.4. list comprehensions

We can define a list using list comprehensions, similar to how we define sets in mathematics. The general format is

[ (f x) | x <- generating_list, (predicate x)]

For each element x from generating_list, if (predicate x) is evaluated to true, then we add the result (f x) to the final list. There may be more than one predicate.

Some examples.

Example 1. Squaring the elements of another list

let list=[1..10]

list1 = [ x**x | x <- list]

Example 2. Reversing a list through list comprehensions

let reversed_list = [ list!!((length list)-i) | i <- [1..(length list)] ]

Example 3. Drawing from multiple lists at the same time

(Loops over all pairs)

[x*y | x <- [1,2,3], y <- [2,3,4]]

4.4. Tuples

5. Functions and functional programming

5.1. Infix convention

`foo`

or with operators, just using them in an infix manner.

5.2. Defining named functions

A function definition in Haskell is a sequence

5.3. Pattern matching in functions

Instead of the case syntax.

5.4. Higher order functions

5.5. Errors

The type of error is [Char]->a which makes it usable in various functions, each of which may return different types.

6. Types and Typeclasses.

(This presentation follows the excellent book "Programming in Haskell" by Graham Hutton, who is a faculty in Glasgow, and who entirely by coincidence, shares the first two initials of ghc.)

6.1. Definition and Type Inference

Definition: A type is a collection of related values.

Typically, all elements of the same type will suport the same set of operations.

Every Haskell expression must have a type. The type is calculated before the expression is evaluated. The process for calculating the type of an expression is called type inference.

One important step in type inference is the rule for function application. This says that if \(f\) is a function that maps expressions of type \(A\) to expressions of type \(B\), and \(e\) is an expression of type \(A\), then \(f(e)\) has type \(B\).

\[f::A \to B, e ::A \qquad {\rm yields}\qquad f (e) :: B.\]

Since the type of the expression is evaluated before the expression is evaluated, Haskell is said to be type-safe - i.e. once the type inference algorithm has certified that an expression is correctly typed, evaluating the expression after that is guarateed not to produce any type errors.

It is important to keep in mind that just because a program is type-safe, it does not mean that it will never produce any error when running. A simple example is the expression 1 `div` 0 which is well-typed (try it in the interactive shell), but will crash when evaluated. This error is classified not to be a type error. Type safety only means that type errors will not happen when evaluating well-typed expressions.

Types are classified into [TBD].

6.2. Basic Types

  1. Bool : contains two values True and False.
  2. Char : single characters
  3. String : all sequences of characters, enclosed in double quotes. A string is the same as a list of ~Char~s.
  4. Int :
  5. Integer : arbitrary sized integers
  6. Float :

A single number like 4 may have more than one type - e.g. 3::Int, 3::Integer, 3::Float. To properly deal with this idea, we use the notion of type classes which we will discuss in a while.

6.3. List types

A list is a sequence of elements of the same type. The elements in a list are enclosed in square brackets, and separated from each other by commas. If the elements are of type T, then we denote the type of a list of such elements by [T].

A list may have infinite length. Such lists can be handled since Haskell has lazy evaluation.

6.4. Tuple types

A finite sequence of components of possibly different types, with elements being enclosed in brackets, separated by commas.

e.g. (1, "Hello") :: Num a => (a, [Char])

Semantic Issue: Since tuples allow elements different types, it must necessarily have finite length - otherwise, we cannot infer its type.

6.5. Function types

A function maps arguments of certain types to values of other types.

Suppose we define

neg True = False
neg False = True

Then neg :: Bool -> Bool.

Similarly,

or False False = False
or True  _     = True
or _     True  = True

Then or: Bool->Bool->Bool.

6.6. Curried functions

[TBD]

6.7. Polymorphic types

We have seen that length calcuates the list of any type. Hence the type of length is [a] -> Int. Since it contains a type variable a instead of a concrete type, we say that length is polymorphic.

Most functions in the Prelude have polymorpic types.

6.8. Overloaded types

If a polymorphic type has a class constraint, then it is said to be overloaded.

For example, (+) :: Num a => a -> a -> a has the constraint Num a, which specifies that the type variable a must be of the type class Num. We will discuss type classes shortly. Another way to say this is that the type a must be an instance of the type class Num.

6.9. Basic classes

A type is a collection of related values.

A class is a collection of types where every type in the class support certain overloaded operations. These operations are called methods.

A few basic classes are as follows.

(If a type a supports all methods of a class, then we can say that a is an instance of that class. A single type a may be an instance of different classes.)

6.9.1. Eq: equality types

Each type in the type class Eq supports the operations (==), (/=).

e.g. The basic types Bool, Char, String, Int, etc. are instances

6.9.2. Ord: ordered types

Each type in the type class Ord supports (>), ~(>=), (<), (<=), min and max.

e.g. Bool, Char, String, Int etc.

6.9.3. Show: showable types

This class contains types whose internal representations can be converted into strings. They must support the method show.

6.9.4. Read : readable types

This clas contains types whose values can be converted from strings. They must support read.

6.9.5. Num : numeric types

Support (+), (-), (*), negate, abs (absolute value), signum (returns the sign of the number, -1 if negative, 0 if 0, and 1 if positive).

6.9.6. Integral: integral types

This contain instances of Num which also support div and mod. For example, it is not possible to define mod over Float~s, so ~Float is an instance of Num but not Integral.

6.9.7. Fractional:

Instances of Num which support (/) and recip.

7. Declaring Types and Typeclasses

We now show how to define new types and type classes in Haskell

7.1. Type declarations

  1. Introduce a new name for an existing type (similar to typedef in C.)
type String = [Char]
  1. Introduce new types, for example, product types (or equivalently, types of tuples.
type Position = (Float,Float)

Type declarations cannot be recursive. Recursive type declarations can be introduced using *data*

7.2. Data Declarations

This is to introduce a completely new type, rather than another name for an existing type.

  1. For example,
data Move = Left | Right | Up | Down

In this declaration, | is called "or" and the new types in the class (Left etc.) are called constructors. Constructors' names must begin with capital letters.

Using this data type, we can define functions

move :: Move -> Position -> Position
move Left(x,y) = (x-1,y)
move Right(x,y) = (x+1,y)
move Down(x,y) = (x,y-1)
move Up(x,y) = (x,y+1)
  1. Data declarations can be parametrized
data Maybe a = Nothing | Just a

safediv :: Int ¡ú Int ¡ú Maybe Int
safediv 0 = Nothing
safediv m n = Just (m ¡®div¡® n)


safehead :: [a] ¡ú Maybe a
safehead [] = Nothing
safehead xs = Just (head xs)
  1. Data declarations can be recursive.

For exaxmple, we can define our own list type as follows.

data List a = Nil | Cons a (List a)

A list may be of the following form:

Cons 1 (Cons 2 Nil)

7.3. Class and instance declarations

7.3.1. Defining classes and instances

We have seen two ways to declare types - using type for synonyms of existing types, and data to create new types.

We now introduce a mechanism for defining classes and instances. (Instances of classes are types).

The standard library defines the class Eq as follows.

class Eq a where 
  (==), (/=) :: a->a->Bool
  x /= y = not (x == y)

To declare an instance of the above class, we must define (==) and (/=).

False == False = True
True == True  = True
_==_           = False

7.3.2. Extending classes

class Eq a => Ord a where
  (<), (>), (<=), (>=) :: a->a->Bool
  ...

and define an instance of the class Ord as in

...

7.3.3. Deriving instances

When we define a new type and want to specify that it is an instance of a number of existing classes, we can use deriving.

data Bool = False | True
            deriving (Eq, Ord, Show, Read)

7.4. The Functor class

We now consider an important class called Functors. This is a class of types which can support mapping over them.

We can define the usual map over lists as

map f [] = []
map f (x:xs) = (f x):(map f xs)

The type of map is map :: (a->b) -> [a] -> [b].

This applies f to each element of the input list, and returns the list of outputs. For map, one essential feature is that the list contains elements all of the same type (otherwise, we cannot apply the same function f over them.)

We now wish to support this operation over other types, for example, binary trees etc. What ever the type of the input "collection" is, we want the output type to be the same "collection".

The class Functor takes a type t as parameter, and requires a function fmap to be implemented. The function fmap should map over the type t and return a value of type t. (It is good to keep the binary tree as an example in mind.)

class Functor t where
   fmap :: (a->b) -> t a -> t b

Suppose our binary tree type is

data BinaryTree a = Nil | Node a (BinaryTree a) (BinaryTree a) 
   deriving (Eq, Show)

(We may choose to override the default Eq to implement a true BinaryTree, for example).

An example of a binary tree is (Node 2 (Node 1 Nil Nil) (Node 3 Nil Nil)). Its type will be

:t (Node 2 (Node 1 Nil Nil) (Node 3 Nil Nil))
(Node 2 (Node 1 Nil Nil) (Node 3 Nil Nil)) :: Num a => BinaryTree a

Suppose we want to provide a function to map over binary trees and return the resulting binary trees. Of course, we can implement a binaryTreeMap function to do this. But, in this case, the user of the function will have to remember this particular name of the function.

binaryTreeMap f Nil = Nil
binaryTreeMap f (Node a left right) = Node (f a) (binaryTreeMap f left) (binaryTreeMap f right)

It will be nicer if we can claim that our BinaryTree belongs to a class of types which can support map using the same function as other types of that class. This provides a uniform way to map over all objects of any of these types. This is what a Functor is.

So, how do we make a list as a Functor? By providing an fmap for lists as follows. (This has already been defined in GHC.Base)

instance Functor [] where
  fmap = map

Hence, we can map over lists also as follows: fmap succ [1,2,3] which outputs [2,3,4].

To make our BinaryTree into a mappable type, we declare it to be an instance of Functor.

instance Functor BinaryTree where
  fmap=binaryTreeMap

and we can use it as follows.

fmap  succ (Node 2 (Node 1 Nil Nil) (Node 3 Nil Nil))

Thus a Functor t converts a type t into a mappable type - one that supports a standard function fmap.

What type is a Functor or any other class like Num? To understand this, we now look at a slightly advanced topic.

In order for a type to be a functor, it must obey some functor laws. These laws are

  1. fmap id = id
  2. fmap (f . g) = (fmap f) . (fmap g)

Exercise. Show that the BinaryTree type satisfies the functor laws.

7.5. Types of Constructors : Kinds (*)

Constructors take types as input, and output other types - they are maps from types to types.

Definition: A type is said to be concrete if it does not take another type as a parameter.

Examples of concrete types are Int, Bool etc.

If a type is not concrete, then it is abstract.

An example of an abstract types is the type List, which takes another type as a parameter (as in List a).

Usually the input types are abstract types, and the output types usually are concrete types.

For example, consider the declaration of the recursive type: data List a = Nil | Cons a (List a).

In order to describe the type of a constructor, which maps types to types, it is necessary to consider the types of the inputs and outputs of the constructors. We end up discussing the type of a type, which in Haskell is called a kind. We can examine the types of constraints using :k in the interactive interpreter.

When we type :k Int, it prints a *. If the kind of a type is a *, then it is a concrete type. A concrete type has no type parameters (unlike List a which we defined earlier, which takes the type variable a as a parameter).

In short: to get the type of a value, we use :t and to get the kind of a type, we use :k.

Prelude> :k Int
Int :: *
Prelude> :k Num
Num :: * -> Constraint

For the type List we just defined, we have

Prelude> :k List
List :: * -> *
Prelude> :k List Int
List Int :: *

Here, List is a constructor that takes a concrete type and returns another concrete type. We know that Int is a concrete type, hence List Int is a concrete type.

The kind of a Functor is Functor:: (*->*) -> Constraint.

What is a Constraint? In order to see the kind of Constraint, we have to do import GHC.Exts. This is an advanced topic which we will not cover. Please have a look at the GHC documentation.

8. Modules

Definition: A module is a collection of related functions, types and typeclasses.

The top-level module may load other modules. The functions, types and typeclasses in the loaded module are available in the top-level module. We can load a module by using the import keyword.

For example, consider the following code from LYAHFGG.

import Data.List
numUniques = length . nub

You can import only some functions from a module using

import Data.List (nub,length)
numUniques = length . nub

9. Applicative Functors

9.1. Applicative Functors : Motivation

Recall that a Functor is a class that supports mapping over it. So if we say that BinaryTree is an instance of Functor, then BinaryTree supports fmap.

Suppose we have a Functor t. Then type of fmap is fmap:: (a->b) : t a -> t b. That is to say, fmap takes two input arguments:

  1. A function of the type a -> b.
  2. A "collection t" where each each element has type a.

and returns

  1. A "collection t" where each element has type b.

Examples of "collection t" we have seen so far are List and BinaryTree.

(From LYAHFGG) Even though we currently think of Functors as mapping "collections" to "collections", the more accurate intuition will be that of a mapping from a "computational context" to another "computational context". This will become more relevant as we discuss Monads.

If a type constructor is to be an instance of Functor, then it must take a single concrete type as parameter (as in the case of, say List). We want to now generalize this to have Functor-like behaviour for type constructors with more than one parameter. This is done with the help of Applicative Functors.

Consider the following data type

data Either a b = Left a | Right b deriving (Eq, Ord, Read, Show)

We could take the idea of currying and consider a "curried" version of Either which has one parameter fixed, as follows.

instance Functor (Either a) where 
 fmap = -- Fill definition here

9.2. Applicative Functors : Usage

10. I/O in Haskell (Not what you expect)

In a file, for example, test.hs, type:

main = putStrLn "Hello World"

Compile the file using ghc test.hs and run test. It should print Hello World. What is main?

It is the entry point for a Haskell program, and must have an IO type. Here, the type of main is IO (). This name is special only inside the module Main. The Main module loads up the other modules.

The type of putStrLn is putStrLn :: String -> IO (). It takes a string as input, and returns an IO action whose result has type (). Recall that tuples were enclosed in brackets. The result type () is known as the empty tuple, and is also known as unit. An IO action is an operation that carries out input-output interactions with terminals or files. This operation will have side-effects like reading from the terminal input or printing to the terminal output, and may also return values. (These are similar to getchar() and putchar functions in C, but have vastly different semantics.)

An IO action is performed when it is given the name of main and we execute the program.

We can perform multiple IO actions in one program using the do syntax as follows.

main = do
   putStrLn "Hello!"
   name <- getLine
   putStrLn ("Hello" ++ name ++ "!")

Note the <- that we use when we want to assign values from getLine. The function getLine returns an IO String. When we "assign" the return value of getLine to name, the type of name becomes String.

Other functions include getChar, print etc.

  1. when
  2. sequence takes a list of IO actions, and returns a list of the results.

    Prelude> xs = sequence [getLine,getLine,getLine]
    Prelude> xs 
    aadfba
    babfad
    avdf
    ["aadfba", "babfad", "avdf"]
    
  3. mapM, mapM_, for and forM apply a function to a list of IO actions.

    Prelude> mapM print [1,2,3]
    1
    2
    3
    [(),(),()]
    

    mapM_ is similar to mapM, except that it discards the return value. This is useful, for example, when we use print.

  4. withFile :: FilePath -> IOMode -> (Handle -> IO a) -> IO a takes takes a file path, an IOMode, and a function which take a handle and returns an IO a action. It returns the return value of that function. The convenience provided by withFile is that we do not have to explicitly close the file afterwards.
  5. readFile :: FilePath -> IO String

10.1. Streams and files

The function getContents :: IO String lazily gets the contents of an IO String until the end. This can be used to get the contents of a file until the end of the stream.

File Handline example:

import System.IO  

main = do  
    handle <- openFile "girlfriend.txt" ReadMode  
    contents <- hGetContents handle  
    putStr contents  
    hClose handle

The source code is very similar to any equivalent code in C. Let us try to see this line by line.

  1. openFile :: FilePath -> IOMode -> IO Handle. In this, the first argument FilePath is merely the string indicating the file name. IOMode can be ReadMode, WriteMode, AppendMode or ReadWriteMode.

    The return type is an IO Handle. This is expected by file handling functions.

  2. hGetGontents is similar to getContents , except that the first argument is a file handle.
  3. hClose takes an argument which is a file handle, and closes the file .

11. Monads

We saw that applicative functors are enhanced functors.

Monads are essentially enhanced applicative functors.

The purpose for which we use monads is the following: suppose we have a "boxed a", and a function which takes an "a" and returns a "boxed b", then how do we apply the "boxed a" to the function?

Essentially, we want a function with type (Monad m) => m a -> (a -> m b) -> m b. That is to say, if "a" is inside a "monad", and we have a function which takes an unadorned "a" and returns "m b", then how do we apply the function to the first argument?

The function which will do this is (>>=), called a "bind".

Definition. Monads are applicative functors which support bind.

To understand Monads, the best way is to study some standard Monads, and see how the usage of Monads makes programming easier. In the following discussion, we aim to understand the following.

  1. One of the most famous Monads is IO, which is used to "contain" the side-effects of printing and reading from files etc. in such a way that the remaining Haskell program remains pure (without side-effects). However, we will start with the Maybe monad and the list monad which are easier to understand.

    It may help to keep in mind that even though IO is the most famous example of a Monad, most Monads are very unlike IO, and their motivation and implementation are easier to understand.

  2. An important use of the bind method is to evaluate expressions in a sequence. We will see how this is done, and why this is important for an imperative style of programming inside the pure Haskell style which is also lazy by default.

We now give the class definition of Monad, and understand its use by looking at some Monad s from the standard Haskell library.

11.1. Definition of the class Monad

class Monad m where  
    return :: a -> m a  

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

    (>>) :: m a -> m b -> m b  
    x >> y = x >>= \_ -> y  

    fail :: String -> m a  
    fail msg = error msg  

The class provides four functions, two of which have definitions inside the class. The function return has to be implemented by the Monad instance. The functions are:

  1. The function return is the "boxing" function which takes in an "a" and returns the "boxed" version of "a", which has type m a. Here, m is a Monad instance.

    The function return is similar to pure for Applicative functors. Since we do not say that Monad s extend Applicative, Monad has its own version of pure, which is called return.

    return is nothing like the return in other languages. For one, it does not end a function when you encounter a return statement.

  2. The >> is where most of the power of Monads come from. Its first argument is a Monad "m a", and its second argument is a function that maps "a" to the Monad "m b". The >>= should apply the function in a reasonable manner and return the output of the function. (>>= is a binary function, hence it can be used in infix notation.)

    The definition of >>= must be provided by the instance.

  3. The >> function takes two monads as arguments, and uses >>=. Its definition makes it clear that it discards the intermediate value is thrown away.
  4. fail with a input string argument calls error with the same argument. (Recall that the type of error is [Char]->a which makes it usable in various functions, each of which may return different types.

11.1.1. The do notation : Syntactic sugar for >>=

11.2. Maybe monad

We have seen that Maybe is a Functor, and is in fact, an Applicative functor. We now see that, in fact, it is a Monad as well. Let us now see how Maybe implements the various functions in the class Monad.

instance Monad Maybe where  
    return x = Just x  
    Nothing >>= f = Nothing  
    Just x >>= f  = f x  
    fail _ = Nothing  

return and fail are easy to understand. We now look at Nothing >>= f and Just x >>= f. Nothing >>= f is Nothing, so the function f is ignored. Just x >>= f evaluates to f x. So if x has type a and f has type a -> m b, Then Just x >>= f has type m b.

The following demonstrates a use of >>=.

Prelude> Just 2 >>= \x -> return (x+1)
Just 3

Since the value is again of type Maybe Int, we can build the following chain of functions.

Prelude> Just 2 >>= \x -> return (x+1) >>= \x -> return (x*2)
Just 6

11.3. List monad

Created: 2022-08-03 Wed 19:53

Validate