• Aucun résultat trouvé

[PDF] Introduction générale au langage de programmation Haskell [Eng] | Cours informatique

N/A
N/A
Protected

Academic year: 2021

Partager "[PDF] Introduction générale au langage de programmation Haskell [Eng] | Cours informatique"

Copied!
64
0
0

Texte intégral

(1)

Paul Hudak

YaleUniversity

Departmentof Computer Science

John Peterson

YaleUniversity

Department of Computer Science

Joseph H. Fasel

University of California

Los Alamos National Laboratory

October, 1999

Copyright c 1999 PaulHudak, JohnPeterson and JosephFasel

Permission is hereby granted, free of charge, to any person obtaining a copy of \A Gentle

Introduction to Haskell" (the Text), to deal in the Text without restriction, including without

limitationthe rights touse, copy, modify,merge,publish,distribute,sublicense,and/or sellcopies

oftheText,andto permitpersonstowhomtheTextisfurnishedto doso,subjectto thefollowing

condition: The above copyrightnoticeand thispermissionnoticeshallbeincludedin allcopiesor

substantialportions oftheText.

1 Introduction

Our purpose in writing this tutorial is not to teach programming, nor even to teach functional

programming. Rather, it is intended to serve asa supplement to the HaskellReport [4], which is

otherwisearatherdensetechnicalexposition. OurgoalistoprovideagentleintroductiontoHaskell

forsomeonewhohasexperiencewithat leastoneother language,preferablya functionallanguage

(evenifonlyan\almost-functional"languagesuchasMLorScheme). Ifthereaderwishesto learn

more about the functional programming style, we highly recommend Bird's text Introduction to

Functional Programming[1]orDavie'sAn Introduction toFunctional ProgrammingSystemsUsing

Haskell [2]. For a useful survey of functional programming languages and techniques, including

some of thelanguagedesignprinciplesusedinHaskell, see[3 ].

The Haskelllanguage hasevolved signi cantlysince its birthin1987. This tutorialdealswith

Haskell 98. Older versions of the language are now obsolete; Haskell usersare encouraged to use

Haskell 98. There are also many extensions to Haskell 98 that have been widely implemented.

Theseare notyeta formalpart oftheHaskelllanguage andare notcoveredin thistutorial.

Our general strategy forintroducinglanguage features is this: motivate the idea, de ne some

terms,givesomeexamples,andthenpointtotheReportfordetails. Wesuggest,however, thatthe

(2)

other hand, Haskell'sStandard Prelude (in AppendixA of theReport and the standard libraries

(found inthe LibraryReport [5]) contain lotsof useful examples of Haskellcode; we encourage a

thoroughreadingoncethistutorialiscompleted. Thiswillnotonlygivethereadera feelforwhat

real Haskell code looks like,butwill also familiarizeher withHaskell's standardset of prede ned

functions andtypes.

Finally, the Haskell web site, http://haskell.org, has a wealth of information about the

Haskelllanguageand its implementations.

[We have alsotakenthecourseofnotlayingoutaplethoraoflexicalsyntaxrulesattheoutset.

Rather, we introducethem incrementally asour examplesdemand, and enclose them in brackets,

as with thisparagraph. This is instark contrast to the organization of the Report, althoughthe

Report remains the authoritative source for details(references such as \x2.1" refer to sections in

theReport).]

Haskell isa typefulprogramminglanguage: 1

typesare pervasive, and thenewcomeris besto

becomingwellawareofthefullpowerandcomplexityofHaskell'stypesystemfromtheoutset. For

those whoseonlyexperience iswithrelatively\untypeful" languagessuchasPerl,Tcl,orScheme,

this may be a diÆcult adjustment; for those familiar with Java, C, Modula, or even ML, the

adjustment shouldbeeasier but stillnotinsigni cant,since Haskell's type systemis di erent and

somewhatricherthanmost. Inanycase,\typefulprogramming"ispartoftheHaskellprogramming

experience,andcannot beavoided.

2 Values, Types, and Other Goodies

Because Haskell is a purely functional language, all computations are done via the evaluation of

expressions (syntactic terms) to yield values (abstract entitiesthat we regard asanswers). Every

value has an associated type. (Intuitively, we can think of types as sets of values.) Examples

of expressions include atomic values such as the integer 5, the character 'a', and the function

\x -> x+1, aswellasstructuredvaluessuch asthelist[1,2,3] and thepair ('b',4).

Just asexpressionsdenotevalues,typeexpressionsaresyntactictermsthat denotetype values

(or justtypes). Examples of type expressionsinclude theatomic types Integer(in nite-precision

integers),Char(characters), Integer->Integer(functionsmappingIntegerto Integer),aswell

asthestructuredtypes[Integer](homogeneouslistsofintegers)and(Char,Integer)(character,

integer pairs).

AllHaskellvaluesare\ rst-class"|theymaybepassedasargumentstofunctions,returnedas

results, placedindata structures,etc. Haskelltypes, on theother hand, arenot rst-class. Types

inasensedescribevalues,and theassociation ofa valuewith itstype iscalledatyping. Usingthe

examples ofvaluesand typesabove, we writetypingsasfollows:

5 :: Integer

'a' :: Char

inc :: Integer -> Integer

[1,2,3] :: [Integer]

('b',4) :: (Char,Integer)

(3)

The \::" can be read\has type."

Functions in Haskellare normally de ned bya seriesof equations. For example, thefunction

inccan be de nedbythesingleequation:

inc n = n+1

An equation is an exampleof a declaration. Another kindof declarationis a typesignature

decla-ration (x4.4.1), withwhich we can declarean explicittypingforinc:

inc :: Integer -> Integer

We willhave muchmore to say aboutfunction de nitionsinSection3.

For pedagogical purposes, when we wish to indicate that an expression e

1

evaluates, or

\re-duces,"to anotherexpressionorvalue e

2 ,wewillwrite: e 1 ) e 2

Forexample, notethat:

inc (inc 3) ) 5

Haskell's static type system de nes the formalrelationship between typesand values (x4.1.3).

ThestatictypesystemensuresthatHaskellprogramsaretypesafe;thatis,thattheprogrammerhas

notmismatchedtypesinsome way. Forexample,wecannotgenerallyaddtogethertwocharacters,

so the expression'a'+'b' is ill-typed. The mainadvantage of statically typed languages is

well-known: Alltypeerrorsaredetectedat compile-time. Notallerrorsarecaughtbythetype system;

an expression such as 1/0 is typable but its evaluation willresult in an error at execution time.

Still,thetypesystem ndsmanyprogramerrorsat compiletime,aids theuserinreasoning about

programs, and also permitsa compiler to generate more eÆcient code (for example, no run-time

type tagsortests arerequired).

The typesystem also ensures that user-suppliedtype signatures are correct. Infact, Haskell's

type system is powerful enough to allow us to avoid writing any type signatures at all; 2

we say

that the type system infers the correct types for us. Nevertheless, judicious placement of type

signatures such as that we gave for inc is a good idea, since type signatures are a very e ective

form ofdocumentationand helpbringprogrammingerrors to light.

[The reader will note that we have capitalized identi ers that denote speci c types, such as

IntegerandChar,butnotidenti ersthatdenotevalues,suchasinc. Thisisnotjustaconvention:

itisenforcedbyHaskell'slexicalsyntax. Infact,thecaseoftheothercharactersmatters,too: foo,

fOo,and fOOareall distinctidenti ers.]

2.1 Polymorphic Types

Haskell also incorporates polymorphic types|types that are universally quanti ed in some way

over all types. Polymorphic type expressions essentially describe families of types. For example,

(8a)[a] is the family of types consisting of, for every type a, the type of lists of a. Lists of

(4)

integers(e.g. [1,2,3]),listsof characters(['a','b','c']),even listsoflistsof integers, etc.,are

all membersof thisfamily. (Note,however, that[2,'b'] is not avalidexample, sincethere is no

single typethat containsboth2and 'b'.)

[Identi erssuchasaabove arecalledtype variables, andare uncapitalizedto distinguishthem

from speci c types such as Int. Furthermore,since Haskellhas onlyuniversally quanti ed types,

there is no need to explicitly writeout the symbol for universal quanti cation, and thus we

sim-ply write [a] in the example above. In other words, all type variables are implicitly universally

quanti ed.]

Lists are a commonly used data structure infunctional languages, and are a good vehicle for

explainingthe principles of polymorphism. The list [1,2,3] in Haskell is actually shorthand for

the list 1:(2:(3:[])), where [] is the empty list and : is the in x operator that adds its rst

argument to the front of its second argument (a list). 3

Since : is right associative, we can also

writethislistas1:2:3:[].

Asanexampleofauser-de nedfunctionthatoperatesonlists,considertheproblemofcounting

thenumberofelementsina list:

length :: [a] -> Integer

length [] = 0

length (x:xs) = 1 + length xs

