[Incorporate some comments. Bryan O'Sullivan **20071002055326] { hunk ./en/ch02-starting.xml 9 - There's a number of Haskell implementations available, of - which two are in wide use. Hugs 98 is an interpreter that is + Haskell is a language with many implementations, of + which two are in wide use. Hugs is an interpreter that is hunk ./en/ch02-starting.xml 12 - Haskell Compiler, or &GHC; as it's usually known, is much more - popular. This is the Haskell implementation we'll be using - throughout this book. + Haskell Compiler (&GHC;) is much more popular. Compared to + Hugs, &GHC; is much more complete: it compiles to native code, + supports parallel execution, and provides useful performance + analysis and debugging tools. For these reasons, &GHC; is the + Haskell implementation that we'll be using throughout this + book. hunk ./en/ch02-starting.xml 21 - we can run interactively; and &runghc;, an interpreter that we - can run in batch mode. + we can run interactively; and &runghc;, an interpreter for + running Haskell programs as fast-turnaround scripts after the + manner of Perl or Ruby. hunk ./en/ch02-starting.xml 26 - Which part of GHC do we mean? + How we refer to the components of GHC hunk ./en/ch02-starting.xml 28 - When we discuss the package as a whole, we'll refer to it - as &GHC;. If we're talking about one or another command, - we'll mention either &ghc; or &ghci;. (We'll rarely make - reference to &runghc;.) + When we discuss the &GHC; system as a whole, + we'll refer to it as &GHC;. If we're talking about one or + another command, we'll mention &ghc;, &ghci;, or &runghc; by + name. hunk ./en/ch02-starting.xml 34 - In this book, we assume that you're using at least version - 6.6.1 of &GHC;. To obtain a copy of &GHC; for your platform, + In this book, we assume that you're using at least + version 6.6.1 of &GHC;. If you're using Windows or Mac OS X, + you can get started easily and quickly using a prebuilt + installer. To obtain a copy of &GHC; for these platforms, hunk ./en/ch02-starting.xml 40 - packages. If you're using Windows or Mac OS X, these binary - packages are the best ones to use. + packages and installers. hunk ./en/ch02-starting.xml 43 - that the baseline version? + that the baseline version? We're likely to hold + off on a decision until much closer to publication. For now, + we'll stick with 6.6.1. hunk ./en/ch02-starting.xml 47 - Many Linux distributions, and BSD and other Unix variants, - make pre-packaged versions of &GHC; available. Because they are - built specifically for each environment, these packages are less - hassle to use than the generic binary packages. You can find a - list of such packages at the &GHC; Many Linux distributors, and providers of BSD and + other Unix variants, make custom binary packages of &GHC; + available. Because these are built specifically for each + environment, they are much easier to install and use than the + generic binary packages that are available from the &GHC; + download page. You can find a list of distributions that + custom-build &GHC; at the &GHC; . + a variety of popular platforms, we've provided some instructions + in . hunk ./en/ch02-starting.xml 68 - explore modules and type information. + explore modules and type information. If you're familiar with + Python, it's somewhat similar to the interactive Python + interpreter. + + The &ghci; command is a tool for evaluating Haskell + expressions, using existing code from libraries or source files + that we've written. It also provides commands that let us + inspect some details of modules and expressions. It is not a + complete interpreter for all of Haskell. We typically cannot + copy some code out of a Haskell source file and paste it into + &ghci;. In this respect, it's more restrictive than, say, the + interactive Python interpreter, which can accept all Python + code. + + On Unix-like systems, we run &ghci; as a command in a shell + window. On Windows, it's available as a menu item accessible + off the Start Menu. For example, if you installed using the + &GHC; installer on Windows XP, you should go to All + Programs, then GHC; you'll then see + &ghci; in the list. (See for a + screenshot.) hunk ./en/ch02-starting.xml 91 - by a Prelude> prompt. + by a Prelude> prompt. (Here, we're showing + it run on a Linux box.) hunk ./en/ch02-starting.xml 106 - The word Prelude in the prompt indicates that - the standard prelude, a fairly large standard - library of useful functions, is loaded and ready for us to use. - When we load other modules or source files, they'll show up in - the prompt, too. + The word Prelude in the prompt + indicates that the standard prelude, a standard + library of useful functions, is loaded and ready to use. When we + load other modules or source files, they'll show up in the + prompt, too. + + The Prelude + module is sometimes referred to as the standard + prelude, because its contents are defined by the + Haskell 98 standard. Usually, it's simply shortened to + the prelude. hunk ./en/ch02-starting.xml 119 - The ephemeral ghci prompt + About the ghci prompt hunk ./en/ch02-starting.xml 124 - line for our input. For brevity, we have replaced &ghci;'s + line for our input. + + For brevity and consistency, we have replaced &ghci;'s hunk ./en/ch02-starting.xml 131 + The prelude is always implicitly available; we + don't need to take any actions to use the types, values, or + functions it defines. To use definitions from other modules, we + must load them into &ghci;, using the :module + command. + + &basics.ghci:module; + hunk ./en/ch02-starting.xml 142 - On most systems, &ghci; has some amount of command line - editing ability. On Unix-like systems, it uses the GNU - readline library, which is powerful and customisable. On - Windows, &ghci;'s command line editing capabilities are - provided by the doskey command. - - If you haven't used command line editing before, it's a - huge time saver. The basics are common to both Unix-like and - Windows systems. Pressing the up arrow key on your keyboard recalls - the last line of input you entered; pressing On most systems, &ghci; has some amount of + command line editing ability. If you're not familiar with + command line editing, it's a huge time saver. The basics are + common to both Unix-like and Windows systems. Pressing the + up arrow key on your keyboard + recalls the last line of input you entered; pressing + inside a line of input. On Unix (but not Windows, + unfortunately), the tab key + completes partially typed identifiers. hunk ./en/ch02-starting.xml 156 - Just knowing this much will save you a lot of repeated - typing. If you want to learn more about command line editing - on your system, consult the readline or - doskey documentation. - + + Where to look for more information + + We've barely scratched the surface of command line + editing here. Since you can work more effectively if you're + more familiar with the capabilities of your command line + editing system, you might find it useful to do some further + reading. hunk ./en/ch02-starting.xml 165 + On Unix-like systems, &ghci; uses the GNU + readline library, which is powerful and + customisable. On Windows, &ghci;'s command line editing + capabilities are provided by the doskey + command. + + hunk ./en/ch02-starting.xml 179 - Where some people might run a calculator program, I often - drop into &ghci; to perform simple calculations. Using it this - way serves as a good way to become familiar with &ghci; itself, - and with the basics of Haskell expressions. + In addition to providing a convenient interface + for testing code fragments, &ghci; can function as a readily + accessible desktop calculator. We can easily express any + calculator operation in &ghci; and, as an added bonus, we can + add more complex operations as we become more familiar with + Haskell. Even using the interpreter in this simple way can help + us to become more comfortable with how Haskell works. hunk ./en/ch02-starting.xml 190 - We can immediately start typing expressions, to see what - &ghci; will do with them. Basic arithmetic works as we might - expect. + We can immediately start entering expressions, + to see what &ghci; will do with them. Basic arithmetic works + similarly to familiar languages like C and Python. hunk ./en/ch02-starting.xml 200 - operator. + operator. We'll be talking more about exponentiation + in . hunk ./en/ch02-starting.xml 205 - Like other languages that use infix notation to write - mathematical expressions, Haskell has a notion of operator - precedence. This allows us to get rid of a few parentheses. - For example, the multiplication operator has a higher - precedence than the addition operator, so Haskell treats the - two following expressions as equivalent. - - &basics.ghci:parens; - - - Don't be too aggressive with parenthesis removal - - As in other languages, it's often better to leave at - least some parentheses in place, even when Haskell allows us - to omit them. Their presence can help future readers - (including ourselves) to understand what we intended. + + Why are there parentheses around operators? hunk ./en/ch02-starting.xml 208 - Even more importantly, complex expressions - that rely completely on operator precedence are notorious - sources of bugs. A compiler and a human can easily end up - with different notions of what a long, parenthesis-free - expression is supposed to do. - + When we write operators by themselves, we'll usually + write them surrounded by parentheses, for example + (+). This is a standard Haskell way of + treating an operator as a function. + hunk ./en/ch02-starting.xml 221 - past writing the simplest of expressions. + beyond the simplest expressions. hunk ./en/ch02-starting.xml 223 - &basics.ghci:neg; + We'll start by writing a negative number. hunk ./en/ch02-starting.xml 225 - Later on, we'll be seeing how Haskell lets us devise - entirely new infix operators. Now that we've been forewarned, - the following may not prove too surprising. + &basics.ghci:neg.simple; + + The - above is a unary operator. In other + words, we didn't write the single number -3; we + wrote the number 3, and applied the operator + - to it. The - operator is + Haskell's only unary operator, and we can't mix it with infix + operators. + + &basics.ghci:neg.error; + + If we want to use the unary minus near an infix operator, + we must wrap the expression it applies to in + parentheses. + + &basics.ghci:neg.better; hunk ./en/ch02-starting.xml 249 - And here's one that similar to the problematic negative - number example above, but results in a different error - message. + And here's one that seems similar to the + problematic negative number example above, but results in a + different error message. hunk ./en/ch02-starting.xml 255 - What's happening here is that the Haskell parser is - reading +- as a single token, and trying to - use it as an operator. Once again, a few parentheses get us - and &ghci; looking at the expression in the same way. + Here, the Haskell implementation is reading + +- as a single operator. Haskell lets us + define new operators (a subject that we'll return to later), + but we haven't defined this one. Once again, a few + parentheses get us and &ghci; looking at the expression in the + same way. hunk ./en/ch02-starting.xml 264 - Compared to other languages, this unusual treatment of - negative numbers is an annoyance, for sure, but it at least - represents a reasoned trade-off. As we mentioned, Haskell lets - us define new operators at any time, and choose the precedence - and associativity of those operators. The language designers - chose to accept a slightly cumbersome syntax for negative - numbers in exchange for this expressive power. + Compared to other languages, this unusual + treatment of negative numbers might seem annoying, but it + represents a reasoned trade-off. Haskell lets us define new + operators at any time. This isn't some kind of esoteric + language feature; we'll see quite a few user-defined operators + in the chapters ahead. The language designers chose to accept + a slightly cumbersome syntax for negative numbers in exchange + for this expressive power. + + + + Boolean logic, operators, and value comparisons + + The values of Boolean logic in Haskell are + &True; and &False;. The language uses C-influenced operators + for working with Boolean values. + + &basics.ghci:boolean; + + Here, (&&) is logical + and, and (||) is logical + or. + + Unlike some other languages, Haskell does + not treat the + number zero as synonymous with False, nor + does it consider any non-zero value to be True. + + &basics.ghci:boolean.bad; + + Once again, we're faced with a substantial-looking error + message. It tells us that the Boolean type, Bool, + is not a member of the family of numeric types, + Num. The error message is rather long because + &ghci; is pointing out the location of the problem, and + hinting at a possible change we could make that might fix the + problem. + + Most of Haskell's comparison operators are + similar to those used in C and languages influenced by + C. + + &basics.ghci:comparison; + + There's one exception: the is not + equal to operator is (/=) + (somewhat visually similar to the mathematical ¬Equal; + operator), not the (!=) you might expect + from a language that borrows many other operators from + C. + + &basics.ghci:neq; + + + + + Operator precedence and associativity + + Like other languages that use infix notation to + write some expressions, Haskell has a notion of + operator precedence. We can use parentheses to explicitly + group parts of an expression, and precedence allows us to + omit a few parentheses. For example, the multiplication + operator has a higher precedence than the addition operator, + so Haskell treats the following two expressions as + equivalent. + + &basics.ghci:parens; + + Haskell assigns numeric precedence values to operators, + with 1 being the lowest precedence and 9 the highest. A + higher-precedence operator gets parsed before a + lower-precedence operator. We can use &ghci; to inspect the + precedence levels of individual operators, using its + :type command. + + &basics.ghci:precedence; + + Since (*) has a higher precedence + than (+), we can now see why 1 + 4 + * 4 is parsed as 1 + (4 * 4), and not + (1 + 4) * 4. + + Haskell also defines associativity of + operators. This determines whether an expression containing + multiple uses of an operator is parsed from left to right, or + right to left. The (+) and + (*) operators are left associative, which + is represented as infixl in the &ghci; output + above. A right associative operator would be displayed with + infixr. + + The combination of precedence and associativity rules are + usually referred to as fixity + rules. hunk ./en/ch02-starting.xml 364 - &ghci; defines at least one well-known mathematical - constant for us. + Haskell's prelude, the standard library we + mentioned earlier, defines at least one well-known + mathematical constant for us. hunk ./en/ch02-starting.xml 387 - We can define e ourselves; the &let; - construct allows us to introduce a new variable. + Using the &let; construct, we can define + e ourselves. hunk ./en/ch02-starting.xml 396 + + + This syntax is ghci-specific hunk ./en/ch02-starting.xml 400 + The syntax for &let; that &ghci; accepts is not the same + as we would use in a normal Haskell program. We'll see the + normal syntax in . + hunk ./en/ch02-starting.xml 406 - - Comparison and Boolean operators - - Haskell gives us the usual operators for working with - Boolean values. - - &basics.ghci:boolean; - - Unlike some other languages, Haskell does - not treat the - number zero as synonymous with False, nor - does it accept non-zero as True. - - &basics.ghci:boolean.bad; - - Comparison operators are mostly going to be - familiar from other languages that have taken some syntactic - cues from C. - - &basics.ghci:comparison; - - There's one exception: the is not - equal operator is (/=) - (somewhat visually similar to the mathematical ¬Equal; - operator), not the (!=) you might expect - from a language that borrows many other operators from - C. - - &basics.ghci:neq; - - - - - Rational numbers, the Haskell prelude, and modules - - In addition to integers and floating point numbers, - Haskell supports rational numbers. Haskell coders collect - self-contained hunks of code into - modules. The integer and floating point - numbers, and the operators we've seen so far, are packaged in - a module named Prelude, whose name we've already - seen in &ghci;'s prompt. - - (The Prelude module - is often referred to as the standard prelude, - because its contents are defined by the Haskell 98 standard. - Sometimes, it's simply shortened to the - prelude.) - - The prelude is always implicitly available; we don't need - to take any actions to use the types, values, or functions it - defines. But to use definitions from other modules, we must - import them. To use rational numbers, - the module we need to import is named Data.Ratio. We can use a &ghci; - command named :module to import - it. - - &basics.ghci:module; + + Navigating the thicket of fixity rules hunk ./en/ch02-starting.xml 409 - The notation for writing a rational number is as - follows. + It's sometimes better to leave at least some + parentheses in place, even when Haskell allows us to omit + them. Their presence can help future readers (including + ourselves) to understand what we intended. hunk ./en/ch02-starting.xml 414 - &basics.ghci:ratio; + Even more importantly, complex expressions that + rely completely on operator precedence are notorious sources + of bugs. A compiler and a human can easily end up with + different notions of what even a short, parenthesis-free + expression is supposed to do. hunk ./en/ch02-starting.xml 420 - The (%) operator above takes two - integers and constructs a rational number from them. + Here's a cautionary example of mixing different operators + of the same fixities: (*) and + (/). The following two expressions give + subtly different results. hunk ./en/ch02-starting.xml 425 - Arithmetic on rational numbers works in the same way as on - other types of number, even allowing the same - operators. - - &basics.ghci:ratarith; - - Haskell represents a rational number with the lowest - denominator it can. For example, the result of the following - expression is simplified from 254%7 to - something easier to read. - - &basics.ghci:denom; + &basics.ghci:grouping; hunk ./en/ch02-starting.xml 427 + When deciding whether to use parentheses, you can probably + rely on yourself and your readers to remember the language's + precedence rules for the most common arithmetic and logical + operators: (||) is 2; + (&&) is 3; + (+) and (-) are + 6; while (*) and + (/) are 7. For + associativities and for other operators, it's not often wise + to assume that readers will remember the rules, so parentheses + are often safest. hunk ./en/ch02-starting.xml 441 - Aside: the faces of exponentiation + Aside: the many faces of exponentiation hunk ./en/ch02-starting.xml 446 - We've already seen an exponentiation operator in Haskell: - (^) raises a number to an integer power. - The word integer is significant here: if - we try to raise a number to the power of a floating point - number using the (^) operator, exciting - things will happen. - - &basics.ghci:intpower; - - Notice from the second example that it doesn't matter - whether or not the base is an integer, only that the exponent - must be. + Mathematicians have three different ways of + looking at exponentiation, and Haskell has a specific operator + for each one. hunk ./en/ch02-starting.xml 450 - There's a further constraint on the exponent that is not - immediately obvious: it must be not just an integer, but a - non-negative integer. + The first way of looking at exponentiation is to multiply + a number a by itself a given number + n of times. Here, the base + a can be any number, but the exponent + n must be an integer, and it must be + non-negative. hunk ./en/ch02-starting.xml 457 - &basics.ghci:exponent.bad; - - If you think about the simplest definition of - exponentiation, which is a number repeatedly multiplied by - itself a given number of times, this restriction makes - sense. + &basics.ghci:intpower; hunk ./en/ch02-starting.xml 459 - Haskell's exponentiation operator follows the convention + Haskell's exponentiation operators follow the convention hunk ./en/ch02-starting.xml 466 - Haskell also provides a generalised integer exponentiation - operator, (^^). This accepts both - positive and negative exponents, following the rule that a - number raised to a negative exponent is the reciprocal of the - number raised to the positive exponent. Let's try this with - both integer and rational bases. + Haskell's type system enforces for us the requirement that + the exponent be an integer. If we try using a fractional + exponent, &ghci; will report a type error, telling us that it + expects an integral value here. + + &basics.ghci:exponent.bad; + + The second mathematical definition of + exponentiation works for both positive and negative integer + exponents. Where a positive exponent multiplies the base by + itself repeatedly, a negative exponent divides the number one + by the base repeatedly. If the base is zero, a negative + exponent thus leads to division by zero. hunk ./en/ch02-starting.xml 482 - Finally, Haskell also gives us a floating point - exponentiation operator, (**). + Finally, we have an operator that is defined for + real numbers, (**). hunk ./examples/ch02/basics.ghci 11 ---# neg +--# neg.simple hunk ./examples/ch02/basics.ghci 14 + +--# neg.error hunk ./examples/ch02/basics.ghci 17 + +--# neg.better + hunk ./examples/ch02/basics.ghci 21 +3 + (-(13 * 37)) hunk ./examples/ch02/basics.ghci 53 -True -False hunk ./examples/ch02/basics.ghci 72 -(4 * 4) + 1 -4 * 4 + 1 +1 + (4 * 4) +1 + 4 * 4 + +--# precedence + +:info (+) +:info (*) + +--# grouping + +5 * 8 / 3 +5 * (8 / 3) hunk ./examples/ch02/basics.ghci 113 -12 ^ 2.1 hunk ./examples/ch02/basics.ghci 116 -12 ^ 2 -12 ^ (-2) +12 ^ 2.1 hunk ./examples/ch02/basics.ghci 121 +12 ^ (-1) hunk ./examples/ch02/basics.ghci 126 -(12%1) ^^ (-2) +0 ^^ (-2) }