Difference between revisions of "Cookbook"

From HaskellWiki
Jump to navigation Jump to search
(Added link to similar F# cookbook)
 
(56 intermediate revisions by one other user not shown)
Line 1: Line 1:
  +
== Haskell Cookbook ==
  +
* [[Cookbook/Compilers and interpreters|Haskell compilers and interpreters]]
  +
* [[Cookbook/Numbers|Numbers]]
  +
* [[Cookbook/Lists and strings|Lists and strings]]
  +
* [[Cookbook/Other data structures|Other data structures]]
  +
* [[Cookbook/Dates And Time|Dates and time]]
  +
* [[Cookbook/Pattern matching|Pattern matching]]
  +
* [[Cookbook/Interactivity|Interactivity]]
  +
* [[Cookbook/Files|Files]]
  +
* [[Cookbook/Network programming|Network programming]]
  +
* [[Cookbook/XML|XML]]
  +
* [[Cookbook/Databases access|Databases access]]
  +
* [[Cookbook/Graphical user interfaces|Graphical user interfaces]]
  +
* [[Cookbook/PDF files|PDF files]]
  +
* [[Cookbook/FFI|FFI]]
  +
* [[Cookbook/Testing|Testing]]
  +
  +
== Similar projects for other programming languages ==
  +
* [http://cl-cookbook.sourceforge.net/ Common Lisp Cookbook]
  +
* [http://pleac.sourceforge.net/ PLEAC]
  +
* [http://www.zenspider.com/Languages/Ruby/Cookbook/index.html Ruby Cookbook]
  +
* [http://schemecookbook.org/Cookbook/WebHome Scheme Cookbook]
  +
* [http://fssnip.net/ F# Snippets]
  +
[[Category:FAQ]]
 
[[Category:How to]]
 
[[Category:How to]]
{{Template:Anonymousdraft}}
 
 
'''We need to start a Haskell centered cookbook (aka, not a [http://pleac.sourceforge.net/ 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 "[http://www.haskell.org/hoogle/?q=Prelude Prelude]". Also, if you ever want to search for a function, based on the name, type or module, take a look at the excellent [http://www.haskell.org/hoogle/ 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>
 
 
[http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html Prelude] is the "base" library of Haskell.
 
 
To create variables at the GHCi prompt, use `let'
 
<haskell>
 
Prelude> let x = 5
 
Prelude> x
 
5
 
Prelude> let y = 3
 
Prelude> y
 
3
 
Prelude> x + y
 
8
 
</haskell>
 
 
`let' is also the way to create simple functions at the GHCi prompt
 
<haskell>
 
Prelude> let fact n = product [1..n]
 
Prelude> fact 5
 
120
 
</haskell>
 
 
 
=== Checking Types ===
 
To check the type of an expression or function, use the command `:t'
 
<haskell>
 
Prelude> :t x
 
x :: Integer
 
Prelude> :t "Hello"
 
"Hello" :: [Char]
 
</haskell>
 
Haskell has the following types defined in the [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html Standard Prelude].
 
<haskell>
 
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
 
</haskell>
 
 
== Strings ==
 
 
Since strings are lists of characters, you can use any available list function.
 
 
=== Combining strings ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| combining two strings
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3A%2B%2B (++)]
 
|<haskell>
 
"foo" ++ "bar" --> "foobar"
 
</haskell>
 
|-
 
| combining many strings
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:concat concat]
 
| <haskell>
 
concat ["foo", "bar", "baz"] --> "foobarbaz"
 
</haskell>
 
|}
 
 
=== Accessing substrings ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| accessing the first character
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:head head]
 
|<haskell>
 
head "foo bar baz" --> 'f'
 
</haskell>
 
|-
 
| accessing the last character
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Alast last]
 
|<haskell>
 
last "foo bar baz" --> 'z'
 
</haskell>
 
|-
 
| accessing the character at a given index
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3A!! (!!)]
 
|<haskell>
 
"foo bar baz" !! 4 --> 'b'
 
</haskell>
 
|-
 
| accessing the first <code>n</code> characters
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:take take]
 
| <haskell>
 
take 3 "foo bar baz" --> "foo"
 
</haskell>
 
|-
 
| accessing the last <code>n</code> characters
 
| TODO
 
| TODO
 
|-
 
| accessing the <code>n</code> characters starting from index <code>m</code>
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:drop drop], [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:take take]
 
| <haskell>
 
take 4 $ drop 2 "foo bar baz" --> "o ba"
 
</haskell>
 
|}
 
 
=== Splitting strings ===
 
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| splitting a string into a list of words
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:words words]
 
| <haskell>words "foo bar\t baz\n" --> ["foo","bar","baz"]
 
</haskell>
 
|-
 
| splitting a string into two parts
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3AsplitAt splitAt]
 
| <haskell>splitAt 3 "foo bar baz" --> ("foo"," bar baz")
 
</haskell>
 
|}
 
 
=== Multiline strings ===
 
<haskell>
 
"foo\
 
\bar" --> "foobar"
 
</haskell>
 
 
=== Converting between characters and values ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| converting a character to a numeric value
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Char.html#v:ord ord]
 
|<haskell>
 
import Char
 
ord 'A' --> 65
 
</haskell>
 
|-
 
| converting a numeric value to a character
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Char.html#v%3Achr chr]
 
| <haskell>
 
import Char
 
chr 99 --> 'c'
 
</haskell>
 
|}
 
 
=== Reversing a string by words or characters ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| reversing a string by characters
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:reverse reverse]
 
|<haskell>
 
reverse "foo bar baz" --> "zab rab oof"
 
</haskell>
 
|-
 
| reversing a string by words
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Awords words], [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:reverse reverse], [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Aunwords unwords]
 
| <haskell>
 
unwords $ reverse $ words "foo bar baz" --> "baz bar foo"
 
</haskell>
 
|-
 
| reversing a string by characters by words
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Awords words], [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:reverse reverse], [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map map], [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Aunwords unwords]
 
| <haskell>
 
unwords $ map reverse $ words "foo bar baz" --> "oof rab zab"
 
</haskell>
 
|}
 
 
=== Converting case ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| converting a character to upper-case
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Char.html#v%3AtoUpper toUpper]
 
|<haskell>
 
import Char
 
toUpper 'a' --> "A"
 
</haskell>
 
|-
 
| converting a string to upper-case
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Char.html#v%3AtoUpper toUpper], [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map map]
 
|<haskell>
 
import Char
 
map toUpper "Foo Bar" --> "FOO BAR"
 
</haskell>
 
|-
 
| converting a character to lower-case
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Char.html#v%3AtoLower toLower]
 
| <haskell>
 
import Char
 
toLower 'A' --> "a"
 
</haskell>
 
|-
 
| converting a string to lower-case
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Char.html#v%3AtoLower toLower], [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:map map]
 
| <haskell>
 
import Char
 
map toLower "Foo Bar" --> "foo bar"
 
</haskell>
 
|}
 
 
=== Interpolation ===
 
 
TODO
 
 
=== Performance ===
 
 
For high performance requirements (where you would typically consider
 
C), consider using [http://hackage.haskell.org/packages/archive/bytestring/latest/doc/html/Data-ByteString.html Data.ByteString].
 
 
=== Unicode ===
 
 
TODO
 
 
== Numbers ==
 
Numbers in Haskell can be of the type <hask>Int, Integer, Float, Double, or Rational</hask>.
 
 
=== Rounding numbers ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| rounding
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:round round]
 
|<haskell>
 
round 3.4 --> 3
 
round 3.5 --> 4
 
</haskell>
 
|-
 
| getting the least number not less than <code>x</code>
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Aceiling ceiling]
 
|<haskell>
 
ceiling 3.1 --> 4
 
</haskell>
 
|-
 
| getting the greatest number not greater than <code>x</code>
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Afloor floor]
 
|<haskell>
 
floor 3.5 --> 3
 
</haskell>
 
|}
 
 
=== Taking logarithms ===
 
<haskell>
 
log 2.718281828459045 --> 1.0
 
logBase 10 10000 --> 4.0
 
</haskell>
 
 
=== Generating random numbers ===
 
<haskell>
 
import System.Random
 
 
main = do
 
gen <- getStdGen
 
let ns = randoms gen :: [Int]
 
print $ take 10 ns
 
</haskell>
 
 
=== Binary representation of numbers ===
 
<haskell>
 
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
 
</haskell>
 
 
=== Using complex numbers ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| creating a complex number from real and imaginary rectangular components
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Complex.html#v%3A%3A%2B (:+)]
 
|<haskell>
 
import Complex
 
1.0 :+ 0.0 --> 1.0 :+ 0.0
 
</haskell>
 
|-
 
| creating a complex number from polar components
 
| [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Complex.html#v%3AmkPolar mkPolar]
 
|<haskell>
 
import Complex
 
mkPolar 1.0 pi --> (-1.0) :+ 1.2246063538223773e-16
 
</haskell>
 
|}
 
 
== Dates and time ==
 
 
=== Finding today's date ===
 
 
<haskell>
 
import Data.Time
 
 
c <- getCurrentTime --> 2009-04-21 14:25:29.5585588 UTC
 
(y,m,d) = toGregorian $ utctDay c --> (2009,4,21)
 
</haskell>
 
 
=== Adding to or subtracting from a date ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| adding days to a date
 
| [http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Calendar.html#v%3AaddDays addDays]
 
|<haskell>
 
import Date.Time
 
a = fromGregorian 2009 12 31 --> 2009-12-31
 
b = addDays 1 a --> 2010-01-01
 
</haskell>
 
|-
 
| subtracting days from a date
 
| [http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Calendar.html#v%3AaddDays addDays]
 
|<haskell>
 
import Date.Time
 
a = fromGregorian 2009 12 31 --> 2009-12-31
 
b = addDays (-7) a --> 2009-12-24
 
</haskell>
 
|}
 
 
=== Difference of two dates ===
 
 
{| class="wikitable"
 
|-
 
! Problem
 
! Solution
 
! Examples
 
|-
 
| calculating the difference of two dates
 
| [http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Calendar.html#v%3AdiffDays diffDays]
 
|<haskell>
 
import Date.Time
 
a = fromGregorian 2009 12 31 --> 2009-12-31
 
b = fromGregorian 2010 12 32 --> 2010-12-31
 
diffDays b a --> 365
 
</haskell>
 
|}
 
 
=== CPU time ===
 
Use [http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-CPUTime.html#v%3AgetCPUTime System.CPUTime.getCPUTime] to get the CPU time in picoseconds.
 
 
You can time a computation like this
 
<haskell>
 
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)
 
</haskell>
 
 
== Lists ==
 
In Haskell, lists are what Arrays are in most other languages. Haskell has all of the general list manipulation functions, see also <hask>Data.List</hask>.
 
 
<haskell>
 
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
 
</haskell>
 
 
Furthermore, Haskell supports some neat concepts.
 
 
===Infinite lists===
 
<haskell>
 
Prelude> [1..]
 
</haskell>
 
 
The list of all squares:
 
<haskell>
 
square x = x*x
 
squares = map square [1..]
 
</haskell>
 
 
But in the end, you probably don't want to use infinite lists, but make them finite. You can do this with <hask>take</hask>:
 
 
<haskell>
 
Prelude> take 10 squares
 
[1,4,9,16,25,36,49,64,81,100]
 
</haskell>
 
 
===List comprehensions===
 
 
The list of all squares can also be written in a more comprehensive way, using list comprehensions:
 
 
<haskell>
 
squares = [x*x | x <- [1..]]
 
</haskell>
 
 
List comprehensions allow for constraints as well:
 
 
<haskell>
 
-- multiples of 3 or 5
 
mults = [ x | x <- [1..], mod x 3 == 0 || mod x 5 == 0 ]
 
</haskell>
 
 
== Other data structures ==
 
 
GHC comes with some handy data-structures by default. If you want to use a Map, use [http://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-Map.html 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 [http://haskell.org/ghc/docs/latest/html/libraries/index.html 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 [http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html Data.Map] we can construct a fast map using this data-structure:
 
 
<haskell>
 
import qualified Data.Map as Map
 
 
myMap :: Map.Map String Int
 
myMap = Map.fromList [("alice", 111), ("bob", 333), ("douglas", 42)]
 
</haskell>
 
 
We can then do quick lookups:
 
<haskell>
 
bobsPhone :: Maybe Int
 
bobsPhone = Map.lookup "bob" myMap
 
</haskell>
 
 
Map is often imported <hask>qualified</hask> 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.
 
 
[http://hackage.haskell.org/packages/archive/array/latest/doc/html/Data-Array-IArray.html Immutable arrays] like <hask>Data.Array.IArray.Array i e</hask> 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 <hask>n</hask> in one go.
 
<haskell>
 
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,[])]
 
</haskell>
 
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.
 
<haskell>
 
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)]
 
</haskell>
 
 
 
[http://hackage.haskell.org/packages/archive/array/latest/doc/html/Data-Array-MArray.html Mutable arrays] like <hask>Data.Array.IO.IOArray i e</hask> 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 [http://hackage.haskell.org/packages/archive/array/latest/doc/html/Data-Array-Diff.html diff arrays] like <hask>Data.Array.Diff.DiffArray i e</hask> 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.''
 
<haskell>
 
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
 
</haskell>
 
 
== 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 [http://www.serpentine.com/blog/2007/02/27/a-haskell-regular-expression-tutorial/ a nice introduction] to using the new regex libraries.
 
 
== Interactivity ==
 
 
=== Reading a string ===
 
Strings can be read as input using [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3AgetLine getLine].
 
<haskell>
 
Prelude> getLine
 
Foo bar baz
 
"Foo bar baz"
 
</haskell>
 
 
=== Printing a string ===
 
Strings can be output in a number of different ways.
 
<haskell>
 
Prelude> putStr "Foo"
 
FooPrelude>
 
</haskell>
 
As you can see, [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3AputStr putStr] does not include the newline character `\n'. We can either use putStr like this:
 
<haskell>
 
Prelude> putStr "Foo\n"
 
Foo
 
</haskell>
 
Or use [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3AputStrLn putStrLn], which is already in the Standard Prelude
 
<haskell>
 
Prelude> putStrLn "Foo"
 
Foo
 
</haskell>
 
We can also use [http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Aprint print] to print a string, '''including the quotation marks.'''
 
<haskell>
 
Prelude> print "Foo"
 
"Foo"
 
</haskell>
 
 
=== 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.
 
 
<haskell>
 
import System.IO
 
 
main = do
 
h <- openFile "c:\\test.txt" ReadMode
 
contents <- hGetContents h
 
putStrLn contents
 
hClose h
 
</haskell>
 
 
The same program, with some higher-lever functions:
 
 
<haskell>
 
main = do
 
contents <- readFile "c:\\test.txt"
 
putStrLn contents
 
</haskell>
 
 
=== Writing to a file ===
 
 
The following program writes the first 100 squares to a file:
 
<haskell>
 
-- 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"
 
</haskell>
 
 
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 <hask>appendFile</hask>.
 
 
=== Creating a temporary file ===
 
 
TODO
 
 
=== Writing a filter ===
 
Using <hask>interact :: (String -> String) -> IO ()</hask>, you can easily do things with stdin and stdout.
 
 
A program to sum up numbers:
 
 
<haskell>main = interact $ show . sum . map read . lines</haskell>
 
 
A program that adds line numbers to each line:
 
 
<haskell>
 
main = interact numberLines
 
numberLines = unlines . zipWith combine [1..] . lines
 
where combine lineNumber text = concat [show lineNumber, " ", text]
 
</haskell>
 
 
 
=== 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.
 
 
<haskell>
 
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
 
</haskell>
 
== 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 [[http://haskell.org/arrows/ Arrows]].
 
 
=== Parsing XML ===
 
 
== Databases access ==
 
There are two packages you can use to connect to MySQL, PostgreSQL, Sqlite3 and ODBC databases: [http://software.complete.org/software/projects/show/hdbc 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:
 
<haskell>
 
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
 
</haskell>
 
 
 
$ 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:
 
 
<haskell>
 
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]
 
</haskell>
 
 
This code was taken from [[WxHaskell/Quick_start | "a quick start with wxHaskell"]].
 
 
=== Gtk2Hs ===
 
[http://haskell.org/gtk2hs/screenshots/ Gtk2Hs] is a GUI Library for
 
Haskell based on GTK. [http://home.telfort.nl/sp969709/gtk2hs/ Gtk2Hs Tutorial].
 
 
Hello world example:
 
 
<haskell>
 
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
 
</haskell>
 
 
For more examples, see: [[Applications and libraries/Games]]
 
 
=== HOpenGL ===
 
[[http://www.haskell.org/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
 
[[http://haskell-tetris.pbwiki.com/Main]] by Jim.
 
 
See also: [[Applications and libraries/Games]]
 
 
=== SDL ===
 
There are some Haskell bindings to [http://libsdl.org/ SDL] at [http://hackage.haskell.org/packages/archive/pkg-list.html Hackage].
 
 
== PDF files ==
 
 
For the following recipes you need to install [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HPDF HPDF].
 
 
=== Creating an empty PDF file ===
 
 
<haskell>
 
import Graphics.PDF
 
 
main :: IO ()
 
main = do
 
let output = "test1.pdf"
 
let rect = PDFRect 0 0 200 300
 
 
runPdf output standardDocInfo rect $ do
 
addPage Nothing
 
 
</haskell>
 
 
=== Pages with different sizes ===
 
 
If you pass "Nothing" to the function "addPage", the document size will be used for the size of the new page.
 
 
Let’s create three pages, the last two pages with different dimensions:
 
 
<haskell>
 
import Graphics.PDF
 
 
main :: IO ()
 
main = do
 
let output = "test2.pdf"
 
let rect = PDFRect 0 0 200 300
 
 
runPdf output standardDocInfo rect $ do
 
addPage Nothing
 
addPage $ Just $ PDFRect 0 0 100 100
 
addPage $ Just $ PDFRect 0 0 150 150
 
</haskell>
 
 
== FFI ==
 
=== How to interface with C===
 
 
Magnus has written [http://therning.org/magnus/archives/315 a nice example ] on how to call a C function operating on a user defined type.
 
 
== Testing ==
 
 
=== QuickCheck ===
 
 
TODO
 
 
=== HUnit ===
 
 
TODO
 

Latest revision as of 18:49, 26 May 2011