SlideShare ist ein Scribd-Unternehmen logo
1 von 168
Downloaden Sie, um offline zu lesen
Haskell
A 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
Recursive Functions

hue   :: Color -> Maybe Double
hue   Red     = Just 0
hue   Green = Just 120
hue   Blue    = Just 240
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 b
data   Maybe a = Nothing | Just a
data   [a] = [] | a:[a]

type String = [Char]
Parametric Functions

(.) :: (b -> c) -> (a -> b) -> a -> c
infixr . -- 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] -> Bool
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] -> Bool
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] -> Bool
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] -> Bool
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] -> Bool
infix 4 `elem`
x `elem` xs = case filter (== x) xs of
  [] -> False
              (==) :: Eq a => a -> a -> Bool
  _ -> True

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

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

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

elem :: a -> [a] -> Bool
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 :: Eq a => a -> [a] -> Bool
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 :: Eq a => a -> [a] -> Bool
infix 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
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 Instance
ghci> :i Color



instance Eq Color where
  Red      == Red      = True
  Green == Green = True
  Blue     == Blue     = True
  Mix c c' == Mix d d' = c == d && c' == d'
  _        == _        = False
ghci> :i Color
data Color = Red | Green | Blue | Mix
Color Color
  ! Defined at example.hs:1:6-10
  --
instance Eq Color -- Defined at
example.hs:3:10-17
ghci>
ghci> :i Color
data Color = Red | Green | Blue | Mix
Color Color
  ! Defined at example.hs:1:6-10
  --
instance Eq Color -- Defined at
example.hs:3:10-17
ghci> :i Eq
Default Definitions
ghci> :i Color
data Color = Red | Green | Blue | Mix
Color Color
   ! Eq a where example.hs:1:6-10
    -- Defined at
 class
instance Eq Color -- Defined at
   (==), (/=) :: a -> a -> Bool
example.hs:3:10-17
ghci> :i=Eq (x == y)
   x /= y   not
class Eq=anot (x /= y)
   x == y    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
ghci> :i Color
data Color = Red | Green | Blue | Mix
Color Color
   ! Eq a where example.hs:1:6-10
    -- Defined at
 class
instance Eq Color -- Defined at
   (==), (/=) :: a -> a -> Bool
example.hs:3:10-17
ghci> :i=Eq (x == y)
   x /= y   not
class Eq=anot (x /= y)
   x == y    where
   (==) :: a -> a -> Bool
   (/=) :: a -> a -> Bool
   ! Defined in GHC.Classes
    --
... followed by 26 instances ...
... some Eq instances ...
instance Eq Color
instance Eq Bool
instance Eq Char
... some Eq instances ...
instance Eq Color
instance Eq Bool
instance Eq Char

instance Eq a => Eq [a]
instance (Eq a, Eq b) => Eq (a, b)
ghci> :t compare
ghci> :t compare
compare :: Ord a => a -> a -> Ordering
ghci>
ghci> :t compare
compare :: Ord a => a -> a -> Ordering
ghci> :i Ord
Ord Instance
ghci> :t compare
compare :: Ord a => a -> a -> Ordering
ghci> :i Ord
class Eq a Color where
 instance Ord => Ord a where
! Red
    compare :: a -> a -> Ordering
            <= _        = True
! Green::<= -> a -> = False
    (<)      a Red       Bool
! Green :: a_-> a -> Bool
    (>=) <=             = True
! Blue ::<= -> a -> = False
    (>)      a Red       Bool
! Blue :: aGreen -> Bool
    (<=) <= -> a = False
   Blue     <= _        = True
! max :: a -> a -> a
   Mix c c' <= Mix d d'
! min :: a -> a -> a
    | c == d            = c' <= d'
      -- Defined in GHC.Classes
    | 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
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
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
ghci> show (Mix Red Green)



data Color = Red | Green | Blue
            | Mix Color Color
 deriving (Eq, Ord, Read, Show)
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 read
read :: Read a => String -> a
ghci>
ghci> :t read
read :: Read a => String -> a
ghci> hue (read "Mix Red Green")
ghci> :t read
read :: Read a => String -> a
ghci> hue (read "Mix Red Green")
60.0
ghci>
ghci> :t read
read :: Read a => String -> a
ghci> hue (read "Mix Red Green")
60.0
ghci> read "Mix Red Green"
ghci> :t read
read :: Read a => String -> a
ghci> hue (read "Mix Red Green")
60.0
ghci> read "Mix Red Green" :: Color
Type Classes Compared
ghci> :t read
read :: Read a => String -> a
ghci> hue (read "Mix Red Green")
60.0
ghci> read "Mix Red Green" :: Color
Mix Red Green
ghci>
Type Classes Compared
Type Classes Compared
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
Type Classes Compared

              OO Class        Type Class

                                 Type
  Instance     Object
                              (Not Value)

              Dynamic      Static on Any Part
  Dispatch
             on Receiver   (Like Overloading)

                            Class Conditions
 Extension   Subclassing
                             (No Subtypes)

                                Default
   Reuse     Inheritance
                            (No Overriding)
intFromHexString :: String -> Int
intFromHexString []     =0
intFromHexString (c:cs) =
  digitToInt c *
    16 ^ length cs +
       intFromHexString cs
numberFromString :: Num a => String -> a
numberFromString [] = 0
numberFromString (c:cs) =
  fromIntegral (digitToInt c) *
    10 ^ fromIntegral (length cs) +
      integerFromString cs
