Learn Haskell in 10 minutes

From HaskellWiki
Revision as of 14:37, 13 July 2007 by Cdsmith (talk | contribs)
Jump to navigation Jump to search

Overview

Haskell is a functional (that is, everything is done with function calls), statically, implicitly typed (types are checked by the compiler, but you don't have to declare them), lazy (nothing is done until it needs to be) language. It's closest popular relative is probably the ML family of languages.

The most common Haskell compiler is GHC. You can download GHC from http://www.haskell.org/ghc/download_ghc_661.html. GHC binaries are available for Linux, FreeBSD, MacOS, Windows, and Solaris. Once you've installed GHC, you get two programs you're interested in right now: ghc, and ghci. The first compiles Haskell libraries or applications to binary code. The second is an interpreter that lets you write Haskell code and get feedback right away.

Simple Expressions

You can type most math expressions directly into ghci and get an answer.

 Prelude> 3 * 5
 15
 Prelude> 4 ^ 2 - 1
 15
 Prelude> (1 - 5)^(3 * 2 - 4)
 16

Strings are in "double quotes." You can concatenate them with ++.

 Prelude> "Hello"
 "Hello"
 Prelude> "Hello" ++ ", Haskell"
 "Hello, Haskell"

Calling functions is done by putting the arguments directly after the function. There are no parentheses as part of the function call:

 Prelude> succ 5
 6
 Prelude> truncate 6.59
 6
 Prelude> round 6.59
 7
 Prelude> sqrt 2
 1.4142135623730951
 Prelude> not (5 < 3)
 True
 Prelude> gcd 21 14
 7

The Console

I/O actions can be used to read from and write to the console. Some common ones include:

 Prelude> putStrLn "Hello, Haskell"
 Hello, Haskell
 Prelude> putStr "No newline"
 No newlinePrelude> print (5 + 4)
 9
 Prelude> print (1 < 2)
 True

The putStr and putStrLn functions output strings. The print function outputs any type of value. (If you print a string, it will have quotes around it.)

If you need multiple I/O actions in one expression, you can use a do block. Actions are separated by semicolons.

 Prelude> do { putStr "2 + 2 = " ; print (2 + 2) }
 2 + 2 = 4
 Prelude> do { putStrLn "ABCDE" ; putStrLn "12345" }
 ABCDE
 12345

Reading can be done with getLine (which gives back a String) or readLn (which gives back whatever type of value you want). The <- symbol is used to assign a value to the result of an I/O action.

 Prelude> do { n <- readLn ; print (n^2) }
 4
 16

(The 4 was input. The 16 was a result.)

There is actually another way to write do blocks. If you leave off the braces and semicolons, then indentation becomes significant. This doesn't work so well in ghci, but try putting the file in a source file (say, Test.hs) and build it.

main = do putStrLn "What is 2 + 2?"
          x <- readLn
          if x == 4
              then putStrLn "You're right!"
              else putStrLn "You're wrong!"

You can build with ghc --make Test.hs, and the result will be called Test. (On Windows, Test.exe) You get an if statement as a bonus.

Every line that starts in the same column as the first putStrLn is part of the do block. This is called "layout", and Haskell uses it to avoid making you put in statement terminators and braces all the time. (The then and else phrases have to be indented for this reason: if they started in the same column, they'd be separate statements, which is wrong.)

(Note: Do not indent with tabs if you're using layout. It technically still works if your tabs are 8 spaces, but it's a bad idea.)

Simple Types

So far, not a single type declaration has been mentioned. That's because Haskell does type inference. You generally don't have to declare types unless you want to. If you do want to declare types, you use :: to do it.

 Prelude> 5 :: Int
 5
 Prelude> 5 :: Double
 5.0

You can also ask ghci what type it has chosen for something. This is useful because you don't generally have to declare your types.

 Prelude> :t True
 True :: Bool
 Prelude> :t 'X'
 'X' :: Char
 Prelude> :t "Hello, Haskell"
 "Hello, Haskell" :: [Char]

(In case you noticed, [Char] is another way of saying String. See the section on lists later.)

Things get more interesting for numbers.

 Prelude> :t 42
 42 :: (Num t) => t
 Prelude> :t 42.0
 42.0 :: (Fractional t) => t
 Prelude> :t gcd 15 20
 gcd 15 20 :: (Integral t) => t

These types use "type classes." They mean:

  • 42 can be used as any numeric type. (This is why I was able to declare 5<hask> as either an Int or a Double earlier.) * <hask>42.0 can be any fractional type, but not an integral type.
  • gcd 15 20 (which is a function call, incidentally) can be any integral type, but not a fractional type.

There are five numeric types in the Haskell "prelude" (the part of the library you get without having to import anything):

  • Int is an integer with at least 30 bits of precision.
  • Integer is an integer with unlimited precision.
  • Float is a single precision floating point number.
  • Double is a double precision floating point number.
  • Rational is a fraction type, with no rounding error.

All five are instances of the Num type class. The first two are instances of Integral, and the last two are instances of Fractional.

Putting it all together,

 Prelude> gcd 42 35 :: Int
 7
 Prelude> gcd 42 35 :: Double
 
 <interactive>:1:0:
     No instance for (Integral Double)

The final type worth mentioning here is (), pronounced "unit." It only has one value, also written as () and pronounced "unit."

 Prelude> ()
 ()
 Prelude> :t ()
 () :: ()

You can think of this as similar to the void keyword in C family languages. You can return () from a function or I/O action if you don't want to return anything.

Structured Data

Basic data types can be easily combined in two ways: lists, which go in [square brackets], and tuples, which go in (parentheses).

Lists are used to hold multiple values of the same type.

 Prelude> [1, 2, 3]
 [1,2,3]
 Prelude> [1 .. 5]
 [1,2,3,4,5]
 Prelude> [1, 3 .. 10]
 [1,3,5,7,9]
 Prelude> [True, False, True]
 [True,False,True]

Strings are just lists of characters.

 Prelude> ['H', 'e', 'l', 'l', 'o']
 "Hello"

The : operator appends an item to the beginning of a list. (It is Haskell's version of LISP's cons).

 Prelude> 'C' : ['H', 'e', 'l', 'l', 'o']
 "CHello"

Tuples hold a fixed number of values, which can have different types.

 Prelude> (1, True)
 (1,True)
 Prelude> zip [1 .. 5] ['a' .. 'e']
 [(1,'a'),(2,'b'),(3,'c'),(4,'d'),(5,'e')]

The last example used zip, a library function that turns two lists into a list of tuples.

The types are probably what you'd expect.

 Prelude> :t ['a' .. 'c']
 ['a' .. 'c'] :: [Char]
 Prelude> :t [('x', True), ('y', False)]
 [('x', True), ('y', False)] :: [(Char, Bool)]

Lists are used a lot in Haskell. There are several functions that do nice things with them.

 Prelude> [1 .. 5]
 [1,2,3,4,5]
 Prelude> map (+ 2) [1 .. 5]
 [3,4,5,6,7]
 Prelude> filter (> 2) [1 .. 5]
 [3,4,5]

TODO: Can't think of a good way to describe fold

There are two nice functions on ordered pairs (tuples of two elements):

 Prelude> fst (1, 2)
 1
 Prelude> snd (1, 2)
 2
 Prelude> map fst [(1, 2), (3, 4), (5, 6)]
 [1,3,5]

Function Definitions

We wrote a function earlier, called main:

main = do putStrLn "What is 2 + 2?"
          x <- readLn
          if x == 4
              then putStrLn "You're right!"
              else putStrLn "You're wrong!"

Let's write another, and call it factorial. I'm also adding a module header, which is good form.

module Main where

factorial n = if n == 0 then 1 else n * factorial (n - 1)

main = do putStrLn "What is 5! ?"
          x <- readLn
          if x == factorial 5
              then putStrLn "You're right!"
              else putStrLn "You're wrong!"

Build again with ghc --make Test.hs. And,

 $ ./Test
 What is 5! ?
 120
 You're right!

There's a function. Just like the built-in functions, it can be called as factorial 5 without needing parentheses.

Now ask ghci for the type.

 $ ghci Test.hs
 << GHCi banner >>
 Ok, modules loaded: Main.
 Prelude Main> :t factorial
 factorial :: (Num a) => a -> a

Function types are written with the argument type, a ->, and the result type. (This also has the type class Num.)

Factorial can be simplified by writing it with case analysis.

factorial 0 = 1
factorial n = n * factorial (n - 1)

Syntax

Let

If/Then/Else

Case

Using Library Stuff

Packages and Modules

Importing

Standard Library Haddock

Installing Stuff with Cabal

Advanced Data Types

Arithmetic Lists

List Comprehensions

Type Synonyms

Data vs Newtype

Type Classes and Instances

Advanced Syntax

Operators

(+) and `foo`

Fixity Declarations

Advanced Functions

Currying

Lambdas

Sections

Monads

File I/O

Reading files

Writing Files