The Haskell programming language

Martin Sulzmann

The Haskell programming language

Expression-based

example1 x = let y = x
             in x + y

Numbers are overloaded

example2 :: Num a => a -> a
example2 x = let y = x
             in x + y

Numbers and associated operations like +, -, … are overloaded. More on this later

Pure versus impure functions

Pure

example3 :: String -> String
example3 x = let y = x ++ "Hallo"
             in y

Pure = Functions behavior solely defined by its inputs

A pure function will always compute the same result for the same set of inputs (no side effects)

Impure

Impure = not pure some side effects

We may obtain different results/behaviors for the same sets of inputs.

example4 :: String -> IO String
example4 x = do let y = x ++ "Hallo"
                z <- getLine
                print (y++z)
                return y

Command style syntax

Above can be written as follows.

example4b :: String -> IO String
example4b x =
         let y = x ++ "Hallo"
         in  do { z <- getLine;
                  print (y++z);
                  return z }

We find here a sequence of commands separated by “;”.

Commands are state transforming functions

Above is syntactic sugar for the following.

example4c :: String -> IO String
example4c x =
         let y = x ++ "Hallo"
         in getLine
                 >>=
                   (\z -> print (y++z)
                             >>=
                               (\_ -> return z))

The bind operator >>= composes two state transforming functions.

Monads

Operations >>= and return can be overloaded to deal with different kind of side effects.

return :: Monad m => a -> m a

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

Both operators form a mathematical structure known as a monad.

Monads allow for the systematic control of side effects where

Consider the above example again.

example4c :: String -> IO String
example4c x =
         let y = x ++ "Hallo"
         in getLine                                    -- getLine :: IO String
                 >>=                                   -- >>= :: IO String -> (String -> IO String) -> IO String
                   (\z -> print (y++z)                 -- z :: String   and   print (y++z) :: IO ()
                             >>=                       -- >>= :: IO () -> (() -> IO String) -> IO String
                               (\_ -> return z))       -- return z :: IO String

Further reading

The concept of monads found in Haskell is connected to Kleisli categories.

Comparison to imperative programming languages (C, Java, …)

int x;
scanf("%d",&x);
x = x + 1;
printf("%d",x);
int incPure(int x) {
   return x+1;
}

int incImpure(int x) {
  printf("Fire missile");
  return x+1;
}

Functions and operators

Lambdas/Anonymous functions

plus x y = x + y

plus2 x = \y -> x + y

plus3 = \x -> \y -> x + y

Partial function application

inc = plus 1

example5 = inc 3

Operator notation for functions

example6 = plus 1 5

example7 = 1 `plus` 5

Function notaton for operators

example8 = (+) 1 5

inc2 = (1+)

example9 = inc2 5

Function application is left associative

example10 = (plus 2) 3

example11 = plus 2 3

We can omit the paranthesis because function application is left associative

Function types are right associative

add :: Int -> Int -> Int
add = \x -> \y -> x + y


add2 :: Int -> (Int -> Int)
add2 = \x -> \y -> x + y

Functions add and add2 are identical.

add 1 yields a function.

Hence, we can argue that add is of type Int -> (Int -> Int).

We can omit the paranthesis because function types are left associative.

Data types and pattern matching

Data types (“sum types”)

data Res = Succ Int | Fail String

divSafe x y
  | y == 0 = Fail "division by zero"
  | otherwise = Succ (x `div` y)

Parametric data types

data R a = SuccR a | FailR String

divSafe2 :: Int -> Int -> R Int
divSafe2 x y
  | y == 0 = FailR "division by zero"
  | otherwise = SuccR (x `div` y)

The following data types are provided by the Prelude

data Maybe a = Just a | Nothing

data Either a b = Left a | Right b

Re-use existing data types.

divSafe3 :: Int -> Int -> Either Int String
divSafe3 x y
  | y == 0 = Right "division by zero"
  | otherwise = Left (x `div` y)

divSafe4 :: Int -> Int -> Maybe Int
divSafe4 x y
  | y == 0 = Nothing
  | otherwise = Just (x `div` y)

Pattern matching and case expressions

