Cookbook: Difference between revisions
(A few more examples, plug hsSDL) |
JohnHamilton (talk | contribs) mNo edit summary |
||
Line 274: | Line 274: | ||
=== Map === | === Map === | ||
A naive implementation of a map would be using a list of | 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 [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html Data.Map] we can construct a fast map using this data-structure: | Using [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html Data.Map] we can construct a fast map using this data-structure: |
Revision as of 06:14, 6 March 2007
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 GOOD (aka, not a PLEAC clone) Haskell cookbook.
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
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
Input
Strings can be read as input using getLine.
Prelude> getLine
Foo bar baz
"Foo bar baz"
Output
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"
Concatenation
Concatenation of strings (or any other list) is done with the `++' operator.
Prelude> "foo" ++ "bar"
"foobar"
Regular expressions
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.
Interpolation
Performance
For high performance requirements (where you would typically consider C), consider using Data.ByteString.
Unicode (?)
Numbers
Numbers in Haskell can be of the type Int, Integer, Float, Double, or Rational
.
Random numbers
main = do
gen <- getStdGen
ns <- randoms gen
print $ take 10 ns
Dates and time
Use System.Time.getClockTime to get a properly formatted date stamp.
Prelude> System.Time.getClockTime
Wed Feb 21 20:05:35 CST 2007
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
.
Prelude> head [1,2,3]
1
Prelude> tail [1,2,3]
[2,3]
Prelude> length [1,2,3]
3
Prelude> init [1,2,3]
[1,2]
Prelude> 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..]]
Pattern matching
Haskell does implicit pattern matching.
A good example of pattern matching is done in the fact function for finding a factorial.
fact :: Integer -> Integer
fact 0 = 1
fact n = n * fact (n - 1)
In this function, fact :: Integer -> Integer
is the functions type definition.
The next line, fact 0 = 1
is a pattern match, so when the argument to the function fact is 0, the return value is 1.
The 3rd and final line of this function is another pattern match, which says that, whatever number was entered as the argument, is multiplied by the factorial of that number, minus 1. Notice this function is recursive.
Pattern matching in Haskell evaluates the patterns in the order they are written, so fact 0 = 1
is evaluated before fact n = n * fact (n - 1)
.
Files
Simple IO
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]
Reading from files
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 files
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
.
Logging to a file
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 myMap "bob"
Map is often imported qualified
to avoid name-clashing with the Prelude. See Import for more information.
Set
Tree
ByteString
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 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
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
MySQL
PostgreSQL
SQLite
Graphical user interfaces
SDL
There are some Haskell bindings to [SDL] at [1].