numberFromString :: Num a => String -> a
numberFromString [] = 0
numberFromString (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'
List (Nondeterminism)

instance Monad [] where
  return x = [x]
  xs >>= k = concat (map k xs)
[ (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)
Generalized Map

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


ord <$> "abc" --> [97, 98, 99]
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)
MonadPlus Class

class Monad m => MonadPlus m where
  mzero :: m a
  mplus :: m a -> m a -> m a
List (Nondeterminism)

instance MonadPlus [] where
  mzero = []
  mplus = (++)
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 Char
getChar = Getter $ s -> case s of
 c:cs -> (c , cs)
 ""   -> ('0', "")
Derived Action

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

get getLine "hellonworld" --> ("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 a
infixr 1 <|>
(<|>) = mplus
Primitive Actions

anyChar    :: Parser Char
anyChar    = 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 Char
satisfy f = do
 c <- anyChar
 if f c
   then return c
   else mzero
Derived Actions

char :: Char -> Parser Char
char c = satisfy (== c)
Derived Actions

string :: String -> Parser String
string ""        = 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 Char
space = satisfy isSpace <?> "space"

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

hexDigit :: Parser Char
hexDigit = 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



-- Example
eE = oneOf "eE"
Parser Combinators

noneOf :: String -> Parser Char



-- Example
notDoubleQuote = noneOf """
Parser Combinators

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

-- Definition
between open close p = do
  open
  x <- p
  close
  return x
Parser Combinators

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



-- Definition
option x p = p <|> return x
Parser Combinators

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



-- Example
hexDigit4 = count 4 hexDigit
Parser Combinators

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



-- Example
digits = many1 digit
Parser Combinators

skipMany :: Parser a -> Parser ()



-- Example
skipMany p = many p >> return ()
Parser Combinators

spaces :: Parser ()



-- Definition
spaces = skipMany space
Parser Combinators

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



-- Example
words =
  (many1 . satisfy) (not . isSpace) `sepBy` spaces
Space Management

justOne :: Parser a -> Parser a
justOne = 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 String
jsstring = between doubleQuote doubleQuote $
  many character
Parse String

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

doubleQuote :: Parser Char
doubleQuote = char '"'
Parse String

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

doubleQuote :: Parser Char
doubleQuote = char '"'

character :: Parser Char
character = (char '' >> escapeChar)
        <|> notDoubleQuote
escapeChar :: Parser Char
escapeChar = char '"'
         <|> char ''
         <|> char '/'
         <|> 'b' <$ char   'b'
         <|> 'f' <$ char   'f'
         <|> 'n' <$ char   'n'
         <|> 'r' <$ char   'r'
         <|> 't' <$ char   't'
         <|> unicode
unicode :: Parser Char
unicode = do
 char 'u'
 digits <- hexDigit4
 let n = intFromHexString digits
 return $ chr n
Parse Number
Parse Number

number :: Parser Double
number = do
 s <- sign
 n <- int
 f <- frac
 e <- expon
 return $ s * (n + f) * e
sign :: Parser Double
sign = option 1 $ (-1) <$ char '-'

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

expon :: Parser Double
expon = option 1 $ do
 eE
 s <- sign
 n <- digits
 return $ s * 10 ** numberFromString n
Parse JSON
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"
pair :: Parser (String, Value)
pair = do
  s <- jsstring
  sp_char_sp ':'
  v <- value
  spaces
  return (s, v)
parseJSON :: String -> Value
parseJSON 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

Weitere ähnliche Inhalte

Was ist angesagt?

Algorithm Design and Analysis - Practical File
Algorithm Design and Analysis - Practical FileAlgorithm Design and Analysis - Practical File
Algorithm Design and Analysis - Practical FileKushagraChadha1
 
関数潮流(Function Tendency)
関数潮流(Function Tendency)関数潮流(Function Tendency)
関数潮流(Function Tendency)riue
 
learn you some erlang - chap0 to chap2
learn you some erlang - chap0 to chap2learn you some erlang - chap0 to chap2
learn you some erlang - chap0 to chap2경미 김
 
learn you some erlang - chap3 to chap5
learn you some erlang - chap3 to chap5learn you some erlang - chap3 to chap5
learn you some erlang - chap3 to chap5경미 김
 
Ciklum net sat12112011-alexander fomin-expressions and all, all, all
Ciklum net sat12112011-alexander fomin-expressions and all, all, allCiklum net sat12112011-alexander fomin-expressions and all, all, all
Ciklum net sat12112011-alexander fomin-expressions and all, all, allCiklum Ukraine
 
Haskellで学ぶ関数型言語
Haskellで学ぶ関数型言語Haskellで学ぶ関数型言語
Haskellで学ぶ関数型言語ikdysfm
 
Functional Patterns for the non-mathematician
Functional Patterns for the non-mathematicianFunctional Patterns for the non-mathematician
Functional Patterns for the non-mathematicianBrian Lonsdorf
 
10.5 more on language of functions x
10.5 more on language of functions x10.5 more on language of functions x
10.5 more on language of functions xmath260
 
Lisp and prolog in artificial intelligence
Lisp and prolog in artificial intelligenceLisp and prolog in artificial intelligence
Lisp and prolog in artificial intelligenceArtiSolanki5
 
1.3 solving equations
1.3 solving equations1.3 solving equations
1.3 solving equationsmath260
 
3 algebraic expressions y
3 algebraic expressions y3 algebraic expressions y
3 algebraic expressions ymath266
 
Higher nov 2008_p1old
Higher nov 2008_p1oldHigher nov 2008_p1old
Higher nov 2008_p1oldybamary
 

Was ist angesagt? (20)

Bc0039
Bc0039Bc0039
Bc0039
 
Promise
PromisePromise
Promise
 
20170509 rand db_lesugent
20170509 rand db_lesugent20170509 rand db_lesugent
20170509 rand db_lesugent
 
Algorithm Design and Analysis - Practical File
Algorithm Design and Analysis - Practical FileAlgorithm Design and Analysis - Practical File
Algorithm Design and Analysis - Practical File
 
関数潮流(Function Tendency)
関数潮流(Function Tendency)関数潮流(Function Tendency)
関数潮流(Function Tendency)
 
learn you some erlang - chap0 to chap2
learn you some erlang - chap0 to chap2learn you some erlang - chap0 to chap2
learn you some erlang - chap0 to chap2
 
learn you some erlang - chap3 to chap5
learn you some erlang - chap3 to chap5learn you some erlang - chap3 to chap5
learn you some erlang - chap3 to chap5
 
Ciklum net sat12112011-alexander fomin-expressions and all, all, all
Ciklum net sat12112011-alexander fomin-expressions and all, all, allCiklum net sat12112011-alexander fomin-expressions and all, all, all
Ciklum net sat12112011-alexander fomin-expressions and all, all, all
 
Millionways
MillionwaysMillionways
Millionways
 
Haskellで学ぶ関数型言語
Haskellで学ぶ関数型言語Haskellで学ぶ関数型言語
Haskellで学ぶ関数型言語
 
Functional Patterns for the non-mathematician
Functional Patterns for the non-mathematicianFunctional Patterns for the non-mathematician
Functional Patterns for the non-mathematician
 
Array notes
Array notesArray notes
Array notes
 
10.5 more on language of functions x
10.5 more on language of functions x10.5 more on language of functions x
10.5 more on language of functions x
 
Intoduction to php arrays
Intoduction to php arraysIntoduction to php arrays
Intoduction to php arrays
 
Pytables
PytablesPytables
Pytables
 
Lisp and prolog in artificial intelligence
Lisp and prolog in artificial intelligenceLisp and prolog in artificial intelligence
Lisp and prolog in artificial intelligence
 
1.3 solving equations
1.3 solving equations1.3 solving equations
1.3 solving equations
 
3 algebraic expressions y
3 algebraic expressions y3 algebraic expressions y
3 algebraic expressions y
 
Higher nov 2008_p1old
Higher nov 2008_p1oldHigher nov 2008_p1old
Higher nov 2008_p1old
 
Integral table
Integral tableIntegral table
Integral table
 

Ähnlich wie Haskell Tour (Part 3)

Beginning Haskell, Dive In, Its Not That Scary!
Beginning Haskell, Dive In, Its Not That Scary!Beginning Haskell, Dive In, Its Not That Scary!
Beginning Haskell, Dive In, Its Not That Scary!priort
 
An introduction to property-based testing
An introduction to property-based testingAn introduction to property-based testing
An introduction to property-based testingVincent Pradeilles
 
Introduction to Recursion (Python)
Introduction to Recursion (Python)Introduction to Recursion (Python)
Introduction to Recursion (Python)Thai Pangsakulyanont
 
Refined types (FP-Syd)
Refined types (FP-Syd)Refined types (FP-Syd)
Refined types (FP-Syd)Dom De Re
 
Some Pitfalls with Python and Their Possible Solutions v0.9
Some Pitfalls with Python and Their Possible Solutions v0.9Some Pitfalls with Python and Their Possible Solutions v0.9
Some Pitfalls with Python and Their Possible Solutions v0.9Yann-Gaël Guéhéneuc
 
Groovy puzzlers по русски с Joker 2014
Groovy puzzlers по русски с Joker 2014Groovy puzzlers по русски с Joker 2014
Groovy puzzlers по русски с Joker 2014Baruch Sadogursky
 
Defining filter using (a) recursion (b) folding (c) folding with S, B and I c...
Defining filter using (a) recursion (b) folding (c) folding with S, B and I c...Defining filter using (a) recursion (b) folding (c) folding with S, B and I c...
Defining filter using (a) recursion (b) folding (c) folding with S, B and I c...Philip Schwarz
 
Defining filter using (a) recursion (b) folding with S, B and I combinators (...
Defining filter using (a) recursion (b) folding with S, B and I combinators (...Defining filter using (a) recursion (b) folding with S, B and I combinators (...
Defining filter using (a) recursion (b) folding with S, B and I combinators (...Philip Schwarz
 
Functional Programming with Groovy
Functional Programming with GroovyFunctional Programming with Groovy
Functional Programming with GroovyArturo Herrero
 
Implement the following sorting algorithms Bubble Sort Insertion S.pdf
Implement the following sorting algorithms  Bubble Sort  Insertion S.pdfImplement the following sorting algorithms  Bubble Sort  Insertion S.pdf
Implement the following sorting algorithms Bubble Sort Insertion S.pdfkesav24
 
Dataclasses en Python 3.7: Empieza a borrar código
Dataclasses en Python 3.7: Empieza a borrar códigoDataclasses en Python 3.7: Empieza a borrar código
Dataclasses en Python 3.7: Empieza a borrar códigoJacobo de Vera
 
Functional programming from its fundamentals
Functional programming from its fundamentalsFunctional programming from its fundamentals
Functional programming from its fundamentalsMauro Palsgraaf
 
Groovy puzzlers jug-moscow-part 2
Groovy puzzlers jug-moscow-part 2Groovy puzzlers jug-moscow-part 2
Groovy puzzlers jug-moscow-part 2Evgeny Borisov
 
Truth, deduction, computation lecture g
Truth, deduction, computation   lecture gTruth, deduction, computation   lecture g
Truth, deduction, computation lecture gVlad Patryshev
 

Ähnlich wie Haskell Tour (Part 3) (20)

Beginning Haskell, Dive In, Its Not That Scary!
Beginning Haskell, Dive In, Its Not That Scary!Beginning Haskell, Dive In, Its Not That Scary!
Beginning Haskell, Dive In, Its Not That Scary!
 
Números Reales - Genesis Sira
Números Reales - Genesis SiraNúmeros Reales - Genesis Sira
Números Reales - Genesis Sira
 
An introduction to property-based testing
An introduction to property-based testingAn introduction to property-based testing
An introduction to property-based testing
 
Introduction to Recursion (Python)
Introduction to Recursion (Python)Introduction to Recursion (Python)
Introduction to Recursion (Python)
 
Refined types (FP-Syd)
Refined types (FP-Syd)Refined types (FP-Syd)
Refined types (FP-Syd)
 
Haskell Jumpstart
Haskell JumpstartHaskell Jumpstart
Haskell Jumpstart
 
Some Pitfalls with Python and Their Possible Solutions v0.9
Some Pitfalls with Python and Their Possible Solutions v0.9Some Pitfalls with Python and Their Possible Solutions v0.9
Some Pitfalls with Python and Their Possible Solutions v0.9
 
P3 2017 python_regexes
P3 2017 python_regexesP3 2017 python_regexes
P3 2017 python_regexes
 
Groovy puzzlers по русски с Joker 2014
Groovy puzzlers по русски с Joker 2014Groovy puzzlers по русски с Joker 2014
Groovy puzzlers по русски с Joker 2014
 
Defining filter using (a) recursion (b) folding (c) folding with S, B and I c...
Defining filter using (a) recursion (b) folding (c) folding with S, B and I c...Defining filter using (a) recursion (b) folding (c) folding with S, B and I c...
Defining filter using (a) recursion (b) folding (c) folding with S, B and I c...
 
Defining filter using (a) recursion (b) folding with S, B and I combinators (...
Defining filter using (a) recursion (b) folding with S, B and I combinators (...Defining filter using (a) recursion (b) folding with S, B and I combinators (...
Defining filter using (a) recursion (b) folding with S, B and I combinators (...
 
Functional Programming with Groovy
Functional Programming with GroovyFunctional Programming with Groovy
Functional Programming with Groovy
 
Implement the following sorting algorithms Bubble Sort Insertion S.pdf
Implement the following sorting algorithms  Bubble Sort  Insertion S.pdfImplement the following sorting algorithms  Bubble Sort  Insertion S.pdf
Implement the following sorting algorithms Bubble Sort Insertion S.pdf
 
Dataclasses en Python 3.7: Empieza a borrar código
Dataclasses en Python 3.7: Empieza a borrar códigoDataclasses en Python 3.7: Empieza a borrar código
Dataclasses en Python 3.7: Empieza a borrar código
 
Functional programming from its fundamentals
Functional programming from its fundamentalsFunctional programming from its fundamentals
Functional programming from its fundamentals
 
Recursion part 2
Recursion part 2Recursion part 2
Recursion part 2
 
Scala Parallel Collections
Scala Parallel CollectionsScala Parallel Collections
Scala Parallel Collections
 
Groovy puzzlers jug-moscow-part 2
Groovy puzzlers jug-moscow-part 2Groovy puzzlers jug-moscow-part 2
Groovy puzzlers jug-moscow-part 2
 
Scala by Luc Duponcheel
Scala by Luc DuponcheelScala by Luc Duponcheel
Scala by Luc Duponcheel
 
Truth, deduction, computation lecture g
Truth, deduction, computation   lecture gTruth, deduction, computation   lecture g
Truth, deduction, computation lecture g
 

Kürzlich hochgeladen

Kotlin Multiplatform & Compose Multiplatform - Starter kit for pragmatics
Kotlin Multiplatform & Compose Multiplatform - Starter kit for pragmaticsKotlin Multiplatform & Compose Multiplatform - Starter kit for pragmatics
Kotlin Multiplatform & Compose Multiplatform - Starter kit for pragmaticscarlostorres15106
 
Unblocking The Main Thread Solving ANRs and Frozen Frames
Unblocking The Main Thread Solving ANRs and Frozen FramesUnblocking The Main Thread Solving ANRs and Frozen Frames
Unblocking The Main Thread Solving ANRs and Frozen FramesSinan KOZAK
 
Unleash Your Potential - Namagunga Girls Coding Club
Unleash Your Potential - Namagunga Girls Coding ClubUnleash Your Potential - Namagunga Girls Coding Club
Unleash Your Potential - Namagunga Girls Coding ClubKalema Edgar
 
Benefits Of Flutter Compared To Other Frameworks
Benefits Of Flutter Compared To Other FrameworksBenefits Of Flutter Compared To Other Frameworks
Benefits Of Flutter Compared To Other FrameworksSoftradix Technologies
 
Artificial intelligence in the post-deep learning era
Artificial intelligence in the post-deep learning eraArtificial intelligence in the post-deep learning era
Artificial intelligence in the post-deep learning eraDeakin University
 
Scanning the Internet for External Cloud Exposures via SSL Certs
Scanning the Internet for External Cloud Exposures via SSL CertsScanning the Internet for External Cloud Exposures via SSL Certs
Scanning the Internet for External Cloud Exposures via SSL CertsRizwan Syed
 
New from BookNet Canada for 2024: BNC BiblioShare - Tech Forum 2024
New from BookNet Canada for 2024: BNC BiblioShare - Tech Forum 2024New from BookNet Canada for 2024: BNC BiblioShare - Tech Forum 2024
New from BookNet Canada for 2024: BNC BiblioShare - Tech Forum 2024BookNet Canada
 
FULL ENJOY 🔝 8264348440 🔝 Call Girls in Diplomatic Enclave | Delhi
FULL ENJOY 🔝 8264348440 🔝 Call Girls in Diplomatic Enclave | DelhiFULL ENJOY 🔝 8264348440 🔝 Call Girls in Diplomatic Enclave | Delhi
FULL ENJOY 🔝 8264348440 🔝 Call Girls in Diplomatic Enclave | Delhisoniya singh
 
Unlocking the Potential of the Cloud for IBM Power Systems
Unlocking the Potential of the Cloud for IBM Power SystemsUnlocking the Potential of the Cloud for IBM Power Systems
Unlocking the Potential of the Cloud for IBM Power SystemsPrecisely
 
SIEMENS: RAPUNZEL – A Tale About Knowledge Graph
SIEMENS: RAPUNZEL – A Tale About Knowledge GraphSIEMENS: RAPUNZEL – A Tale About Knowledge Graph
SIEMENS: RAPUNZEL – A Tale About Knowledge GraphNeo4j
 
Making_way_through_DLL_hollowing_inspite_of_CFG_by_Debjeet Banerjee.pptx
Making_way_through_DLL_hollowing_inspite_of_CFG_by_Debjeet Banerjee.pptxMaking_way_through_DLL_hollowing_inspite_of_CFG_by_Debjeet Banerjee.pptx
Making_way_through_DLL_hollowing_inspite_of_CFG_by_Debjeet Banerjee.pptxnull - The Open Security Community
 
My Hashitalk Indonesia April 2024 Presentation
My Hashitalk Indonesia April 2024 PresentationMy Hashitalk Indonesia April 2024 Presentation
My Hashitalk Indonesia April 2024 PresentationRidwan Fadjar
 
Advanced Test Driven-Development @ php[tek] 2024
Advanced Test Driven-Development @ php[tek] 2024Advanced Test Driven-Development @ php[tek] 2024
Advanced Test Driven-Development @ php[tek] 2024Scott Keck-Warren
 
Breaking the Kubernetes Kill Chain: Host Path Mount
Breaking the Kubernetes Kill Chain: Host Path MountBreaking the Kubernetes Kill Chain: Host Path Mount
Breaking the Kubernetes Kill Chain: Host Path MountPuma Security, LLC
 
Presentation on how to chat with PDF using ChatGPT code interpreter
Presentation on how to chat with PDF using ChatGPT code interpreterPresentation on how to chat with PDF using ChatGPT code interpreter
Presentation on how to chat with PDF using ChatGPT code interpreternaman860154
 
Beyond Boundaries: Leveraging No-Code Solutions for Industry Innovation
Beyond Boundaries: Leveraging No-Code Solutions for Industry InnovationBeyond Boundaries: Leveraging No-Code Solutions for Industry Innovation
Beyond Boundaries: Leveraging No-Code Solutions for Industry InnovationSafe Software
 
08448380779 Call Girls In Friends Colony Women Seeking Men
08448380779 Call Girls In Friends Colony Women Seeking Men08448380779 Call Girls In Friends Colony Women Seeking Men
08448380779 Call Girls In Friends Colony Women Seeking MenDelhi Call girls
 
Connect Wave/ connectwave Pitch Deck Presentation
Connect Wave/ connectwave Pitch Deck PresentationConnect Wave/ connectwave Pitch Deck Presentation
Connect Wave/ connectwave Pitch Deck PresentationSlibray Presentation
 
Maximizing Board Effectiveness 2024 Webinar.pptx
Maximizing Board Effectiveness 2024 Webinar.pptxMaximizing Board Effectiveness 2024 Webinar.pptx
Maximizing Board Effectiveness 2024 Webinar.pptxOnBoard
 

Kürzlich hochgeladen (20)

Kotlin Multiplatform & Compose Multiplatform - Starter kit for pragmatics
Kotlin Multiplatform & Compose Multiplatform - Starter kit for pragmaticsKotlin Multiplatform & Compose Multiplatform - Starter kit for pragmatics
Kotlin Multiplatform & Compose Multiplatform - Starter kit for pragmatics
 
Unblocking The Main Thread Solving ANRs and Frozen Frames
Unblocking The Main Thread Solving ANRs and Frozen FramesUnblocking The Main Thread Solving ANRs and Frozen Frames
Unblocking The Main Thread Solving ANRs and Frozen Frames
 
Unleash Your Potential - Namagunga Girls Coding Club
Unleash Your Potential - Namagunga Girls Coding ClubUnleash Your Potential - Namagunga Girls Coding Club
Unleash Your Potential - Namagunga Girls Coding Club
 
Benefits Of Flutter Compared To Other Frameworks
Benefits Of Flutter Compared To Other FrameworksBenefits Of Flutter Compared To Other Frameworks
Benefits Of Flutter Compared To Other Frameworks
 
Vulnerability_Management_GRC_by Sohang Sengupta.pptx
Vulnerability_Management_GRC_by Sohang Sengupta.pptxVulnerability_Management_GRC_by Sohang Sengupta.pptx
Vulnerability_Management_GRC_by Sohang Sengupta.pptx
 
Artificial intelligence in the post-deep learning era
Artificial intelligence in the post-deep learning eraArtificial intelligence in the post-deep learning era
Artificial intelligence in the post-deep learning era
 
Scanning the Internet for External Cloud Exposures via SSL Certs
Scanning the Internet for External Cloud Exposures via SSL CertsScanning the Internet for External Cloud Exposures via SSL Certs
Scanning the Internet for External Cloud Exposures via SSL Certs
 
New from BookNet Canada for 2024: BNC BiblioShare - Tech Forum 2024
New from BookNet Canada for 2024: BNC BiblioShare - Tech Forum 2024New from BookNet Canada for 2024: BNC BiblioShare - Tech Forum 2024
New from BookNet Canada for 2024: BNC BiblioShare - Tech Forum 2024
 
FULL ENJOY 🔝 8264348440 🔝 Call Girls in Diplomatic Enclave | Delhi
FULL ENJOY 🔝 8264348440 🔝 Call Girls in Diplomatic Enclave | DelhiFULL ENJOY 🔝 8264348440 🔝 Call Girls in Diplomatic Enclave | Delhi
FULL ENJOY 🔝 8264348440 🔝 Call Girls in Diplomatic Enclave | Delhi
 
Unlocking the Potential of the Cloud for IBM Power Systems
Unlocking the Potential of the Cloud for IBM Power SystemsUnlocking the Potential of the Cloud for IBM Power Systems
Unlocking the Potential of the Cloud for IBM Power Systems
 
SIEMENS: RAPUNZEL – A Tale About Knowledge Graph
SIEMENS: RAPUNZEL – A Tale About Knowledge GraphSIEMENS: RAPUNZEL – A Tale About Knowledge Graph
SIEMENS: RAPUNZEL – A Tale About Knowledge Graph
 
Making_way_through_DLL_hollowing_inspite_of_CFG_by_Debjeet Banerjee.pptx
Making_way_through_DLL_hollowing_inspite_of_CFG_by_Debjeet Banerjee.pptxMaking_way_through_DLL_hollowing_inspite_of_CFG_by_Debjeet Banerjee.pptx
Making_way_through_DLL_hollowing_inspite_of_CFG_by_Debjeet Banerjee.pptx
 
My Hashitalk Indonesia April 2024 Presentation
My Hashitalk Indonesia April 2024 PresentationMy Hashitalk Indonesia April 2024 Presentation
My Hashitalk Indonesia April 2024 Presentation
 
Advanced Test Driven-Development @ php[tek] 2024
Advanced Test Driven-Development @ php[tek] 2024Advanced Test Driven-Development @ php[tek] 2024
Advanced Test Driven-Development @ php[tek] 2024
 
Breaking the Kubernetes Kill Chain: Host Path Mount
Breaking the Kubernetes Kill Chain: Host Path MountBreaking the Kubernetes Kill Chain: Host Path Mount
Breaking the Kubernetes Kill Chain: Host Path Mount
 
Presentation on how to chat with PDF using ChatGPT code interpreter
Presentation on how to chat with PDF using ChatGPT code interpreterPresentation on how to chat with PDF using ChatGPT code interpreter
Presentation on how to chat with PDF using ChatGPT code interpreter
 
Beyond Boundaries: Leveraging No-Code Solutions for Industry Innovation
Beyond Boundaries: Leveraging No-Code Solutions for Industry InnovationBeyond Boundaries: Leveraging No-Code Solutions for Industry Innovation
Beyond Boundaries: Leveraging No-Code Solutions for Industry Innovation
 
08448380779 Call Girls In Friends Colony Women Seeking Men
08448380779 Call Girls In Friends Colony Women Seeking Men08448380779 Call Girls In Friends Colony Women Seeking Men
08448380779 Call Girls In Friends Colony Women Seeking Men
 
Connect Wave/ connectwave Pitch Deck Presentation
Connect Wave/ connectwave Pitch Deck PresentationConnect Wave/ connectwave Pitch Deck Presentation
Connect Wave/ connectwave Pitch Deck Presentation
 
Maximizing Board Effectiveness 2024 Webinar.pptx
Maximizing Board Effectiveness 2024 Webinar.pptxMaximizing Board Effectiveness 2024 Webinar.pptx
Maximizing Board Effectiveness 2024 Webinar.pptx
 

Haskell Tour (Part 3)

  • 1. Haskell A Whirlwind Tour (Part III) William Taysom ~ 2011
  • 2.
  • 3. Haskell is a non-strict, purely functional programming language with strong, static type inference.
  • 5. Recursive Data data Color = Red | Green | Blue | Mix Color Color
  • 6. Recursive Functions hue :: Color -> Maybe Double hue Red = Just 0 hue Green = Just 120 hue Blue = Just 240
  • 7. 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
  • 8. Parametric Data data (a, b) = (a, b) data Either a b = Left a | Right b data Maybe a = Nothing | Just a data [a] = [] | a:[a] type String = [Char]
  • 9. Parametric Functions (.) :: (b -> c) -> (a -> b) -> a -> c infixr . -- 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
  • 10. 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]
  • 12. 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
  • 13. Membership Test elem :: a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 14. Membership Test elem :: a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 15. Membership Test elem :: a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 16. Membership Test elem :: a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 17. Membership Test elem :: a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False (==) :: Eq a => a -> a -> Bool _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 18. Membership Test elem :: a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False (==) :: Eq a => a -> a -> Bool _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 19. Membership Test elem :: a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 20. Membership Test elem :: Eq a => a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 21. Membership Test elem :: Eq a => a -> [a] -> Bool infix 4 `elem` x `elem` xs = case filter (== x) xs of [] -> False _ -> True 'q' `elem` a_z --> True '8' `elem` a_z --> False
  • 22. 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
  • 23. 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
  • 24. Eq Instance ghci> :i Color instance Eq Color where Red == Red = True Green == Green = True Blue == Blue = True Mix c c' == Mix d d' = c == d && c' == d' _ == _ = False
  • 25. ghci> :i Color data Color = Red | Green | Blue | Mix Color Color ! Defined at example.hs:1:6-10 -- instance Eq Color -- Defined at example.hs:3:10-17 ghci>
  • 26. ghci> :i Color data Color = Red | Green | Blue | Mix Color Color ! Defined at example.hs:1:6-10 -- instance Eq Color -- Defined at example.hs:3:10-17 ghci> :i Eq
  • 27. Default Definitions ghci> :i Color data Color = Red | Green | Blue | Mix Color Color ! Eq a where example.hs:1:6-10 -- Defined at class instance Eq Color -- Defined at (==), (/=) :: a -> a -> Bool example.hs:3:10-17 ghci> :i=Eq (x == y) x /= y not class Eq=anot (x /= y) x == y where (==) :: a -> a -> Bool (/=) :: a -> a -> Bool ! Defined in GHC.Classes -- ... followed by 26 instances ...
  • 28. Default Definitions class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
  • 29. Default Definitions class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
  • 30. Default Definitions class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
  • 31. Default Definitions ghci> :i Color data Color = Red | Green | Blue | Mix Color Color ! Eq a where example.hs:1:6-10 -- Defined at class instance Eq Color -- Defined at (==), (/=) :: a -> a -> Bool example.hs:3:10-17 ghci> :i=Eq (x == y) x /= y not class Eq=anot (x /= y) x == y where (==) :: a -> a -> Bool (/=) :: a -> a -> Bool ! Defined in GHC.Classes -- ... followed by 26 instances ...
  • 32. ... some Eq instances ... instance Eq Color instance Eq Bool instance Eq Char
  • 33. ... some Eq instances ... instance Eq Color instance Eq Bool instance Eq Char instance Eq a => Eq [a] instance (Eq a, Eq b) => Eq (a, b)
  • 35. ghci> :t compare compare :: Ord a => a -> a -> Ordering ghci>
  • 36. ghci> :t compare compare :: Ord a => a -> a -> Ordering ghci> :i Ord
  • 37. Ord Instance ghci> :t compare compare :: Ord a => a -> a -> Ordering ghci> :i Ord class Eq a Color where instance Ord => Ord a where ! Red compare :: a -> a -> Ordering <= _ = True ! Green::<= -> a -> = False (<) a Red Bool ! Green :: a_-> a -> Bool (>=) <= = True ! Blue ::<= -> a -> = False (>) a Red Bool ! Blue :: aGreen -> Bool (<=) <= -> a = False Blue <= _ = True ! max :: a -> a -> a Mix c c' <= Mix d d' ! min :: a -> a -> a | c == d = c' <= d' -- Defined in GHC.Classes | otherwise = c <= d _ <= _ = False
  • 38. 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
  • 39. 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
  • 40. Derived Instances data Color = Red | Green | Blue | Mix Color Color deriving (Eq, Ord, Read, Show)
  • 41. Derived Instances data Color = Red | Green | Blue | Mix Color Color deriving (Eq, Ord, Read, Show)
  • 42. Derived Instances ghci> show (Mix Red Green) data Color = Red | Green | Blue | Mix Color Color deriving (Eq, Ord, Read, Show)
  • 43. ghci> show (Mix Red Green) "Mix Red Green" ghci>
  • 44. ghci> show (Mix Red Green) "Mix Red Green" ghci> read "Mix Red Green"
  • 45. 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"
  • 46. 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"
  • 47. 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"
  • 48.
  • 50. ghci> :t read read :: Read a => String -> a ghci>
  • 51. ghci> :t read read :: Read a => String -> a ghci> hue (read "Mix Red Green")
  • 52. ghci> :t read read :: Read a => String -> a ghci> hue (read "Mix Red Green") 60.0 ghci>
  • 53. ghci> :t read read :: Read a => String -> a ghci> hue (read "Mix Red Green") 60.0 ghci> read "Mix Red Green"
  • 54. ghci> :t read read :: Read a => String -> a ghci> hue (read "Mix Red Green") 60.0 ghci> read "Mix Red Green" :: Color
  • 55. Type Classes Compared ghci> :t read read :: Read a => String -> a ghci> hue (read "Mix Red Green") 60.0 ghci> read "Mix Red Green" :: Color Mix Red Green ghci>
  • 58. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 59. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 60. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 61. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 62. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 63. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 64. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 65. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 66. Type Classes Compared OO Class Type Class Type Instance Object (Not Value) Dynamic Static on Any Part Dispatch on Receiver (Like Overloading) Class Conditions Extension Subclassing (No Subtypes) Default Reuse Inheritance (No Overriding)
  • 67.
  • 68.
  • 69.
  • 70. intFromHexString :: String -> Int intFromHexString [] =0 intFromHexString (c:cs) = digitToInt c * 16 ^ length cs + intFromHexString cs
  • 71. numberFromString :: Num a => String -> a numberFromString [] = 0 numberFromString (c:cs) = fromIntegral (digitToInt c) * 10 ^ fromIntegral (length cs) + integerFromString cs
  • 72. numberFromString :: Num a => String -> a numberFromString [] = 0 numberFromString (c:cs) = fromIntegral (digitToInt c) * 10 ^ fromIntegral (length cs) + integerFromString cs fromIntegral :: (Num b, Integral a) => a -> b
  • 73.
  • 74.
  • 76. 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
  • 77. Maybe (Failure) instance Monad Maybe where return = Just Nothing >>= k = Nothing Just x >>= k = k x
  • 78. 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
  • 79. hue (Mix c c') = case (hue c, hue c') of (Just h, Just h') -> ... _ -> Nothing
  • 80. hue (Mix c c') = case hue c of Just h -> case hue c' of Just h' -> ... Nothing -> Nothing Nothing -> Nothing
  • 81. hue (Mix c c') = case hue c of Just h -> hue c' >>= h' -> ... Nothing -> Nothing
  • 82. hue (Mix c c') = hue c >>= h -> hue c' >>= h' -> ...
  • 83. hue (Mix c c') = hue c >>= h -> do h' <- hue c'; ...
  • 84. hue (Mix c c') = do h <- hue c do h' <- hue c'; ...
  • 85. hue (Mix c c') = do h <- hue c h' <- hue c' ...
  • 86. 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'
  • 87. 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'
  • 88. List (Nondeterminism) instance Monad [] where return x = [x] xs >>= k = concat (map k xs)
  • 89. [ (a, b, c) | c <- nats, b <- [1..c], a <- [1..b]]
  • 90. [ (a, b, c) | c <- nats, b <- [1..c], a <- [1..b]] do c <- nats b <- [1..c] a <- [1..b] return (a, b, c)
  • 91. Generalized Map (<$>) :: Monad m => (a -> b) -> m a -> m b f <$> m = m >>= return . f ord <$> "abc" --> [97, 98, 99]
  • 92. Constant Map (<$) :: Monad m => a -> m b -> m a (<$) = (<$>) . const 'x' <$ "abc" --> "xxx"
  • 93. [ (a, b, c) | c <- nats, b <- [1..c], a <- [1..b]] do c <- nats b <- [1..c] a <- [1..b] return (a, b, c)
  • 94. [ (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)
  • 95. MonadPlus Class class Monad m => MonadPlus m where mzero :: m a mplus :: m a -> m a -> m a
  • 96. List (Nondeterminism) instance MonadPlus [] where mzero = [] mplus = (++)
  • 97. Guard guard :: MonadPlus m => Bool -> m () guard True = return () guard False = mzero
  • 98. Getter data Getter a = Getter (String -> (a, String)) get :: Getter a -> String -> (a, String) get (Getter g) = g
  • 99. 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'
  • 100. Primitive Action getChar :: Getter Char getChar = Getter $ s -> case s of c:cs -> (c , cs) "" -> ('0', "")
  • 101. Derived Action getLine :: Getter String getLine = do c <- getChar if c == 'n' || c == '0' then return "" else do s <- getLine return $ c:s get getLine "hellonworld" --> ("hello", "world")
  • 102. IO data IO a = IO (RealWorld -> (a, RealWorld)) putChar :: Char -> IO ()
  • 103. Print Functions putStr :: String -> IO () putStr "" = return () putStr (c:cs) = do putChar c putStr cs
  • 104. Print Functions putStrLn :: String -> IO () putStrLn s = do putStr s putChar 'n'
  • 105. Main Point “The business of the program is to construct one gianormous action which is then performed.” — Simon Peyton-Jones
  • 106. hello.hs main = putStrLn "hello, world"
  • 109. Parsers data Parser a = Parser (String -> [(a, String)]) parse :: Parser a -> String -> [(a, String)] parse (Parser p) = p
  • 110. 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]
  • 111. Parsers instance MonadPlus Parser where mzero = Parser $ s -> [] mplus p q = Parser $ s -> parse p s ++ parse q s
  • 112. Parsers instance MonadPlus Parser where mzero = Parser $ s -> [] mplus p q = Parser $ s -> parse p s ++ parse q s (<|>) :: Parser a -> Parser a -> Parser a infixr 1 <|> (<|>) = mplus
  • 113. Primitive Actions anyChar :: Parser Char anyChar = Parser $ s -> case s of c:cs -> [(c, cs)] "" -> [] eof :: Parser () eof = Parser $ s -> case s of c:cs -> [] "" -> [((), "")]
  • 114. Derived Actions satisfy :: (Char -> Bool) -> Parser Char satisfy f = do c <- anyChar if f c then return c else mzero
  • 115. Derived Actions char :: Char -> Parser Char char c = satisfy (== c)
  • 116. Derived Actions string :: String -> Parser String string "" = return "" string s@(c:cs) = do char c string cs return s
  • 117. Backtracking hiHeHello = string "hi" <|> string "he" <|> string "hello"
  • 118. Backtracking hiHeHello = string "hi" <|> string "he" <|> string "hello" parse hiHeHello "hello" --> [("he","llo"), ("hello","")]
  • 119. Parsec type Parser = Parsec String ()
  • 120. Parsec type Parser = Parsec String () hiHeHello = string "hi" <|> string "he" <|> string "hello" parseTest hiHeHello "hello" >>-> unexpected "e" expecting "hi"
  • 121. Optional Backtracking try :: Parser a -> Parser a
  • 122. Optional Backtracking try :: Parser a -> Parser a hiHeHello' = try (string "hi") <|> string "he" <|> string "hello"
  • 123. Optional Backtracking try :: Parser a -> Parser a hiHeHello' = try (string "hi") <|> string "he" <|> string "hello" parseTest hiHeHello' "hello" >>-> "he"
  • 124. Error Messages (<?>) :: Parser a -> String -> Parser a
  • 125. Error Messages (<?>) :: Parser a -> String -> Parser a space :: Parser Char space = satisfy isSpace <?> "space" digit :: Parser Char digit = satisfy isDigit <?> "digit" hexDigit :: Parser Char hexDigit = satisfy isHexDigit <?> "hexadecimal digit"
  • 126. Error Messages parseTest (space <|> digit <|> hexDigit) "hello" >>-> unexpected "h" expecting space, digit or hexadecimal digit
  • 127. Parser Combinators oneOf :: String -> Parser Char -- Example eE = oneOf "eE"
  • 128. Parser Combinators noneOf :: String -> Parser Char -- Example notDoubleQuote = noneOf """
  • 129. Parser Combinators between :: Parser a -> Parser b -> Parser c -> Parser c -- Definition between open close p = do open x <- p close return x
  • 130. Parser Combinators option :: a -> Parser a -> Parser a -- Definition option x p = p <|> return x
  • 131. Parser Combinators count :: Int -> Parser a -> Parser [a] -- Example hexDigit4 = count 4 hexDigit
  • 132. Parser Combinators many, many1 :: Parser a -> Parser [a] -- Example digits = many1 digit
  • 133. Parser Combinators skipMany :: Parser a -> Parser () -- Example skipMany p = many p >> return ()
  • 134. Parser Combinators spaces :: Parser () -- Definition spaces = skipMany space
  • 135. Parser Combinators sepBy :: Parser a -> Parser b -> Parser [a] -- Example words = (many1 . satisfy) (not . isSpace) `sepBy` spaces
  • 136. Space Management justOne :: Parser a -> Parser a justOne = between spaces (spaces >> eof)
  • 137. 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
  • 138. 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 ','
  • 140. Parse String jsstring :: Parser String jsstring = between doubleQuote doubleQuote $ many character
  • 141. Parse String jsstring :: Parser String jsstring = between doubleQuote doubleQuote $ many character doubleQuote :: Parser Char doubleQuote = char '"'
  • 142. Parse String jsstring :: Parser String jsstring = between doubleQuote doubleQuote $ many character doubleQuote :: Parser Char doubleQuote = char '"' character :: Parser Char character = (char '' >> escapeChar) <|> notDoubleQuote
  • 143. escapeChar :: Parser Char escapeChar = char '"' <|> char '' <|> char '/' <|> 'b' <$ char 'b' <|> 'f' <$ char 'f' <|> 'n' <$ char 'n' <|> 'r' <$ char 'r' <|> 't' <$ char 't' <|> unicode
  • 144. unicode :: Parser Char unicode = do char 'u' digits <- hexDigit4 let n = intFromHexString digits return $ chr n
  • 146. Parse Number number :: Parser Double number = do s <- sign n <- int f <- frac e <- expon return $ s * (n + f) * e
  • 147. sign :: Parser Double sign = option 1 $ (-1) <$ char '-' int :: Parser Double int = 0 <$ char '0' <|> numberFromString <$> digits
  • 148. frac :: Parser Double frac = option 0 $ do char '.' n <- digits return $ numberFromString n / 10 ^^ length n expon :: Parser Double expon = option 1 $ do eE s <- sign n <- digits return $ s * 10 ** numberFromString n
  • 152. Parse JSON data Value = String String | Number Double | Object [(String, Value)] | Array [Value] | Bool Bool | Null
  • 153. Parse JSON value = String <$>jsstring <|> Number <$>number <|> Object <$>commaGroup '{' pair '}' <|> Array <$>commaGroup '[' value ']' <|> Bool True <$ string "true" <|> Bool False <$ string "false" <|> Null <$ string "null"
  • 154. Parse JSON data Value = String String | Number Double | Object [(String, Value)] | Array [Value] | Bool Bool | Null
  • 155. Parse JSON value = String <$>jsstring <|> Number <$>number <|> Object <$>commaGroup '{' pair '}' <|> Array <$>commaGroup '[' value ']' <|> Bool True <$ string "true" <|> Bool False <$ string "false" <|> Null <$ string "null"
  • 156. pair :: Parser (String, Value) pair = do s <- jsstring sp_char_sp ':' v <- value spaces return (s, v)
  • 157. parseJSON :: String -> Value parseJSON s = case parse (justOne value) "" s of Left err -> error $ "JSON parse error " ++ show err Right v -> v
  • 158. parseJSON "{"just": ["some", 4, "u24E4"]}" --> Object [("just", Array [String "some", Number 4.0, String "9444"])]
  • 159. 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 ","
  • 162. Summary Parsers Monads Type Classes Parametric Types Functions and Data Types
  • 163. Summary Parsers Monads Type Classes Parametric Types Functions and Data Types
  • 164. Summary Parsers Monads Type Classes Parametric Types Functions and Data Types
  • 165. Summary Parsers Monads Type Classes Parametric Types Functions and Data Types
  • 166. Summary Parsers Monads Type Classes Parametric Types Functions and Data Types
  • 167. Haskell is a non-strict, purely functional programming language with strong, static type inference.