Thisde nitionisalmostself-explanatory. We canreadtheequationsassaying: \The lengthofthe

empty listis 0, and thelength of a list whose rst element is x and remainder is xs is 1 plusthe

length of xs." (Note the naming convention used here; xs is the plural of x, and should be read

thatway.)

Although intuitive, this example highlights an important aspect of Haskell that is yet to be

explained: pattern matching. The left-handsidesof theequationscontain patternssuchas[] and

x:xs. In a function application these patterns are matched against actual parameters in a fairly

intuitiveway([]onlymatchestheemptylist,andx:xswillsuccessfullymatchanylistwithatleast

one element, binding xto the rst element and xs to the rest of the list). If thematch succeeds,

the right-hand sideis evaluated and returned as theresult of theapplication. If it fails, the next

equation istried, and ifall equationsfail,an errorresults.

De ningfunctionsbypatternmatchingisquitecommoninHaskell,andtheusershouldbecome

familiarwiththevariouskindsofpatternsthatareallowed;wewillreturntothisissueinSection4.

The length functionis also an exampleof a polymorphicfunction. It can be applied to a list

containing elements ofanytype,forexample [Integer],[Char],or[[Integer]].

length [1,2,3] ) 3

length ['a','b','c'] ) 3

length [[1],[2],[3]] ) 3

Here aretwoother usefulpolymorphicfunctionsonliststhatwillbeusedlater. Functionhead

returns the rstelement of alist,functiontailreturns allbutthe rst.

(5)

head :: [a] -> a

head (x:xs) = x

tail :: [a] -> [a]

tail (x:xs) = xs

Unlikelength,these functionsarenotde nedforall possiblevaluesoftheirargument. Aruntime

erroroccurswhenthese functions areappliedto an emptylist.

With polymorphic types, we nd that some types are in a sense strictly more general than

othersin the sensethat theset of valuesthey de ne is larger. Forexample, the type [a] is more

generalthan [Char]. Inother words,thelatter type can be derivedfrom theformerbyasuitable

substitutionfora. Withregardtothisgeneralizationordering,Haskell'stypesystempossessestwo

important properties: First, every well-typed expression is guaranteed to have a uniqueprincipal

type (explained below), and second, the principal type can be inferred automatically (x4.1.3). In

comparisontoamonomorphicallytypedlanguagesuchasC,thereaderwill ndthatpolymorphism

improvesexpressiveness, andtypeinference lessenstheburden oftypes ontheprogrammer.

An expression'sorfunction'sprincipaltypeistheleastgeneraltypethat, intuitively,\contains

all instancesof theexpression". Forexample, theprincipaltype ofheadis [a]->a; [b]->a,a->a,

or even a are correct types, but too general, whereas something like [Integer]->Integeris too

speci c. Theexistenceof uniqueprincipaltypesisthehallmarkfeatureoftheHindley-Milner type

system, which forms the basis of the type systems of Haskell, ML, Miranda, 4

and several other

(mostly functional)languages.

2.2 User-De ned Types

We can de ne ourowntypesinHaskell usinga datadeclaration, which we introducevia a series

of examples(x4.2.1).

An important prede nedtype inHaskellis thatof truth values:

data Bool = False | True

Thetype beingde nedhereisBool,and ithasexactlytwo values: Trueand False. TypeBoolis

anexampleofa(nullary)typeconstructor,andTrueandFalseare(alsonullary)data constructors

(orjust constructors, forshort).

Similarly,we might wishto de ne acolortype:

data Color = Red | Green | Blue | Indigo | Violet

Both Bool and Color are examples of enumerated types, since they consist of a nite number of

nullarydata constructors.

Here isan exampleof a type withjustone dataconstructor:

data Point a = Pt a a

Becauseofthesingleconstructor,atypelikePointisoftencalledatupletype,sinceitisessentially

(6)

justa cartesianproduct(inthiscasebinary)ofother types. 5

Incontrast, multi-constructor types,

such asBooland Color,arecalled(disjoint)union orsumtypes.

More importantly, however, Point is an example of a polymorphic type: for any type t, it

de nes thetype ofcartesianpointsthatusetas thecoordinatetype. The Pointtypecan nowbe

seen clearly as a unarytype constructor,since from the type t it constructs a new type Point t.

(In the same sense, usingthe list example given earlier, [] is also a type constructor. Given any

type t we can \apply" [] to yield a new type [t]. The Haskellsyntax allows [] tto be written

as [t]. Similarly,-> is a type constructor: given two types t and u, t->uis the type of functions

mappingelementsof type tto elementsof typeu.)

Note that the type of the binary data constructor Pt is a -> a -> Point a, and thus the

followingtypings arevalid:

Pt 2.0 3.0 :: Point Float

Pt 'a' 'b' :: Point Char

Pt True False :: Point Bool

Onthe otherhand, an expressionsuch asPt 'a' 1is ill-typed because'a' and 1areof di erent

types.

Itisimportanttodistinguishbetweenapplyingadataconstructortoyieldavalue,andapplying

a type constructor to yielda type; theformer happens at run-time and is how we compute things

inHaskell, whereasthelatter happensat compile-time and is partof thetype system's process of

ensuring typesafety.

[TypeconstructorssuchasPointand dataconstructors suchasPtareinseparate namespaces.

Thisallows thesame name to beused forbothatype constructor and dataconstructor, asinthe

following:

data Point a = Point a a

While this may seem a little confusing at rst, it serves to make the link between a type and its

dataconstructor more obvious.]

2.2.1 Recursive Types

Typescan also be recursive,asinthetype of binarytrees:

data Tree a = Leaf a | Branch (Tree a) (Tree a)

Herewehavede nedapolymorphicbinarytreetypewhoseelementsareeitherleafnodescontaining

a value of typea,orinternalnodes (\branches") containing (recursively)two sub-trees.

When reading datadeclarationssuch asthis, rememberagain thatTreeis atypeconstructor,

whereas Branch and Leaf are data constructors. Aside from establishing a connection between

these constructors,theabovedeclaration isessentiallyde ningthefollowingtypesforBranchand

Leaf:

Branch :: Tree a -> Tree a -> Tree a

Leaf :: a -> Tree a

(7)

With this example we have de ned a type suÆciently rich to allow de ning some interesting

(recursive) functions that use it. For example, supposewe wish to de ne a functionfringe that

returnsalistofalltheelementsintheleavesofatreefromlefttoright. It'susuallyhelpfultowrite

down thetype of new functions rst; inthiscase we see thatthe type shouldbe Tree a -> [a].

That is, fringeis a polymorphicfunction that, for anytype a, maps trees of ainto listsof a. A

suitablede nitionfollows:

fringe :: Tree a -> [a]

fringe (Leaf x) = [x]

fringe (Branch left right) = fringe left ++ fringe right

Here ++is thein xoperatorthat concatenatestwo lists(itsfullde nitionwillbegiven inSection

9.1). As with the length example given earlier, the fringe function is de ned using pattern

matching,exceptthat herewesee patterns involving user-de nedconstructors: Leafand Branch.

[Notethattheformalparametersareeasilyidenti edastheonesbeginningwithlower-caseletters.]

2.3 Type Synonyms

For convenience, Haskell provides a way to de ne type synonyms; i.e. names for commonly used

types. Type synonymsarecreated usinga typedeclaration (x4.2.2). Here areseveral examples:

type String = [Char]

type Person = (Name,Address)

type Name = String

data Address = None | Addr String

Type synonyms do not de ne new types, but simply give new names for existing types. For

example,thetypePerson -> Nameis preciselyequivalentto (String,Address) -> String. The

new names are often shorter than the types they are synonymous with, but this is not the only

purposeoftypesynonyms: theycanalsoimprovereadabilityofprogramsbybeingmoremnemonic;

indeed,the above exampleshighlightthis. We caneven givenew namesto polymorphictypes:

type AssocList a b = [(a,b)]

Thisis thetype of \association lists"which associate valuesof type awiththose of typeb.

2.4 Built-in Types Are Not Special

Earlierweintroducedseveral\built-in"typessuchaslists,tuples,integers,andcharacters. Wehave

also shownhow newuser-de nedtypescan be de ned. Asidefromspecialsyntax,arethebuilt-in

typesinanywaymorespecialthantheuser-de nedones? The answerisno. Thespecialsyntaxis

forconvenience andfor consistencywithhistoricalconvention,buthasno semantic consequences.

Wecanemphasizethispointbyconsideringwhatthetypedeclarationswouldlooklikeforthese

(8)

data Char = 'a' | 'b' | 'c' | ... -- This is not valid

| 'A' | 'B' | 'C' | ... -- Haskell code!

| '1' | '2' | '3' | ...

...

Theseconstructornamesarenotsyntacticallyvalid; to xthemwe wouldhaveto writesomething

like:

data Char = Ca | Cb | Cc | ...

| CA | CB | CC | ...

| C1 | C2 | C3 | ...

...

Even though these constructors are more concise, they are quite unconventional for representing

characters.

In any case, writing \pseudo-Haskell" code in this way helps us to see through the special

syntax. We see nowthat Charis just an enumerated type consisting of a largenumberof nullary

constructors. Thinking of Char in this way makes it clear that we can pattern-match against

charactersin function de nitions,just as we would expect to be able to do so for any of a type's

constructors.

[This example also demonstrates the use of comments in Haskell; the characters -- and all

subsequent characters to the end of the line are ignored. Haskell also permits nested comments

which have theform{-::: -}and can appearanywhere(x2.2).]

Similarly,we could de neInt( xedprecision integers) andInteger by:

data Int = -65532 | ... | -1 | 0 | 1 | ... | 65532 -- more pseudo-code

data Integer = ... -2 | -1 | 0 | 1 | 2 ...

where-65532and 65532,say, arethemaximumand minimum xedprecisionintegersfora given

implementation. Int isa much larger enumeration thanChar, butit'sstill nite! Incontrast, the

pseudo-codeforInteger isintendedto convey an in niteenumeration.

Tuplesarealso easy to de neplayingthisgame:

data (a,b) = (a,b) -- more pseudo-code

data (a,b,c) = (a,b,c)

data (a,b,c,d) = (a,b,c,d)

. .

. .

. .

Each declaration above de nes a tuple type of a particular length, with (...) playing a role in

boththeexpressionsyntax(asdataconstructor)andtype-expressionsyntax(astypeconstructor).

The vertical dots after the last declaration are intended to convey an in nite number of such

declarations, re ectingthefactthattuples ofall lengths areallowed inHaskell.

Lists arealso easilyhandled, andmore interestingly,they arerecursive:

(9)

list constructor; thus [1,2,3] must be equivalent to the list 1:2:3:[]. (: is right associative.)

The typeof [] is[a],and thetype of:is a->[a]->[a].

[The way \: "is de nedhereis actuallylegalsyntax|in xconstructors are permitted indata

declarations,andaredistinguishedfromin xoperators(forpattern-matchingpurposes)bythefact

thatthey mustbeginwitha \:"(a propertytriviallysatis edby \:").]

