Difference between revisions of "Haskell a la carte"

From HaskellWiki
Jump to navigation Jump to search
m (Various minor changes)
 
(9 intermediate revisions by 5 users not shown)
Line 1: Line 1:
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]
   
New to Haskell? This menu will give you a first impression. Don't read all the explanations, or you'll be starved before the meal.
+
New to Haskell? This menu will give you a first impression. Don't read all the explanations, or you'll be starved before the meal!
   
 
== Apéritifs ==
 
== Apéritifs ==
Foretaste of an excellent meal.
+
Foretaste of an excellent meal:
   
 
* <haskell>
*
 
<haskell>
 
 
qsort :: Ord a => [a] -> [a]
 
qsort :: Ord a => [a] -> [a]
 
qsort [] = []
 
qsort [] = []
 
qsort (x:xs) = qsort (filter (<x) xs) ++ [x] ++ qsort (filter (>=x) xs))
 
qsort (x:xs) = qsort (filter (<x) xs) ++ [x] ++ qsort (filter (>=x) xs))
 
</haskell>
 
</haskell>
::Quicksort in three lines (!). Sorts not only integers but anything that can be compared.
+
::Quicksort in three lines (!). Sorts not only integers but anything that can be compared. But granted, it's not in-place.
   
 
* <haskell>
*
 
<haskell>
 
 
fibs = 1:1:zipWith (+) fibs (tail fibs)
 
fibs = 1:1:zipWith (+) fibs (tail fibs)
 
</haskell>
 
</haskell>
 
::The ''infinite'' list of fibonacci numbers. Just don't try to print all of it.
 
::The ''infinite'' list of fibonacci numbers. Just don't try to print all of it.
   
 
* <haskell>
*
 
<haskell>
 
 
linecount = interact $ show . length . lines
 
linecount = interact $ show . length . lines
 
wordcount = interact $ show . length . words
 
wordcount = interact $ show . length . words
Line 28: Line 25:
   
 
== Entrées ==
 
== Entrées ==
How to read the dishes.
+
How to read the dishes:
   
 
* <haskell>
*
 
<haskell>
 
 
square x = x*x
 
square x = x*x
 
</haskell>
 
</haskell>
::is the function <math>f(x)=x\cdot x</math> which maps a number to its square. While we commonly write parenthesis around function arguments in mathematics and most programming languages, a simple space is enough in Haskell. We're going to apply functions to arguments all around, so why clutter the notation with unnecessary ballast?
+
::is the function <math>f(x)=x\cdot x</math> which maps a number to its square. While we commonly write parentheses around function arguments in mathematics and most programming languages, a simple space is enough in Haskell. We're going to apply functions to arguments all around, so why clutter the notation with unnecessary ballast?
   
 
* <haskell>
*
 
<haskell>
 
 
square :: Int -> Int
 
square :: Int -> Int
 
square x = x*x
 
square x = x*x
Line 43: Line 38:
 
:: Squaring again, this time with a ''type signature'' which says that squaring maps integers to integers. In mathematics, we'd write <math>f:\mathbb{Z}\to\mathbb{Z},\ f(x)=x\cdot x</math>. Every expression in Haskell has a type and the compiler will automatically infer (= figure out) one for you if you're too lazy to write down a type signature yourself. Of course, parenthesis are allowed for grouping, like in <hask>square (4+2)</hask> which is 36 compared to <hask>square 4 + 2</hask> which is 16+2=18.
 
:: Squaring again, this time with a ''type signature'' which says that squaring maps integers to integers. In mathematics, we'd write <math>f:\mathbb{Z}\to\mathbb{Z},\ f(x)=x\cdot x</math>. Every expression in Haskell has a type and the compiler will automatically infer (= figure out) one for you if you're too lazy to write down a type signature yourself. Of course, parenthesis are allowed for grouping, like in <hask>square (4+2)</hask> which is 36 compared to <hask>square 4 + 2</hask> which is 16+2=18.
   
 
* <haskell>
*
 
<haskell>
 
 
square :: Num a => a -> a
 
square :: Num a => a -> a
 
square x = x*x
 
square x = x*x
Line 50: Line 44:
 
:: Squaring yet again, this time with a more general type signature. After all, we can square anything (<hask>a</hask>) that looks like a number (<hask>Num a</hask>). By the way, this general type is the one that the compiler will infer for <hask>square</hask> if you omit an explicit signature.
 
:: Squaring yet again, this time with a more general type signature. After all, we can square anything (<hask>a</hask>) that looks like a number (<hask>Num a</hask>). By the way, this general type is the one that the compiler will infer for <hask>square</hask> if you omit an explicit signature.
   
 
* <haskell>
*
 
