Cookbook

From HaskellWiki
Revision as of 14:44, 22 April 2009 by Lenny222 (talk | contribs) (→‎FFI)
Jump to navigation Jump to search

This article is a draft, with further revisions actively invited. Drafts are typically different than stubs in that these articles are in an active edit process. Feel free to help by expanding the article.

We need to start a Haskell centered cookbook (aka, not a PLEAC clone)

This page is based on the Scheme Cookbook at http://schemecookbook.org/Cookbook/WebHome

Prelude

A lot of functions are defined in the "Prelude". Also, if you ever want to search for a function, based on the name, type or module, take a look at the excellent Hoogle. This is for a lot of people a must-have while debugging and writing Haskell programs.

GHCi/Hugs

GHCi interaction

To start GHCi from a command prompt, simply type `ghci'

   $ ghci
      ___         ___ _
     / _ \ /\  /\/ __(_)
    / /_\// /_/ / /  | |      GHC Interactive, version 6.6, for Haskell 98.
   / /_\\/ __  / /___| |      http://www.haskell.org/ghc/
   \____/\/ /_/\____/|_|      Type :? for help.
   
   Loading package base ... linking ... done.
   Prelude>

Prelude is the "base" library of Haskell.

To create variables at the GHCi prompt, use `let'

Prelude> let x = 5
Prelude> x
5
Prelude> let y = 3
Prelude> y
3
Prelude> x + y
8

`let' is also the way to create simple functions at the GHCi prompt

Prelude> let fact n = product [1..n]
Prelude> fact 5
120


Checking Types

To check the type of an expression or function, use the command `:t'

Prelude> :t x
x :: Integer
Prelude> :t "Hello"
"Hello" :: [Char]

Haskell has the following types defined in the Standard Prelude.

    Int         -- bounded, word-sized integers
    Integer     -- unbounded integers
    Double      -- floating point values
    Char        -- characters
    String      -- equivalent to [Char], strings are lists of characters
    ()          -- the unit type
    Bool        -- booleans
    [a]         -- lists
    (a,b)       -- tuples / product types
    Either a b  -- sum types
    Maybe a     -- optional values

Strings

Since strings are lists of characters, you can use any available list function.

Combining strings

Problem Solution Examples
combining two strings (++)
"foo" ++ "bar"                  --> "foobar"
combining many strings concat
concat ["foo", "bar", "baz"]    --> "foobarbaz"

Accessing substrings

Problem Solution Examples
accessing the first character head
head "foo bar baz"      --> 'f'
accessing the last character last
last "foo bar baz"      --> 'z'
accessing the character at a given index (!!)
"foo bar baz" !! 4      --> 'b'
accessing the first n characters take
take 3 "foo bar baz"    --> "foo"
accessing the last n characters TODO TODO
accessing the n characters starting from index m drop, take
take 4 $ drop 2 "foo bar baz"    --> "o ba"

Splitting strings

Problem Solution Examples
splitting a string into a list of words words
words "foo bar\t baz\n"        --> ["foo","bar","baz"]
splitting a string into two parts splitAt
splitAt 3 "foo bar baz"    --> ("foo"," bar baz")

Multiline strings

"foo\
\bar"               --> "foobar"

Converting between characters and values

Problem Solution Examples
converting a character to a numeric value ord
import Char
ord 'A'    --> 65
converting a numeric value to a character chr
import Char
chr 99     --> 'c'

Reversing a string by words or characters

Problem Solution Examples
reversing a string by characters reverse
reverse "foo bar baz"                        --> "zab rab oof"
reversing a string by words words, reverse, unwords
unwords $ reverse $ words "foo bar baz"      --> "baz bar foo"
reversing a string by characters by words words, reverse, map, unwords
unwords $ map reverse $ words "foo bar baz"  --> "oof rab zab"

Converting case

Problem Solution Examples
converting a character to upper-case toUpper
import Char
toUpper 'a'            --> "A"
converting a string to upper-case toUpper, map
import Char
map toUpper "Foo Bar"  --> "FOO BAR"
converting a character to lower-case toLower
import Char
toLower 'A'            --> "a"
converting a string to lower-case toLower, map
import Char
map toLower "Foo Bar"  --> "foo bar"

Interpolation

TODO

Performance

For high performance requirements (where you would typically consider C), consider using Data.ByteString.

Unicode

TODO

Numbers