At this point the reader should note carefully the di erences between tuples and lists, which

the above de nitions make abundantly clear. In particular, note the recursive nature of the list

type whose elements are homogeneous and of arbitrary length, and the non-recursive nature of a

(particular)tupletypewhoseelementsareheterogeneous andof xedlength. The typingrulesfor

tuplesand listsshouldnowalso be clear:

For(e 1 ,e 2 ,:::,e n ); n2,ift i isthetypeof e i

,thenthetypeofthe tupleis (t

1 ,t 2 ,:::,t n ). For[e 1 ,e 2 ,:::,e n ]; n0,each e i

must have thesame type t,and thetypeof thelistis [t].

2.4.1 List Comprehensions and Arithmetic Sequences

AswithLispdialects,listsarepervasiveinHaskell,andaswithotherfunctionallanguages,thereis

yetmoresyntacticsugartoaidintheircreation. Asidefromtheconstructorsforlistsjustdiscussed,

Haskellprovides anexpressionknownasa list comprehension that isbestexplainedbyexample:

[ f x | x <- xs ]

This expressioncan intuitivelybe read as\the list ofall f xsuch that xis drawn from xs." The

similarityto set notationis nota coincidence. Thephrasex <- xs is calleda generator, of which

more thanone is allowed,asin:

[ (x,y) | x <- xs, y <- ys ]

This listcomprehension formsthecartesian product of thetwo listsxs and ys. The elementsare

selected asifthegeneratorswere\nested"from leftto right (withtherightmostgeneratorvarying

fastest);thus, ifxs is[1,2] andys is[3,4],theresult is [(1,3),(1,4),(2,3),(2,4)].

Besides generators, boolean expressions called guards are permitted. Guards place constraints

ontheelementsgenerated. Forexample,here isaconcisede nitionofeverybody'sfavoritesorting

algorithm:

quicksort [] = []

quicksort (x:xs) = quicksort [y | y <- xs, y<x ]

++ [x]

++ quicksort [y | y <- xs, y>=x]

To further support the use of lists, Haskell has specialsyntax for arithmetic sequences, which

arebestexplained bya seriesof examples:

[1..10] ) [1,2,3,4,5,6,7,8,9,10]

[1,3..10] ) [1,3,5,7,9]

(10)

2.4.2 Strings

Asanotherexampleofsyntacticsugar forbuilt-intypes,we notethattheliteralstring "hello"is

actuallyshorthandforthelistofcharacters['h','e','l','l','o']. Indeed, thetypeof"hello"

isString,whereStringis aprede ned typesynonym (that we gave asan earlierexample):

type String = [Char]

Thismeanswe canuse prede nedpolymorphiclistfunctions to operate on strings. For example:

"hello" ++ " world" ) "hello world"

3 Functions

SinceHaskellisafunctionallanguage,onewouldexpectfunctionstoplayamajorrole,and indeed

they do. Inthissection,we lookat several aspects offunctions inHaskell.

First, considerthisde nitionof a functionwhichadds its twoarguments:

add :: Integer -> Integer -> Integer

add x y = x + y

This is an example of a curried function. 6

An application of add has the form add e

1 e 2 , and is equivalent to (add e 1 ) e 2

, since function application associates to the left. In other words,

applying add to one argument yields a new function which is then applied to the second

argu-ment. This is consistent with thetype of add, Integer->Integer->Integer,which is equivalent

toInteger->(Integer->Integer);i.e.->associatestotheright. Indeed,usingadd,wecande ne

incina di erent way fromearlier:

inc = add 1

This isan example of thepartial application of a curriedfunction, and is one way thata function

can be returned as a value. Let's consider a case in which it's useful to pass a function as an

argument. Thewell-knownmap functionisa perfect example:

map :: (a->b) -> [a] -> [b]

map f [] = []

map f (x:xs) = f x : map f xs

[Functionapplication hashigherprecedence than any in xoperator, andthus theright-hand side

of the second equation parses as (f x) : (map f xs).] The map function is polymorphic and

its type indicates clearly that its rst argument is a function; note also that the two a's must be

instantiated with the same type (likewise for the b's). As an example of the use of map, we can

increment theelementsina list:

map (add 1) [1,2,3] ) [2,3,4]

6

The name curry derives from the person who popularized the idea: Haskell Curry. To get the e ect of an

uncurriedfunction,wecoulduseatuple,asin:

(11)

These examples demonstrate the rst-class nature of functions, which when used in this way

areusuallycalled higher-order functions.

3.1 Lambda Abstractions

Insteadofusingequationstode nefunctions,wecanalsode nethem\anonymously"viaalambda

abstraction. For example, a function equivalent to inc could be written as\x -> x+1. Similarly,

thefunctionaddis equivalent to \x -> \y -> x+y. Nestedlambda abstractionssuch asthismay

bewritten usingthe equivalentshorthand notation\x y -> x+y. Infact, theequations:

inc x = x+1

add x y = x+y

arereallyshorthand for:

inc = \x -> x+1

add = \x y -> x+y

We willhave more to sayaboutsuch equivalences later.

In general, given thatxhastype t

1

andexp hastype t

2

,then\x->exphas typet

1 ->t

2 .

3.2 In x Operators

In xoperatorsarereallyjustfunctions,andcanalsobede nedusingequations. Forexample,here

isa de nitionof alist concatenationoperator:

(++) :: [a] -> [a] -> [a]

[] ++ ys = ys

(x:xs) ++ ys = x : (xs++ys)

[Lexically,in xoperators consist entirelyof \symbols,"asopposedto normal identi erswhichare

alphanumeric (x2.4). Haskell has no pre x operators, with the exception of minus (-), which is

bothin xand pre x.]

Asanotherexample, animportantin xoperatoronfunctions isthatforfunctioncomposition:

(.) :: (b->c) -> (a->b) -> (a->c)

f . g = \ x -> f (g x)

3.2.1 Sections

Since in xoperators arereallyjustfunctions,itmakes senseto be ableto partiallyapplythemas

well. InHaskellthepartialapplicationof an in xoperator iscalleda section. Forexample:

(x+)  \y -> x+y

(12)

[Theparenthesesare mandatory.]

The last form of section given above essentially coerces an in x operator into an equivalent

functional value, and is handy when passing an in x operator as an argument to a function, as

in map (+) [1,2,3] (the reader should verify that this returns a list of functions!). It is also

necessarywhen givinga functiontypesignature, asintheexamples of(++)and(.)given earlier.

We can now see that add de ned earlier is just (+), and inc is just (+1)! Indeed, these

de nitionswoulddo just ne:

inc = (+ 1)

add = (+)