divSafe5 :: Int -> Int -> Maybe Int
divSafe5 x 0 = Nothing
divSafe5 x y = Just (x `div` y)

divSafe6 :: Int -> Int -> Maybe Int
divSafe6 x y = case y of
                 0 -> Nothing
                 _ -> Just (x `div` y)

Lists

Define your own

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

hd :: List a -> a
hd (Cons x _) = x

tl :: List a -> List a
tl (Cons _ xs) = xs

mapL :: (a -> b) -> List a -> List b
mapL f Nil = Nil
mapL f (Cons x xs) = Cons (f x) (mapL f xs)

mapL2 :: (a -> b) -> List a -> List b
mapL2 f ys = case ys of
              Nil       -> Nil
              Cons x xs -> Cons (f x) (mapL f xs)

Built-in lists

-- Empty list
l1 = []

-- List with three elements
l2 = [True, False, False]

l3 = True : (False : (False : []))

Operator : is the “cons” operator.

Any list is represented in terms of : and [].

Pre-defined functions.

head :: [a] -> a
head (x:_) = x


tail :: [a] -> [a]
tail (_:xs) = xs

null :: [a] -> Bool
null [] = True
null _ = False

head and tail are partial functions whereas null is a total function.

List combinators.

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

filter :: (a -> Bool) -> [a] -> [a]
filter p [] = []
filter p (x:xs)
  | p x       =  x : filter p xs
  | otherwise =  filter p xs

and many more.

Type classes

Type classes provide for an expressive form of (method) overloading.

Consider

member x Nil = False
member x (Cons y ys)
    | x == y    = True
    | otherwise = member x ys

What’s the type of member?

*Main> :t member
member :: Eq a => a -> List a -> Bool

Type class instances

instance Eq a => Eq (List a) where
  (==) Nil Nil = True
  (==) (Cons x xs) (Cons y ys) = x == y && xs == ys
  (==) _ _ = False


instance Show a => Show (List a) where
  show Nil = "[]"
  show (Cons x xs) = go ("[" ++ show x) xs
                     where
                        go s Nil = s ++ "]"
                        go s (Cons x xs) = go (s ++ "," ++ show x) xs

Define your own type class

We consider geometric objects. For each such object we wish to compute its area.

We introduce a type class Shape with an overloaded method area.

class Shape a where
   area :: a -> Int

We consider the specific cases of squares and rectangles.

data Square = Square Int

data Rectangle = Rec { len :: Int, width :: Int }

The definition of Rectangle makes use of a data type feature where we can use labels to refer to individual components. The advantage is that we can use labels to unambiguously distinguish among components that are of the same type.

Here are the instances and some simple example.

instance Shape Square where
  area (Square x)    = x * x

instance Shape Rectangle where
  area r    = len r * width r


shapeExample = area r + area s
    where
       r = Rec { width = 2, len = 3 }
       s = Square 4

Super classes

class (Show a, Shape a) => ShapeExt a where
   scale :: a -> Int -> a

Each instance of ShapeExt must also provide for an instance of Show and Shape.

In terms of first-order logic, we can interpret the above as follows.

forall a. ShapeExt a   implies   Show a  and  Shape a

Here are the instances for Square and Rectangle plus a simple example.

instance ShapeExt Square where
  scale (Square x) s = Square (x * s)

instance ShapeExt Rectangle where
  scale r s = Rec { len = len r * s, width = width r * s }

instance Show Square where
  show (Square x) = "square(" ++ show x ++ ")"

instance Show Rectangle where
  show  (Rec {len = l, width = w }) = "rectangle(" ++ show l ++ "," ++ show w ++ ")"


shapeExtExample = area (scale r 3) + area s
    where
       r = Rec { width = 2, len = 3 }
       s = Square 4

How type classes work

Type classes translate to dictionaries.

A dictionary holds the set of methods as described by the type class.

From type classes to dictionaries

class Eq a where
  (==) :: a -> a -> Bool

member :: Eq t => t -> List t -> Bool
member x Nil = False
member x (Cons y ys)
    | x == y    = True
    | otherwise = member x ys

translates to