<haskell>
 
 
average x y = (x+y)/2
 
average x y = (x+y)/2
 
</haskell>
 
</haskell>
 
:: The average of two numbers. Multiple arguments are separated by spaces.
 
:: The average of two numbers. Multiple arguments are separated by spaces.
   
 
* <haskell>
*
 
<haskell>
 
 
average :: Double -> Double -> Double
 
average :: Double -> Double -> Double
 
average x y = (x+y)/2
 
average x y = (x+y)/2
Line 63: Line 55:
 
::Average again, this time with a type signature. Looks a bit strange, but that's the spicey ''currying''. In fact, <hask>average</hask> is a function that takes only one argument (<hask>Double</hask>) but returns a function with one argument (<hask>Double -> Double</hask>).
 
::Average again, this time with a type signature. Looks a bit strange, but that's the spicey ''currying''. In fact, <hask>average</hask> is a function that takes only one argument (<hask>Double</hask>) but returns a function with one argument (<hask>Double -> Double</hask>).
   
 
* <haskell>
*
 
<haskell>
 
 
power a n = if n == 0 then 1 else a * power a (n-1)
 
power a n = if n == 0 then 1 else a * power a (n-1)
 
</haskell>
 
</haskell>
Line 70: Line 61:
 
:: Recursion is the basic building block for iteration in Haskell, there are no <code>for</code> or <code>while</code>-loops. Well, there are functions like <hask>map</hask> or <hask>foldr</hask> that provide something similar. There is no need for special built-in control structures, you can define them yourself as ordinary functions (later).
 
:: Recursion is the basic building block for iteration in Haskell, there are no <code>for</code> or <code>while</code>-loops. Well, there are functions like <hask>map</hask> or <hask>foldr</hask> that provide something similar. There is no need for special built-in control structures, you can define them yourself as ordinary functions (later).
   
 
* <haskell>
*
 
<haskell>
 
 
power a 0 = 1
 
power a 0 = 1
 
power a n = a * power a (n-1)
 
power a n = a * power a (n-1)
Line 77: Line 67:
 
::Exponentiation again, this time with ''pattern matching''. The first equation that matches will be chosen.
 
::Exponentiation again, this time with ''pattern matching''. The first equation that matches will be chosen.
   
 
* <haskell>
*
 
<haskell>
 
 
length [] = 0
 
length [] = 0
 
length (x:xs) = 1 + length xs
 
length (x:xs) = 1 + length xs
Line 84: Line 73:
 
::Calculate the length of a ''list''. What's a list? Well, a list may either be empty (<hask>[]</hask>) or be an element (<hask>x</hask>) prepended (<hask>:</hask>) to another list (<hask>xs</hask>). Read "<hask>xs</hask>" as the plural of "<hask>x</hask>", that is as "ex-es". It's a list of other such elements <hask>x</hask>, after all.
 
::Calculate the length of a ''list''. What's a list? Well, a list may either be empty (<hask>[]</hask>) or be an element (<hask>x</hask>) prepended (<hask>:</hask>) to another list (<hask>xs</hask>). Read "<hask>xs</hask>" as the plural of "<hask>x</hask>", that is as "ex-es". It's a list of other such elements <hask>x</hask>, after all.
   
 
* <haskell>
*
 
<haskell>
 
 
length :: [a] -> Int
 
length :: [a] -> Int
 
length [] = 0
 
length [] = 0
Line 92: Line 80:
 
::Length of a list again, this time with type signature. <hask>[a]</hask> is the type of lists with elements of type <hask>a</hask>. <hask>length </hask> can be used for any such element type.
 
::Length of a list again, this time with type signature. <hask>[a]</hask> is the type of lists with elements of type <hask>a</hask>. <hask>length </hask> can be used for any such element type.
   
 
* <haskell>
*
 
<haskell>
 
 
head :: [a] -> a
 
head :: [a] -> a
 
head (x:xs) = x
 
head (x:xs) = x
Line 99: Line 86:
 
::First element of a list. Undefined for empty lists.
 
::First element of a list. Undefined for empty lists.
   
 
* <haskell>
*
 
<haskell>
 
 
sum [] = 0
 
sum [] = 0
 
sum (x:xs) = x + sum xs
 
sum (x:xs) = x + sum xs
Line 106: Line 92:
 
::Sum all elements of a list.
 
::Sum all elements of a list.
   
 
* <haskell>
*
 
<haskell>
 
 
average xs = sum xs / (fromIntegral (length xs))
 
average xs = sum xs / (fromIntegral (length xs))
 
</haskell>
 
</haskell>
 