Wecan coerceanin xoperatorintoafunctionalvalue,butcan wego theother way? Yes|we

simply enclose an identi er bound to a functional value in backquotes. For example, x `add` y

is the same as add x y. 7

Some functions read better this way. An example is theprede ned list

membershippredicateelem;theexpressionx `elem` xscanbereadintuitivelyas\xisanelement

of xs."

[There are some special rules regarding sections involving the pre x/in x operator -; see

(x3.5,x3.4).]

At thispoint, thereader may be confusedat havingso many ways to de ne a function! The

decisionto provide these mechanisms partly re ectshistoricalconventions, and partly re ectsthe

desireforconsistency (forexample, inthetreatment of in xvs. regular functions).

3.2.2 Fixity Declarations

A xity declaration can be given foranyin xoperatoror constructor (includingthose made from

ordinaryidenti ers,suchas`elem`). Thisdeclarationspeci esaprecedencelevelfrom0to9(with

9 being the strongest; normal application is assumed to have a precedence level of 10), and left-,

right-, ornon-associativity. Forexample,the xitydeclarationsfor++and .are:

infixr 5 ++

infixr 9 .

Both of these specify right-associativity, the rst with a precedence level of 5, the other 9. Left

associativityisspeci edvia infixl,and non-associativitybyinfix. Also, the xityofmore than

one operatormaybespeci edwiththesame xitydeclaration. Ifno xitydeclaration isgivenfor

aparticularoperator,itdefaultstoinfixl 9. (Seex5.9foradetailedde nitionoftheassociativity

rules.)

3.3 Functions are Non-strict

Supposebotis de nedby:

7

Notecarefullythat addisenclosedinbackquotes,notapostrophes asusedinthesyntaxofcharacters;i.e. 'f'is

(13)

bot = bot

In other words, bot is a non-terminating expression. Abstractly, we denote the value of a

non-terminatingexpression as? (read \bottom"). Expressions that resultin some kindof a run-time

error,suchas1/0,alsohavethisvalue. Suchanerrorisnotrecoverable: programswillnotcontinue

pasttheseerrors. ErrorsencounteredbytheI/Osystem,suchasanend-of- leerror,arerecoverable

and are handledina di erent manner. (Such an I/O erroris really notan errorat all butrather

an exception. Much more willbe said aboutexceptions inSection7.)

A functionfissaidto bestrict if,whenapplied toa nonterminatingexpression, italsofailsto

terminate. Inotherwords,fisstricti thevalueoff botis?. Formostprogramminglanguages,

all functions are strict. But this is not soin Haskell. As a simple example, consider const1,the

constant 1 function,de ned by:

const1 x = 1

The value of const1 bot in Haskell is 1. Operationally speaking, since const1 does not \need"

thevalueofits argument,it neverattemptsto evaluateit,and thusnevergetscaughtina

nonter-minating computation. For this reason, non-strict functions are also called \lazy functions", and

aresaid to evaluatetheirarguments\lazily",or\byneed".

SinceerrorandnonterminatingvaluesaresemanticallythesameinHaskell,theaboveargument

also holdsforerrors. Forexample, const1 (1/0)also evaluates properlyto 1.

Non-strict functionsare extremely usefulina varietyof contexts. The mainadvantageis that

theyfreetheprogrammerfrommanyconcernsaboutevaluationorder. Computationallyexpensive

valuesmay be passedas arguments to functions withoutfear of them being computedif they are

notneeded. An importantexampleof thisisa possiblyin nitedatastructure.

Anotherwayofexplainingnon-strictfunctionsisthatHaskellcomputesusingde nitionsrather

thantheassignments foundintraditionallanguages. Reada declarationsuch as

v = 1/0

as`de ne vas1/0'insteadof`compute1/0andstoretheresultinv'. Onlyifthevalue(de nition)

of v is needed will the division by zero error occur. By itself, this declaration does not imply

any computation. Programming using assignments requires careful attention to the ordering of

the assignments: themeaning of the program depends on theorder inwhich the assignmentsare

executed. De nitions,in contrast, are much simpler: they can be presentedin anyorder without

a ecting themeaningof theprogram.

3.4 \In nite" Data Structures

Oneadvantageofthenon-strictnatureofHaskellisthatdataconstructorsarenon-strict,too. This

should not be surprising, sinceconstructors are really just a special kindof function (the

distin-guishingfeature being that they can be usedin pattern matching). For example, the constructor

forlists,(:),is non-strict.

(14)

Figure 1: CircularFibonacci Sequence

ones = 1 : ones

Perhapsmore interestingis thefunctionnumsFrom:

numsFrom n = n : numsFrom (n+1)

ThusnumsFrom nisthein nitelistofsuccessiveintegersbeginningwithn. Fromitwecanconstruct

an in nitelistof squares:

squares = map (^2) (numsfrom 0)

(Note theuseof a section;^isthe in xexponentiation operator.)

Ofcourse,eventuallyweexpecttoextractsome niteportionofthelistforactualcomputation,

and there are lotsof prede ned functions inHaskell that do thissort of thing: take, takeWhile,

filter,and others. The de nitionofHaskellincludesa largesetofbuilt-infunctionsand types|

thisis calledthe \StandardPrelude". The completeStandard Preludeis includedin AppendixA

oftheHaskellreport;seetheportionnamedPreludeListformanyusefulfunctionsinvolvinglists.

Forexample, takeremovesthe rst nelementsfrom alist:

take 5 squares ) [0,1,4,9,16]

The de nition of onesabove is an example of a circular list. In most circumstances laziness

hasan important impacton eÆciency, sincean implementationcan be expectedto implementthe

listas atrue circularstructure, thussavingspace.

Foranotherexampleoftheuseofcircularity,theFibonaccisequencecanbecomputedeÆciently

asthefollowingin nite sequence:

fib = 1 : 1 : [ a+b | (a,b) <- zip fib (tail fib) ]

where zip is a Standard Prelude function that returns the pairwise interleaving of its two list

arguments:

zip (x:xs) (y:ys) = (x,y) : zip xs ys

zip xs ys = []

Note howfib, an in nite list,is de ned interms of itself, asifit were\chasing its tail." Indeed,

(15)

3.5 The Error Function

Haskell has a built-in function called error whose type is String->a. This is a somewhat odd

function: From its type it looks asifit is returninga value of a polymorphic type aboutwhich it

knows nothing, sinceitneverreceivesa value ofthat type asan argument!

In fact, there is one value\shared" byall types: ?. Indeed, semanticallythat is exactly what

valueisalwaysreturnedbyerror(recallthatallerrorshavevalue?). However, wecanexpectthat

areasonableimplementationwillprintthestringargumenttoerrorfordiagnosticpurposes. Thus

this function is useful when we wish to terminate a program when something has \gone wrong."

Forexample, theactualde nitionof headtaken from theStandardPreludeis:

head (x:xs) = x

head [] = error "head{PreludeList}: head []"

4 Case Expressions and Pattern Matching

Earlier we gave several examples of pattern matching in de ning functions|for example length

andfringe. Inthissectionwewilllookat thepattern-matchingprocess ingreaterdetail(x3.17). 8

Patterns are not \ rst-class;" there is only a xed set of di erent kinds of patterns. We have

alreadyseenseveral examplesofdataconstructorpatterns;bothlengthandfringede nedearlier

use such patterns,the formeron the constructors of a \built-in" type (lists),the latteron a

user-de nedtype(Tree). Indeed,matchingispermittedusingtheconstructorsofanytype,user-de ned

or not. This includes tuples, strings, numbers, characters, etc. For example, here's a contrived

functionthat matches againsta tupleof\constants:"

contrived :: ([a], Char, (Int, Float), String, Bool) -> Bool

contrived ([], 'b', (1, 2.0), "hi", True) = False

Thisexample alsodemonstrates thatnestingof patternsis permitted (toarbitrary depth).

Technically speaking, formal parameters 9

are also patterns|it's just that they never fail to

match a value. As a \sidee ect" of the successful match, the formal parameter is boundto the

value it is being matched against. For this reason patterns in any one equation are not allowed

to havemore thanone occurrence ofthesame formalparameter(a propertycalledlinearity x3.17,

x3.3, x4.4.2).

Patternssuchasformalparametersthatneverfailtomatcharesaidtobeirrefutable,incontrast

to refutable patterns which mayfailto match. The patternused inthecontrivedexampleabove

isrefutable. Therearethreeotherkindsofirrefutablepatterns,twoofwhichwewillintroducenow

(the otherwewilldelayuntilSection4.4).

8

Pattern matching in Haskell is di erent from that found in logic programming languages such as Prolog; in

particular, it canbe viewed as \one-way" matching, whereasProlog allows \two-way" matching (via uni cation),

alongwithimplicitbacktrackinginitsevaluationmechanism.

(16)

As-patterns. Sometimesitis convenient toname a patternforuseon theright-handsideof an

