Sie sind auf Seite 1von 14

Haskell Cheat Sheet Strings • \& – A “null” escape character which allows

numeric escape codes next to numeric liter-


• "abc" – Unicode string, sugar for
This cheat sheet lays out the fundamental ele- als. For example, \x2C4 is ∧ (in Unicode)
['a','b','c'].
ments of the Haskell language: syntax, keywords while \x2C\&4 is ,4. This sequence cannot
• 'a' – Single character.
and other elements. It is presented as both an ex- be used in character literals.
ecutable Haskell file and a printable document.
Multi-line Strings Normally, it is a syntax error
Load the source into your favorite interpreter to
if a string has any newline characters. That is, this Numbers
play with code samples shown.
is a syntax error:
• 1 – Integer or floating point value.
string1 = "My long • 1.0, 1e10 – Floating point value.
Basic Syntax string." • 0o1, 0O1 – Octal value.
• 0x1, 0X1 – Hexadecimal value.
Backslashes (‘\’) can “escape” a newline:
Comments • -1 – Negative number; the minus sign (“-”)
string1 = "My long \ cannot be separated from the number.
A single line comment starts with ‘--’ and extends \string."
to the end of the line. Multi-line comments start
with ’{-’ and extend to ’-}’. Comments can be The area between the backslashes is ignored. Enumerations
nested. Newlines in the string must be represented explic-
itly: • [1..10] – List of numbers – 1, 2, . . ., 10.
Comments above function definitions should
• [100..] – Infinite list of numbers – 100,
start with ‘{- |’ and those next to parameter types string2 = "My long \n\ 101, 102, . . . .
with ‘-- ^’ for compatibility with Haddock, a sys- \string." • [110..100] – Empty list, but
tem for documenting Haskell code.
[110, 109 .. 100] will give a list from 110
That is, string1 evaluates to:
to 100.
Reserved Words My long string. • [0, -1 ..] – Negative integers.
• [-110..-100] – Syntax error; need
While string2 evaluates to:
The following words are reserved in Haskell. It is [-110.. -100] for negatives.
a syntax error to give a variable or a function one My long • [1,3..99], [-1,3..99] – List from 1 to 99
of these names. string. by 2, -1 to 99 by 4.
In fact, any value which is in the Enum class can be
• case • import • of Escape Codes The following escape codes can used:
• class • in • module be used in characters or strings: • ['a' .. 'z'] – List of characters – a, b,
• data • infix • newtype • \n, \r, \f, etc. – The standard codes for new- . . ., z.
• deriving • infixl • then line, carriage return, form feed, etc. are sup- • ['z', 'y' .. 'a'] – z, y, x, . . ., a.
• do • infixr • type ported. • [1.0, 1.5 .. 2] – [1.0,1.5,2.0].
• else • instance • where • \72, \x48, \o110 – A character with the value • [UppercaseLetter ..] – List of
• if • let 72 in decimal, hex and octal, respectively. GeneralCategory values (from Data.Char).


c 2010 Justin Bailey. 1 jgbailey@codeslower.com
Lists & Tuples Function Definition Indent the body at least Function Definition
one space from the function name:
• [] – Empty list. Functions are defined by declaring their name,
• [1,2,3] – List of three numbers. square x = any arguments, and an equals sign:
• 1 : 2 : 3 : [] – Alternate way to write x * x
lists using “cons” (:) and “nil” ([]). square x = x * x
• "abc" – List of three characters (strings are Unless a where clause is present. In that case, in- All functions names must start with a lowercase
lists). dent the where clause at least one space from the letter or “_”. It is a syntax error otherwise.
• 'a' : 'b' : 'c' : [] – List of characters function name and any function bodies at least
(same as "abc"). one space from the where keyword:
• (1,"a") – 2-element tuple of a number and Pattern Matching Multiple “clauses” of a func-
tion can be defined by “pattern-matching” on the
a string. square x =
• (head, tail, 3, 'a') – 4-element tuple of values of arguments. Here, the agree function has
x2
four separate cases:
two functions, a number and a character. where x2 =
x * x -- Matches when the string "y" is given.
“Layout” rule, braces and semi-colons. agree1 "y" = "Great!"
Let Indent the body of the let at least one space -- Matches when the string "n" is given.
Haskell can be written using braces and semi- from the first definition in the let. If let appears agree1 "n" = "Too bad."
colons, just like C. However, no one does. Instead, on its own line, the body of any definition must -- Matches when string beginning
the “layout” rule is used, where spaces represent appear in the column after the let: -- with 'y' given.
scope. The general rule is: always indent. When agree1 ('y':_) = "YAHOO!"
the compiler complains, indent more. square x = -- Matches for any other value given.
let x2 = agree1 _ = "SO SAD."
x * x
Braces and semi-colons Semi-colons termi- Note that the ‘_’ character is a wildcard and
in x2
nate an expression, and braces represent scope. matches any value.
They can be used after several keywords: where, Pattern matching can extend to nested values.
As can be seen above, the in keyword must also be
let, do and of. They cannot be used when defin- Assuming this data declaration:
in the same column as let. Finally, when multiple
ing a function body. For example, the below will
definitions are given, all identifiers must appear in
not compile. data Bar = Bil (Maybe Int) | Baz
the same column.
and recalling the definition of Maybe from page 7
square2 x = { x * x; }
we can match on nested Maybe values when Bil is
Declarations, Etc. present:
However, this will work fine:
The following section details rules on function f (Bil (Just _)) = ...
square2 x = result declarations, list comprehensions, and other areas f (Bil Nothing) = ...
where { result = x * x; } of the language. f Baz = ...


c 2010 Justin Bailey. 2 jgbailey@codeslower.com
Pattern-matching also allows values to be as- Guards Boolean functions can be used as syntax, however, can match based on those record
signed to variables. For example, this function de- “guards” in function definitions along with pat- names. Given this data type:
termines if the string given is empty or not. If not, tern matching. An example without pattern
data Color = C { red
the value bound to str is converted to lower case: matching:
, green
toLowerStr [] = [] which n , blue :: Int }
toLowerStr str = map toLower str | n == 0 = "zero!"
we can match on green only:
| even n = "even!"
Note that str above is similer to _ in that it will
| otherwise = "odd!" isGreenZero (C { green = 0 }) = True
match anything; the only difference is that the
isGreenZero _ = False
value matched is also given a name. Notice otherwise – it always evaluates to True
and can be used to specify a “default” branch. Argument capture is possible with this syntax, al-
n + k Patterns This (sometimes controversial) Guards can be used with patterns. Here is a though it gets clunky. Continuing the above, we
pattern-matching facility makes it easy to match function that determines if the first character in a now define a Pixel type and a function to replace
certain kinds of numeric expressions. The idea string is upper or lower case: values with non-zero green components with all
is to define a base case (the “n” portion) with a black:
what [] = "empty string!"
constant number for matching, and then to define
what (c:_) data Pixel = P Color
other matches (the “k” portion) as additives to the
| isUpper c = "upper case!"
base case. Here is a rather inefficient way of test- -- Color value untouched if green is 0
| isLower c = "lower case"
ing if a number is even or not: setGreen (P col@(C { green = 0 })) = P col
| otherwise = "not a letter!"
isEven 0 = True setGreen _ = P (C 0 0 0)
isEven 1 = False Matching & Guard Order Pattern-matching
isEven (n + 2) = isEven n proceeds in top to bottom order. Similarly, guard Lazy Patterns This syntax, also known as ir-
expressions are tested from top to bottom. For ex- refutable patterns, allows pattern matches which
Argument Capture Argument capture is use- ample, neither of these functions would be very always succeed. That means any clause using the
ful for pattern-matching a value and using it, with- interesting: pattern will succeed, but if it tries to actually use
out declaring an extra variable. Use an ‘@’ symbol the matched value an error may occur. This is gen-
in between the pattern to match and the variable allEmpty _ = False erally useful when an action should be taken on
to bind the value to. This facility is used below to allEmpty [] = True the type of a particular value, even if the value isn’t
bind the head of the list in l for display, while also present.
binding the entire list to ls in order to compute its alwaysEven n For example, define a class for default values:
length: | otherwise = False
| n `div` 2 == 0 = True class Def a where
len ls@(l:_) = "List starts with " ++ defValue :: a -> a
show l ++ " and is " ++ Record Syntax Normally pattern matching oc- The idea is you give defValue a value of the right
show (length ls) ++ " items long." curs based on the position of arguments in the type and it gives you back a default value for that
len [] = "List is empty!" value being matched. Types declared with record type. Defining instances for basic types is easy:


c 2010 Justin Bailey. 3 jgbailey@codeslower.com
instance Def Bool where List Comprehensions Or, to find all occurrences of a particular break
defValue _ = False value br in a list word (indexing from 0):
A list comprehension consists of four types of el-
ements: generators, guards, local bindings, and tar- idxs word br =
instance Def Char where
gets. A list comprehension creates a list of target [i | (i, c) <- zip [0..] word
defValue _ = ' '
values based on the generators and guards given. , c == br]
Maybe is a littler trickier, because we want to get This comprehension generates all squares: A unique feature of list comprehensions is that
a default value for the type, but the constructor
squares = [x * x | x <- [1..]] pattern matching failures do not cause an error;
might be Nothing. The following definition would
they are just excluded from the resulting list.
work, but it’s not optimal since we get Nothing x <- [1..] generates a list of all Integer values
when Nothing is passed in. and puts them in x, one by one. x * x creates each
Operators
instance Def a => Def (Maybe a) where element of the list by multiplying x by itself.
defValue (Just x) = Just (defValue x) Guards allow certain elements to be excluded. There are very few predefined “operators” in
defValue Nothing = Nothing The following shows how divisors for a given Haskell—most that appear predefined are actually
number (excluding itself) can be calculated. No- syntax (e.g., “=”). Instead, operators are simply
We’d rather get a Just (default value) back in- tice how d is used in both the guard and target functions that take two arguments and have spe-
stead. Here is where a lazy pattern saves us – expression. cial syntactic support. Any so-called operator can
we can pretend that we’ve matched Just x and be applied as a prefix function using parentheses:
use that to get a default value, even if Nothing is divisors n =
[d | d <- [1..(n `div` 2)] 3 + 4 == (+) 3 4
given:
, n `mod` d == 0] To define a new operator, simply define it as a nor-
instance Def a => Def (Maybe a) where
Local bindings provide new definitions for use in mal function, except the operator appears between
defValue ~(Just x) = Just (defValue x)
the generated expression or subsequent genera- the two arguments. Here’s one which inserts a
As long as the value x is not actually evaluated, tors and guards. Below, z is used to represent the comma between two strings and ensures no extra
we’re safe. None of the base types need to look minimum of a and b: spaces appear:
at x (see the “_” matches they use), so things will
strange = [(a,z) | a <-[1..3] first ## last =
work just fine.
, b <-[1..3] let trim s = dropWhile isSpace
One wrinkle with the above is that we must
, c <- [1..3] (reverse (dropWhile isSpace
provide type annotations in the interpreter or the
, let z = min a b (reverse s)))
code when using a Nothing constructor. Nothing
, z < c ] in trim last ++ ", " ++ trim first
has type Maybe a but, if not enough other infor-
mation is available, Haskell must be told what a Comprehensions are not limited to numbers. Any > " Haskell " ## " Curry "
is. Some example default values: list will do. All upper case letters can be gener- Curry, Haskell
-- Return "Just False" ated:
Of course, full pattern matching, guards, etc. are
defMB = defValue (Nothing :: Maybe Bool) ups = available in this form. Type signatures are a bit
-- Return "Just ' '" [c | c <- [minBound .. maxBound] different, though. The operator “name” must ap-
defMC = defValue (Nothing :: Maybe Char) , isUpper c] pear in parentheses:


c 2010 Justin Bailey. 4 jgbailey@codeslower.com
(##) :: String -> String -> String > 2 + 3 * 5 toL33t 'a' = '4'
17 -- etc.
Allowable symbols which can be used to define > 2 `plus1` 3 `mult1` 5 toL33t c = c
operators are: 25
Notice that l33t has no arguments specified.
# $ % & * + . / < = > ? @ \ ^ | - ~ Reversing associativity also has interesting effects. Also, the final argument to convertOnly is not
However, there are several “operators” which can- Redefining division as right associative: given. However, the type signature of l33t tells
not be redefined. They are: <-, -> and =. The last, the whole story:
infixr 7 `div1`
=, cannot be redefined by itself, but can be used as div1 a b = a / b l33t :: String -> String
part of multi-character operator. The “bind” func-
tion, >>=, is one example. We get interesting results: That is, l33t takes a string and produces a string.
> 20 / 2 / 2 It is a “constant”, in the sense that l33t always
Precedence & Associativity The precedence returns a value that is a function which takes a
5.0
and associativity, collectively called fixity, of any
> 20 `div1` 2 `div1` 2 string and produces a string. l33t returns a “cur-
operator can be set through the infix, infixr and ried” form of convertOnly, where only two of its
20.0
infixl keywords. These can be applied both to three arguments have been supplied.
top-level functions and to local definitions. The This can be taken further. Say we want to write
syntax is:
Currying
a function which only changes upper case letters.
In Haskell, functions do not have to get all of their We know the test to apply, isUpper, but we don’t
{infix | infixr | infixl} precedence op arguments at once. For example, consider the want to specify the conversion. That function can
convertOnly function, which only converts certain be written as:
where precedence varies from 0 to 9. Op can actu-
elements of string depending on a test:
ally be any function which takes two arguments convertUpper = convertOnly isUpper
(i.e., any binary operation). Whether the operator convertOnly test change str =
is left or right associative is specified by infixl map (\c -> if test c which has the type signature:
or infixr, respectively. Such infix declarations then change c
convertUpper :: (Char -> Char)
have no associativity. else c) str
-> String -> String
Precedence and associativity make many of
the rules of arithmetic work “as expected.” For ex- Using convertOnly, we can write the l33t func-
That is, convertUpper can take two arguments.
ample, consider these minor updates to the prece- tion which converts certain letters to numbers:
The first is the conversion function which converts
dence of addition and multiplication: l33t = convertOnly isL33t toL33t individual characters and the second is the string
infixl 8 `plus1` where to be converted.
plus1 a b = a + b isL33t 'o' = True A curried form of any function which takes
infixl 7 `mult1` isL33t 'a' = True multiple arguments can be created. One way to
mult1 a b = a * b -- etc. think of this is that each “arrow” in the function’s
isL33t _ = False signature represents a new function which can be
The results are surprising: toL33t 'o' = '0' created by supplying one more argument.


c 2010 Justin Bailey. 5 jgbailey@codeslower.com
Sections Operators are functions, and they can noGreen2 c = c { green = 0 } multBy n = \m -> n * m
be curried like any other. For example, a curried
Here we capture the Color value in c and return a
version of “+” can be written as: For example:
new Color value. That value happens to have the
add10 = (+) 10 same value for red and blue as c and it’s green
component is 0. We can combine this with pattern > let mult10 = multBy 10
However, this can be unwieldy and hard to read.
matching to set the green and blue fields to equal > mult10 10
“Sections” are curried operators, using parenthe-
the red field: 100
ses. Here is add10 using sections:
makeGrey c@(C { red = r }) =
add10 = (10 +)
c { green = r, blue = r }
Type Signatures
The supplied argument can be on the right or left,
Notice we must use argument capture (“c@”) to
which indicates what position it should take. This
get the Color value and pattern matching with Haskell supports full type inference, meaning in
is important for operations such as concatenation:
record syntax (“C { red = r}”) to get the inner most cases no types have to be written down. Type
onLeft str = (++ str) red field. signatures are still useful for at least two reasons.
onRight str = (str ++)
Which produces quite different results: Anonymous Functions Documentation—Even if the compiler can figure
An anonymous function (i.e., a lambda expression out the types of your functions, other pro-
> onLeft "foo" "bar" grammers or even yourself might not be able
"barfoo" or lambda for short), is a function without a name.
They can be defined at any time like so: to later. Writing the type signatures on all
> onRight "foo" "bar" top-level functions is considered very good
"foobar" \c -> (c, c) form.
which defines a function that takes an argument
“Updating” values and record syntax Specialization—Typeclasses allow functions with
and returns a tuple containing that argument in
Haskell is a pure language and, as such, has no both positions. They are useful for simple func- overloading. For example, a function to
mutable state. That is, once a value is set it never tions which don’t need a name. The following negate any list of numbers has the signature:
changes. “Updating” is really a copy operation, determines if a string consists only of mixed case
with new values in the fields that “changed.” For letters and whitespace.
negateAll :: Num a => [a] -> [a]
example, using the Color type defined earlier, we
mixedCase str =
can write a function that sets the green field to
all (\c -> isSpace c ||
zero easily: However, for efficiency or other reasons you
isLower c ||
may only want to allow Int types. You
noGreen1 (C r _ b) = C r 0 b isUpper c) str
would accomplish that with a type signa-
The above is a bit verbose and can be rewritten Of course, lambdas can be the returned from func- ture:
using record syntax. This kind of “update” only tions too. This classic returns a function which
sets values for the field(s) specified and copies the will then multiply its argument by the one origi-
rest: nally given: negateAll :: [Int] -> [Int]


c 2010 Justin Bailey. 6 jgbailey@codeslower.com
Type signatures can appear on top-level func- the annotation above is on the expression read x, Nesting & Capture Nested matching and bind-
tions and nested let or where definitions. Gen- not on the variable x. Only function application ing are also allowed. For example, here is the def-
erally this is useful for documentation, although (e.g., read x) binds tighter than annotations. If inition of the Maybe type:
in some cases they are needed to prevent poly- that was not the case, the above would need to be
morphism. A type signature is first the name of written (read x) :: Int. data Maybe a = Just a | Nothing
the item which will be typed, followed by a ::, Using Maybe we can determine if any choice
followed by the types. An example of this has al- was given using a nested match:
ready been seen above.
Unit
Type signatures do not need to appear directly anyChoice1 ch =
() – “unit” type and “unit” value. The value and
above their implementation. They can be specified case ch of
type that represents no useful information.
anywhere in the containing module (yes, even be- Nothing -> "No choice!"
low!). Multiple items with the same signature can Just (First _) -> "First!"
also be defined together: Just Second -> "Second!"
Keywords
_ -> "Something else."
pos, neg :: Int -> Int
Haskell keywords are listed below, in alphabetical Binding can be used to manipulate the value
... order. matched:

pos x | x < 0 = negate x anyChoice2 ch =


Case case ch of
| otherwise = x
case is similar to a switch statement in C# or Java, Nothing -> "No choice!"
neg y | y > 0 = negate y but can match a pattern: the shape of the value be-
Just score@(First "gold") ->
| otherwise = y ing inspected. Consider a simple data type:
"First with gold!"
Just score@(First _) ->
data Choices = First String | Second | "First with something else: "
Type Annotations Sometimes Haskell cannot
Third | Fourth ++ show score
determine what type is meant. The classic demon-
_ -> "Not first."
stration of this is the so-called “show . read”
problem: case can be used to determine which choice was
given: Matching Order Matching proceeds from top
canParseInt x = show (read x) to bottom. If anyChoice1 is reordered as follows,
whichChoice ch = the first pattern will always succeed:
Haskell cannot compile that function because it
case ch of
does not know the type of read x. We must limit anyChoice3 ch =
First _ -> "1st!"
the type through an annotation: case ch of
Second -> "2nd!"
_ -> "Something else."
canParseInt x = show (read x :: Int) _ -> "Something else."
Nothing -> "No choice!"
Annotations have the same syntax as type signa- As with pattern-matching in function definitions, Just (First _) -> "First!"
tures, but may adorn any expression. Note that the ‘_’ token is a “wildcard” matching any value. Just Second -> "Second!"


c 2010 Justin Bailey. 7 jgbailey@codeslower.com
Guards Guards, or conditional matches, can be Notice that the declaration only gives the type Data
used in cases just like function definitions. The signature of the function—no implementation is
only difference is the use of the -> instead of given here (with some exceptions, see “Defaults” So-called algebraic data types can be declared as fol-
=. Here is a simple function which does a case- on page 8). Continuing, we can define several in- lows:
insensitive string match: stances:

strcmp s1 s2 = case (s1, s2) of instance Flavor Bool where data MyType = MyValue1 | MyValue2
([], []) -> True flavor _ = "sweet"
(s1:ss1, s2:ss2)
instance Flavor Char where MyType is the type’s name. MyValue1 and
| toUpper s1 == toUpper s2 ->
flavor _ = "sour" MyValue are values of the type and are called con-
strcmp ss1 ss2
structors. Multiple constructors are separated with
| otherwise -> False Evaluating flavor True gives:
the ‘|’ character. Note that type and constructor
_ -> False > flavor True names must start with a capital letter. It is a syn-
"sweet" tax error otherwise.
Class
While flavor 'x' gives:
A Haskell function is defined to work on a certain > flavor 'x'
type or set of types and cannot be defined more "sour" Constructors with Arguments The type above
than once. Most languages support the idea of is not very interesting except as an enumeration.
“overloading”, where a function can have differ- Defaults Default implementations can be given Constructors that take arguments can be declared,
ent behavior depending on the type of its argu- for functions in a class. These are useful when cer- allowing more information to be stored:
ments. Haskell accomplishes overloading through tain functions can be defined in terms of others in
class and instance declarations. A class defines the class. A default is defined by giving a body
one or more functions that can be applied to any to one of the member functions. The canonical ex- data Point = TwoD Int Int
types which are members (i.e., instances) of that ample is Eq, which defines /= (not equal) in terms | ThreeD Int Int Int
class. A class is analogous to an interface in Java of == :
or C#, and instances to a concrete implementation
class Eq a where Notice that the arguments for each constructor are
of the interface.
(==) :: a -> a -> Bool type names, not constructors. That means this
A class must be declared with one or more
(/=) :: a -> a -> Bool kind of declaration is illegal:
type variables. Technically, Haskell 98 only al-
lows one type variable, but most implementations (/=) a b = not (a == b)
of Haskell support so-called multi-parameter type Recursive definitions can be created. Continuing data Poly = Triangle TwoD TwoD TwoD
classes, which allow more than one type variable. the Eq example, == can be defined in terms of /=:
We can define a class which supplies a flavor (==) a b = not (a /= b)
for a given type: instead, the Point type must be used:
However, if instances do not provide enough con-
class Flavor a where crete implementations of member functions then
flavor :: a -> String any program using those instances will loop. data Poly = Triangle Point Point Point


c 2010 Justin Bailey. 8 jgbailey@codeslower.com
Type and Constructor Names Type and con- data Contact = Contact { ctName :: String Two forms of deriving are possible. The first
structor names can be the same, because they will , ctEmail :: String is used when a type only derives one class:
never be used in a place that would cause confu- , ctPhone :: String } data Priority = Low | Medium | High
sion. For example: These names are referred to as selector or acces- deriving Show
data User = User String | Admin String sor functions and are just that, functions. They The second is used when multiple classes are de-
must start with a lowercase letter or underscore rived:
which declares a type named User with two con- and cannot have the same name as another func-
structors, User and Admin. Using this type in a data Alarm = Soft | Loud | Deafening
tion in scope. Thus the “ct” prefix on each above.
function makes the difference clear: deriving (Read, Show)
Multiple constructors (of the same type) can use
the same accessor function for values of the same It is a syntax error to specify deriving for any
whatUser (User _) = "normal user." other classes besides the seven given above.
type, but that can be dangerous if the accessor is
whatUser (Admin _) = "admin user."
not used by all constructors. Consider this rather
Some literature refers to this practice as type pun- contrived example: Class Constraints Data types can be declared
ning. with class constraints on the type variables, but
data Con = Con { conValue :: String }
this practice is discouraged. It is better to hide the
| Uncon { conValue :: String }
“raw” data constructors using the module system
Type Variables Declaring so-called polymorphic | Noncon
data types is as easy as adding type variables in and instead export “smart” constructors which
apply appropriate constraints. In any case, the
the declaration: whichCon con = "convalue is " ++
syntax used is:
conValue con
data Slot1 a = Slot1 a | Empty1 data (Num a) => SomeNumber a = Two a a
If whichCon is called with a Noncon value, a run-
This declares a type Slot1 with two constructors, | Three a a a
time error will occur.
Slot1 and Empty1. The Slot1 constructor can take Finally, as explained elsewhere, these names This declares a type SomeNumber which has one
an argument of any type, which is represented by can be used for pattern matching, argument cap- type variable argument. Valid types are those in
the type variable a above. ture and “updating.” the Num class.
We can also mix type variables and specific
types in constructors: Deriving Many types have common operations Deriving
data Slot2 a = Slot2 a Int | Empty2 which are tedious to define yet necessary, such as See the section on deriving under the data key-
the ability to convert to and from strings, compare word on page 9.
Above, the Slot2 constructor can take a value of for equality, or order in a sequence. These capa-
any type and an Int value. bilities are defined as typeclasses in Haskell.
Do
Because seven of these operations are so com-
Record Syntax Constructor arguments can be mon, Haskell provides the deriving keyword The do keyword indicates that the code to follow
declared either positionally, as above, or using which will automatically implement the typeclass will be in a monadic context. Statements are sepa-
record syntax, which gives a name to each argu- on the associated type. The seven supported type- rated by newlines, assignment is indicated by <-,
ment. For example, here we declare a Contact classes are: Eq, Read, Show, Ord, Enum, Ix, and and a let form is introduced which does not re-
type with names for appropriate arguments: Bounded. quire the in keyword.


c 2010 Justin Bailey. 9 jgbailey@codeslower.com
If and IO if can be tricky when used with let result = file -> do
IO. Conceptually it is no different from an if if exists f <- readFile file
in any other context, but intuitively it is hard to then 1 putStrLn ("The file is " ++
develop. Consider the function doesFileExists else 0 show (length f)
from System.Directory: return result ++ " bytes long.")
doesFileExist :: FilePath -> IO Bool Again, notice where return is. We don’t put it in An alternative syntax uses semi-colons and braces.
the let statement. Instead we use it once at the A do is still required, but indention is unnecessary.
The if statement has this “signature”:
end of the function. This code shows a case example, but the principle
if-then-else :: Bool -> a -> a -> a applies to if as well:

That is, it takes a Bool value and evaluates to some Multiple do’s When using do with if or case, countBytes3 =
other value based on the condition. From the type another do is required if either branch has multi- do
signatures it is clear that doesFileExist cannot be ple statements. An example with if: putStrLn "Enter a filename."
used directly by if: args <- getLine
countBytes1 f =
case args of
wrong fileName = do
[] -> putStrLn "No args given."
if doesFileExist fileName putStrLn "Enter a filename."
file -> do { f <- readFile file;
then ... args <- getLine
putStrLn ("The file is " ++
else ... if length args == 0
show (length f)
-- no 'do'.
That is, doesFileExist results in an IO Bool ++ " bytes long."); }
then putStrLn "No filename given."
value, while if wants a Bool value. Instead, the else
correct value must be “extracted” by running the -- multiple statements require
Export
IO action: -- a new 'do'. See the section on module on page 11.
right1 fileName = do do
exists <- doesFileExist fileName f <- readFile args If, Then, Else
if exists putStrLn ("The file is " ++
show (length f) Remember, if always “returns” a value. It is an
then return 1
else return 0 ++ " bytes long.") expression, not just a control flow statement. This
function tests if the string given starts with a lower
Notice the use of return. Because do puts us “in- And one with case: case letter and, if so, converts it to upper case:
side” the IO monad, we can’t “get out” except
countBytes2 = -- Use pattern-matching to
through return. Note that we don’t have to use
do -- get first character
if inline here—we can also use let to evaluate
putStrLn "Enter a filename." sentenceCase (s:rest) =
the condition and get a value first:
args <- getLine if isLower s
right2 fileName = do case args of then toUpper s : rest
exists <- doesFileExist fileName [] -> putStrLn "No args given." else s : rest


c 2010 Justin Bailey. 10 jgbailey@codeslower.com
-- Anything else is empty string again. This is useful for capturing common por- Module
sentenceCase _ = [] tions of your function and re-using them. Here is
A module is a compilation unit which exports
a silly example which gives the sum of a list of
functions, types, classes, instances, and other
Import numbers, their average, and their median:
modules. A module can only be defined in one
listStats m = file, though its exports may come from multiple
See the section on module on page 11.
let numbers = [1,3 .. m] sources. To make a Haskell file a module, just add
total = sum numbers a module declaration at the top:
In mid = head (drop (m `div` 2)
numbers) module MyModule where
See let on page 11.
in "total: " ++ show total ++ Module names must start with a capital letter but
", mid: " ++ show mid otherwise can include periods, numbers and un-
Infix, infixl and infixr derscores. Periods are used to give sense of struc-
See the section on operators on page 4. Deconstruction The left-hand side of a let ture, and Haskell compilers will use them as indi-
definition can also destructure its argument, in cations of the directory a particular source file is,
case sub-components are to be accessed. This defi- but otherwise they have no meaning.
Instance nition would extract the first three characters from The Haskell community has standardized a set
See the section on class on page 8. a string of top-level module names such as Data, System,
firstThree str = Network, etc. Be sure to consult them for an ap-
let (a:b:c:_) = str propriate place for your own module if you plan
Let
in "Initial three characters are: " ++ on releasing it to the public.
Local functions can be defined within a function show a ++ ", " ++
using let. The let keyword must always be fol- show b ++ ", and " ++ Imports The Haskell standard libraries are di-
lowed by in. The in must appear in the same col- show c vided into a number of modules. The functional-
umn as the let keyword. Functions defined have ity provided by those libraries is accessed by im-
Note that this is different than the following,
access to all other functions and variables within porting into your source file. To import everything
which only works if the string has exactly three
the same scope (including those defined by let). exported by a library, just use the module name:
characters:
In this example, mult multiplies its argument n
onlyThree str = import Text.Read
by x, which was passed to the original multiples.
mult is used by map to give the multiples of x up let (a:b:c:[]) = str Everything means everything: functions, data
to 10: in "The characters given are: " ++ types and constructors, class declarations, and
show a ++ ", " ++ even other modules imported and then exported
multiples x = show b ++ ", and " ++ by the that module. Importing selectively is ac-
let mult n = n * x show c complished by giving a list of names to import.
in map mult [1..10] For example, here we import some functions from
Of Text.Read:
let “functions” with no arguments are actually
constants and, once evaluated, will not evaluate See the section on case on page 7. import Text.Read (readParen, lex)


c 2010 Justin Bailey. 11 jgbailey@codeslower.com
Data types can be imported in a number of ways. Instance Declarations It must be noted that Exports If an export list is not provided, then
We can just import the type and no constructors: instance declarations cannot be excluded from all functions, types, constructors, etc. will be
import: all instance declarations in a module will available to anyone importing the module. Note
import Text.Read (Lexeme)
be imported when the module is imported. that any imported modules are not exported in
Of course, this prevents our module from pattern- this case. Limiting the names exported is accom-
matching on the values of type Lexeme. We can plished by adding a parenthesized list of names
import one or more constructors explicitly: Qualified Imports The names exported by a before the where keyword:
module (i.e., functions, types, operators, etc.) can
import Text.Read (Lexeme(Ident, Symbol)) have a prefix attached through qualified imports. module MyModule (MyType
All constructors for a given type can also be im- This is particularly useful for modules which have , MyClass
ported: a large number of functions having the same name , myFunc1
as Prelude functions. Data.Set is a good example: ...)
import Text.Read (Lexeme(..))
where
We can also import types and classes defined in import qualified Data.Set as Set
the module: The same syntax as used for importing can be
This form requires any function, type, construc- used here to specify which functions, types, con-
import Text.Read (Read, ReadS) tor or other name exported by Data.Set to now structors, and classes are exported, with a few dif-
In the case of classes, we can import the functions be prefixed with the alias (i.e., Set) given. Here is ferences. If a module imports another module, it
defined for a class using syntax similar to import- one way to remove all duplicates from a list: can also export that module:
ing constructors for data types:
removeDups a = module MyBigModule (module Data.Set
import Text.Read (Read(readsPrec , module Data.Char)
Set.toList (Set.fromList a)
, readList)) where
Note that, unlike data types, all class functions are A second form does not create an alias. Instead,
imported unless explicitly excluded. To only im- the prefix becomes the module name. We can import Data.Set
port the class, we use this syntax: write a simple function to check if a string is all import Data.Char
upper case:
import Text.Read (Read()) A module can even re-export itself, which can be
useful when all local definitions and a given im-
import qualified Char
Exclusions If most, but not all, names are to ported module are to be exported. Below we ex-
be imported from a module, it would be tedious port ourselves and Data.Set, but not Data.Char:
to list them all. For that reason, imports can also allUpper str =
be specified via the hiding keyword: all Char.isUpper str module AnotherBigModule (module Data.Set
, module AnotherBigModule)
import Data.Char hiding (isControl where
Except for the prefix specified, qualified imports
, isMark)
support the same syntax as normal imports. The
Except for instance declarations, any type, func- name imported can be limited in the same ways import Data.Set
tion, constructor or class can be hidden. as described above. import Data.Char


c 2010 Justin Bailey. 12 jgbailey@codeslower.com
Newtype Finally, it should be noted that any deriving Where
clause which can be attached to a data declaration
While data introduces new values and type just Similar to let, where defines local functions and
can also be used when declaring a newtype.
creates synonyms, newtype falls somewhere be- constants. The scope of a where definition is the
tween. The syntax for newtype is quite restricted— current function. If a function is broken into mul-
only one constructor can be defined, and that con-
Return
tiple definitions through pattern-matching, then
structor can only take one argument. Continuing See do on page 9. the scope of a particular where clause only ap-
the above example, we can define a Phone type as plies to that definition. For example, the function
follows: Type result below has a different meaning depending
newtype Home = H String on the arguments given to the function strlen:
This keyword defines a type synonym (i.e., alias).
newtype Work = W String This keyword does not define a new type, like
data Phone = Phone Home Work strlen [] = result
data or newtype. It is useful for documenting code
where result = "No string given!"
As opposed to type, the H and W “values” on but otherwise has no effect on the actual type of
strlen f = result ++ " characters long!"
Phone are not just String values. The typechecker a given function or value. For example, a Person
where result = show (length f)
treats them as entirely new types. That means our data type could be defined as:
lowerName function from above would not com- data Person = Person String String
pile. The following produces a type error:
where the first constructor argument represents Where vs. Let A where clause can only be de-
fined at the level of a function definition. Usu-
lPhone (Phone hm wk) = their first name and the second their last. How-
ally, that is identical to the scope of let defini-
Phone (lower hm) (lower wk) ever, the order and meaning of the two arguments
is not very clear. A type declaration can help: tion. The only difference is when guards are being
Instead, we must use pattern-matching to get to used. The scope of the where clause extends over
type FirstName = String all guards. In contrast, the scope of a let expres-
the “values” to which we apply lower:
type LastName = String sion is only the current function clause and guard,
lPhone (Phone (H hm) (W wk)) = data Person = Person FirstName LastName if any.
Phone (H (lower hm)) (W (lower wk)) Because type introduces a synonym, type check-
The key observation is that this keyword does not ing is not affected in any way. The function lower,
introduce a new value; instead it introduces a new defined as: Contributors
type. This gives us two very useful properties: lower s = map toLower s
• No runtime cost is associated with the new My thanks to those who contributed patches
which has the type
type, since it does not actually produce new and useful suggestions: Dave Bayer, Paul But-
values. In other words, newtypes are abso- lower :: String -> String ler, Elisa Firth, Marc Fontaine, Brian Gianforcaro,
lutely free! can be used on values with the type FirstName or Cale Gibbard, Andrew Harris, Stephen Hicks,
• The type-checker is able to enforce that com- LastName just as easily: Kurt Hutchinson, Johan Kiviniemi, Patrik Jansson,
mon types such as Int or String are used Adrian Neumann, Barak Pearlmutter, Lanny Rip-
in restricted ways, specified by the program- lName (Person f l ) = ple, Markus Roberts, Holger Siegel, Falko Spiller,
mer. Person (lower f) (lower l) Adam Vogt, Leif Warner, and Jeff Zaroyko.


c 2010 Justin Bailey. 13 jgbailey@codeslower.com
Version cheatsheet). The latest released ver- CodeSlower.com (http://blog.codeslower.
sion of the PDF can be downloaded from com/) for other projects and writings.
This is version 2.8. The source can be http://cheatsheet.codeslower.com. Visit
found at GitHub (http://github.com/m4dc4p/


c 2010 Justin Bailey. 14 jgbailey@codeslower.com

Das könnte Ihnen auch gefallen