::Arithmetic mean. <hask>fromIntegral</hask> converts the integer result of <hask>length</hask> into a decimal number for the division <hask>/</hask>.
 
::Arithmetic mean. <hask>fromIntegral</hask> converts the integer result of <hask>length</hask> into a decimal number for the division <hask>/</hask>.
  +
 
* <haskell>
  +
(++) :: [a] -> [a] -> [a]
  +
(++) [] ys = ys
  +
(++) (x:xs) ys = x:(xs ++ ys)
 
</haskell>
  +
::Concatenate two lists. Custom infix operators can be defined freely.
   
 
== Soupes ==
 
== Soupes ==
The best soup is made by combining the available ingredients.
+
The best soup is made by combining the available ingredients:
   
 
* <haskell>
*
 
<haskell>
 
 
(.) :: (b -> c) -> (a -> b) -> (a -> c)
 
(.) :: (b -> c) -> (a -> b) -> (a -> c)
 
(.) f g x = f (g x)
 
(.) f g x = f (g x)
Line 124: Line 115:
 
::The dot <hask>f . g</hask> is good old function composition <math>f \circ g</math>. First apply g, then apply f. Simple example: squaring something twice.
 
::The dot <hask>f . g</hask> is good old function composition <math>f \circ g</math>. First apply g, then apply f. Simple example: squaring something twice.
   
  +
* <haskell>
*
 
<haskell>
 
 
minimum = head . qsort
 
minimum = head . qsort
 
</haskell>
 
</haskell>
 
:: To find the least element of a list, first sort and then take the first element. You think that takes too much time (<math>O(n\cdot\log n)</math> instead of <math>O(n)</math>)? Well, thanks to ''lazy evaluation'', it doesn't! In Haskell, expressions are evaluated only as much as needed. Therefore, the sorting won't proceed further than producing the first element of the sorted list. Ok, the sorting function has to play along and produce that one quickly, but many like quicksort (in the average case) or mergesort do so.
 
:: To find the least element of a list, first sort and then take the first element. You think that takes too much time (<math>O(n\cdot\log n)</math> instead of <math>O(n)</math>)? Well, thanks to ''lazy evaluation'', it doesn't! In Haskell, expressions are evaluated only as much as needed. Therefore, the sorting won't proceed further than producing the first element of the sorted list. Ok, the sorting function has to play along and produce that one quickly, but many like quicksort (in the average case) or mergesort do so.
  +
  +
* <haskell>
  +
sum = foldr (+) 0
  +
product = foldr (*) 1
  +
concat = foldr (++) []
  +
</haskell>
  +
:: Tired of implementing a recursive function every time you're traversing a list? No need for that, <hask>fold</hask> captures the recursion, you just tell it how to combine the list elements. It can be defined as:
  +
::<haskell>
  +
foldr f z [] = z
  +
foldr f z (x:xs) = x `f` foldr f z xs
  +
</haskell>
   
 
== Plats principaux ==
 
== Plats principaux ==
   
 
== Desserts==
 
== Desserts==
Sugar-sweet and en passant.
+
Sugar-sweet and en passant:
  +
  +
* <haskell>
  +
sequence :: Monad m => [m a] -> m [a]
  +
sequence = foldr (liftM2 (:)) (return [])
  +
  +
GHCi> sequence [[1,2],[3,4],[5,6]]
  +
[[1,3,5],[1,3,6],[1,4,5],[1,4,6],[2,3,5],[2,3,6],[2,4,5],[2,4,6]]
  +
</haskell>
  +
:: Execute a list of monadic effects in sequence. By using different monads, you get interesting results! In the list monad for example, <hask>sequence</hask> computes the cartesian product of lists.
   
 
== Vins ==
 
== Vins ==
  +
* <haskell>
*
 
<haskell>
 
 
apfelmus 2007
 
apfelmus 2007
 
</haskell>
 
</haskell>
::Wait, that's the author! Hiccup!
+
::Wait, that's the author! ''Hiccup!''

Latest revision as of 23:56, 25 June 2021


New to Haskell? This menu will give you a first impression. Don't read all the explanations, or you'll be starved before the meal!

Apéritifs

Foretaste of an excellent meal:

  •   qsort :: Ord a => [a] -> [a]
      qsort []     = []
      qsort (x:xs) = qsort (filter (<x) xs) ++ [x] ++ qsort (filter (>=x) xs))
    
Quicksort in three lines (!). Sorts not only integers but anything that can be compared. But granted, it's not in-place.
  •   fibs = 1:1:zipWith (+) fibs (tail fibs)
    
The infinite list of fibonacci numbers. Just don't try to print all of it.
  •   linecount = interact $ show . length . lines
      wordcount = interact $ show . length . words
    