equation. For example,a functionthatduplicates the rst element ina listmight bewritten as:

f (x:xs) = x:x:xs

(Recallthat\:"associatestotheright.) Notethatx:xsappearsbothasapatternontheleft-hand

side, and an expressionon the right-hand side. To improve readability,we might prefer to write

x:xsjustonce, which we can achieve usingan as-patternasfollows: 10

f s@(x:xs) = x:s

Technically speaking,as-patterns always resultina successfulmatch,althoughthesub-pattern(in

thiscase x:xs) could,ofcourse, fail.

Wild-cards. Anothercommonsituationismatchingagainstavaluewereallycarenothingabout.

Forexample, thefunctions headandtailde nedin Section2.1can berewritten as:

head (x:_) = x

tail (_:xs) = xs

in which we have \advertised" the fact that we don't care what a certain part of the input is.

Eachwild-cardindependentlymatchesanything,butincontrasttoaformalparameter,each binds

nothing; forthisreasonmorethan one isallowed inan equation.

4.1 Pattern-Matching Semantics

So far we have discussed how individualpatterns are matched, how some arerefutable, some are

irrefutable, etc. But what drives the overall process? In what order are the matches attempted?

What ifnonesucceeds? This sectionaddressesthese questions.

Pattern matching can either fail, succeed or diverge. A successful match binds the formal

parametersinthepattern. Divergenceoccurswhenavalueneededbythepatterncontainsanerror

(?). The matching process itself occurs \top-down, left-to-right." Failure of a pattern anywhere

inone equationresults infailure ofthe wholeequation, and thenext equation is thentried. If all

equationsfail,the value of thefunctionapplication is?, andresultsin arun-time error.

Forexample, if [1,2] is matched against [0,bot], then 1 fails to match 0, sothe result is a

failedmatch. (Recall thatbot,de ned earlier,is avariableboundto ?.) Butif[1,2]is matched

against [bot,0],thenmatching1against botcausesdivergence(i.e. ?).

The other twist to thissetofrulesis thattop-levelpatterns mayalso havea booleanguard,as

inthisde nitionofa functionthat formsanabstract version ofa number'ssign:

sign x | x > 0 = 1

| x == 0 = 0

| x < 0 = -1

Note that a sequence of guardsmay be providedfor thesame pattern; as withpatterns, they are

evaluatedtop-down,and the rst thatevaluates to Trueresultsinasuccessful match.

10

(17)

4.2 An Example

The pattern-matching rules can have subtle e ects on the meaning of functions. For example,

considerthisde nitionof take:

take 0 _ = []

take _ [] = []

take n (x:xs) = x : take (n-1) xs

and thisslightlydi erent version(the rst 2equations have beenreversed):

take1 _ [] = []

take1 0 _ = []

take1 n (x:xs) = x : take1 (n-1) xs

Nownote thefollowing:

take 0 bot ) []

take1 0 bot ) ?

take bot [] ) ?

take1 bot [] ) []

We see that takeis \more de ned" with respect to its second argument, whereas take1 is more

de ned with respect to its rst. It is diÆcult to say in this case which de nition is better. Just

remember that incertain applications, itmaymake a di erence. (TheStandardPrelude includes

a de nitioncorresponding to take.)

4.3 Case Expressions

Patternmatching provides a way to \dispatch control" based on structural properties of a value.

In many circumstances we don't wish to de ne a function every time we need to do this, but

so far we have only shown how to do pattern matching in function de nitions. Haskell's case

expression provides a way to solve this problem. Indeed, the meaning of pattern matching in

function de nitions is speci ed in the Report in terms of case expressions, which are considered

more primitive. In particular,afunction de nitionof theform:

fp 11 ::: p 1k =e 1 ::: fp n1 ::: p nk =e n whereeach p ij

is apattern, is semanticallyequivalent to:

f x1 x2 ::: xk = case (x1, :::, xk) of (p 11 ; :::; p 1k ) ->e 1 ::: (p n1 ; :::; p nk ) ->e n

(18)

take m ys = case (m,ys) of

(0,_) -> []

(_,[]) -> []

(n,x:xs) -> x : take (n-1) xs

Apointnotmadeearlieristhat,fortypecorrectness,thetypesoftheright-handsidesofacase

expressionorsetofequationscomprisingafunctionde nitionmustallbethesame;moreprecisely,

they mustall share a commonprincipaltype.

The pattern-matching rules for case expressions are the same as we have given for function

de nitions, so there is really nothing new to learn here, other than to note the convenience that

case expressions o er. Indeed, there's one use of a case expressionthat is socommon that it has

special syntax: the conditional expression. In Haskell, conditional expressions have the familiar

form: if e 1 thene 2 elsee 3

which isreallyshort-handfor:

casee 1 of True -> e 2 False -> e 3

From thisexpansionit shouldbe clearthat e

1

musthave type Bool,ande

2 and e

3

must have the

same (butotherwise arbitrary)type. Inother words,if-then-elsewhen viewed asafunctionhas

type Bool->a->a->a.

4.4 Lazy Patterns

Thereis one other kindofpattern allowed inHaskell. Itis calleda lazy pattern, and has theform

~pat. Lazy patterns are irrefutable: matching a value v against ~pat always succeeds, regardless

of pat. Operationallyspeaking, ifan identi er inpatislater \used"on theright-hand-side,it will

beboundto that portionof thevalue thatwould resultifv wereto successfully match pat, and?

otherwise.

Lazypatternsareusefulincontexts wherein nitedatastructuresarebeingde nedrecursively.

For example, in nite lists are an excellent vehicle for writing simulation programs, and in this

context the in nite lists are often called streams. Consider the simple case of simulating the

interactions between a server process server and a client process client,where client sends a

sequence of requests to server, and server replies to each request with some kind of response.

Thissituation isshown pictoriallyinFigure 2. (Note thatclientalso takesan initialmessage as

argument.) Usingstreams to simulate the message sequences, the Haskell code corresponding to

thisdiagram is:

reqs = client init resps

resps = server reqs

Theserecursive equationsarea directlexical transliterationof thediagram.

Let usfurtherassumethat thestructureof theserverand clientlooksomethinglikethis:

(19)

Figure 2: Client-ServerSimulation

where we assume that next is a function that, given a response from the server, determines the

next request, and process is a function that processes a request from the client, returning an

appropriateresponse.

Unfortunately,thisprogramhasaseriousproblem: itwillnotproduceanyoutput! Theproblem

isthatclient,asusedintherecursivesettingofreqsandresps,attemptsamatchontheresponse

list before it has submitted its rst request! In other words, the pattern matching is being done

\too early." Onewayto xthisis to rede neclientasfollows:

client init resps = init : client (next (head resps)) (tail resps)

Althoughworkable,thissolutiondoesnotreadaswellasthatgivenearlier. A better solutionisto

usea lazypattern:

client init ~(resp:resps) = init : client (next resp) resps

Because lazy patterns are irrefutable, the match will immediately succeed, allowing the initial

request to be \submitted", in turn allowing the rst response to be generated; the engineis now

\primed",and therecursion takes careof therest.

As anexampleof thisprogram inaction,ifwede ne:

init = 0

next resp = resp

process req = req+1

thenwesee that:

take 10 reqs ) [0,1,2,3,4,5,6,7,8,9]

Asanotherexampleoftheuseoflazypatterns,considerthede nitionofFibonaccigivenearlier:

fib = 1 : 1 : [ a+b | (a,b) <- zip fib (tail fib) ]

We might try rewritingthisusinganas-pattern:

fib@(1:tfib) = 1 : 1 : [ a+b | (a,b) <- zip fib tfib ]

Thisversionof fibhas the(small) advantage of notusingtailon theright-hand side,sinceit is

availablein\destructured"form on theleft-handsideastfib.