Numbers in Haskell can be of the type Int, Integer, Float, Double, or Rational.

Rounding numbers

Problem Solution Examples
rounding round
round 3.4      --> 3
round 3.5      --> 4
getting the least number not less than x ceiling
ceiling 3.1    --> 4
getting the greatest number not greater than x floor
floor 3.5      --> 3

Taking logarithms

log 2.718281828459045  --> 1.0
logBase 10 10000       --> 4.0

Generating random numbers

import System.Random

main = do
  gen <- getStdGen
  let ns = randoms gen :: [Int]
  print $ take 10 ns

Binary representation of numbers

import Data.Bits
import Data.List (foldl')

-- Extract a range of bits, most-significant first
bitRange :: Bits a => a -> Int -> Int -> [Bool]
bitRange n lo hi = foldl' (\l -> \x -> testBit n x : l) [] [lo..hi]

-- Extract all bits, most-significant first
bits :: Bits a => a -> [Bool]
bits n = bitRange n 0 (bitSize n - 1)

-- Display a number in binary, including leading zeroes.
-- c.f. Numeric.showHex
showBits :: Bits a => a -> ShowS
showBits = showString . map (\b -> if b then '1' else '0') . bits

Using complex numbers

Problem Solution Examples
creating a complex number from real and imaginary rectangular components (:+)
import Complex
1.0 :+ 0.0        --> 1.0 :+ 0.0
creating a complex number from polar components mkPolar
import Complex
mkPolar 1.0 pi    --> (-1.0) :+ 1.2246063538223773e-16

Dates and time

Finding today's date

import Data.Time

c <- getCurrentTime                  --> 2009-04-21 14:25:29.5585588 UTC 
(y,m,d) = toGregorian $ utctDay c    --> (2009,4,21)

Adding to or subtracting from a date

Problem Solution Examples
adding days to a date addDays
import Date.Time
a = fromGregorian 2009 12 31    --> 2009-12-31
b = addDays 1 a                 --> 2010-01-01
subtracting days from a date addDays
import Date.Time
a = fromGregorian 2009 12 31    --> 2009-12-31
b = addDays (-7) a              --> 2009-12-24

Difference of two dates

Problem Solution Examples
calculating the difference of two dates diffDays
import Date.Time
a = fromGregorian 2009 12 31    --> 2009-12-31
b = fromGregorian 2010 12 32    --> 2010-12-31
diffDays b a                    --> 365

CPU time

Use System.CPUTime.getCPUTime to get the CPU time in picoseconds.

You can time a computation like this

getCPUTimeDouble :: IO Double
getCPUTimeDouble = do t <- System.CPUTime.getCPUTime; return ((fromInteger t) * 1e-12)

main = do
    t1 <- getCPUTimeDouble
    print (fib 30)
    t2 <- getCPUTimeDouble
    print (t2-t1)

Lists

In Haskell, lists are what Arrays are in most other languages. Haskell has all of the general list manipulation functions, see also Data.List.

head [1,2,3]      --> 1
tail [1,2,3]      --> [2,3]
length [1,2,3]    --> 3
init [1,2,3]      --> [1,2]
last [1,2,3]      --> 3

Furthermore, Haskell supports some neat concepts.

Infinite lists

Prelude> [1..]

The list of all squares:

square x = x*x
squares = map square [1..]

But in the end, you probably don't want to use infinite lists, but make them finite. You can do this with take:

Prelude> take 10 squares
[1,4,9,16,25,36,49,64,81,100]

List comprehensions

The list of all squares can also be written in a more comprehensive way, using list comprehensions:

squares = [x*x | x <- [1..]]

List comprehensions allow for constraints as well:

-- multiples of 3 or 5
mults = [ x | x <- [1..], mod x 3 == 0 || mod x 5 == 0 ]

Other data structures

GHC comes with some handy data-structures by default. If you want to use a Map, use Data.Map. For sets, you can use Data.Set. A good way to find efficient data-structures is to take a look at the hierarchical libraries, see Haskell Hierarchical Libraries and scroll down to 'Data'.

Map

A naive implementation of a map would be using a list of tuples in the form of (key, value). This is used a lot, but has the big disadvantage that most operations take O(n) time.

Using Data.Map we can construct a fast map using this data-structure:

import qualified Data.Map as Map

myMap :: Map.Map String Int
myMap = Map.fromList [("alice", 111), ("bob", 333), ("douglas", 42)]

We can then do quick lookups:

bobsPhone :: Maybe Int
bobsPhone = Map.lookup "bob" myMap

Map is often imported qualified to avoid name-clashing with the Prelude. See Import for more information.

Set

TODO

Tree

TODO

ByteString

TODO

Arrays

Arrays are generally eschewed in Haskell. However, they are useful if you desperately need constant lookup or update or if you have huge amounts of raw data.

Immutable arrays like Data.Array.IArray.Array i e offer lookup in constant time but they get copied when you update an element. Use them if they can be filled in one go. The following example groups a list of numbers according to their residual after division by n in one go.

bucketByResidual :: Int -> [Int] -> Array Int [Int]
bucketByResidual n xs = accumArray (\xs x -> x:xs) [] (0,n-1) [(x `mod` n, x) | x <- xs]

Data.Arra.IArray> bucketByResidual 4 [x*x | x <- [1..10]]
array (0,3) [(0,[100,64,36,16,4]),(1,[81,49,25,9,1]),(2,[]),(3,[])]

Data.Arra.IArray> amap reverse it
array (0,3) [(0,[4,16,36,64,100]),(1,[1,9,25,49,81]),(2,[]),(3,[])]

Note that the array can fill itself up in a circular fashion. Useful for dynamic programming. Here is the Edit distance between two strings without array updates.

editDistance :: Eq a => [a] -> [a] -> Int
editDistance xs ys = table ! (m,n)
    where
    (m,n) = (length xs, length ys)
    x     = array (1,m) (zip [1..] xs)
    y     = array (1,n) (zip [1..] ys)
    
    table :: Array (Int,Int) Int
    table = array bnds [(ij, dist ij) | ij <- range bnds]
    bnds  = ((0,0),(m,n))
    
    dist (0,j) = j
    dist (i,0) = i
    dist (i,j) = minimum [table ! (i-1,j) + 1, table ! (i,j-1) + 1,
        if x ! i == y ! j then table ! (i-1,j-1) else 1 + table ! (i-1,j-1)]


Mutable arrays like Data.Array.IO.IOArray i e are updated in place, but they have to live in the IO-monad or the ST-monad in order to not destroy referential transparency. There are also diff arrays like Data.Array.Diff.DiffArray i e that look like immutable arrays but do updates in place if used in a single threaded way. Here is depth first search with diff arrays that checks whether a directed graph contains a cycle. Note: this example really belongs to Map or Set.

import Control.Monad.State
type Node  = Int
data Color = White | Grey | Black 

hasCycle :: Array Node [Node] -> Bool
hasCycle graph = runState (mapDfs $ indices g) initSeen
    where
    initSeen :: DiffArray Node Color
    initSeen  = listArray (bounds graph) (repeat White)
    mapDfs    = fmap or . mapM dfs
    dfs node  = get >>= \seen -> case (seen ! node) of
        Black -> return False
        Grey  -> return True  -- we found a cycle
        White -> do
            modify $  \seen -> seen // [(node,Grey )]
            found  <- mapDfs (graph ! node)
            modify $  \seen -> seen // [(node,Black)]
            return found

Pattern matching

Regular expressions are useful in some situations where the Data.List library is unwieldy. Posix style regular expressions are available in the core libraries, and a suite of other regular expression libraries are [also available], including PCRE and TRE-style regexes.

Bryan O'Sullivan has written a nice introduction to using the new regex libraries.

Interactivity

Reading a string

Strings can be read as input using getLine.

Prelude> getLine
Foo bar baz
"Foo bar baz"

Printing a string

Strings can be output in a number of different ways.

Prelude> putStr "Foo"
FooPrelude>

As you can see, putStr does not include the newline character `\n'. We can either use putStr like this:

Prelude> putStr "Foo\n"
Foo

Or use putStrLn, which is already in the Standard Prelude

Prelude> putStrLn "Foo"
Foo

We can also use print to print a string, including the quotation marks.

Prelude> print "Foo"
"Foo"

Parsing command line arguments

TODO

Files

Reading from a file

The System.IO library contains the functions needed for file IO. The program below displays the contents of the file c:\test.txt.

import System.IO

main = do
  h <- openFile "c:\\test.txt" ReadMode
  contents <- hGetContents h
  putStrLn contents
  hClose h

The same program, with some higher-lever functions:

main = do
  contents <- readFile "c:\\test.txt"
  putStrLn contents

Writing to a file

The following program writes the first 100 squares to a file:

-- generate a list of squares with length 'num' in string-format.
numbers num = unlines $ take num $ map (show . \x -> x*x) [1..]

main = do
  writeFile "test.txt" (numbers 100)
  putStrLn "successfully written"

This will override the old contents of the file, or create a new file if the file doesn't exist yet. If you want to append to a file, you can use appendFile.

Creating a temporary file

TODO

Writing a filter

Using interact :: (String -> String) -> IO (), you can easily do things with stdin and stdout.

A program to sum up numbers:

main = interact $ show . sum . map read . lines

A program that adds line numbers to each line:

main = interact numberLines
numberLines = unlines . zipWith combine [1..] . lines
 where combine lineNumber text = concat [show lineNumber, " ", text]


Logging to a file

Network programming

The following example makes use of the Network and System.IO libraries to open a socket connection to Google and retrieve the Google home page.

    import Network;
    import System.IO;
	
    main = withSocketsDo $ do
	h <- connectTo "www.google.com" (PortNumber 80)
	hSetBuffering h LineBuffering
	hPutStr h "GET / HTTP/1.1\nhost: www.google.com\n\n"
	contents <- hGetContents h
	putStrLn contents
	hClose h

XML

Libraries

There are multiple libraries available. In my own (limited) experience, I could only get HXT to do everything I wanted. It does make heavy use of [Arrows].

Parsing XML

Databases access

There are two packages you can use to connect to MySQL, PostgreSQL, Sqlite3 and ODBC databases: HDBC and Hsql

MySQL

TODO

PostgreSQL

TODO

SQLite

Suppose you have created a 'test.db' database like this,

$ sqlite3 test.db "create table t1 (t1key INTEGER PRIMARY KEY,data TEXT,num double,timeEnter DATE);"

$ sqlite3 test.db "insert into t1 (data,num) values ('This is sample data',3);"

$ sqlite3 test.db "insert into t1 (data,num) values ('More sample data',6);"

$ sqlite3 test.db "insert into t1 (data,num) values ('And a little more',9);"

Using HDBC and HDBC-sqlite3 packages, you can connect and query it like this:

import Control.Monad
import Database.HDBC
import Database.HDBC.Sqlite3

main = do conn <- connectSqlite3 "test.db"
          rows <- quickQuery' conn "SELECT * from t1" []
          forM_ rows $ \row -> putStrLn $ show row


$ ghc --make sqlite.hs

$ ./sqlite

output:

[SqlString "1",SqlString "This is sample data",SqlString "3.0",SqlNull]

[SqlString "2",SqlString "More sample data",SqlString "6.0",SqlNull]

[SqlString "3",SqlString "And a little more",SqlString "9.0",SqlNull]

Graphical user interfaces

wxHaskell

WxHaskell is a portable and native GUI library for Haskell based on the wxWidgets Library.

Hello World example:

module Main where
import Graphics.UI.WX

main :: IO ()
main
  = start hello

hello :: IO ()
hello
  = do f    <- frame    [text := "Hello!"]
       quit <- button f [text := "Quit", on command := close f]
       set f [layout := widget quit]

This code was taken from "a quick start with wxHaskell".

Gtk2Hs

Gtk2Hs is a GUI Library for Haskell based on GTK. Gtk2Hs Tutorial.

Hello world example:

import Graphics.UI.Gtk

main :: IO ()
main = do
    initGUI
    w <- windowNew
    b <- buttonNew
    set b [buttonLabel := "Quit"]
    onClicked b $ widgetDestroy w
    set w [windowTitle := "Hello", containerBorderWidth := 10]
    containerAdd w b
    onDestroy w mainQuit
    widgetShowAll w
    mainGUI

For more examples, see: Applications and libraries/Games

HOpenGL

[HOpenGL] is a Haskell binding for the OpenGL graphics API (GL 1.2.1 / GLU 1.3) and the portable OpenGL utility toolkit GLUT. There is a Haskell OpenGL Tetris program at [[1]] by Jim.

See also: Applications and libraries/Games

SDL

There are some Haskell bindings to [SDL] at Hackage.


PDF Files

TODO: HPDF

Creating an empty PDF file

TODO

FFI

How to interface with C

Magnus has written a nice example on how to call a C function operating on a user defined type.

Testing

QuickCheck

TODO

HUnit

TODO