Count the number of lines or words from standard input.

Entrées

How to read the dishes:

  •   square x = x*x
    
is the function which maps a number to its square. While we commonly write parentheses around function arguments in mathematics and most programming languages, a simple space is enough in Haskell. We're going to apply functions to arguments all around, so why clutter the notation with unnecessary ballast?
  •   square :: Int -> Int
      square x = x*x
    
Squaring again, this time with a type signature which says that squaring maps integers to integers. In mathematics, we'd write . Every expression in Haskell has a type and the compiler will automatically infer (= figure out) one for you if you're too lazy to write down a type signature yourself. Of course, parenthesis are allowed for grouping, like in square (4+2) which is 36 compared to square 4 + 2 which is 16+2=18.
  •   square :: Num a => a -> a
      square x = x*x
    
Squaring yet again, this time with a more general type signature. After all, we can square anything (a) that looks like a number (Num a). By the way, this general type is the one that the compiler will infer for square if you omit an explicit signature.
  •   average x y = (x+y)/2
    
The average of two numbers. Multiple arguments are separated by spaces.
  •   average :: Double -> Double -> Double
      average x y = (x+y)/2
    
Average again, this time with a type signature. Looks a bit strange, but that's the spicey currying. In fact, average is a function that takes only one argument (Double) but returns a function with one argument (Double -> Double).
  •   power a n = if n == 0 then 1 else a * power a (n-1)
    
, defined with recursion. Assumes that the exponent n is not negative, that is n >= 0.
Recursion is the basic building block for iteration in Haskell, there are no for or while-loops. Well, there are functions like map or foldr that provide something similar. There is no need for special built-in control structures, you can define them yourself as ordinary functions (later).
  •   power a 0 = 1
      power a n = a * power a (n-1)
    
Exponentiation again, this time with pattern matching. The first equation that matches will be chosen.
  •   length []     = 0
      length (x:xs) = 1 + length xs
    
Calculate the length of a list. What's a list? Well, a list may either be empty ([]) or be an element (x) prepended (:) to another list (xs). Read "xs" as the plural of "x", that is as "ex-es". It's a list of other such elements x, after all.
  •   length :: [a] -> Int
      length []     = 0
      length (x:xs) = 1 + length xs
    
Length of a list again, this time with type signature. [a] is the type of lists with elements of type a. length can be used for any such element type.
  •   head :: [a] -> a
      head (x:xs) = x
    
First element of a list. Undefined for empty lists.
  •   sum []     = 0
      sum (x:xs) = x + sum xs
    
Sum all elements of a list.
  •   average xs = sum xs / (fromIntegral (length xs))
    
Arithmetic mean. fromIntegral converts the integer result of length into a decimal number for the division /.
  •   (++) :: [a] -> [a] -> [a]
      (++) []     ys = ys
      (++) (x:xs) ys = x:(xs ++ ys)
    
Concatenate two lists. Custom infix operators can be defined freely.

Soupes

The best soup is made by combining the available ingredients:

  •   (.) :: (b -> c) -> (a -> b) -> (a -> c)
      (.) f g x = f (g x)
    
      fourthPower = square . square
    
The dot f . g is good old function composition . First apply g, then apply f. Simple example: squaring something twice.
  •   minimum = head . qsort
    
To find the least element of a list, first sort and then take the first element. You think that takes too much time ( instead of )? Well, thanks to lazy evaluation, it doesn't! In Haskell, expressions are evaluated only as much as needed. Therefore, the sorting won't proceed further than producing the first element of the sorted list. Ok, the sorting function has to play along and produce that one quickly, but many like quicksort (in the average case) or mergesort do so.
  •   sum     = foldr (+) 0
      product = foldr (*) 1
      concat  = foldr (++) []
    
Tired of implementing a recursive function every time you're traversing a list? No need for that, fold captures the recursion, you just tell it how to combine the list elements. It can be defined as:
  foldr f z []     = z
  foldr f z (x:xs) = x `f` foldr f z xs

Plats principaux

Desserts

Sugar-sweet and en passant:

  •   sequence :: Monad m => [m a] -> m [a]
      sequence = foldr (liftM2 (:)) (return [])
    
      GHCi> sequence [[1,2],[3,4],[5,6]]
      [[1,3,5],[1,3,6],[1,4,5],[1,4,6],[2,3,5],[2,3,6],[2,4,5],[2,4,6]]
    
Execute a list of monadic effects in sequence. By using different monads, you get interesting results! In the list monad for example, sequence computes the cartesian product of lists.

Vins

  •   apfelmus 2007
    
Wait, that's the author! Hiccup!