[Thiskindof equationiscalledapatternbindingbecauseitisa top-levelequationinwhichthe

(20)

Now, using the same reasoning as earlier, we should be led to believe that this program will

notgenerateanyoutput. Curiously,however, itdoes,and thereasonissimple: inHaskell,pattern

bindingsareassumedto have an implicit~infrontof them,re ectingthemostcommon behavior

expectedofpatternbindings,andavoidingsomeanomaloussituations whicharebeyondthescope

ofthistutorial. ThusweseethatlazypatternsplayanimportantroleinHaskell,ifonlyimplicitly.

4.5 Lexical Scoping and Nested Forms

Itisoften desirabletocreate a nestedscopewithinanexpression,forthepurposeofcreating local

bindingsnotseen elsewhere|i.e. some kindof \block-structuring"form. InHaskellthere are two

ways to achievethis:

Let Expressions. Haskell's let expressions are useful whenever a nested set of bindings is

re-quired. Asa simpleexample,consider:

let y = a*b

f x = (x+y)/y

in f c + f d

The set of bindings created by a let expression is mutually recursive, and pattern bindings are

treated as lazy patterns (i.e. they carry an implicit ~). The onlykind of declarationspermitted

aretype signatures, functionbindings, and pattern bindings.

Where Clauses. Sometimes it is convenient to scope bindingsover several guarded equations,

which requiresa whereclause:

f x y | y>z = ...

| y==z = ...

| y<z = ...

where z = x*x

Notethat thiscannotbedonewitha letexpression,whichonlyscopesovertheexpressionwhich

itencloses. A whereclauseisonlyallowed at thetoplevelof asetof equationsorcaseexpression.

Thesamepropertiesandconstraintsonbindingsinletexpressionsapplytothoseinwhereclauses.

These two forms of nestedscope seemvery similar, but rememberthat a let expressionis an

expression,whereasawhereclauseisnot|itispartofthesyntaxoffunctiondeclarationsandcase

expressions.

4.6 Layout

Thereader mayhavebeenwonderinghowit isthatHaskellprogramsavoidtheuseof semicolons,

or some other kind of terminator, to mark the end of equations, declarations, etc. For example,

considerthisletexpressionfromthe lastsection:

let y = a*b

(21)

Howdoestheparser knownotto parsethisas:

let y = a*b f

x = (x+y)/y

in f c + f d

?

The answer is that Haskell uses a two-dimensional syntax called layout that essentially relies

on declarations being \lined up in columns." In the above example, note that y and f begin in

the same column. The rulesfor layout arespelledoutin detail inthe Report(x2.7, xB.3), butin

practice,use oflayoutisratherintuitive. Just remembertwo things:

First, the next character followingany of the keywords where, let, orof is what determines

the starting column for the declarations in the where, let, or case expression being written (the

rulealso appliesto where used in the class and instance declarations to be introduced inSection

5). Thuswe can begin thedeclarations on thesame lineas thekeyword, thenext line, etc. (The

do keyword, to bediscussedlater, also uses layout).

Second, just be sure thatthe startingcolumn is further to the right than the startingcolumn

associatedwiththeimmediatelysurroundingclause(otherwise itwouldbe ambiguous). The

\ter-mination"ofadeclarationhappenswhensomethingappearsatortotheleftofthestartingcolumn

associatedwiththat bindingform. 11

Layout is actually shorthand for an explicitgrouping mechanism, which deserves mention

be-cause itcan beusefulunder certaincircumstances. The letexampleabove isequivalent to:

let { y = a*b

; f x = (x+y)/y

}

in f c + f d

Note theexplicitcurlybraces and semicolons. Oneway inwhich thisexplicitnotationis usefulis

when more thanone declaration isdesired ona line;forexample, thisisa validexpression:

let y = a*b; z = a/b

f x = (x+y)/z

in f c + f d

Foranotherexample oftheexpansionof layout into explicitdelimiters, seex2.7.

The use of layout greatly reduces the syntactic clutter associated with declaration lists, thus

enhancingreadability. It iseasy to learn, and itsuse isencouraged.

5 Type Classes and Overloading

There isone nal featureofHaskell's type systemthatsets itapart from other programming

lan-guages. Thekindofpolymorphismthatwehavetalked aboutsofariscommonlycalledparametric

polymorphism. There is another kindcalled ad hoc polymorphism, better known as overloading.

Here aresome examplesof ad hoc polymorphism:

11

(22)

 The literals1, 2,etc. areoften usedto represent both xed andarbitrary precisionintegers.

 Numericoperatorssuchas+are oftende nedto workon manydi erentkinds ofnumbers.

 Theequalityoperator(==inHaskell)usuallyworksonnumbersandmanyother (butnotall)

types.

Notethat theseoverloadedbehaviors aredi erentforeachtype (infactthebehaviorissometimes

unde ned,orerror),whereasinparametricpolymorphismthetype trulydoesnotmatter (fringe,

forexample,reallydoesn'tcarewhatkindofelementsarefoundintheleavesofatree). InHaskell,

typeclassesprovideastructured way to controladhocpolymorphism,oroverloading.

Let'sstartwithasimple,butimportant,example: equality. Therearemanytypesforwhichwe

wouldlikeequalityde ned,butsomeforwhichwewouldnot. Forexample,comparingtheequality

offunctionsisgenerallyconsideredcomputationallyintractable,whereasweoftenwanttocompare

two lists forequality. 12

To highlight the issue,considerthisde nition ofthe functionelem which

testsformembershipina list:

x `elem` [] = False

x `elem` (y:ys) = x==y || (x `elem` ys)

[For thestylisticreason we discussed inSection 3.1, we have chosen to de ne elemin in xform.

== and ||arethe in xoperators forequalityand logicalor, respectively.]

Intuitivelyspeaking,thetypeofelem\ought"to be: a->[a]->Bool. Butthiswouldimplythat==

hastypea->a->Bool,eventhoughwejustsaidthatwedon'texpect== tobede nedforall types.

Furthermore, as we have noted earlier, even if == were de ned on all types, comparing two

lists forequalityis very di erent from comparingtwo integers. In this sense, we expect == to be

overloaded to carry onthese varioustasks.

Type classes convenientlysolve bothof these problems. They allow usto declare which types

areinstancesofwhichclass, andtoprovidede nitionsoftheoverloadedoperationsassociatedwith

a class. Forexample,let's de nea type classcontaining anequalityoperator:

class Eq a where

(==) :: a -> a -> Bool

Here Eq is the name of the class being de ned, and == is the single operation in the class. This

declarationmayberead\atypeaisaninstanceoftheclassEqifthereisan(overloaded)operation

==,of theappropriate type,de nedon it." (Note that== isonlyde nedon pairsofobjects ofthe

same type.)

The constraint that a type a must be an instance of the class Eq is written Eq a. Thus Eq a

is not a type expression, but rather it expresses a constraint on a type, and is called a context.

Contexts are placed at the front of type expressions. For example, the e ect of the above class

declaration isto assignthe followingtypeto ==:

(==) :: (Eq a) => a -> a -> Bool

12

Thekindofequalityweare referringto hereis \value equality,"and opposed tothe \pointerequality"found,

(23)

Thisshouldberead,\ForeverytypeathatisaninstanceoftheclassEq,==hastypea->a->Bool".

Thisisthetypethatwouldbeusedfor==intheelemexample,andindeedtheconstraintimposed

bythecontext propagates to theprincipaltype forelem:

elem :: (Eq a) => a -> [a] -> Bool

This isread, \Forevery typea thatis an instance of theclass Eq,elemhastype a->[a]->Bool".

This is just what we want|itexpresses the fact that elemis not de ned on all types, just those

forwhich we know how to compareelementsforequality.

So farsogood. ButhowdowespecifywhichtypesareinstancesoftheclassEq,and theactual

behaviorof ==on each ofthose types? Thisis donewithan instance declaration. For example:

instance Eq Integer where

x == y = x `integerEq` y

The de nition of == is called a method. The function integerEq happens to be the primitive

functionthat compares integersfor equality,but ingeneral any validexpressionis allowed on the

right-hand side, just as for any other function de nition. The overall declaration is essentially

saying: \Thetype Integer isan instance ofthe classEq,and here isthede nitionof themethod

corresponding to the operation ==." Given this declaration, we can now compare xed precision

integers forequalityusing==. Similarly:

instance Eq Float where

x == y = x `floatEq` y

allows usto compare oatingpointnumbersusing==.

Recursivetypes such asTreede nedearliercan also behandled:

instance (Eq a) => Eq (Tree a) where

Leaf a == Leaf b = a == b

(Branch l1 r1) == (Branch l2 r2) = (l1==l2) && (r1==r2)

_ == _ = False

NotethecontextEq ainthe rstline|thisisnecessarybecausetheelementsintheleaves(of type

a)arecomparedforequalityinthesecondline. Theadditionalconstraintisessentiallysayingthat

we cancompare treesofa'sforequalityaslongaswe knowhowto comparea'sforequality. Ifthe

context were omitted fromthe instancedeclaration, astatic type errorwould result.

TheHaskellReport,especiallythePrelude,containsawealthofusefulexamplesoftypeclasses.

Indeed, aclass Eqis de nedthat isslightlylarger thantheone de ned earlier:

class Eq a where

(==), (/=) :: a -> a -> Bool

x /= y = not (x == y)

Thisisan exampleofaclass withtwooperations,one forequality,theother forinequality. It also

demonstratestheuseof adefault method,inthiscasefortheinequalityoperation/=. Ifa method

for a particular operation is omitted in an instance declaration, then the default one de ned in

the class declaration, if it exists, is used instead. For example, the three instances of Eq de ned

(24)

Haskell also supports a notionof class extension. Forexample, we may wishto de ne a class

Ord which inherits all of the operationsinEq, but inaddition has a set of comparison operations

and minimumand maximumfunctions:

class (Eq a) => Ord a where

(<), (<=), (>=), (>) :: a -> a -> Bool

max, min :: a -> a -> a

Note thecontext inthe classdeclaration. We saythat Eq is a superclass of Ord (conversely,Ord

is a subclass of Eq), and any type which is an instance of Ord must also bean instance of Eq. (In

thenext Sectionwegive a fullerde nitionofOrd taken from thePrelude.)

One bene t of such class inclusions is shorter contexts: a type expression for a function that

uses operations from both the Eq and Ord classes can use the context (Ord a), rather than

(Eq a, Ord a), since Ord \implies" Eq. More importantly, methods for subclass operations can

assumetheexistenceofmethodsforsuperclassoperations. Forexample,theOrddeclarationinthe

StandardPreludecontainsthisdefaultmethod for(<):

x < y = x <= y && x /= y

Asan exampleof theuseof Ord,the principaltypingofquicksortde ned inSection2.4.1 is:

quicksort :: (Ord a) => [a] -> [a]

In other words, quicksort only operates on lists of values of ordered types. This typing for

quicksortarises because of theuseof thecomparison operators <and >=in itsde nition.

Haskellalsopermitsmultipleinheritance,sinceclassesmayhavemore thanone superclass. For

example, thedeclaration

class (Eq a, Show a) => C a where ...

creates aclass Cwhich inheritsoperationsfrombothEqand Show.

ClassmethodsaretreatedastopleveldeclarationsinHaskell. Theysharethesame namespace

as ordinary variables; a name cannot be used to denote both a class method and a variable or

methodsindi erent classes.

Contexts arealso allowed indatadeclarations;see x4.2.1.

Classmethodsmayhaveadditionalclassconstraintsonanytypevariableexcepttheonede ning

thecurrent class. Forexample, inthisclass:

class C a where

m :: Show b => a -> b

the method m requires that type b is in class Show. However, the method m could not place any

additional class constraints on type a. These would instead have to be part of the context inthe

classdeclaration.

So far, we have been using\ rst-order" types. Forexample, the type constructor Treehasso

faralways been pairedwithan argument,as inTree Integer (a tree containing Integervalues)

(25)

no values in Haskell that have this type, but such \higher-order" types can be used in class

declarations.

To begin,considerthefollowingFunctor class(taken from thePrelude):

class Functor f where

fmap :: (a -> b) -> f a -> f b

The fmap function generalizesthe map function used previously. Note that the type variable f is

applied to other types in f a and f b. Thus we would expect it to be bound to a type such as

Treewhich can be appliedto an argument. An instance of FunctorfortypeTreewould be:

instance Functor Tree where

fmap f (Leaf x) = Leaf (f x)

fmap f (Branch t1 t2) = Branch (fmap f t1) (fmap f t2)

Thisinstance declaration declaresthatTree,ratherthanTree a,is an instanceof Functor. This

capabilityisquite useful,and here demonstratestheabilityto describegeneric \container" types,

allowingfunctionssuchasfmaptoworkuniformlyoverarbitrarytrees, lists,andother datatypes.

[Typeapplicationsarewritteninthesame mannerasfunctionapplications. ThetypeT a bis

parsedas(T a) b. Typessuchastupleswhichusespecialsyntax canbewritteninan alternative

style which allows currying. For functions, (->) is a type constructor; the types f -> g and

(->) f g are the same. Similarly, the types [a] and [] a are the same. For tuples, the type

constructors (as wellasthedataconstructors) are(,),(,,),and soon.]

Asweknow,thetypesystemdetectstypingerrorsinexpressions. Butwhatabouterrorsdueto

malformedtypeexpressions? Theexpression(+) 1 2 3resultsinatypeerrorsince(+)takesonly

two arguments. Similarly,thetype Tree Int Intshould produce some sort of an error sincethe

Treetype takesonlya singleargument. So,howdoesHaskelldetect malformed typeexpressions?

The answer is a second type system which ensures the correctness of types! Each type has an

associatedkind whichensuresthat thetype isused correctly.

Type expressionsareclassi ed into di erent kindswhich take one of twopossibleforms:

 The symbol  representsthe kind of type associated withconcrete dataobjects. That is,if

thevaluev hastype t,thekindof v mustbe.

 If 

1 and 

2

are kinds, then 

1 ! 

2

is the kind of types that take a type of kind 

1 and

returna typeof kind

2 .

Thetype constructorTreehasthekind!;thetypeTree Inthasthekind. Membersofthe

Functorclass mustall have thekind!;a kindingerrorwouldresultfrom andeclaration such

as

instance Functor Integer where ...

sinceInteger hasthekind.

Kinds do not appear directly in Haskell programs. The compiler infers kinds before doing

type checking withoutanyneed for`kinddeclarations'. Kindsstayinthebackgroundof a Haskell

program exceptwhen an erroneous type signatureleads to a kinderror. Kindsare simpleenough

(26)

A Di erent Perspective. Before going on to further examplesof the useof type classes, it is

worth pointing out two other views of Haskell'stype classes. The rst is by analogy withob

ject-orientedprogramming(OOP).Inthefollowinggeneral statement aboutOOP,simplysubstituting

typeclass forclass, and typeforobject, yieldsa validsummary ofHaskell'stype classmechanism:

\Classes capturecommon setsof operations. Aparticular objectmaybean instanceof aclass,

and willhave a method corresponding to each operation. Classesmaybe arrangedhierarchically,

formingnotionsofsuperclassesandsubclasses,andpermittinginheritanceof operations/methods.

A defaultmethodmayalso be associatedwithan operation."

In contrastto OOP,it shouldbeclearthat typesarenotobjects,and inparticularthere is no

notionof an object's ortype's internal mutablestate. An advantage over some OOPlanguages is

thatmethodsinHaskellarecompletelytype-safe: anyattempttoapplyamethodto avaluewhose

type is notin the required class willbe detected at compile time instead of at runtime. In other

words,methods arenot\lookedup" at runtimebutaresimplypassedashigher-orderfunctions.

Adi erentperspectivecanbegottenbyconsideringtherelationshipbetweenparametricandad

hocpolymorphism. We have shownhow parametric polymorphismis usefulinde ningfamiliesof

typesbyuniversallyquantifyingoveralltypes. Sometimes,however,thatuniversalquanti cationis

toobroad|wewishto quantifyoversome smallersetoftypes,suchasthosetypeswhoseelements

can be compared forequality. Type classescan be seen as providing a structured way to do just

this. Indeed, we can thinkofparametric polymorphismasakindof overloadingtoo! It's justthat

the overloading occurs implicitly over all types instead of a constrained set of types (i.e. a type

class).

Comparison to Other Languages. The classes used by Haskell are similar to those used in

otherobject-orientedlanguagessuch asC++ andJava. However, there aresomesigni cant

di er-ences:

 Haskellseparatesthede nitionof a typefrom thede nitionof themethodsassociatedwith

that type. A class in C++ or Java usually de nes both a data structure (the member

variables) and thefunctions associated with the structure(the methods). In Haskell, these

de nitionsareseparated.

 Theclassmethodsde nedbya Haskellclasscorrespondto virtualfunctionsinaC++ class.

Eachinstanceofaclassprovidesitsownde nitionforeachmethod;classdefaultscorrespond

to defaultde nitionsfora virtualfunctioninthebase class.

 HaskellclassesareroughlysimilartoaJavainterface. Likeaninterfacedeclaration,aHaskell

classdeclaration de nes aprotocolforusingan objectrather thande ninganobjectitself.

 Haskelldoes notsupportthe C++ overloadingstyle inwhich functionswith di erent types

share acommon name.

(27)

 C++andJavaattachidentifyinginformation(suchasaVTable)totheruntimerepresentation

ofanobject. InHaskell,suchinformationisattachedlogicallyinsteadofphysicallytovalues,

throughthetype system.

 Thereisno accesscontrol(suchaspublicorprivateclassconstituents)builtinto theHaskell

class system. Instead, the module system must be used to hide or reveal components of a

class.

6 Types, Again

Here we examinesome ofthe more advancedaspects of typedeclarations.

6.1 The Newtype Declaration

Acommonprogrammingpracticeistode neatypewhoserepresentationisidenticaltoanexisting

one but which has a separate identity in the type system. In Haskell, the newtype declaration

creates anew typefrom an existingone. Forexample,natural numbers can be representedbythe

type Integerusingthefollowingdeclaration:

newtype Natural = MakeNatural Integer

Thiscreatesanentirelynewtype,Natural,whoseonlyconstructorcontainsasingleInteger. The

constructor MakeNaturalconverts betweenan Naturaland an Integer:

toNatural :: Integer -> Natural

toNatural x | x < 0 = error "Can't create negative naturals!"

| otherwise = MakeNatural x

fromNatural :: Natural -> Integer

fromNatural (MakeNatural i) = i

The followinginstance declarationadmits Naturalto the Numclass:

instance Num Natural where

fromInteger = toNatural

x + y = toNatural (fromNatural x + fromNatural y)

x - y = let r = fromNatural x - fromNatural y in

if r < 0 then error "Unnatural subtraction"

else toNatural r

x * y = toNatural (fromNatural x * fromNatural y)

Without thisdeclaration,NaturalwouldnotbeinNum. Instancesdeclaredfortheoldtypedonot

carry over to the new one. Indeed, the whole purpose of thistype is to introduce a di erent Num

instance. ThiswouldnotbepossibleifNatural werede ned asatypesynonym of Integer.

Allofthisworksusingadatadeclaration insteadofanewtypedeclaration. However, thedata

(28)

See section 4.2.3 of the report for a more discussion of the relation between newtype, data, and

typedeclarations.

[Except forthe keyword, thenewtype declaration uses thesame syntax asa data declaration

with a single constructor containing a single eld. This is appropriate since types de ned using

newtype arenearly identicalto those created byan ordinarydatadeclaration.]

6.2 Field Labels

The eldswithinaHaskelldatatypecanbeaccessedeitherpositionallyorbynameusing eld labels.

Considera datatype fora two-dimensionalpoint:

data Point = Pt Float Float

The two components of a Point are the rst and second arguments to the constructor Pt. A

functionsuch as

pointx :: Point -> Float

pointx (Pt x _) = x

may be used to refer to the rst component of a point in a more descriptive way, but, for large

structures,it becomes tediousto create suchfunctions byhand.

Constructors in a data declaration may be declared with associated eld names, enclosed in

braces. These eldnamesidentifythecomponentsofconstructorbynameratherthanbyposition.

Thisis an alternativeway to de nePoint:

data Point = Pt {pointx, pointy :: Float}

This data type is identical to the earlier de nition of Point. The constructor Pt is the same in

bothcases. However,thisdeclarationalsode nes two eldnames,pointxandpointy. These eld

namescanbeusedasselector functions to extractacomponentfromastructure. Inthisexample,

theselectors are:

pointx :: Point -> Float

pointy :: Point -> Float

Thisis a functionusingthese selectors:

absPoint :: Point -> Float

absPoint p = sqrt (pointx p * pointx p +

pointy p * pointy p)

Fieldlabelscanalsobeusedtoconstructnewvalues. TheexpressionPt {pointx=1, pointy=2}

isidenticaltoPt 1 2. Theuseof eldnamesinthedeclarationofadataconstructordoesnot

pre-cludethepositionalstyleof eldaccess; bothPt {pointx=1, pointy=2}andPt 1 2areallowed.

When constructing a value using eld names, some eldsmay be omitted; these absent eldsare

unde ned.

(29)

An update function uses eld values in an existing structure to ll in components of a new

structure. If p is a Point, then p {pointx=2} is a point with the same pointy as p but with

pointxreplacedby2. This isnota destructiveupdate: theupdatefunctionmerelycreatesa new

copyof theobject, llinginthespeci ed eldswithnew values.

[The bracesusedinconjunction with eldlabelsare somewhatspecial: Haskellsyntaxusually

allows braces to be omitted usingthe layout rule (described in Section4.6). However, thebraces

associatedwith eld namesmustbe explicit.]

Field names are not restricted to types with a single constructor (commonly called `record'

types). Inatypewithmultipleconstructors,selectionorupdateoperationsusing eldnamesmay