data DictEq a = DictEqVal (a->a->Bool)
unDict (DictEqVal f) = f

memberDict :: DictEq a -> a -> List a -> Bool
memberDict d x Nil = False
memberDict (DictEqVal eq) x (Cons y ys)
    | eq x y    = True
    | otherwise = memberDict (DictEqVal eq) x ys

From type classes instances to dictionary constructors

-- instance Eq Bool
dBool = DictEqVal (\x -> \y -> case (x,y) of
                                     (True,True) -> True
                                     (False,False) -> True
                                     _ -> False)

-- instance Eq a => Eq a
dictEqList :: DictEq t -> DictEq (List t)
dictEqList (DictEqVal eq) =
   DictEqVal (\x -> \y ->
               case (x,y) of
                 (Nil, Nil) -> True
                 (Cons x xs, Cons y ys) ->
                            (eq x y) &&
                            (unDict (dictEqList (DictEqVal eq))) xs ys
                 _ -> False)

Insert dictionaries

exMem = member True (Cons False Nil)

exMemDict= memberDict dBool True (Cons False Nil)


exMem2 = member (Cons True Nil) (Cons (Cons True Nil) Nil)

exMemDict2 = memberDict (dictEqList dBool) (Cons True Nil) (Cons (Cons True Nil) Nil)

Complete source code


example1 x = let y = x
             in x + y

example2 :: Num a => a -> a
example2 x = let y = x
             in x + y


-- Pure versus impure

example3 :: String -> String
example3 x = let y = x ++ "Hallo"
             in y

example4 :: String -> IO String
example4 x = do let y = x ++ "Hallo"
                z <- getLine
                print (y++z)
                return y


example4b :: String -> IO String
example4b x =
         let y = x ++ "Hallo"
         in  do { z <- getLine;
                  print (y++z);
                  return z }


example4c :: String -> IO String
example4c x =
         let y = x ++ "Hallo"
         in getLine
                 >>=
                   (\z -> print (y++z)
                             >>=
                               (\_ -> return z))


-- Functions versus operators

plus x y = x + y

plus2 x = \y -> x + y

plus3 = \x -> \y -> x + y

inc = plus 1

example5 = inc 3

example6 = plus 1 5

example7 = 1 `plus` 5

example8 = (+) 1 5

inc2 = (1+)

example9 = inc2 5

example10 = (plus 2) 3

example11 = plus 2 3


add :: Int -> Int -> Int
add = \x -> \y -> x + y


add2 :: Int -> (Int -> Int)
add2 = \x -> \y -> x + y

example12 = add 1 2 + add2 1 2


-- data types and pattern matching


data Res = Succ Int | Fail String

divSafe x y
  | y == 0 = Fail "division by zero"
  | otherwise = Succ (x `div` y)


-- parametric data types


data R a = SuccR a | FailR String

divSafe2 :: Int -> Int -> R Int
divSafe2 x y
  | y == 0 = FailR "division by zero"
  | otherwise = SuccR (x `div` y)


divSafe3 :: Int -> Int -> Either Int String
divSafe3 x y
  | y == 0 = Right "division by zero"
  | otherwise = Left (x `div` y)

divSafe4 :: Int -> Int -> Maybe Int
divSafe4 x y
  | y == 0 = Nothing
  | otherwise = Just (x `div` y)

divSafe5 :: Int -> Int -> Maybe Int
divSafe5 x 0 = Nothing
divSafe5 x y = Just (x `div` y)

divSafe6 :: Int -> Int -> Maybe Int
divSafe6 x y = case y of
                 0 -> Nothing
                 _ -> Just (x `div` y)

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

hd :: List a -> a
hd (Cons x _) = x

tl :: List a -> List a
tl (Cons _ xs) = xs

mapL :: (a -> b) -> List a -> List b
mapL f Nil = Nil
mapL f (Cons x xs) = Cons (f x) (mapL f xs)

mapL2 :: (a -> b) -> List a -> List b
mapL2 f ys = case ys of
              Nil       -> Nil
              Cons x xs -> Cons (f x) (mapL f xs)


l = Cons 1 (Cons 2 Nil)

-- built-in lists


