Haskell Tour (Part 3)

Post on 05-Sep-2014

965 views 2 download

Tags:

description

The exciting conclusion to our Haskell introduction. Today we talk about type classes, monads, a monadic parser combinators (e.g. Parsec) climaxing with an example JSON parser.

Transcript of Haskell Tour (Part 3)

HaskellA Whirlwind Tour

(Part III)William Taysom ~ 2011

Haskell is a non-strict, purely functional programming language with strong,static type inference.

Review

Recursive Data

data Color = Red | Green | Blue | Mix Color Color

hue :: Color -> Maybe Doublehue Red = Just 0hue Green = Just 120hue Blue = Just 240

Recursive Functions

hue (Mix c c') = case (hue c, hue c') of (Just h, Just h') -> let m = average h h' m' = norm (m + 180) d = distance h m in case compare d 90 of LT -> Just m EQ -> Nothing GT -> Just m' _ -> Nothing

Parametric Data

data (a, b) = (a, b)data Either a b = Left a | Right bdata Maybe a = Nothing | Just adata [a] = [] | a:[a]

type String = [Char]

Parametric Functions

(.) :: (b -> c) -> (a -> b) -> a -> cinfixr . -- defaults to 9(f . g) x = f (g x)

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

List Comprehensions

primitivePythagoreanTriples = [ (a, b, c) | c <- nats, b <- [1..c], a <- [1..b], a^2 + b^2 == c^2, gcd a b == 1]

primes = sieve [2..] where sieve (p:xs) = p : sieve [x | x <- xs, rem x p /= 0]

Type Classes

Membership Test

infix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

Membership Test

elem :: a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

Membership Test

elem :: a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

Membership Test

elem :: a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

Membership Test

elem :: a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

Membership Test

elem :: a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

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

Membership Test

elem :: a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

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

Membership Test

elem :: a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

Membership Test

elem :: Eq a => a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

Membership Test

elem :: Eq a => a -> [a] -> Boolinfix 4 `elem`x `elem` xs = case filter (== x) xs of [] -> False _ -> True

'q' `elem` a_z --> True'8' `elem` a_z --> False

Eq Instance

instance Eq Color where Red == Red = True Green == Green = True Blue == Blue = True Mix c c' == Mix d d' = c == d && c' == d' _ == _ = False

instance Eq Color where Red == Red = True Green == Green = True Blue == Blue = True Mix c c' == Mix d d' = c == d && c' == d' _ == _ = False

Eq Instance

instance Eq Color where Red == Red = True Green == Green = True Blue == Blue = True Mix c c' == Mix d d' = c == d && c' == d' _ == _ = False

Eq Instanceghci> :i Color

ghci> :i Colordata Color = Red | Green | Blue | Mix Color Color !-- Defined at example.hs:1:6-10instance Eq Color -- Defined at example.hs:3:10-17ghci>

ghci> :i Colordata Color = Red | Green | Blue | Mix Color Color !-- Defined at example.hs:1:6-10instance Eq Color -- Defined at example.hs:3:10-17ghci> :i Eq

Default Definitions

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

ghci> :i Colordata Color = Red | Green | Blue | Mix Color Color !-- Defined at example.hs:1:6-10instance Eq Color -- Defined at example.hs:3:10-17ghci> :i Eqclass Eq a where (==) :: a -> a -> Bool (/=) :: a -> a -> Bool !-- Defined in GHC.Classes... followed by 26 instances ...

Default Definitions

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

Default Definitions

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

Default Definitions

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

Default Definitions

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

ghci> :i Colordata Color = Red | Green | Blue | Mix Color Color !-- Defined at example.hs:1:6-10instance Eq Color -- Defined at example.hs:3:10-17ghci> :i Eqclass Eq a where (==) :: a -> a -> Bool (/=) :: a -> a -> Bool !-- Defined in GHC.Classes... followed by 26 instances ...

... some Eq instances ...instance Eq Colorinstance Eq Boolinstance Eq Char

... some Eq instances ...instance Eq Colorinstance Eq Boolinstance Eq Char

instance Eq a => Eq [a]instance (Eq a, Eq b) => Eq (a, b)

ghci> :t compare

ghci> :t comparecompare :: Ord a => a -> a -> Orderingghci>

ghci> :t comparecompare :: Ord a => a -> a -> Orderingghci> :i Ord

instance Ord Color where Red <= _ = True Green <= Red = False Green <= _ = True Blue <= Red = False Blue <= Green = False Blue <= _ = True Mix c c' <= Mix d d' | c == d = c' <= d' | otherwise = c <= d _ <= _ = False

Ord Instanceghci> :t comparecompare :: Ord a => a -> a -> Orderingghci> :i Ordclass Eq a => Ord a where! compare :: a -> a -> Ordering! (<) :: a -> a -> Bool! (>=) :: a -> a -> Bool! (>) :: a -> a -> Bool! (<=) :: a -> a -> Bool! max :: a -> a -> a! min :: a -> a -> a -- Defined in GHC.Classes

instance Ord Color where Red <= _ = True Green <= Red = False Green <= _ = True Blue <= Red = False Blue <= Green = False Blue <= _ = True Mix c c' <= Mix d d' | c == d = c' <= d' | otherwise = c <= d _ <= _ = False

Ord Instance

instance Ord Color where Red <= _ = True Green <= Red = False Green <= _ = True Blue <= Red = False Blue <= Green = False Blue <= _ = True Mix c c' <= Mix d d' | c == d = c' <= d' | otherwise = c <= d _ <= _ = False

Ord Instance

Derived Instances

data Color = Red | Green | Blue | Mix Color Color deriving (Eq, Ord, Read, Show)

Derived Instances

data Color = Red | Green | Blue | Mix Color Color deriving (Eq, Ord, Read, Show)

Derived Instances

data Color = Red | Green | Blue | Mix Color Color deriving (Eq, Ord, Read, Show)

ghci> show (Mix Red Green)

ghci> show (Mix Red Green)"Mix Red Green"ghci>

ghci> show (Mix Red Green)"Mix Red Green"ghci> read "Mix Red Green"

ghci> show (Mix Red Green)"Mix Red Green"ghci> read "Mix Red Green"<interactive>:1:1: Ambiguous type variable `a0' in the constraint: (Read a0) arising from a use of `read' Probable fix: add a type signature that fixes these type variable(s) In the expression: read "Mix Red Green" In an equation for `it': it = read "Mix Red Green"

ghci> show (Mix Red Green)"Mix Red Green"ghci> read "Mix Red Green"<interactive>:1:1: Ambiguous type variable `a0' in the constraint: (Read a0) arising from a use of `read' Probable fix: add a type signature that fixes these type variable(s) In the expression: read "Mix Red Green" In an equation for `it': it = read "Mix Red Green"

ghci> show (Mix Red Green)"Mix Red Green"ghci> read "Mix Red Green"<interactive>:1:1: Ambiguous type variable `a0' in the constraint: (Read a0) arising from a use of `read' Probable fix: add a type signature that fixes these type variable(s) In the expression: read "Mix Red Green" In an equation for `it': it = read "Mix Red Green"

ghci> :t read

ghci> :t readread :: Read a => String -> aghci>

ghci> :t readread :: Read a => String -> aghci> hue (read "Mix Red Green")

ghci> :t readread :: Read a => String -> aghci> hue (read "Mix Red Green")60.0ghci>

ghci> :t readread :: Read a => String -> aghci> hue (read "Mix Red Green")60.0ghci> read "Mix Red Green"

ghci> :t readread :: Read a => String -> aghci> hue (read "Mix Red Green")60.0ghci> read "Mix Red Green" :: Color

Type Classes Comparedghci> :t readread :: Read a => String -> aghci> hue (read "Mix Red Green")60.0ghci> read "Mix Red Green" :: ColorMix Red Greenghci>

Type Classes Compared

Type Classes Compared

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

Type Classes Compared

OO Class Type Class

Instance Object Type(Not Value)

Dispatch Dynamic on Receiver

Static on Any Part(Like Overloading)

Extension Subclassing Class Conditions(No Subtypes)

Reuse Inheritance Default(No Overriding)

intFromHexString :: String -> IntintFromHexString [] = 0intFromHexString (c:cs) = digitToInt c * 16 ^ length cs + intFromHexString cs

numberFromString :: Num a => String -> anumberFromString [] = 0numberFromString (c:cs) = fromIntegral (digitToInt c) * 10 ^ fromIntegral (length cs) + integerFromString cs

numberFromString :: Num a => String -> anumberFromString [] = 0numberFromString (c:cs) = fromIntegral (digitToInt c) * 10 ^ fromIntegral (length cs) + integerFromString cs

fromIntegral :: (Num b, Integral a) => a -> b

Monads

Monad Class

class Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b m >> n = m >>= \_ -> n

Maybe (Failure)

instance Monad Maybe where return = Just Nothing >>= k = Nothing Just x >>= k = k x

hue (Mix c c') = case (hue c, hue c') of (Just h, Just h') -> let m = average h h' m' = norm (m + 180) d = distance h m in case compare d 90 of LT -> Just m EQ -> Nothing GT -> Just m' _ -> Nothing

hue (Mix c c') = case (hue c, hue c') of (Just h, Just h') -> ... _ -> Nothing

hue (Mix c c') = case hue c of Just h -> case hue c' of Just h' -> ... Nothing -> Nothing Nothing -> Nothing

hue (Mix c c') = case hue c of Just h -> hue c' >>= \h' -> ... Nothing -> Nothing

hue (Mix c c') = hue c >>= \h -> hue c' >>= \h' -> ...

hue (Mix c c') = hue c >>= \h -> do h' <- hue c'; ...

hue (Mix c c') = do h <- hue c do h' <- hue c'; ...

hue (Mix c c') = do h <- hue c h' <- hue c' ...

hue (Mix c c') = do h <- hue c h' <- hue c' let m = average h h' m' = norm (m + 180) d = distance h m in case compare d 90 of LT -> Just m EQ -> Nothing GT -> Just m'

hue (Mix c c') = do h <- hue c h' <- hue c' let m = average h h' m' = norm (m + 180) d = distance h m case compare d 90 of LT -> Just m EQ -> Nothing GT -> Just m'

instance Monad [] where return x = [x] xs >>= k = concat (map k xs)

List (Nondeterminism)

[ (a, b, c) | c <- nats, b <- [1..c], a <- [1..b]]

[ (a, b, c) | c <- nats, b <- [1..c], a <- [1..b]]

do c <- nats b <- [1..c] a <- [1..b] return (a, b, c)

(<$>) :: Monad m => (a -> b) -> m a -> m bf <$> m = m >>= return . f

ord <$> "abc" --> [97, 98, 99]

Generalized Map

Constant Map

(<$) :: Monad m => a -> m b -> m a(<$) = (<$>) . const

'x' <$ "abc" --> "xxx"

[ (a, b, c) | c <- nats, b <- [1..c], a <- [1..b]]

do c <- nats b <- [1..c] a <- [1..b] return (a, b, c)

[ (a, b, c) | c <- nats, b <- [1..c], a <- [1..b], a^2 + b^2 == c^2]

do c <- nats b <- [1..c] a <- [1..b] guard $ a^2 + b^2 == c^2 return (a, b, c)

class Monad m => MonadPlus m where mzero :: m a mplus :: m a -> m a -> m a

MonadPlus Class

instance MonadPlus [] where mzero = [] mplus = (++)

List (Nondeterminism)

Guard

guard :: MonadPlus m => Bool -> m ()guard True = return ()guard False = mzero

Getter

data Getter a = Getter (String -> (a, String))

get :: Getter a -> String -> (a, String)get (Getter g) = g

Getter

instance Monad Getter where return x = Getter $ \s -> (x, s) g >>= k = Getter $ \s -> let (x, s') = get g s in get (k x) s'

Primitive Action

getChar :: Getter ChargetChar = Getter $ \s -> case s of c:cs -> (c , cs) "" -> ('\0', "")

Derived Action

getLine :: Getter StringgetLine = do c <- getChar if c == '\n' || c == '\0' then return "" else do s <- getLine return $ c:s

get getLine "hello\nworld" --> ("hello", "world")

IO

data IO a = IO (RealWorld -> (a, RealWorld))

putChar :: Char -> IO ()

Print Functions

putStr :: String -> IO ()putStr "" = return ()putStr (c:cs) = do putChar c putStr cs

Print Functions

putStrLn :: String -> IO ()putStrLn s = do putStr s putChar '\n'

Main Point

“The business of the program is to construct one gianormous action which is then performed.”

— Simon Peyton-Jones

hello.hs

main = putStrLn "hello, world"

Parsers

Parsers

Parsers

data Parser a = Parser (String -> [(a, String)])

parse :: Parser a -> String -> [(a, String)]parse (Parser p) = p

Parsers

instance Monad Parser where return x = Parser $ \s -> [(x, s)] p >>= k = Parser $ \s -> concat [parse (k x) s' | (x, s') <- parse p s]

Parsers

instance MonadPlus Parser where mzero = Parser $ \s -> [] mplus p q = Parser $ \s -> parse p s ++ parse q s

Parsers

instance MonadPlus Parser where mzero = Parser $ \s -> [] mplus p q = Parser $ \s -> parse p s ++ parse q s

(<|>) :: Parser a -> Parser a -> Parser ainfixr 1 <|>(<|>) = mplus

Primitive Actions

anyChar :: Parser CharanyChar = Parser $ \s -> case s of c:cs -> [(c, cs)] "" -> []

eof :: Parser ()eof = Parser $ \s -> case s of c:cs -> [] "" -> [((), "")]

Derived Actions

satisfy :: (Char -> Bool) -> Parser Charsatisfy f = do c <- anyChar if f c then return c else mzero

Derived Actions

char :: Char -> Parser Charchar c = satisfy (== c)

Derived Actions

string :: String -> Parser Stringstring "" = return ""string s@(c:cs) = do char c string cs return s

Backtracking

hiHeHello = string "hi" <|> string "he" <|> string "hello"

Backtracking

hiHeHello = string "hi" <|> string "he" <|> string "hello"

parse hiHeHello "hello" --> [("he","llo"), ("hello","")]

Parsec

type Parser = Parsec String ()

Parsec

type Parser = Parsec String ()

hiHeHello = string "hi" <|> string "he" <|> string "hello"

parseTest hiHeHello "hello" >>-> unexpected "e" expecting "hi"

Optional Backtracking

try :: Parser a -> Parser a

Optional Backtracking

try :: Parser a -> Parser a

hiHeHello' = try (string "hi") <|> string "he" <|> string "hello"

Optional Backtracking

try :: Parser a -> Parser a

hiHeHello' = try (string "hi") <|> string "he" <|> string "hello"

parseTest hiHeHello' "hello" >>-> "he"

Error Messages

(<?>) :: Parser a -> String -> Parser a

Error Messages

(<?>) :: Parser a -> String -> Parser a

space :: Parser Charspace = satisfy isSpace <?> "space"

digit :: Parser Chardigit = satisfy isDigit <?> "digit"

hexDigit :: Parser CharhexDigit = satisfy isHexDigit <?> "hexadecimal digit"

Error Messages

parseTest (space <|> digit <|> hexDigit) "hello" >>-> unexpected "h" expecting space, digit or hexadecimal digit

Parser Combinators

oneOf :: String -> Parser Char

-- ExampleeE = oneOf "eE"

Parser Combinators

noneOf :: String -> Parser Char

-- ExamplenotDoubleQuote = noneOf "\""

Parser Combinators

between :: Parser a -> Parser b -> Parser c -> Parser c

-- Definitionbetween open close p = do open x <- p close return x

Parser Combinators

option :: a -> Parser a -> Parser a

-- Definitionoption x p = p <|> return x

Parser Combinators

count :: Int -> Parser a -> Parser [a]

-- ExamplehexDigit4 = count 4 hexDigit

Parser Combinators

many, many1 :: Parser a -> Parser [a]

-- Exampledigits = many1 digit

Parser Combinators

skipMany :: Parser a -> Parser ()

-- ExampleskipMany p = many p >> return ()

Parser Combinators

spaces :: Parser ()

-- Definitionspaces = skipMany space

Parser Combinators

sepBy :: Parser a -> Parser b -> Parser [a]

-- Examplewords = (many1 . satisfy) (not . isSpace) `sepBy` spaces

Space Management

justOne :: Parser a -> Parser ajustOne = between spaces (spaces >> eof)

Space Management

char_sp :: Char -> Parser ()char_sp c = do char c spaces

sp_char_sp :: Char -> Parser ()sp_char_sp c = do spaces char_sp c

Space Management

commaGroup :: Char -> Parser a -> Char -> Parser [a]

commaGroup open item close = between (char_sp open) (sp_char_sp close) $ item `sepBy` sp_char_sp ','

Parse String

Parse String

jsstring :: Parser Stringjsstring = between doubleQuote doubleQuote $ many character

Parse String

jsstring :: Parser Stringjsstring = between doubleQuote doubleQuote $ many character

doubleQuote :: Parser ChardoubleQuote = char '"'

Parse String

jsstring :: Parser Stringjsstring = between doubleQuote doubleQuote $ many character

doubleQuote :: Parser ChardoubleQuote = char '"'

character :: Parser Charcharacter = (char '\\' >> escapeChar) <|> notDoubleQuote

escapeChar :: Parser CharescapeChar = char '"' <|> char '\\' <|> char '/' <|> '\b' <$ char 'b' <|> '\f' <$ char 'f' <|> '\n' <$ char 'n' <|> '\r' <$ char 'r' <|> '\t' <$ char 't' <|> unicode

unicode :: Parser Charunicode = do char 'u' digits <- hexDigit4 let n = intFromHexString digits return $ chr n

Parse Number

Parse Number

number :: Parser Doublenumber = do s <- sign n <- int f <- frac e <- expon return $ s * (n + f) * e

sign :: Parser Doublesign = option 1 $ (-1) <$ char '-'

int :: Parser Doubleint = 0 <$ char '0' <|> numberFromString <$> digits

frac :: Parser Doublefrac = option 0 $ do char '.' n <- digits return $ numberFromString n / 10 ^^ length n

expon :: Parser Doubleexpon = option 1 $ do eE s <- sign n <- digits return $ s * 10 ** numberFromString n

Parse JSON

Parse JSON

Parse JSON

data Value = String String | Number Double | Object [(String, Value)] | Array [Value] | Bool Bool

| Null

Parse JSON

value = String <$> jsstring <|> Number <$> number <|> Object <$> commaGroup '{' pair '}' <|> Array <$> commaGroup '[' value ']' <|> Bool True <$ string "true" <|> Bool False <$ string "false" <|> Null <$ string "null"

Parse JSON

data Value = String String | Number Double | Object [(String, Value)] | Array [Value] | Bool Bool

| Null

Parse JSON

value = String <$> jsstring <|> Number <$> number <|> Object <$> commaGroup '{' pair '}' <|> Array <$> commaGroup '[' value ']' <|> Bool True <$ string "true" <|> Bool False <$ string "false" <|> Null <$ string "null"

Parse JSON

pair :: Parser (String, Value)pair = do s <- jsstring sp_char_sp ':' v <- value spaces return (s, v)

parseJSON :: String -> ValueparseJSON s = case parse (justOne value) "" s of Left err -> error $ "JSON parse error " ++ show err Right v -> v

parseJSON "{\"just\": [\"some\", 4, \"\\u24E4\"]}" --> Object [("just", Array [String "some", Number 4.0, String "\9444"])]

parseJSON "{\"just\": [\"some\", 4, \"\\u24E4\"]}" --> Object [("just", Array [String "some", Number 4.0, String "\9444"])]

parseJSON "{\"just\": [\"some\", 4 \"\\u24E4\"]}" >>-> *** Exception: JSON parse error (line 1, column 21): unexpected "\"" expecting space or ","

Summary

Summary

Summary

Parsers

Monads

Type Classes

Parametric Types

Functions and Data Types

Summary

Parsers

Monads

Type Classes

Parametric Types

Functions and Data Types

Summary

Parsers

Monads

Type Classes

Parametric Types

Functions and Data Types

Summary

Parsers

Monads

Type Classes

Parametric Types

Functions and Data Types

Summary

Parsers

Monads

Type Classes

Parametric Types

Functions and Data Types

Haskell is a non-strict, purely functional programming language with strong,static type inference.

Thank You