failat runtime. Thisissimilarto thebehaviorof theheadfunctionwhenappliedto anemptylist.

Field labels share thetop levelnamespace with ordinaryvariables and class methods. A eld

namecannot beusedinmorethanone datatype inscope. However,withinadatatype,the same

eld name can be used in more than one of theconstructors so long asit has thesame typingin

all cases. For example,inthisdata type

data T = C1 {f :: Int, g :: Float}

| C2 {f :: Int, h :: Bool}

the eld name fappliesto bothconstructors inT. Thusifxis of type T, thenx {f=5}willwork

forvaluescreatedbyeitherof theconstructors inT.

Field names does not change the basic nature of an algebraic data type; they are simply a

convenientsyntaxforaccessingthecomponentsofadatastructurebynameratherthanbyposition.

They make constructors with many components more manageable since elds can be added or

removed without changing every reference to the constructor. For full details of eld labels and

theirsemantics, seeSection x4.2.1.

6.3 Strict Data Constructors

DatastructuresinHaskellaregenerally lazy: thecomponentsarenotevaluateduntilneeded. This

permits structures that contain elements which, if evaluated, would lead to an error or fail to

terminate. Lazy data structures enhancethe expressivenessof Haskelland are anessential aspect

of theHaskellprogrammingstyle.