-- Empty list
l1 = []

-- List with three elements
l2 = [True, False, False]

l3 = True : (False : (False : []))


coerce :: List a -> [a]
coerce Nil = []
coerce (Cons x xs) = (:) x (coerce xs)

coerceF :: [a] -> List a
coerceF [] = Nil
coerceF (x:xs) = Cons x (coerceF xs)


mapL3 f xs = coerceF (map f (coerce xs))

-- type classes


member x Nil = False
member x (Cons y ys)
    | x == y    = True
    | otherwise = member x ys

-- Variant where we use "case" and "if-then-else".
memberI x ys =
    case ys of
      Nil -> False
      (Cons y ys) -> if x == y then True
                     else memberI x ys


{-

Idea:
 Combine the check for "x == y" with the pattern check.

-}

{-
member2 x Nil = False
member2 x (Cons x ys) = True
                        -- The above complicates the pattern check.
                        -- We check for a non-empty pattern where
                        -- the head element equals x.

                        -- The above is not allowed in Haskell (and Rust, ...)
                        -- Pattern variables must always be distinct!

                        -- Extra conditions, like "x == y" must be
                        -- expressed within the "function body".
member2 x (Cons y ys) = member2 x ys
-}

{-

Languages such as Prolog support more expressive patterns like

"member2 x (Cons x ys) = ..."

-}



instance Eq a => Eq (List a) where
  (==) Nil Nil = True
  (==) (Cons x xs) (Cons y ys) = x == y && xs == ys
  (==) _ _ = False


instance Show a => Show (List a) where
  show Nil = "[]"
  show (Cons x xs) = go ("[" ++ show x) xs
                     where
                        go s Nil = s ++ "]"
                        go s (Cons x xs) = go (s ++ "," ++ show x) xs



ll2 = Cons (Cons 1 Nil) (Cons (Cons 2 (Cons 3 Nil)) Nil)


class Shape a where
   area :: a -> Int

data Square = Square Int

data Rectangle = Rec { len :: Int, width :: Int }


instance Shape Square where
  area (Square x)    = x * x

instance Shape Rectangle where
  area r    = len r * width r


shapeExample = area r + area s
    where
       r = Rec { width = 2, len = 3 }
       s = Square 4


class (Show a, Shape a) => ShapeExt a where
   scale :: a -> Int -> a

-- super classes

instance ShapeExt Square where
  scale (Square x) s = Square (x * s)

instance ShapeExt Rectangle where
  scale r s = Rec { len = len r * s, width = width r * s }

instance Show Square where
  show (Square x) = "square(" ++ show x ++ ")"

instance Show Rectangle where
  show  (Rec {len = l, width = w }) = "rectangle(" ++ show l ++ "," ++ show w ++ ")"


shapeExtExample = area (scale r 3) + area s
    where
       r = Rec { width = 2, len = 3 }
       s = Square 4


-- how type classes work

data DictEq a = DictEqVal (a->a->Bool)
unDict (DictEqVal f) = f

memberDict :: DictEq a -> a -> List a -> Bool
memberDict d x Nil = False
memberDict (DictEqVal eq) x (Cons y ys)
    | eq x y    = True
    | otherwise = memberDict (DictEqVal eq) x ys


-- instance Eq Bool
dBool = DictEqVal (\x -> \y -> case (x,y) of
                                     (True,True) -> True
                                     (False,False) -> True
                                     _ -> False)

-- instance Eq a => Eq a
dictEqList :: DictEq t -> DictEq (List t)
dictEqList (DictEqVal eq) =
   DictEqVal (\x -> \y ->
               case (x,y) of
                 (Nil, Nil) -> True
                 (Cons x xs, Cons y ys) ->
                            (eq x y) &&
                            (unDict (dictEqList (DictEqVal eq))) xs ys
                 _ -> False)


exMem = member True (Cons False Nil)

exMemDict= memberDict dBool True (Cons False Nil)


exMem2 = member (Cons True Nil) (Cons (Cons True Nil) Nil)

exMemDict2 = memberDict (dictEqList dBool) (Cons True Nil) (Cons (Cons True Nil) Nil)