> {-# LANGUAGE FlexibleInstances #-}
> module Intro where
>
> import Prelude hiding (length, head)
>
> import Data.Char (toLower)We saw Err a as a data type that wraps values of type a. The most used Haskell data type is a list
[1, 2, 3] :: [Int]
[True] :: [Bool]
['c', 'h', 'a', 'r'] :: [Char]
"char" :: StringWhat is the type of the empty list
[] :: ??List operations
> length :: [a] -> Int
> length [] = 0
> length (x:xs) = 1 + length xslength [1, 2, 3, 4] = 4
length [] = 0
length "string" = 6Note: length is polymorphic it operates on lists of every type.
> head :: [a] -> a
> head (x:_) = x
> head [] = error "head on empty list"Get the tail of a list
tail "Mexico!!!!!" = "exico!!!!!"
tail [1, 2, 3, 4] = [2, 3, 4]> tail :: [a] -> [a]
> tail = undefinedConcatinate two lists
"I love " ++ "Mexico!!!!!" = "I love Mexico!!!!!"
[-1, 0] ++ [1, 2, 3, 4] = [2, 3, 4](++) :: [a] -> [a] -> [a]
[] ++ xs = xsLets write a function that converts a string to uppercase. Recall that in Haskell, a String is just a list of Char. We must start with a function that will convert an individual Char to its uppercase version. Once we find this function, we will simply jog over the list, and apply the function to each Char.
How might we find such a transformer? Lets query Hoogle for a function of the appropriate type! Ah, we see that the module Data.Char contains a function.
toLower :: Char -> Charand so now, we can write the simple recursive function
toLowerString :: String -> String
toLowerString [] = []
toLowerString (c:cs) = toLower c : toLowerString csLets now write a function that given a list of integers increases each of its elements by 1
plusOneList :: [Int] -> [Int]
plusOneList [] = []
plusOneList (n:ns) = (n+1) : plusOneList nstoLowerString = foo toLower plusOneList = foo (+1)
– foo1 f := toLower < foo :: (Char -> Char) -> [Char] -> [Char] < foo f [] = [] < foo f (c:cs) = f c : foo cs
< foo :: (Int -> Int) -> [Int] -> [Int] – foo f:= (+1) < foo f [] = [] < foo f (n:ns) = f n : foo ns
Now, in a lesser language, you might be quite happy with the above code. But what separates a good programmer from a great one, is the ability to abstract.
Like humans and monkeys, the functions toLowerString and plusOneList share 93% of their DNA — the notion of jogging over the list. The common pattern is described by the polymorphic higher-order function map
map f [] = []
map f (x:xs) = (f x) : (map f xs)
How did we arrive at this? Well, you find what is enshrine in the function’s body that which is common to the different instances, namely the recursive jogging strategy; and the bits that are different, simply become the function’s parameters! Thus, the map function abstracts, or if you have a vivid imagination, locks up in a bottle, the extremely common pattern of jogging over the list.
Verily, the type of map tells us exactly what it does
map :: (a -> b) -> [a] -> [b]
That is, it takes an a -> b transformer and list of a values, and transforms each value to return a list of b values. We can now safely reuse the pattern, by instantiating the transformer with different specific operations.
> toLowerString = map toLower
> plusOneList = map (+1)Much better.
Err valuesRemember our Err data type?
> data Err a = Value a | Error a Write a function that increases the value of the Err data by one.
> plusOneErr :: Err Int -> Err Int
> plusOneErr (Value x) = Value (x+1)
> plusOneErr (Error x) = Error (x+1)
>
> foo :: Err Char -> Err Char
> foo (Value x) = Value (toLower x)
> foo (Error x) = Error (toLower x)Did you follow the mapping abstraction discussed above? If so, you would define a mapping function for Err values
> mapErr :: (a -> b) -> Err a -> Err b
> mapErr f (Error x) = Error $ f x
> mapErr f (Value x) = Value $ f x > plusOneErr :: Err Int -> Err Int
> plusOneErr = mapErr (+1)Then, use mapErr to write the desired function.
We take the abstraction one level up! See how map and mapErr are similar
map :: (a -> b) -> [a] -> [b]
mapErr :: (a -> b) -> Err a -> Err bWe define these two functions to be instances of an abstract interface, or class in Haskell terms. First we provide the class definition
class Functor f where
fmap :: (a -> b) -> f a -> f bmap :: (a -> b) -> [a] -> [a] fmap :: (a -> b) -> f a -> f b
Then, we provide instances for this class.
For the Err data type
instance Functor Err where
fmap = mapErrand for the list
instance Functor [] where
fmap = mapWith this, we can always replace each map and mapErr invocation with fmap.
Once you’ve put on the FP goggles, you start seeing computation patterns everywhere.
Lets write a function that adds all the elements of a list.
listAdd [] = 0
listAdd (x:xs) = x + (listAdd xs)Next, a function that multiplies the elements of a list.
listMul [] = 1
listMul (x:xs) = x * (listMul xs)Can you see the pattern? Again, the only bits that are different are the base case value, and the op being performed at each step. We’ll just turn those into parameters, and lo!
foldr op base [] = base
foldr op base (x:xs) = x `op` (foldr op base xs) Now, each of the individual functions are just specific instances of the general foldr pattern.
> listAdd = foldr (+) 0
> listMul = foldr (*) 1To develop some intuition about foldr lets “run” it a few times by hand.
foldr op base [x1,x2,...,xn]
== {- unfold -}
x1 `op` (foldr op base [x2,...,xn])
== {- unfold -}
x1 `op` (x2 `op` (foldr op base [...,xn]))
== {- unfold -}
x1 `op` (x2 `op` (... `op` (xn `op` base)))Aha! It has a rather pleasing structure that mirrors that of lists; the : is replaced by the op and the [] is replaced by base. Thus, can you see how to use it to eliminate recursion from the recursion from
listLen [] = 0
listLen (x:xs) = 1 + (listLen xs)>
> llen = foldr (\x acc -> acc + 1) 0 > listLen = foldr (\_ tailLen -> 1 + tailLen) 0How would you use it to eliminate the recursion from our fact function?
fact 0 = 1
fact n = n * fact (n-1)> factorial n = foldr (*) 1 [1..n]Due to laziness, Haskell supports infinite lists. For example the following containts all positive integers
> allInts = [1..]Exercise: Compute an infinite list that containts all the fibonacci numbers!
When you are “streaming” a video, your pc always received data from the web. How do we encode these streaming data in Haskell? A stream is an infinite list! A list without the “base case”.
> data Stream a = St a (Stream a)Write a function that created the Stream of all positive numbers
> posStream :: Stream Int
> posStream = go 0
> where go i = St i $ go (i+1) No instance for (Show (Stream Int)) arising from a use of ‘print’Follow the hint and create an instance Show for the Stream data! Show is the class that is responsible for printing! It has just one method, called show.
class Show a where
show :: a -> StringProvide an instance to show Streams!
> instance Show (Stream Int) where
> show (St s ss) = show s ++ ",\t" ++ show ssBut this is tedious! Hopefully, Haskell automatically derives Show instances for recursive data types.
data Stream a = St a (Stream a) deriving (Show)Now that we can print Streams we see that they are actually infinite. So,
posStreamwill never stop:(
Lets create a function that takes the nth first elements of the Stream:
> takeStream :: Int -> Stream a -> [a]
> takeStream = undefined Note: We can create this function from scratch, or use foldStream and list take!
Finally, make Streams an instance of Eq and Functor. Increase each element of posStream by one to get geOneStream. Then, check wheather posStream is equal to geOneStream and to itself.
The Towers of Hanoi is a puzzle where you are given three pegs, on one of which are stacked n discs in increasing order of size. To solve the puzzle, you must move all the discs from the starting peg to another by moving only one disc at a time and never stacking a larger disc on top of a smaller one. To move n discs from peg a to peg b using peg c as temporary storage:
Write a function
hanoi :: Int -> String -> String -> String -> IO ()
hanoi = error "Define me!"
that, given the number of discs n and peg names a, b, and c, where a is the starting peg, emits the series of moves required to solve the puzzle. For example, running hanoi 2 “a” “b” “c”
should emit the text
[("a","c"),("a","b"),("c","b")]
> fib 0 = 0
> fib 1 = 1
> fib n = fib (n-1) + fib (n-2)> hanoi :: Int -> String -> String -> String -> [(String, String)]
> hanoi 0 _ _ _ = []
> hanoi n a b c = hanoi (n-1) a c b ++ [(a,b)] ++ hanoi (n-1) c b a> posStream' :: Stream Int
> posStream' = go 0
> where go i = St i $ go (i+1) > takeStream' n = take n $ foldStream (:) posStream'
>
> foldStream :: (a -> b -> b) -> Stream a -> b
> foldStream f (St x s) = x `f` foldStream f s