Internally,each eld of a lazy data object is wrapped up in a structure commonly referred to

as a thunk that encapsulates the computation de ningthe eld value. This thunk is not entered

untilthe value is needed; thunks which contain errors (?) do not a ect other elementsof a data

structure. For example, the tuple ('a',?) is a perfectly legal Haskell value. The 'a' may be

usedwithoutdisturbingtheothercomponent ofthetuple. Mostprogramminglanguagesarestrict

insteadoflazy: thatis,allcomponentsofadatastructurearereducedtovaluesbeforebeingplaced

inthestructure.

There are a number of overheads associated with thunks: they take time to construct and

(30)

data declarations allow speci c elds of a constructor to be evaluated immediately, selectively

suppressinglaziness. A eld marked by!ina datadeclaration isevaluated whenthe structureis

createdinstead ofdelayed ina thunk.

There area numberof situations whereitmaybe appropriateto use strictness ags:

 Structurecomponentsthataresureto beevaluatedatsomepointduringprogramexecution.

 Structurecomponentsthatare simpleto evaluateandnevercause errors.

 Typesinwhich partiallyunde nedvaluesarenotmeaningful.

Forexample, thecomplexnumberlibraryde nes theComplex typeas:

data RealFloat a => Complex a = !a :+ !a

[note the in x de nition of the constructor :+.] This de nition marks the two components, the

real and imaginary parts, of the complex number asbeing strict. This is a more compact

repre-sentationof complexnumbersbutthiscomesat theexpenseofmakinga complexnumberwithan

unde ned component, 1 :+ ? for example, totally unde ned (?). As there is no real need for

partiallyde nedcomplexnumbers,itmakessenseto usestrictness agsto achieveamore eÆcient

representation.

Strictness ags may be used to address memory leaks: structures retained by the garbage

collector butnolongernecessary forcomputation.

The strictness ag, !, can only appear in datadeclarations. It cannot be used in other type

signatures or in any other type de nitions. There is no corresponding way to mark function

argumentsasbeingstrict,althoughthesame e ect can be obtainedusingtheseqor!$functions.

See x4.2.1forfurtherdetails.

It is diÆcult to present exact guidelines for the use of strictness ags. They should be used

with caution: laziness is one of the fundamental properties of Haskelland adding strictness ags

maylead to hardto ndin niteloopsorhave otherunexpected consequences.

7 Input/Output

The I/O system in Haskell is purely functional, yet has all of the expressive power foundin

con-ventional programming languages. In imperative languages, programs proceed via actions which

examine and modifythe current state of the world. Typical actions include reading and setting

globalvariables,writing les,readinginput,and openingwindows. Such actionsarealso apart of

Haskellbutarecleanlyseparated from thepurelyfunctionalcore ofthe language.

Haskell's I/O system is built around a somewhat daunting mathematical foundation: the

monad. However, understanding of the underlying monad theory is not necessary to program

usingtheI/Osystem. Rather,monadsareaconceptualstructureintowhichI/Ohappensto t. It

Références

Documents relatifs

Specifically, given a series of observations x 1:T , which can be noisy, partially and irregularly sam- pled of a dynamical system, DAODEN supposes that the generation process of x

L’archive ouverte pluridisciplinaire HAL, est destinée au dépôt et à la diffusion de documents scientifiques de niveau recherche, publiés ou non, émanant des

Apprendre se structure autour de la somme d’informations prises dans des contextes différents supposés com- plémentaires  ».  L’exemple  de  la  visite 

Dès janvier, alors que l’Organisation mondiale de la santé s’était prononcée contre les restrictions du trafic international de voyageurs, la circulation en provenance de Chine

Dans la lutte contre Boko Haram et la gestion de la crise anglophone, tout comme dans le cadre du processus démocratique, les forces de sécurité se sont exposées à des

L’influence des think tanks sur la politique étrangère de Donald Trump peut donc être démontrée; on remarque toutefois que l’immédiateté relativement nouvelle du débat

Par ailleurs, il faut noter une différence importante entre les cas de familles victimes de la disparition individualisée d’un de leurs proches, notamment les cas de « disparus sur

Le niveau d’eau d’un bief doit respecter les conditions du rectangle de navigation (voir figure 2) tout en étant le plus proche possible du niveau normal de navigation ou nor-