haskell-98-tutorial-sources/ 0040755 0001064 0000062 00000000000 07121454527 014414 5 ustar jcp ftp haskell-98-tutorial-sources/arrays.verb 0100644 0001064 0000062 00000032377 07065471401 016603 0 ustar jcp ftp %**
A Gentle Introduction to Haskell: Arrays
%**~header
\section{Arrays}
Ideally, arrays in a functional language would be regarded simply as
functions from indices to values, but pragmatically, in order to
assure efficient access to array elements, we need to
be sure we can take advantage of the special properties of the domains
of these functions, which are isomorphic to finite contiguous subsets
of the integers. Haskell, therefore, does not treat arrays as general
functions with an application operation, but as abstract data types
with a subscript operation.
Two main approaches to functional arrays may be discerned: {\em
incremental} and {\em monolithic} definition. In the incremental
case, we have a function that produces an empty array of a given size
and another that takes an array, an index, and a value, producing a
new array that differs from the old one only at the given index.
Obviously, a naive implementation of such an array semantics would be
intolerably inefficient, either requiring a new copy of an array for each
incremental redefinition, or taking linear time for array lookup; thus, serious attempts at using this
approach employ sophisticated static analysis and clever run-time
devices to avoid excessive copying. The monolithic approach, on the
other hand, constructs an array all at once, without reference to
intermediate array values. Although Haskell has an incremental array
update operator, the main thrust of the array facility is monolithic.
Arrays are not part of the Standard Prelude---the standard library
contains the array operators. Any module using
arrays must import the @Array@ module.
\subsection{Index types}
The @Ix@ library defines a type class of array indices:
\bprog
@
class (Ord a) => Ix a where
range :: (a,a) -> [a]
index :: (a,a) a -> Int
inRange :: (a,a) -> a -> Bool
@
\eprog
Instance declarations are provided for @Int@, @Integer@, @Char@,
@Bool@, and tuples of @Ix@ types up to length 5; in addition, instances may be
automatically derived for enumerated and tuple types. We regard the
primitive types as vector indices, and tuples as indices of
multidimensional rectangular arrays. Note that the first argument of
each of the operations of class @Ix@ is a pair of indices; these are
typically the {\em bounds} (first and last indices) of an array. For
example, the bounds of a 10-element, zero-origin vector with @Int@
indices would be @(0,9)@, while a 100 by 100 1-origin matrix might have
the bounds @((1,1),(100,100))@. (In many other languages, such bounds
would be written in a form like @1:100, 1:100@, but the present
form fits the type system better, since each bound is of the same
type as a general index.)
The @range@ operation takes a bounds pair and produces the list of
indices lying between those bounds, in index order. For example,
\[ @range (0,4)@\ \ \ \ \red\ \ \ \ @[0,1,2,3,4]@ \]
\[ @range ((0,0),(1,2))@\ \ \ \ \red\ \ \ \ %
@[(0,0), (0,1), (0,2), (1,0), (1,1), (1,2)]@ \]
The @inRange@ predicate determines whether an index lies between a given
pair of bounds. (For a tuple type, this test is performed
component-wise.) Finally, the @index@ operation allows
a particular element of an array to be addressed: given a bounds pair and an
in-range index, the operation yields the zero-origin ordinal of the
index within the range; for example:
\[ @index (1,9) 2@\ \ \ \ \red\ \ \ \ @1@ \]
\[ @index ((0,0),(1,2)) (1,1)@\ \ \ \ \red\ \ \ \ @4@ \]
\subsection{Array Creation}
Haskell's monolithic array creation function forms an array from a
pair of bounds and a list of index-value pairs (an {\em association
list}):
\bprog
@
array :: (Ix a) => (a,a) -> [(a,b)] -> Array a b
@
\eprog
Here, for example, is a definition of an array of the squares
of numbers from 1 to 100:
\bprog
@
squares = array (1,100) [(i, i*i) | i <- [1..100]]
@
\eprog
This array expression is typical in using a list comprehension for
the association list; in fact, this usage results in array expressions
much like the {\em array comprehensions} of the language Id~\cite{id-manual}.
Array subscripting is performed with the infix operator @!@, and the
bounds of an array can be extracted with the function @bounds@:
\[ @squares!7@\ \ \ \ \red\ \ \ \ @49@ \]
\[ @bounds squares@\ \ \ \ \red\ \ \ \ @(1,100)@ \]
We might generalize this example by parameterizing the bounds and the
function to be applied to each index:
\bprog
@
mkArray :: (Ix a) => (a -> b) -> (a,a) -> Array a b
mkArray f bnds = array bnds [(i, f i) | i <- range bnds]
@
\eprog
Thus, we could define @squares@ as @mkArray (\i -> i * i) (1,100)@.
Many arrays are defined recursively; that is, with the values of some
elements depending on the values of others. Here, for example, we
have a function returning an array of Fibonacci numbers:
\bprog
@
fibs :: Int -> Array Int Int
fibs n = a where a = array (0,n) ([(0, 1), (1, 1)] ++
[(i, a!(i-2) + a!(i-1)) | i <- [2..n]])
@
\eprog
Another example of such a recurrence is the "n" by "n" {\em wavefront}
matrix, in which elements of the first row and first column all have
the value "1" and other elements are sums of their neighbors to the
west, northwest, and north:
\bprog
@
wavefront :: Int -> Array (Int,Int) Int
wavefront n = a where
a = array ((1,1),(n,n))
([((1,j), 1) | j <- [1..n]] ++
[((i,1), 1) | i <- [2..n]] ++
[((i,j), a!(i,j-1) + a!(i-1,j-1) + a!(i-1,j))
| i <- [2..n], j <- [2..n]])
@
\eprog
The wavefront matrix is so called because in a parallel
implementation, the recurrence dictates that the computation can begin
with the first row and column in parallel and proceed as a
wedge-shaped wave, traveling from northwest to southeast. It is
important to note, however, that no order of computation is specified
by the association list.
In each of our examples so far, we have given a unique association for
each index of the array and only for the indices within the bounds
of the array, and indeed, we must do this in general for an array
be fully defined. An association with an out-of-bounds index results
in an error; if an index is missing or appears more than once, however,
there is no immediate error, but the value of the array at that index
is then undefined, so that subscripting the array with such an index
yields an error.
\subsection{Accumulation}
We can relax the restriction that an index appear at most once in the
association list by specifying how to combine multiple values
associated with a single index; the result is called an {\em accumulated
array}:
\bprog
@
accumArray :: (Ix a) -> (b -> c -> b) -> b -> (a,a) -> [Assoc a c] -> Array a b
@
\eprog
The first argument of @accumArray@ is the {\em accumulating function},
the second is an initial value (the same for each element of the array),
and the remaining arguments are bounds and an association list, as with
the @array@ function. Typically, the accumulating function is @(+)@, and
the initial value, zero; for example, this function takes a pair of
bounds and a list of values (of an index type) and yields a histogram;
that is, a table of the number of occurrences of each value within the
bounds:
\bprog
@
hist :: (Ix a, Integral b) => (a,a) -> [a] -> Array a b
hist bnds is = accumArray (+) 0 bnds [(i, 1) | i <- is, inRange bnds i]
@
\eprog
Suppose we have a collection of measurements on the interval "[a,b)", and
we want to divide the interval into decades and count the number of
measurements within each:
\bprog
@
decades :: (RealFrac a) => a -> a -> [a] -> Array Int Int
decades a b = hist (0,9) . map decade
where decade x = floor ((x - a) * s)
s = 10 / (b - a)
@
\eprog
\subsection{Incremental updates}
In addition to the monolithic array creation functions, Haskell also
has an incremental array update function, written as the infix
operator @//@; the simplest case, an array @a@ with element @i@
updated to @v@, is written @a // [(i, v)]@. The reason for the square
brackets is that the left argument of @(//)@ is an association list,
usually containing a proper subset of the indices of the array:
\bprog
@
(//) :: (Ix a) => Array a b -> [(a,b)] -> Array a b
@
\eprog
As with the @array@ function, the indices in the association list
must be unique for the values to be defined. For example, here
is a function to interchange two rows of a matrix:
\bprog
@
swapRows :: (Ix a, Ix b, Enum b) => a -> a -> Array (a,b) c -> Array (a,b) c
swapRows i i' a = a // ([((i ,j), a!(i',j)) | j <- [jLo..jHi]] ++
[((i',j), a!(i ,j)) | j <- [jLo..jHi]])
where ((iLo,jLo),(iHi,jHi)) = bounds a
@
\eprog
The concatenation here of two separate list comprehensions over the same
list of @j@ indices is, however, a slight inefficiency; it's like
writing two loops where one will do in an imperative language.
Never fear, we can perform the equivalent of a loop fusion optimization
in Haskell:
\bprog
@
swapRows i i' a = a // [assoc | j <- [jLo..jHi],
assoc <- [((i ,j), a!(i',j)),
((i',j), a!(i, j))] ]
where ((iLo,jLo),(iHi,jHi)) = bounds a
@
\eprog
\subsection{An example: Matrix Multiplication}
We complete our introduction to Haskell arrays with the familiar
example of matrix multiplication, taking advantage of overloading
to define a fairly general function. Since only multiplication and
addition on the element type of the matrices is involved, we get
a function that multiplies matrices of any numeric type unless we
try hard not to. Additionally, if we are careful to apply only
@(!)@ and the operations of @Ix@ to indices, we get genericity over
index types, and in fact, the four row and column index types need
not all be the same. For simplicity, however, we require that
the left column indices and right row indices be of the same type, and
moreover, that the bounds be equal:
\bprog
@
matMult :: (Ix a, Ix b, Ix c, Num d) =>
Array (a,b) d -> Array (b,c) d -> Array (a,c) d
matMult x y = array resultBounds
[((i,j), sum [x!(i,k) * y!(k,j) | k <- range (lj,uj)])
| i <- range (li,ui),
j <- range (lj',uj') ]
where ((li,lj),(ui,uj)) = bounds x
((li',lj'),(ui',uj')) = bounds y
resultBounds
| (lj,uj)==(li',ui') = ((li,lj'),(ui,uj'))
| otherwise = error "matMult: incompatible bounds"
@
\eprog
As an aside, we can also define @matMult@ using @accumArray@,
resulting in a presentation that more closely resembles the
usual formulation in an imperative language:
\bprog
@
matMult x y = accumArray (+) 0 resultBounds
[((i,j), x!(i,k) * y!(k,j))
| i <- range (li,ui),
j <- range (lj',uj')
k <- range (lj,uj) ]
where ((li,lj),(ui,uj)) = bounds x
((li',lj'),(ui',uj')) = bounds y
resultBounds
| (lj,uj)==(li',ui') = ((li,lj'),(ui,uj'))
| otherwise = error "matMult: incompatible bounds"
@
\eprog
We can generalize further by making the function higher-order,
simply replacing @sum@ and @(*)@ by functional parameters:
\bprog
@
genMatMult :: (Ix a, Ix b, Ix c) =>
([f] -> g) -> (d -> e -> f) ->
Array (a,b) d -> Array (b,c) e -> Array (a,c) g
genMatMult sum' star x y =
array resultBounds
[((i,j), sum' [x!(i,k) `star` y!(k,j) | k <- range (lj,uj)])
| i <- range (li,ui),
j <- range (lj',uj') ]
where ((li,lj),(ui,uj)) = bounds x
((li',lj'),(ui',uj')) = bounds y
resultBounds
| (lj,uj)==(li',ui') = ((li,lj'),(ui,uj'))
| otherwise = error "matMult: incompatible bounds"
@
\eprog
APL fans will recognize the usefulness of functions like the following:
\bprog
@
genMatMult maximum (-)
genMatMult and (==)
@
\eprog
With the first of these, the arguments are numeric matrices, and the
"(i,j)"-th element of the result is the maximum difference between
corresponding elements of the "i"-th row and "j"-th column of the
inputs. In the second case, the arguments are matrices of any equality
type, and the result is a Boolean matrix in which element "(i,j)"
is @True@ if and only if the "i"-th row of the first argument and
"j"-th column of the second are equal as vectors.
Notice that the element types of @genMatMult@ need not be the same,
but merely appropriate for the function parameter @star@. We could
generalize still further by dropping the requirement that the first
column index and second row index types be the same; clearly, two
matrices could be considered conformable as long as the lengths
of the columns of the first and the rows of the second are equal.
The reader may wish to derive this still more general version.
({\bf Hint:} Use the @index@ operation to determine the lengths.)
%**~footer
haskell-98-tutorial-sources/classes.verb 0100644 0001064 0000062 00000041211 07121452152 016715 0 ustar jcp ftp %**A Gentle Introduction to Haskell: Classes
%**~header
\section{Type Classes and Overloading}
\label{tut-type-classes}
There is one final feature of Haskell's type system that sets it apart
from other programming languages. The kind of polymorphism that we
have talked about so far is commonly called {\em parametric}
polymorphism. There is another kind called {\em ad hoc} polymorphism,
better known as {\em overloading}. Here are some examples of {\em ad hoc}
polymorphism:
\begin{itemize}
\item The literals @1@, @2@, etc. are often used to represent both
fixed and arbitrary precision integers.
\item Numeric operators such as @+@ are often defined to work on
many different kinds of numbers.
\item The equality operator (@==@ in Haskell) usually works on
numbers and many other (but not all) types.
\end{itemize}
Note that these overloaded behaviors are different for each type
(in fact the behavior is sometimes undefined, or error), whereas in
parametric polymorphism the type truly does not matter (@fringe@, for
example, really doesn't care what kind of elements are found in the
leaves of a tree). In Haskell, {\em type classes} provide a
structured way to control {\em ad hoc} polymorphism, or overloading.
Let's start with a simple, but important, example: equality.
There are many types for which we would like equality defined, but
some for which we would not. For example, comparing the equality of
functions is generally considered computationally intractable, whereas
we often want to compare two lists for equality.\footnote{The kind of
equality we are referring to here is ``value equality,'' and opposed
to the ``pointer equality'' found, for example, with Java's @==@.
Pointer equality is not referentially transparent, and thus does not
sit well in a purely functional language.} To highlight the issue,
consider this definition of the function @elem@ which tests for
membership in a list:
\bprog
@
x `elem` [] = False
x `elem` (y:ys) = x==y || (x `elem` ys)
@
\eprog
\syn{For the stylistic reason we discussed in Section \ref{tut-lambda},
we have chosen to define @elem@ in infix form. @==@ and @||@ are the
infix operators for equality and logical or, respectively.}
\noindent Intuitively speaking, the type of @elem@ ``ought'' to be:
@a->[a]->Bool@. But this would imply that @==@ has type @a->a->Bool@,
even though we just said that we don't expect @==@ to be defined for
all types.
Furthermore, as we have noted earlier, even if @==@ were
defined on all types, comparing two lists for equality is very
different from comparing two integers. In this sense, we expect @==@
to be {\em overloaded} to carry on these various tasks.
{\em Type classes} conveniently solve both of these problems. They
allow us to declare which types are {\em instances} of which class,
and to provide definitions of the overloaded {\em operations}
associated with a class. For example, let's define a type class
containing an equality operator:
\bprog
@
class Eq a where
(==) :: a -> a -> Bool
@
\eprog
Here @Eq@ is the name of the class being defined, and @==@ is the
single operation in the class. This declaration may be read ``a type
@a@ is an instance of the class @Eq@ if there is an (overloaded)
operation @==@, of the appropriate type, defined on it.'' (Note that
@==@ is only defined on pairs of objects of the 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 {\em context}.
Contexts are placed at the front of type expressions. For example,
the effect of the above class declaration is to assign the following
type to @==@:
\bprog
@
(==) :: (Eq a) => a -> a -> Bool
@
\eprog
This should be read, ``For every type @a@ that is an instance of the
class @Eq@, @==@ has type @a->a->Bool@''. This is the type that would
be used for @==@ in the @elem@ example, and indeed the constraint
imposed by the context propagates to the principal type for @elem@:
\bprog
@
elem :: (Eq a) => a -> [a] -> Bool
@
\eprog
This is read, ``For every type @a@ that is an instance of the
class @Eq@, @elem@ has type @a->[a]->Bool@''. This is just what we
want---it expresses the fact that @elem@ is not defined on all
types, just those for which we know how to compare elements for
equality.
So far so good. But how do we specify which types are instances of
the class @Eq@, and the actual behavior of @==@ on each of those
types? This is done with an {\em instance declaration}. For example:
\bprog
@
instance Eq Integer where
x == y = x `integerEq` y
@
\eprog
The definition of @==@ is called a {\em method}. The function @integerEq@
happens to
be the primitive function that compares integers for equality, but in
general any valid expression is allowed on the right-hand side, just
as for any other function definition. The overall declaration is
essentially saying: ``The type @Integer@ is an instance of the class @Eq@,
and here is the definition of the method corresponding to the
operation @==@.'' Given this declaration, we can now compare fixed
precision integers for equality using @==@. Similarly:
\bprog
@
instance Eq Float where
x == y = x `floatEq` y
@
\eprog
allows us to compare floating point numbers using @==@.
Recursive types such as @Tree@ defined earlier can also be handled:
\bprog
@
instance (Eq a) => Eq (Tree a) where
Leaf a == Leaf b = a == b
(Branch l1 r1) == (Branch l2 r2) = (l1==l2) && (r1==r2)
_ == _ = False
@
\eprog
Note the context @Eq a@ in the first line---this is necessary because
the elements in the leaves (of type @a@) are compared for equality in
the second line. The additional constraint is essentially saying that we can
compare trees of @a@'s for equality as long as we know how to compare
@a@'s for equality. If the context were omitted from the instance
declaration, a static type error would result.
The Haskell Report, especially the Prelude, contains a wealth
of useful examples of type classes.
Indeed, a class @Eq@ is defined
that is slightly larger than the one defined earlier:
\bprog
@
class Eq a where
(==), (/=) :: a -> a -> Bool
x /= y = not (x == y)
@
\eprog
This is an example of a class with two operations, one for
equality, the other for inequality. It also demonstrates the use of a
{\em default method}, in this case for the inequality operation @/=@.
If a method for a particular operation is omitted in an instance
declaration, then the default one defined in the class declaration, if
it exists, is used instead. For example, the three instances of @Eq@
defined earlier will work perfectly well with the above class
declaration, yielding just the right definition of inequality that we
want: the logical negation of equality.
Haskell also supports a notion of {\em class extension}. For example,
we may wish to define a class @Ord@ which {\em inherits} all of the
operations in @Eq@, but in addition has a set of comparison operations
and minimum and maximum functions:
\bprog
@
class (Eq a) => Ord a where
(<), (<=), (>=), (>) :: a -> a -> Bool
max, min :: a -> a -> a
@
\eprog
Note the context in the @class@ declaration. We say that @Eq@ is a
{\em superclass} of @Ord@ (conversely, @Ord@ is a {\em subclass} of
@Eq@), and any type which is an instance of @Ord@ must also be an
instance of @Eq@.
(In the next Section we give a fuller definition of @Ord@ taken from
the Prelude.)
One benefit 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 assume the existence of methods
for superclass operations. For example, the @Ord@ declaration in the
Standard Prelude contains this default method for @(<)@:
\bprog
@
x < y = x <= y && x /= y
@
\eprog
As an example of the use of @Ord@, the principal typing of @quicksort@
defined in Section \ref{tut-list-comps} is:
\bprog
@
quicksort :: (Ord a) => [a] -> [a]
@
\eprog
In other words, @quicksort@ only operates on lists of values of
ordered types. This typing for @quicksort@ arises because of the use
of the comparison operators @<@ and @>=@ in its definition.
Haskell also permits {\em multiple inheritance}, since classes may
have more than one superclass. For example, the declaration
\bprog
@
class (Eq a, Show a) => C a where ...
@
\eprog
creates a class @C@ which inherits operations from both @Eq@ and @Show@.
Class methods are treated as top level declarations in
Haskell. They share the same namespace as ordinary variables; a name
cannot be used to denote both a class method and a variable or methods
in different classes.
Contexts are also allowed in @data@ declarations; see \see{datatype-decls}.
Class methods may have additional class constraints on any type
variable except the one defining the current class. For example, in
this class:
\bprog
@
class C a where
m :: Show b => a -> b
@
\eprog
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 in the class
declaration.
So far, we have been using ``first-order'' types. For example, the
type constructor @Tree@ has so far always been paired with an
argument, as in @Tree Integer@ (a tree containing @Integer@ values) or
@Tree a@
(representing the family of trees containing @a@ values). But @Tree@
by itself is a type constructor, and as such takes a type as an
argument and returns a type as a result. There are no values in
Haskell that have this type, but such ``higher-order'' types can be
used in @class@ declarations.
To begin, consider the following @Functor@ class (taken from the Prelude):
\bprog
@
class Functor f where
fmap :: (a -> b) -> f a -> f b
@
\eprog
The @fmap@ function generalizes the @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 @Tree@
which can be applied to an argument. An instance of @Functor@
for type @Tree@ would be:
\bprog
@
instance Functor Tree where
fmap f (Leaf x) = Leaf (f x)
fmap f (Branch t1 t2) = Branch (fmap f t1) (fmap f t2)
@
\eprog
This instance declaration declares that @Tree@, rather than @Tree a@,
is an instance of @Functor@. This capability is quite useful, and
here demonstrates the ability to describe generic ``container'' types,
allowing functions such as @fmap@ to work uniformly over arbitrary
trees, lists, and other data types.
\syn{Type applications are written in the same manner as
function applications. The type @T a b@ is parsed as @(T a) b@.
Types such as tuples which use special syntax can be written in an
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 well as the data constructors) are @(,)@,
@(,,)@, and so on.}
As we know, the type system detects typing errors in expressions. But
what about errors due to malformed type expressions? The expression
@(+) 1 2 3@ results in a type error since @(+)@ takes only two arguments.
Similarly, the type @Tree Int Int@ should produce some sort of an
error since the @Tree@ type takes only a single argument. So, how
does Haskell detect malformed type expressions? The answer is a second
type system which ensures the correctness of types! Each
type has an associated "kind" which ensures that the type is used
correctly.
Type expressions are classified into different {\em kinds} which take
one of two possible forms:
\begin{itemize}
\item The symbol $\ast$ represents the kind of type associated with
concrete data objects. That is, if the value "v" has type "t", the
kind of "v" must be $\ast$.
\item If $\kappa_1$ and $\kappa_2$ are kinds, then
$\kappa_1\rightarrow\kappa_2$ is the kind of types that take a type of
kind $\kappa_1$ and return a type of kind $\kappa_2$.
\end{itemize}
The type constructor @Tree@ has the kind $\ast\rightarrow\ast$; the
type @Tree Int@ has the kind $\ast$. Members of the @Functor@ class
must all have the kind $\ast\rightarrow\ast$; a kinding error would
result from an declaration such as
\bprog
@
instance Functor Integer where ...
@
\eprog
since @Integer@ has the kind $\ast$.
Kinds do not appear directly in Haskell programs.
The compiler infers kinds before doing type checking without any need
for `kind declarations'. Kinds stay in the background of a Haskell
program except when an erroneous type signature leads to a kind
error. Kinds are
simple enough that compilers should be able to provide descriptive
error messages when kind conflicts occur. See
\see{type-syntax} and \see{kindinference} for more information about
kinds.
\paragraph*{A Different Perspective.}
Before going on to further examples of the use of type classes, it is
worth pointing out two other views of Haskell's type classes.
The first is by analogy with object-oriented programming (OOP). In the
following general statement about OOP, simply substituting {\em type
class} for {\em class}, and {\em type} for {\em object}, yields a valid
summary of Haskell's type class mechanism:
``{\em Classes} capture common sets of operations. A particular
{\em object} may be an instance of a {\em class}, and will have a
method corresponding to each operation. {\em Classes} may be arranged
hierarchically, forming notions of super{\em classes} and sub{\em
classes}, and permitting inheritance of operations/methods.
A default method may also be associated with an operation.''
In contrast to OOP, it should be clear that types are not
objects, and in particular there is no notion of an object's or type's
internal mutable state. An advantage over some OOP languages is that
methods in
Haskell are completely type-safe: any attempt to apply a method to a
value whose type is not in the required class will be detected at
compile time instead of at runtime. In other words, methods are not
``looked up'' at runtime but are simply passed as higher-order
functions.
A different perspective can be gotten by considering the relationship
between parametric and {\em ad hoc} polymorphism. We have shown how
parametric polymorphism is useful in defining families of types by
universally quantifying over all types. Sometimes, however,
that universal quantification is too broad---we wish to quantify over
some smaller set of types, such as those types whose elements can be
compared for equality. Type classes can be seen as providing a
structured way to do just this. Indeed, we can think of parametric
polymorphism as a kind of overloading too! It's just that the
overloading occurs implicitly over all types instead of a constrained
set of types (i.e.~a type class).
\paragraph*{Comparison to Other Languages.}
The classes used by Haskell are similar to those used in other
object-oriented languages such as C++ and Java. However, there are
some significant differences:
\begin{itemize}
\item Haskell separates the definition of a type from the definition
of the methods associated with that type. A class in C++ or Java
usually defines both a data structure (the member variables) and the
functions associated with the structure (the methods). In Haskell,
these definitions are separated.
\item The class methods defined by a Haskell class correspond to
virtual functions in a C++ class. Each instance of a class provides
its own definition for each method; class defaults correspond to
default definitions for a virtual function in the base class.
\item Haskell classes are roughly similar to a Java interface. Like
an interface declaration, a Haskell class declaration defines a
protocol for using an object rather than defining an object itself.
\item Haskell does not support the C++ overloading style in which
functions with different types share a common name.
\item The type of a Haskell object cannot be implicitly coerced; there
is no universal base class such as @Object@ which values can be
projected into or out of.
\item C++ and Java attach identifying information (such as a VTable)
to the runtime representation of an object. In Haskell, such
information is attached logically instead of physically to values,
through the type system.
\item There is no access control (such as public or private class
constituents) built into the Haskell class system. Instead, the module
system must be used to hide or reveal components of a class.
\end{itemize}
%**~footer
haskell-98-tutorial-sources/end.verb 0100644 0001064 0000062 00000001566 06774446522 016060 0 ustar jcp ftp %**A Gentle Introduction to Haskell: The Next Stage
%**~eheader
\section{The Next Stage}
A large collection of Haskell resources is available on the web at
@haskell.org@. Here you will find compilers, demos, papers, and much
valuable information about Haskell and functional programming.
Haskell compilers or interpreters run on almost all hardware and
operating systems. The Hugs system is both small and portable -- it
is an excellent vehicle for learning Haskell.
\section{Acknowledgements}
Thanks to Patricia Fasel and Mark Mundt at Los Alamos, and Nick
Carriero, Charles Consel, Amir Kishon, Sandra Loosemore, Martin
Odersky, and David Rochberg at Yale University for
their quick readings of earlier drafts of this manuscript. Special
thanks to Erik Meijer for his extensive comments on the new material
added for version 1.4 of this tutorial.
%**~efooter
haskell-98-tutorial-sources/functions.verb 0100644 0001064 0000062 00000033214 07065436745 017315 0 ustar jcp ftp %**A Gentle Introduction to Haskell: Functions
%**~header
%%%
\section{Functions}
\label{tut-functions}
Since Haskell is a functional language, one would expect functions to
play a major role, and indeed they do. In this section, we look at
several aspects of functions in Haskell.
First, consider this definition of a function which adds its two
arguments:
\bprog
@
add :: Integer -> Integer -> Integer
add x y = x + y
@
\eprog
This is an example of a {\em curried} function.\footnote{The name {\em
curry} derives from the person who popularized the idea: Haskell
Curry. To get the effect of an {\em uncurried} function, we could use
a {\em tuple}, as in:
\bprog
@
add (x,y) = x + y
@
\eprog
But then we see that this version of @add@ is really just a function
of one argument!} 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 {\em left}. In other words, applying
@add@ to one argument yields a new function which is then applied to
the second argument. This is consistent with the type of @add@,
@Integer->Integer->Integer@, which is equivalent to
@Integer->(Integer->Integer)@; i.e.~@->@
associates to the {\em right}. Indeed, using @add@, we can define
@inc@ in a different way from earlier:
\bprog
@
inc = add 1
@
\eprog
This is an example of the {\em partial application} of a curried
function, and is one way that a function can be returned as a value.
Let's consider a case in which it's useful to pass a function as an
argument. The well-known @map@ function is a perfect example:
\bprog
@
map :: (a->b) -> [a] -> [b]
map f [] = []
map f (x:xs) = f x : map f xs
@
\eprog
\syn{Function application has higher precedence than any infix
operator, and thus the right-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 first 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 the elements in a list:
\[
@map (add 1) [1,2,3]@\ \ \ \ \red\ \ \ \ @[2,3,4]@
\]
These examples demonstrate the first-class nature of functions, which
when used in this way are usually called {\em higher-order} functions.
\subsection{Lambda Abstractions}
\label{tut-lambda}
Instead of using equations to define functions, we can also define
them ``anonymously'' via a {\em lambda abstraction}. For example, a
function equivalent to @inc@ could be written as @\x -> x+1@.
Similarly, the function @add@ is equivalent to @\x -> \y -> x+y@.
Nested lambda abstractions such as this may be written using the
equivalent shorthand notation @\x y -> x+y@. In fact, the equations:
\bprog
@
inc x = x+1
add x y = x+y
@
\eprog
are really shorthand for:
\bprog
@
inc = \x -> x+1
add = \x y -> x+y
@
\eprog
We will have more to say about such equivalences later.
In general, given that @x@ has type $t_1$ and @exp@ has type $t_2$,
then @\x->exp@ has type $t_1$@->@$t_2$.
\subsection{Infix Operators}
\label{tut-infix-ops}
Infix operators are really just functions, and can also be defined
using equations. For example, here is a definition of a
list concatenation operator:
\bprog
@
(++) :: [a] -> [a] -> [a]
[] ++ ys = ys
(x:xs) ++ ys = x : (xs++ys)
@
\eprog
\syn{Lexically, infix operators consist entirely of ``symbols,'' as
opposed to normal identifiers which are alphanumeric (\see{ids}).
Haskell has no prefix operators, with the exception of minus (@-@),
which is both infix and prefix.}
As another example, an important infix operator on functions is that
for {\em function composition}:
\bprog
@
(.) :: (b->c) -> (a->b) -> (a->c)
f . g = \ x -> f (g x)
@
\eprog
\subsubsection{Sections}
\label{tut-sections}
Since infix operators are really just functions, it makes sense to be
able to partially apply them as well. In Haskell the partial
application of an infix operator is called a {\em section}. For
example:
\[\ba{ccc}
@(x+)@\ \ \ \ &\equiv&\ \ \ \ @\y -> x+y@ \\
@(+y)@\ \ \ \ &\equiv&\ \ \ \ @\x -> x+y@ \\
@(+)@ \ \ \ \ &\equiv&\ \ \ \ @\x y -> x+y@
\ea\]
\syn{The parentheses are mandatory.}
The last form of section given above essentially coerces an infix
operator into an equivalent functional value, and is handy when
passing an infix 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 necessary when giving a function type
signature, as in the examples of @(++)@ and @(.)@ given earlier.
We can now see that @add@ defined earlier is just @(+)@, and @inc@ is
just @(+1)@! Indeed, these definitions would do just fine:
\bprog
@
inc = (+ 1)
add = (+)
@
\eprog
We can coerce an infix operator into a functional value, but can we go
the other way? Yes---we simply enclose an identifier bound to a
functional value in backquotes. For example, @x `add` y@ is the same
as @add x y@.\footnote{Note carefully that @add@ is enclosed in {\em
backquotes}, not {\em apostrophes} as used in the syntax of
characters; i.e. @'f'@ is a character, whereas @`f`@ is an infix
operator. Fortunately, most ASCII terminals distinguish these much
better than the font used in this manuscript.} Some functions read
better this way. An example is the predefined list membership
predicate @elem@; the expression @x `elem` xs@ can be read intuitively
as ``@x@ is an element of @xs@.''
\syn{There are some special rules regarding sections involving
the prefix/infix operator @-@; see (\see{sections},\see{operators}).}
At this point, the reader may be confused at having so many ways to
define a function! The decision to provide these mechanisms partly
reflects historical conventions, and partly reflects the desire for
consistency (for example, in the treatment of infix vs. regular
functions).
% That's all right---the designers of Haskell are too.
\subsubsection{Fixity Declarations}
A {\em fixity declaration} can be given for any infix operator or
constructor (including those made from ordinary identifiers, such as
@`elem`@).
%\footnote{Fixity declarations must only appear at the very
%beginning of a Haskell {\em module}, as will be described in Section
%\ref{tut-modules}.}
This declaration specifies a precedence level from
0 to 9 (with 9 being the strongest; normal application is assumed to
have a precedence level of 10), and left-, right-, or
non-associativity. For example, the fixity declarations for @++@ and
@.@ are:
\bprog
@
infixr 5 ++
infixr 9 .
@
\eprog
Both of these specify right-associativity, the first with a precedence
level of 5, the other 9. Left associativity is specified via
@infixl@, and non-associativity by @infix@. Also, the fixity of more
than one operator may be specified with the same fixity declaration.
If no fixity declaration is given for a particular operator, it
defaults to @infixl 9@. (See \see{fixity} for a detailed definition
of the associativity rules.)
\subsection{Functions are Non-strict}
\label{tut-non-strict}
Suppose @bot@ is defined by:
\bprog
@
bot = bot
@
\eprog
In other words, @bot@ is a non-terminating expression. Abstractly, we
denote the {\em value} of a non-terminating expression as $\bot$ (read
``bottom''). Expressions that result in some kind of a run-time
error, such as @1/0@, also have this value. Such an error is not
recoverable: programs will not continue past these errors. Errors
encountered by the I/O system, such as an end-of-file error, are
recoverable and are handled in a different manner. (Such an I/O error
is really not an error at all but rather an exception. Much more will
be said about exceptions in Section \ref{tut-io}.)
A function @f@ is said to be {\em strict} if, when applied to a
nonterminating expression, it also fails to terminate. In other
words, @f@ is strict iff the value of @f bot@ is $\bot$. For most
programming languages, {\em all} functions are strict. But this is
not so in Haskell. As a simple example, consider @const1@, the
constant 1 function, defined by:
\bprog
@
const1 x = 1
@
\eprog
The value of @const1 bot@ in Haskell is @1@. Operationally speaking,
since @const1@ does not ``need'' the value of its argument, it never
attempts to evaluate it, and thus never gets caught in a
nonterminating computation. For this reason, non-strict functions are
also called ``lazy functions'', and are said to evaluate their
arguments ``lazily'', or ``by need''.
Since error and nonterminating values are semantically the same in
Haskell, the above argument also holds for errors. For example,
@const1 (1/0)@ also evaluates properly to @1@.
Non-strict functions are extremely useful in a variety of contexts.
The main advantage is that they free the programmer from many concerns
about evaluation order. Computationally expensive values may be
passed as arguments to functions without fear of them being computed
if they are not needed. An important example of this is a possibly
{\em infinite} data structure.
Another way of explaining non-strict functions is that Haskell
computes using "definitions" rather than the "assignments" found in
traditional languages. Read a declaration such as
\bprog
@
v = 1/0
@
\eprog
as `define @v@ as @1/0@' instead of `compute @1/0@ and store the
result in @v@'. Only if the value (definition) 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: the meaning of the program depends on the order in which
the assignments are executed. Definitions, in contrast, are much
simpler: they can be presented in any order without affecting the
meaning of the program.
\subsection{``Infinite'' Data Structures}
\label{tut-infinite}
One advantage of the non-strict nature of Haskell is that data
constructors are non-strict, too. This should not be surprising,
since constructors are really just a special kind of function (the
distinguishing feature being that they can be used in pattern
matching). For example, the constructor for lists, @(:)@, is
non-strict.
Non-strict constructors permit the definition of (conceptually) {\em
infinite} data structures. Here is an infinite list of ones:
\bprog
@
ones = 1 : ones
@
\eprog
Perhaps more interesting is the function @numsFrom@:
\bprog
@
numsFrom n = n : numsFrom (n+1)
@
\eprog
Thus @numsFrom n@ is the infinite list of successive integers
beginning with @n@. From it we can construct an infinite list of
squares:
\bprog
@
squares = map (^2) (numsfrom 0)
@
\eprog
(Note the use of a section; @^@ is the infix exponentiation operator.)
Of course, eventually we expect to extract some finite portion of the
list for actual computation, and there are lots of predefined
functions in Haskell that do this sort of thing: @take@, @takeWhile@,
@filter@, and others. The definition of Haskell includes a large set
of built-in functions and types---this is called the ``Standard
Prelude''. The complete Standard Prelude is included in Appendix A of
the Haskell report; see the portion named @PreludeList@ for many
useful functions involving lists. For example, @take@ removes the first @n@
elements from a list:
\[ @take 5 squares@\ \ \ \ \red\ \ \ \ @[0,1,4,9,16]@ \]
The definition of @ones@ above is an example of a {\em circular list}.
In most circumstances laziness has an important impact on efficiency,
since an implementation can be expected to implement the list as a
true circular structure, thus saving space.
For another example of the use of circularity, the Fibonacci sequence
can be computed efficiently as the following infinite sequence:
\bprog
@
fib = 1 : 1 : [ a+b | (a,b) <- zip fib (tail fib) ]
@
\eprog
where @zip@ is a Standard Prelude function that returns the pairwise
interleaving of its two list arguments:
\bprog
@
zip (x:xs) (y:ys) = (x,y) : zip xs ys
zip xs ys = []
@
\eprog
Note how @fib@, an infinite list, is defined in terms of itself, as if
it were ``chasing its tail.'' Indeed, we can draw a picture of this
computation as shown in Figure \ref{tut-fib-fig}.
%**
%**
Figure 1
For another application of infinite lists, see Section \ref{tut-lazy-patterns}.
%*ignore
\begin{figure}
\begin{center}
\mbox{
{\epsfxsize=2.5in \epsfbox{fig1.eps}}}
\end{center}
\caption{Circular Fibonacci Sequence}
\label{tut-fib-fig}
\end{figure}
%*endignore
\subsection{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
as if it is returning a value of a polymorphic type about which it
knows nothing, since it never receives a value of that type as an
argument!
In fact, there {\em is} one value ``shared'' by all types: $\bot$.
Indeed, semantically that is exactly what value is always returned by
@error@ (recall that all errors have value $\bot$). However, we can
expect that a reasonable implementation will print the string argument
to @error@ for diagnostic purposes. Thus this function is useful when
we wish to terminate a program when something has ``gone wrong.'' For
example, the actual definition of @head@ taken from the Standard
Prelude is:
\bprog
@
head (x:xs) = x
head [] = error "head{PreludeList}: head []"
@
\eprog
%**~footer
haskell-98-tutorial-sources/goodies.verb 0100644 0001064 0000062 00000054607 07065431554 016740 0 ustar jcp ftp %**A Gentle Introduction to Haskell: Values and Types
%**~header
\section{Values, Types, and Other Goodies}
\label{tut-values-etc}
Because Haskell is a purely functional language, all computations are
done via the evaluation of {\em expressions} (syntactic terms) to
yield {\em values} (abstract entities that we regard as answers).
Every value has an associated
{\em 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@, as well as
structured values such as the list @[1,2,3]@ and the pair @('b',4)@.
Just as expressions denote values, type expressions are
syntactic terms that denote type values (or just {\em types}).
Examples of type expressions include the atomic types @Integer@
(infinite-precision integers), @Char@ (characters), @Integer->Integer@
(functions mapping @Integer@ to @Integer@), as well as the structured types
@[Integer]@ (homogeneous lists of integers) and @(Char,Integer)@
(character, integer pairs).
All Haskell values are ``first-class''---they may be passed as
arguments to functions, returned as results, placed in data
structures, etc. Haskell types, on the other hand, are {\em not}
first-class. Types in a sense describe values, and the
association of a value with its type is called a {\em typing}. Using
the examples of values and types above, we write typings as follows:
\bprog
@
5 :: Integer
'a' :: Char
inc :: Integer -> Integer
[1,2,3] :: [Integer]
('b',4) :: (Char,Integer)
@
\eprog
The ``@::@'' can be read ``has type.''
Functions in Haskell are normally defined by a series of {\em
equations}. For example, the function @inc@ can be
defined by the single equation:
\bprog
@
inc n = n+1
@
\eprog
An equation is an example of a {\em declaration}. Another kind of
declaration is a {\em type signature declaration}
(\see{type-signatures}), with which we can declare an explicit typing
for @inc@:
\bprog
@
inc :: Integer -> Integer
@
\eprog
We will have much more to say about function definitions in Section
\ref{tut-functions}.
For pedagogical purposes, when we wish to indicate that an expression
$e_1$ evaluates, or ``reduces,'' to another expression or value $e_2$,
we will write:
\[ e_1\ \ \ \ \red\ \ \ \ e_2 \]
For example, note that:
\[ @inc (inc 3)@\ \ \ \ \red\ \ \ \ @5@ \]
Haskell's static type system defines the formal relationship
between types and values (\see{type-semantics}). The static type
system ensures that Haskell programs are {\em type safe}; that is,
that the programmer has not mismatched types in some way. For
example, we cannot generally add together two characters, so the
expression @'a'+'b'@ is ill-typed. The main advantage of statically
typed languages is well-known: All type errors are detected at
compile-time. Not all errors are caught by the type system; an
expression such as @1/0@ is typable but its evaluation will result in
an error at execution time. Still, the type system finds many
program errors at compile time, aids the user in reasoning about
programs, and also permits a compiler to generate more efficient code
(for example, no run-time type tags or tests are required).
The type system also ensures that user-supplied type signatures are
correct. In fact, Haskell's type system is powerful enough to allow
us to avoid writing any type signatures at all;\footnote{With a few
exceptions to be described later.} we say that the type
system {\em 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 effective form of documentation and
help bring programming errors to light.
\syn{The reader will note that we have capitalized identifiers that
denote specific types, such as @Integer@ and @Char@, but not identifiers
that denote values, such as @inc@. This is not just a convention: it
is enforced by Haskell's lexical syntax. In fact, the case of the
other characters matters, too: @foo@, @fOo@, and @fOO@ are all
distinct identifiers.}
\subsection{Polymorphic Types}
\label{tut-polymorphism}
Haskell also incorporates {\em polymorphic} types---types that are
universally quantified in some way over all types. Polymorphic
type expressions essentially describe families of types. For
example, $(\forall$@a@$)$@[a]@ is the family of types consisting of,
for every type @a@, the type of lists of @a@. Lists of integers
(e.g.~@[1,2,3]@), lists of characters (@['a','b','c']@), even lists of
lists of integers, etc., are all members of this family. (Note,
however, that @[2,'b']@ is {\em not} a valid example, since there is
no single type that contains both @2@ and @'b'@.)
\syn{Identifiers such as @a@ above are called {\em type variables},
and are uncapitalized to distinguish them from specific types such as
@Int@. Furthermore, since Haskell has only universally quantified
types, there is no need to explicitly write out the symbol for
universal quantification, and thus we simply write @[a]@ in the
example above. In other words, all type variables are implicitly
universally quantified.}
Lists are a commonly used data structure in functional languages, and
are a good vehicle for explaining the 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 infix
operator that adds its first argument to the front of its second
argument (a list).\footnote{@:@ and @[]@ are like Lisp's @cons@ and
@nil@, respectively.} Since @:@ is right associative, we can also
write this list as @1:2:3:[]@.
As an example of a user-defined function that operates on lists,
consider the problem of counting the number of elements in a list:
\bprog
@
length :: [a] -> Integer
length [] = 0
length (x:xs) = 1 + length xs
@
\eprog
This definition is almost self-explanatory. We can read the equations
as saying: ``The length of the empty list is 0, and the length of a
list whose first element is @x@ and remainder is @xs@ is 1 plus the
length of @xs@.'' (Note the naming convention used here; @xs@ is the
plural of @x@, and should be read that way.)
Although intuitive, this example highlights an important aspect of
Haskell that is yet to be explained: {\em pattern matching}. The
left-hand sides of the equations contain patterns such as @[]@
and @x:xs@. In a function application these patterns are
matched against actual parameters in a fairly intuitive way (@[]@
only matches the empty list, and @x:xs@ will successfully match any
list with at least one element, binding @x@ to the first element and
@xs@ to the rest of the list). If the match succeeds, the right-hand
side is evaluated and returned as the result of the application. If
it fails, the next equation is tried, and if all equations fail, an
error results.
Defining functions by pattern matching is quite common in Haskell, and
the user should become familiar with the various kinds of patterns
that are allowed; we will return to this issue in
Section~\ref{tut-pattern-matching}.
The @length@ function is also an example of a polymorphic
function. It can
be applied to a list containing elements of any type, for example
@[Integer]@, @[Char]@, or @[[Integer]]@.
\[\ba{lcl}
@length [1,2,3]@ &\ \ \ \ \red\ \ \ \ & 3\\
@length ['a','b','c']@&\ \ \ \ \red\ \ \ \ & 3\\
@length [[1],[2],[3]]@ &\ \ \ \ \red\ \ \ \ & 3
\ea\]
Here are two other useful polymorphic functions on lists that will be
used later. Function @head@ returns the first element of a list,
function @tail@ returns all but the first.
\bprog
@
head :: [a] -> a
head (x:xs) = x
tail :: [a] -> [a]
tail (x:xs) = xs
@
\eprog
Unlike @length@, these functions are not defined for all possible
values of their argument. A runtime error occurs when these functions
are applied to an empty list.
With polymorphic types, we find that some types are in a sense
strictly more general than others in the sense that the set of
values they define is larger. For example, the type @[a]@
is more general than @[Char]@. In other words, the latter type can be
derived from the former by a suitable substitution for @a@. With
regard to this generalization ordering, Haskell's type system
possesses two important properties: First, every well-typed expression
is guaranteed to have a unique principal type (explained below),
and second, the principal type can be inferred automatically
(\see{type-semantics}). In comparison to a monomorphically
typed language such as C, the reader will find that
polymorphism improves expressiveness, and type inference
lessens the burden of types on the programmer.
An expression's or function's principal type is the least general type
that, intuitively, ``contains all instances of the expression''. For
example, the principal type of @head@ is @[a]->a@; @[b]->a@,
@a->a@, or even @a@ are correct types, but too general, whereas something
like @[Integer]->Integer@ is too specific. The existence of unique principal
types is the hallmark feature of the {\em Hindley-Milner type system},
which forms the basis of the type systems of Haskell, ML,
Miranda,\footnote{``Miranda'' is a trademark of Research Software,
Ltd.} and several other (mostly functional) languages.
\subsection{User-Defined Types}
\label{tut-user-types}
We can define our own types in Haskell using a @data@ declaration,
which we introduce via a series of examples (\see{datatype-decls}).
An important predefined type in Haskell is that of truth values:
\bprog
@
data Bool = False | True
@
\eprog
The type being defined here is @Bool@, and it has exactly two values:
@True@ and @False@. Type @Bool@ is an example of a (nullary) {\em type
constructor}, and @True@ and @False@ are (also nullary) {\em data
constructors} (or just {\em constructors}, for short).
Similarly, we might wish to define a color type:
\bprog
@
data Color = Red | Green | Blue | Indigo | Violet
@
\eprog
Both @Bool@ and @Color@ are examples of enumerated types, since
they consist of a finite number of nullary data constructors.
Here is an example of a type with just one data constructor:
\bprog
@
data Point a = Pt a a
@
\eprog
Because of the single constructor, a type like @Point@ is often
called a {\em tuple type}, since it is essentially just a cartesian
product (in this case binary) of other types.\footnote{Tuples are
somewhat like records in other languages.}
In contrast, multi-constructor types, such as @Bool@ and
@Color@, are called (disjoint) union or sum types.
More importantly, however, @Point@ is an example of a
polymorphic type: for any type $t$, it defines the type of cartesian
points that use $t$ as the coordinate type. The @Point@ type can now be seen
clearly as a unary type constructor, since from the type $t$ it
constructs a new type @Point @$t$. (In the same sense, using the list
example given earlier, @[]@ is also a type constructor. Given any type $t$
we can ``apply'' @[]@ to yield a new type @[@$t$@]@. The Haskell
syntax allows @[] @$t$ to be written as @[@$t$@]@. Similarly,
@->@ is a type constructor: given two types $t$ and $u$,
$t$@->@$u$ is the type of functions mapping elements of type $t$ to
elements of type $u$.)
Note that the type of the binary data constructor @Pt@ is @a -> a -> Point a@,
and thus the following typings are valid:
\bprog
@
Pt 2.0 3.0 :: Point Float
Pt 'a' 'b' :: Point Char
Pt True False :: Point Bool
@
\eprog
On the other hand, an expression such as @Pt 'a' 1@ is ill-typed
because @'a'@ and @1@ are of different types.
It is important to distinguish between applying a {\em data constructor} to
yield a {\em value}, and applying a {\em type constructor} to yield a
{\em type}; the former happens at run-time and is how we compute
things in Haskell, whereas the latter happens at compile-time and is
part of the type system's process of ensuring type safety.
\syn{Type constructors such as @Point@ and data constructors such as
@Pt@ are in separate namespaces. This allows the same name to be used
for both a type constructor and data constructor, as in the following:
\bprog
@
data Point a = Point a a
@
\eprog
While this may seem a little confusing at first, it serves to make the
link between a type and its data constructor more obvious.}
\subsubsection{Recursive Types}
\label{tut-recursive-types}
Types can also be recursive, as in the type of binary trees:
\bprog
@
data Tree a = Leaf a | Branch (Tree a) (Tree a)
@
\eprog
Here we have defined a polymorphic binary tree type whose elements
are either leaf nodes containing a value of type @a@, or internal
nodes (``branches'') containing (recursively) two sub-trees.
When reading data declarations such as this, remember again that @Tree@ is a
type constructor, whereas @Branch@ and @Leaf@ are data constructors.
Aside from establishing a connection between these constructors, the
above declaration is essentially defining the following types for
@Branch@ and @Leaf@:
\bprog
@
Branch :: Tree a -> Tree a -> Tree a
Leaf :: a -> Tree a
@
\eprog
With this example we have defined a type sufficiently rich to
allow defining some interesting (recursive) functions that use it.
For example, suppose we wish to define a function @fringe@ that
returns a list of all the elements in the leaves of a tree from left
to right. It's usually helpful to write down the type of new
functions first; in this case we see that the type should be
@Tree a -> [a]@. That is, @fringe@ is a polymorphic function that,
for any type @a@, maps trees of @a@ into lists of @a@. A suitable
definition follows:
\bprog
@
fringe :: Tree a -> [a]
fringe (Leaf x) = [x]
fringe (Branch left right) = fringe left ++ fringe right
@
\eprog
Here @++@ is the infix operator that concatenates two lists (its full
definition will be given in Section \ref{tut-monadic-classes}). As
with the @length@ example given earlier, the @fringe@ function is
defined using pattern matching, except that here we see patterns involving
user-defined constructors: @Leaf@ and @Branch@. \syn{Note that the
formal parameters are easily identified as the ones beginning with
lower-case letters.}
\subsection{Type Synonyms}
\label{tut-type-synonyms}
For convenience, Haskell provides a way to define {\em type synonyms};
i.e.~names for commonly used types. Type synonyms are created using a
@type@ declaration (\see{type-synonym-decls}). Here are several
examples:
\bprog
@
type String = [Char]
type Person = (Name,Address)
type Name = String
data Address = None | Addr String
@
\eprog
Type synonyms do not define new types, but simply give new names
for existing types. For example, the type @Person -> Name@ is
precisely equivalent to @(String,Address) -> String@. The new names
are often shorter than the types they are synonymous with, but this is
not the only purpose of type synonyms: they can also improve
readability of programs by being more mnemonic; indeed, the above
examples highlight this. We can even give new names to polymorphic
types:
\bprog
@
type AssocList a b = [(a,b)]
@
\eprog
This is the type of ``association lists'' which associate values of
type @a@ with those of type @b@.
\subsection{Built-in Types Are Not Special}
\label{tut-built-ins}
Earlier we introduced several ``built-in'' types such as lists,
tuples, integers, and characters. We have also shown how new
user-defined types can be defined. Aside from special syntax, are
the built-in types in any way more special than the user-defined ones?
The answer is {\em no}. The special syntax is for convenience and for
consistency with historical convention, but has no semantic
consequences.
We can emphasize this point by considering what the type
declarations would look like for these built-in types if in fact we
were allowed to use the special syntax in defining them. For example,
the @Char@ type might be written as:
\bprog
@
data Char = 'a' | 'b' | 'c' | ... -- This is not valid
| 'A' | 'B' | 'C' | ... -- Haskell code!
| '1' | '2' | '3' | ...
...
@
\eprog
These constructor names are not syntactically valid; to fix them we
would have to write something like:
\bprog
@
data Char = Ca | Cb | Cc | ...
| CA | CB | CC | ...
| C1 | C2 | C3 | ...
...
@
\eprog
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 now that @Char@ is just an
enumerated type consisting of a large number of nullary constructors.
Thinking of @Char@ in this way makes it clear that we can
pattern-match against characters in function definitions, just as we
would expect to be able to do so for any of a type's constructors.
\syn{This example also demonstrates the use of {\em comments} in
Haskell; the characters @--@ and all subsequent characters to the end
of the line are ignored. Haskell also permits {\em nested} comments
which have the form @{-@$\ldots$@-}@ and can appear anywhere
(\see{lexemes}).}
Similarly, we could define @Int@ (fixed precision integers) and
@Integer@ by:
\bprog
@
data Int = -65532 | ... | -1 | 0 | 1 | ... | 65532 -- more pseudo-code
data Integer = ... -2 | -1 | 0 | 1 | 2 ...
@
\eprog
where @-65532@ and @65532@, say, are the maximum and minimum fixed
precision integers for a given implementation. @Int@ is a much larger
enumeration than @Char@, but it's still finite! In contrast, the
pseudo-code for @Integer@
is intended to convey an {\em infinite} enumeration.
Tuples are also easy to define playing this game:
\bprog
@
data (a,b) = (a,b) -- more pseudo-code
data (a,b,c) = (a,b,c)
data (a,b,c,d) = (a,b,c,d)
. .
. .
. .
@
\eprog
Each declaration above defines a tuple type of a particular length,
with @(...)@ playing a role in both the expression syntax (as data
constructor) and type-expression syntax (as type constructor). The
vertical dots after the last declaration are intended to convey an
infinite number of such declarations, reflecting the fact that tuples
of all lengths are allowed in Haskell.
Lists are also easily handled, and more interestingly, they are recursive:
\bprog
@
data [a] = [] | a : [a] -- more pseudo-code
@
\eprog
We can now see clearly what we described about lists earlier: @[]@ is
the empty list, and @:@ is the infix list constructor; thus @[1,2,3]@
must be equivalent to the list @1:2:3:[]@. (@:@ is right
associative.) The type of @[]@ is @[a]@, and the type of @:@ is
@a->[a]->[a]@.
\syn{The way ``@:@'' is defined here is actually legal syntax---infix
constructors are permitted in @data@ declarations, and are
distinguished from infix operators (for pattern-matching purposes) by
the fact that they must begin with a ``@:@'' (a property trivially
satisfied by ``@:@'').}
At this point the reader should note carefully the differences between
tuples and lists, which the above definitions 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) tuple type whose elements are
heterogeneous and of fixed length. The typing rules for tuples and
lists should now also be clear:
For $@(@e_1@,@e_2@,@\ldots@,@e_n@)@,\ n\geq2$, if $t_i$ is the
type of $e_i$, then the type of the tuple is
$@(@t_1@,@t_2@,@\ldots@,@t_n@)@$.
For $@[@e_1@,@e_2@,@\ldots@,@e_n@]@,\ n\geq0$, each $e_i$ must have
the same type $t$, and the type of the list is @[@$t$@]@.
\subsubsection{List Comprehensions and Arithmetic Sequences}
\label{tut-list-comps}
As with Lisp dialects, lists are pervasive in Haskell, and as with
other functional languages, there is yet more syntactic sugar to aid
in their creation. Aside from the constructors for lists just
discussed, Haskell provides an expression known as a {\em list
comprehension} that is best explained by example:
\bprog
@
[ f x | x <- xs ]
@
\eprog
This expression can intuitively be read as ``the list of all @f x@
such that @x@ is drawn from @xs@.'' The similarity to set notation is
not a coincidence. The phrase @x <- xs@ is called a {\em generator},
of which more than one is allowed, as in:
\bprog
@
[ (x,y) | x <- xs, y <- ys ]
@
\eprog
This list comprehension forms the cartesian product of the two lists
@xs@ and @ys@. The elements are selected as if the generators were
``nested'' from left to right (with the rightmost generator varying
fastest); thus, if @xs@ is @[1,2]@ and @ys@ is @[3,4]@, the result is
@[(1,3),(1,4),(2,3),(2,4)]@.
Besides generators, boolean expressions called {\em guards} are
permitted. Guards place constraints on the elements generated. For
example, here is a concise definition of everybody's favorite sorting
algorithm:
\bprog
@
quicksort [] = []
quicksort (x:xs) = quicksort [y | y <- xs, y=x]
@
\eprog
To further support the use of lists, Haskell has special syntax for
{\em arithmetic sequences}, which are best explained by a series of
examples:
\[\ba{lcl}
@[1..10]@ \ \ \ &\red&\ \ \ @[1,2,3,4,5,6,7,8,9,10]@\\
@[1,3..10]@\ \ \ &\red&\ \ \ @[1,3,5,7,9]@\\
% @[1..]@ \ \ \ &\red&\ \ \ @[1,2,3,4,5, ...@\ \ \ \ \
% \mbox{(infinite sequence)}\\
@[1,3..]@ \ \ \ &\red&\ \ \ @[1,3,5,7,9, ...@\ \ \ \ \
\mbox{(infinite sequence)}\\
\ea\]
More will be said about arithmetic sequences in Section
\ref{tut-enum-classes}, and ``infinite lists'' in Section
\ref{tut-infinite}.
\subsubsection{Strings}
\label{tut-strings}
As another example of syntactic sugar for built-in types, we
note that the literal string @"hello"@ is actually shorthand for the
list of characters @['h','e','l','l','o']@. Indeed, the type of
@"hello"@ is @String@, where @String@ is a predefined type synonym
(that we gave as an earlier example):
\bprog
@
type String = [Char]
@
\eprog
This means we can use predefined polymorphic list functions to operate
on strings. For example:
\[
@"hello" ++ " world"@\ \ \ \ \red\ \ \ \ @"hello world"@
\]
%**~footer
haskell-98-tutorial-sources/haskell-tutorial.verb 0100644 0001064 0000062 00000004157 06774446522 020575 0 ustar jcp ftp
\documentclass[twoside,11pt]{article}
\textheight=8.5in
\textwidth=6.5in
\topmargin=-.3in
\oddsidemargin=0in
\evensidemargin=0in
\parskip=6pt plus2pt minus2pt
\pagestyle{headings}
\input{report-refs}
\usepackage{epsf}
% \renewcommand{\thepage}{T-\arabic{page}}
\newcommand{\folks}[1]{\begin{quote}\sf#1\end{quote}}
\newcommand{\bc}{\begin{center}}
\newcommand{\ec}{\end{center}}
\newcommand{\be}{\begin{enumerate}}
\newcommand{\ee}{\end{enumerate}}
\newcommand{\ba}{\begin{array}}
\newcommand{\ea}{\end{array}}
\newcommand{\x}{\times}
\newcommand{\lam}{\lambda}
\newcommand{\la}{\leftarrow}
\newcommand{\ra}{\rightarrow}
\newcommand{\red}{\Rightarrow}
\newcommand{\see}[1]{\S\ref{#1}}
\newcommand{\syn}[1]{[#1]}
\newcommand{\bprog}{%
\par\noindent\begin{tabular}{@@{\hspace*{17pt}}l@@{}}}
\newcommand{\eprog}{%
\end{tabular}\\[\parskip]}
\newcommand{\eprogNoSkip}{%
\end{tabular}}
\newcommand{\anchor}[2]{#2}
\begin{document}
\title{A Gentle Introduction to Haskell 98}
\author{Paul Hudak\\
Yale University\\
Department of Computer Science
\and
John Peterson\\
Yale University\\
Department of Computer Science
\and
Joseph H. Fasel\\
University of California\\
Los Alamos National Laboratory}
\date{October, 1999}
\maketitle
Copyright \copyright\ 1999 Paul Hudak, John Peterson and Joseph Fasel
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 limitation the
rights to use, copy, modify, merge, publish, distribute, sublicense,
and/or sell copies of the Text, and to permit persons to whom the
Text is furnished to do so, subject to the following condition:
The above copyright notice and this permission notice shall be
included in all copies or substantial portions of the Text.
\input{intro}
\input{goodies}
\input{functions}
\input{patterns}
\input{classes}
\input{moretypes}
\input{io}
\input{stdclasses}
\input{monads}
\input{numbers}
\input{modules}
\input{pitfalls}
\input{arrays}
\input{end}
\bibliographystyle{plain}
\bibliography{tut}
\end{document}
haskell-98-tutorial-sources/intro.verb 0100644 0001064 0000062 00000006670 07121451342 016425 0 ustar jcp ftp %**A Gentle Introduction to Haskell: Introduction
%**~sheader
\section{Introduction}
\label{tut-intro}
Our purpose in writing this tutorial is not to teach programming, nor
even to teach functional programming. Rather, it is intended to serve
as a supplement to the Haskell Report \cite{haskell-98}, which is
otherwise a rather dense technical exposition. Our goal is to provide
a gentle introduction to Haskell for someone who has experience with
at least one other language, preferably a functional language (even if
only an ``almost-functional'' language such as ML or Scheme).
If the
reader wishes to learn more about the functional programming style, we
highly recommend Bird's text {\em Introduction to
Functional Programming} \cite{bird98} or Davie's {\em An Introduction
to Functional Programming Systems Using Haskell} \cite{davie92}.
For a useful survey of functional programming languages
and techniques, including some of the language design principles used
in Haskell, see \cite{huda89a}.
The Haskell language has evolved significantly since its birth in 1987.
This tutorial deals with \anchor{http://haskell.org/report}
{Haskell 98}. Older versions of the language are now obsolete;
Haskell users are encouraged to use Haskell 98. There are also many
extensions to Haskell 98 that have been widely implemented. These are
not yet a formal part of the Haskell language and are not covered in
this tutorial.
Our general strategy for introducing language features is this:
motivate the idea, define some terms, give some examples, and then
point to the Report for details. We suggest, however, that the reader
completely ignore the details until the {\em Gentle Introduction} has been
completely read. On the other hand, Haskell's Standard Prelude (in
Appendix A of the Report and the standard libraries
(found in the \anchor{http://haskell.org/library}
Library Report~\cite{haskell-libs}) contain
lots of useful examples of Haskell code; we
encourage a thorough reading once this tutorial is completed. This
will not only give the reader a feel for what real Haskell code looks
like, but will also familiarize her with Haskell's standard set of
predefined functions and types.
Finally, the Haskell web site, \anchor{http://haskell.org}{{\tt
http://haskell.org}}, has a wealth of information about the Haskell
language and its implementations.
\syn{We have also taken the course of not laying out a plethora of
lexical syntax rules at the outset. Rather, we introduce them
incrementally as our examples demand, and enclose them in brackets, as
with this paragraph. This is in stark contrast to the organization of
the Report, although the Report remains the authoritative source for
details (references such as ``\S 2.1'' refer to sections in the
Report).}
Haskell is a {\em typeful} programming language:\footnote{Coined by Luca Cardelli.} types are pervasive, and the newcomer is best off
becoming well aware of the full power and complexity of Haskell's type
system from the outset. For those whose only experience is with
relatively ``untypeful'' languages such as Perl, Tcl, or Scheme, this may be
a difficult adjustment; for those familiar with Java, C, Modula, or
even ML, the adjustment should be easier but still not insignificant,
since Haskell's type system is different and somewhat richer than
most. In any case, ``typeful programming'' is part of the Haskell
programming experience, and cannot be avoided.
% \maybeInclude{intro-extra}
%**~sfooter
haskell-98-tutorial-sources/io.verb 0100644 0001064 0000062 00000041405 07065470201 015676 0 ustar jcp ftp %**A Gentle Introduction to Haskell: IO
%**~header
\section{Input/Output}
\label{tut-io}
The I/O system in Haskell is purely functional, yet has all of the
expressive power found in conventional programming languages. In
imperative languages, programs proceed via "actions" which examine and
modify the current state of the world. Typical actions include
reading and setting global variables, writing files, reading input,
and opening windows. Such actions are also a part of Haskell but are
cleanly separated from the purely functional core of the 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 using the I/O system.
Rather, monads are a conceptual structure into which I/O happens to fit.
It is no more necessary to understand monad theory to perform Haskell
I/O than it is to understand group theory to do simple arithmetic. A
detailed explanation of monads is found in Section \ref{tut-monads}.
The monadic operators that the I/O system
is built upon are also used for other purposes; we will look
more deeply into monads later. For now, we will avoid the term monad
and concentrate on the use of the I/O system. It's best to think of
the I/O monad as simply an abstract data type.
Actions are defined rather than invoked within the expression
language of Haskell.
Evaluating the definition of an action doesn't actually
cause the action to happen. Rather, the invocation of actions takes
place outside of the expression evaluation we have considered up to
this point.
Actions are either atomic, as defined in system primitives, or
are a sequential composition of other actions.
The I/O monad contains primitives which
build composite actions, a process similar to joining
statements in sequential order using `@;@' in other languages. Thus
the monad serves as the glue which binds together the actions in a
program.
\subsection{Basic I/O Operations}
Every I/O action returns a value. In the type system, the return value is
`tagged' with @IO@ type, distinguishing actions from other
values. For example, the type
of the function @getChar@ is:
\bprog
@
getChar :: IO Char
@
\eprog
The @IO Char@ indicates that @getChar@, when invoked, performs
some action which returns a character. Actions which return no
interesting values use the unit type, @()@. For example, the
@putChar@ function:
\bprog
@
putChar :: Char -> IO ()
@
\eprog
takes a character as an argument but returns nothing useful.
The unit type is similar to @void@ in other languages.
Actions are sequenced using an operator that has a
rather cryptic name: @>>=@ (or `bind'). Instead of using this
operator directly, we choose some syntactic sugar, the @do@
notation, to hide these sequencing operators under a syntax resembling
more conventional languages.
The @do@ notation can be trivially expanded to @>>=@,
as described in \see{do-expressions}.
The keyword @do@ introduces a sequence of statements
which are executed in order. A statement is either an action,
a pattern bound to the result of an action using @<-@, or
a set of local definitions introduced using @let@. The @do@ notation
uses layout in the same manner as @let@ or @where@ so we
can omit braces and semicolons with proper indentation. Here is a
simple program to read and then print a character:
\bprog
@
main :: IO ()
main = do c <- getChar
putChar c
@
\eprog
The use of the name @main@ is important: @main@
is defined to be the entry point of a Haskell program (similar
to the @main@ function in C), and
must have an @IO@ type, usually @IO ()@. (The name @main@ is special
only in the module @Main@; we will have more to say about modules
later.) This
program performs two actions in
sequence: first it reads in a character, binding the result to the
variable c, and then prints the character. Unlike a @let@ expression
where variables are scoped over all definitions, the
variables defined by @<-@ are only in scope in the following statements.
There is still one missing piece. We can invoke actions and examine
their results using @do@, but how do we return a value from a sequence
of actions? For example, consider the @ready@ function that reads a
character and returns @True@ if the character was a `y':
\bprog
@
ready :: IO Bool
ready = do c <- getChar
c == 'y' -- Bad!!!
@
\eprog
This doesn't work because the second statement in the `do' is just a
boolean value, not an action. We need to take this boolean and create
an action that does nothing but return the boolean as its result.
The @return@ function does just that:
\bprog
@
return :: a -> IO a
@
\eprog
The @return@ function completes the set of sequencing primitives. The
last line of @ready@ should read @return (c == 'y')@.
We are now ready to look at more complicated I/O functions. First,
the function @getLine@:
\bprog
@
getLine :: IO String
getLine = do c <- getChar
if c == '\n'
then return ""
else do l <- getLine
return (c:l)
@
\eprog
Note the second @do@ in the else clause. Each @do@ introduces a single
chain of statements. Any intervening
construct, such as the @if@, must use a new @do@ to initiate further
sequences of actions.
The @return@ function admits an ordinary value such as a boolean to
the realm of I/O actions.
What about the other direction? Can we invoke some I/O actions within an
ordinary expression? For example, how can we say @x + print y@
in an expression so that @y@ is printed out as the
expression evaluates? The answer is that we can't! It is "not" possible to
sneak into the imperative universe while in the midst of purely
functional code. Any value `infected' by the imperative world must be
tagged as such. A function such as
\bprog
@
f :: Int -> Int -> Int
@
\eprog
absolutely cannot do any I/O since @IO@ does not
appear in the returned type.
This fact is often quite distressing to
programmers used to placing print statements liberally throughout
their code during debugging. There are, in fact, some unsafe
functions available to get around this problem but these are
better left to advanced programmers. Debugging packages (like @Trace@)
often make liberal use of these `forbidden functions' in an entirely safe
manner.
\subsection{Programming With Actions}
I/O actions are ordinary Haskell
values: they may be passed to functions, placed in structures, and
used as any other Haskell value. Consider this list of actions:
\bprog
@
todoList :: [IO ()]
todoList = [putChar 'a',
do putChar 'b'
putChar 'c',
do c <- getChar
putChar c]
@
\eprog
This list doesn't actually invoke any actions---it simply holds them.
To join these actions into a single action, a function such as
@sequence_@ is needed:
\bprog
@
sequence_ :: [IO ()] -> IO ()
sequence_ [] = return ()
sequence_ (a:as) = do a
sequence as
@
\eprog
This can be simplified by noting that @do x;y@ is expanded to
@x >> y@ (see Section \ref{tut-monadic-classes}). This pattern of
recursion is captured by the @foldr@ function (see the Prelude for a
definition of @foldr@); a better definition of @sequence_@ is:
\bprog
@
sequence_ :: [IO ()] -> IO ()
sequence_ = foldr (>>) (return ())
@
\eprog
The @do@ notation is a useful tool but in this case the underlying
monadic operator, @>>@, is more appropriate. An understanding of the
operators upon which @do@ is built is quite useful to the Haskell
programmer.
The @sequence_@ function can be used to construct @putStr@ from
@putChar@:
\bprog
@
putStr :: String -> IO ()
putStr s = sequence_ (map putChar s)
@
\eprog
One of the differences between Haskell and conventional
imperative programming can be seen in @putStr@. In an imperative
language, mapping an imperative version of @putChar@ over the string
would be sufficient to print it. In Haskell, however, the @map@
function does not perform any action. Instead it creates a list of
actions, one for each character in the string. The folding operation
in @sequence_@
uses the @>>@ function to combine all of the individual actions into a
single action. The @return ()@ used here is
quite necessary -- @foldr@ needs a null action at the end of the chain
of actions it creates (especially if there are no characters in the
string!).
The Prelude and the libraries contains many functions which are
useful for sequencing I/O actions. These are usually generalized to
arbitrary monads; any function with a context including @Monad m =>@
works with the @IO@ type.
\subsection{Exception Handling}
So far, we have avoided the issue of exceptions during I/O operations.
What would happen if @getChar@ encounters an end of
file?\footnote{We use the term "error" for "\bot": a condition which
cannot be recovered from such as non-termination or pattern match
failure. Exceptions, on the other hand, can be caught and handled
within the I/O monad.}
To deal with exceptional conditions such as `file not found' within
the I/O monad, a handling mechanism is used, similar in functionality
to the one in standard ML.
No special syntax or semantics are used; exception handling is part of
the definition of the I/O sequencing operations.
Errors are encoded using a special data type, @IOError@. This type
represents all possible exceptions that may occur within the I/O monad.
This is an abstract type: no constructors for @IOError@ are available
to the user. Predicates allow @IOError@ values to be
queried. For example, the function
\bprog
@
isEOFError :: IOError -> Bool
@
\eprog
determines whether an error was caused by an end-of-file condition.
By making @IOError@ abstract, new sorts of errors may be added to the
system without a noticeable change to the data type. The function
@isEOFError@ is defined in a separate library, @IO@, and must be
explicitly imported into a program.
An {\em exception handler} has type @IOError -> IO a@.
The @catch@ function associates an exception handler with an action or
set of actions:
\bprog
@
catch :: IO a -> (IOError -> IO a) -> IO a
@
\eprog
The arguments to @catch@ are an action and a handler. If the action
succeeds, its result is returned without invoking the handler. If an
error occurs, it is passed to the handler as a value of type
@IOError@ and the action associated with the handler is then invoked.
For example, this version of @getChar@ returns a newline when an error
is encountered:
\bprog
@
getChar' :: IO Char
getChar' = getChar `catch` (\e -> return '\n')
@
\eprog
This is rather crude since it treats all errors in the same manner. If
only end-of-file is to be recognized, the error value must be queried:
\bprog
@
getChar' :: IO Char
getChar' = getChar `catch` eofHandler where
eofHandler e = if isEofError e then return '\n' else ioError e
@
\eprog
The @ioError@ function used here throws an exception on to the next
exception handler. The type of @ioError@ is
\bprog
@
ioError :: IOError -> IO a
@
\eprog
It is similar to
@return@ except that it transfers control to the exception handler
instead of proceeding to the next
I/O action. Nested calls to @catch@ are
permitted, and produce nested exception handlers.
Using @getChar'@, we can redefine @getLine@ to demonstrate the use of
nested handlers:
\bprog
@
getLine' :: IO String
getLine' = catch getLine'' (\err -> return ("Error: " ++ show err))
where
getLine'' = do c <- getChar'
if c == '\n' then return ""
else do l <- getLine'
return (c:l)
@
\eprog
The nested error handlers allow @getChar'@ to catch end of file
while any other error results in a string starting with @"Error: "@
from @getLine'@.
For convenience, Haskell provides a default exception handler at the
topmost level of a program that prints out the
exception and terminates the program.
\subsection{Files, Channels, and Handles}
Aside from the I/O monad and the exception handling mechanism it
provides, I/O facilities in Haskell are for the most part quite
similar to those in other languages. Many of these functions are in
the @IO@ library instead of the Prelude and thus must be explicitly
imported to be in scope (modules and importing are discussed in
Section~\ref{tut-modules}). Also, many of these functions are
discussed in the Library Report instead of the main report.
Opening a file creates a "handle" (of type @Handle@) for use in I/O
transactions. Closing the handle closes the associated file:
\bprog
@
type FilePath = String -- path names in the file system
openFile :: FilePath -> IOMode -> IO Handle
hClose :: Handle -> IO ()
data IOMode = ReadMode | WriteMode | AppendMode | ReadWriteMode
@
\eprog
Handles can also be associated with "channels": communication ports
not directly attached to files. A few channel handles are predefined,
including @stdin@ (standard input), @stdout@ (standard output), and
@stderr@ (standard error). Character level I/O operations include
@hGetChar@ and @hPutChar@, which take a handle as an argument. The
@getChar@ function used previously can be defined as:
\bprog
@
getChar = hGetChar stdin
@
\eprog
Haskell also allows the entire contents of a file or channel to be
returned as a single string:
\bprog
@
getContents :: Handle -> IO String
@
\eprog
Pragmatically, it may seem that @getContents@ must immediately read an
entire file or channel, resulting in poor space and time performance
under certain conditions. However, this is not the case. The key
point is that @getContents@ returns a ``lazy'' (i.e. non-strict) list
of characters (recall that strings are just lists of characters in
Haskell), whose elements are read ``by demand'' just like any other
list. An implementation can be expected to implement this
demand-driven behavior by reading one character at a time from the
file as they are required by the computation.
In this example, a Haskell program copies one file to another:
\bprog
@
main = do fromHandle <- getAndOpenFile "Copy from: " ReadMode
toHandle <- getAndOpenFile "Copy to: " WriteMode
contents <- hGetContents fromHandle
hPutStr toHandle contents
hClose toHandle
putStr "Done."
getAndOpenFile :: String -> IOMode -> IO Handle
getAndOpenFile prompt mode =
do putStr prompt
name <- getLine
catch (openFile name mode)
(\_ -> do putStrLn ("Cannot open "++ name ++ "\n")
getAndOpenFile prompt mode)
@
\eprog
By using the lazy @getContents@ function, the entire contents of the
file need not be read into memory all at once. If @hPutStr@ chooses
to buffer the output by writing the string in fixed sized blocks of
characters, only one block of the input file needs to be in memory at
once. The input file is closed implicitly when the last character has
been read.
\subsection{Haskell and Imperative Programming}
As a final note, I/O programming raises an important issue: this
style looks suspiciously like ordinary imperative programming. For
example, the @getLine@ function:
\bprog
@
getLine = do c <- getChar
if c == '\n'
then return ""
else do l <- getLine
return (c:l)
@
\eprog
bears a striking similarity to imperative code (not in any real language) :
\bprog
@
function getLine() {
c := getChar();
if c == `\n` then return ""
else {l := getLine();
return c:l}}
@
\eprog
So, in the end, has Haskell simply re-invented the imperative wheel?
In some sense, yes. The I/O monad constitutes a small imperative
sub-language inside Haskell, and thus the I/O component of a program
may appear similar to ordinary imperative code. But there is one
important difference: There is no special semantics that the user
needs to deal with. In particular, equational reasoning in Haskell is
not compromised. The imperative feel of the monadic code in a program
does not detract from the functional aspect of Haskell. An
experienced functional programmer should be able to minimize the
imperative component of the program, only using the I/O monad for a
minimal amount of top-level sequencing. The
monad cleanly separates the functional and imperative
program components. In contrast, imperative languages with functional
subsets do not generally have any well-defined barrier between the
purely functional and imperative worlds.
%**~footer
haskell-98-tutorial-sources/modules.verb 0100644 0001064 0000062 00000020273 07065471134 016745 0 ustar jcp ftp %**A Gentle Introduction to Haskell: Modules
%**~header
\section{Modules}
\label{tut-modules}
A Haskell program consists of a collection of {\em
modules}. A module in Haskell serves the dual purpose of controlling
name-spaces and creating abstract data types.
The top level of a module contains any of the various declarations we
have discussed: fixity declarations, data and type declarations, class
and instance declarations, type signatures, function definitions, and
pattern bindings. Except for the fact that
import declarations (to be described shortly) must appear first, the
declarations may appear in any order (the top-level scope is mutually
recursive).
Haskell's module design is relatively conservative: the name-space of
modules is completely flat, and modules are in no way ``first-class.''
Module names are alphanumeric and must begin with an uppercase letter.
There is no formal connection between a Haskell module and the file
system that would (typically) support it. In particular, there is no
connection between module names and file names, and more than one
module could conceivably reside in a single file (one module may even
span several files). Of course, a particular implementation will most
likely adopt conventions that make the connection between modules and
files more stringent.
Technically speaking, a module is really just one big declaration
which begins with the keyword @module@; here's an example for a module
whose name is @Tree@:
\bprog
@
module Tree ( Tree(Leaf,Branch), fringe ) where
data Tree a = Leaf a | Branch (Tree a) (Tree a)
fringe :: Tree a -> [a]
fringe (Leaf x) = [x]
fringe (Branch left right) = fringe left ++ fringe right
@
\eprog
The type @Tree@ and the function @fringe@ should be familiar; they
were given as examples in Section \ref{tut-recursive-types}.
\syn{Because of the @where@ keyword, layout is active at the top
level of a module, and thus the declarations must all line up in the
same column (typically the first). Also note that the module name is
the same as that of the type; this is allowed.}
This module explicitly {\em exports} @Tree@, @Leaf@, @Branch@, and
@fringe@. If the export list following the @module@ keyword is
omitted, {\em all} of the names bound at the top level of the module
would be exported. (In the above example everything is explicitly
exported, so the effect would be the same.) Note that the name of a
type and its constructors have be grouped together, as in
@Tree(Leaf,Branch)@. As short-hand, we could also write @Tree(..)@.
Exporting a subset of the constructors is also possible. The names in
an export list need not be local to the exporting module; any name in
scope may be listed in an export list.
The @Tree@ module may now be {\em imported} into some other module:
\bprog
@
module Main (main) where
import Tree ( Tree(Leaf,Branch), fringe )
main = print (fringe (Branch (Leaf 1) (Leaf 2)))
@
\eprog
The various items being imported into and exported out of a module are
called {\em entities}. Note the explicit import list in the import
declaration; omitting it would cause all entities exported from @Tree@
to be imported.
\subsection{Qualified Names}
There is an obvious problem with importing names directly into the
namespace of module. What if two imported modules contain different
entities with the same name? Haskell solves this problem using
"qualified names". An import declaration may use the
@qualified@ keyword to cause the imported names to be prefixed by the
name of the module imported. These prefixes are followed by the `@.@'
character without intervening whitespace. \syn{Qualifiers are part of
the lexical syntax. Thus, @A.x@ and @A . x@ are quite different: the
first is a qualified name and the second a use of the infix `@.@'
function.} For example, using the @Tree@ module introduced above:
\bprog
@
module Fringe(fringe) where
import Tree(Tree(..))
fringe :: Tree a -> [a] -- A different definition of fringe
fringe (Leaf x) = [x]
fringe (Branch x y) = fringe x
module Main where
import Tree ( Tree(Leaf,Branch), fringe )
import qualified Fringe ( fringe )
main = do print (fringe (Branch (Leaf 1) (Leaf 2)))
print (Fringe.fringe (Branch (Leaf 1) (Leaf 2)))
@
\eprog
Some Haskell programmers prefer to use qualifiers for all imported
entities, making the source of each name explicit with every use.
Others prefer short names and only use qualifiers when absolutely
necessary.
Qualifiers are used to resolve conflicts between different entities
which have the same name. But what if the same entity is imported
from more than one module? Fortunately, such name clashes are
allowed: an entity can be imported by various routes without
conflict. The compiler knows whether entities from different modules
are actually the same.
\subsection{Abstract Data Types}
\label{tut-ADTs}
Aside from controlling namespaces, modules provide the only way to
build abstract data types (ADTs) in Haskell. For example, the
characteristic feature of an ADT is that the {\em representation type}
is {\em hidden}; all operations on the ADT are done at an abstract
level which does not depend on the representation. For example,
although the @Tree@ type is simple enough that we might not normally
make it abstract, a suitable ADT for it might include the following
operations:
\bprog
@
data Tree a -- just the type name
leaf :: a -> Tree a
branch :: Tree a -> Tree a -> Tree a
cell :: Tree a -> a
left, right :: Tree a -> Tree a
isLeaf :: Tree a -> Bool
@
\eprog
A module supporting this is:
\bprog
@
module TreeADT (Tree, leaf, branch, cell,
left, right, isLeaf) where
data Tree a = Leaf a | Branch (Tree a) (Tree a)
leaf = Leaf
branch = Branch
cell (Leaf a) = a
left (Branch l r) = l
right (Branch l r) = r
isLeaf (Leaf _) = True
isLeaf _ = False
@
\eprog
Note in the export list that the type name @Tree@ appears alone
(i.e.~without its constructors). Thus
@Leaf@ and @Branch@ are not exported, and the only way to build or
take apart trees outside of the module is by using the various
(abstract) operations. Of course, the advantage of this information
hiding is that at a later time we could {\em change} the
representation type without affecting users of the type.
\subsection{More Features}
\label{tut-rules}
Here is a brief overview of some other aspects of the module system.
See the report for more details.
\begin{itemize}
\item An @import@ declaration may selectively hide entities using a
@hiding@ clause in the
import declaration. This is useful for explicitly excluding names that
are used for other purposes without having to use qualifiers for other
imported names from the module.
\item An @import@ may contain an @as@ clause to specify a different
qualifier than the name of the importing module. This can be used to
shorten qualifiers from modules with long names or to easily adapt to
a change in module name without changing all qualifiers.
\item Programs implicitly import the @Prelude@ module. An explicit
import of the Prelude overrides the implicit import of all Prelude
names. Thus,
\bprog
@
import Prelude hiding length
@
\eprog
will not import @length@ from the Standard Prelude, allowing the name
@length@ to be defined differently.
\item Instance declarations are not explicitly named in import or
export lists. Every module exports all of its instance declarations
and every import brings all instance declarations into scope.
\item Class methods may be named either in the manner of data
constructors, in parentheses following the class name, or as ordinary
variables.
\end{itemize}
Although Haskell's module system is relatively conservative, there are
many rules concerning the import and export of values. Most of these
are obvious---for instance, it is illegal to import two different
entities having the same name into the same scope. Other rules are
not so obvious---for example, for a given type and class, there cannot
be more than one @instance@ declaration for that combination of type
and class anywhere in the program.
The reader should read the Report for details
(\see{modules}).
%**~footer
haskell-98-tutorial-sources/monads.verb 0100644 0001064 0000062 00000056126 07121451365 016561 0 ustar jcp ftp %**A Gentle Introduction to Haskell: About Monads
%**~header
\section{About Monads}
\label{tut-monads}
Many newcomers to Haskell are puzzled by the concept of {\em monads}.
Monads are frequently encountered in Haskell: the IO system is constructed
using a monad, a special syntax for monads has been provided (@do@
expressions), and the standard libraries contain an entire module dedicated
to monads. In this section we explore monadic programming in more detail.
This section is perhaps less ``gentle'' than the others. Here we
address not only the language features that involve monads but also
try to reveal the bigger picture: why monads are such an important
tool and how they are used. There is no
single way of explaining monads that works for everyone; more
explanations can be found at {\tt haskell.org}. Another good
introduction to practical programming using monads is Wadler's
{\em Monads for Functional Programming}~\cite{wadler:mffp}.
\subsection{Monadic Classes}
\label{tut-monadic-classes}
The Prelude contains a number of classes defining monads are they
are used in Haskell. These classes are based on the monad construct
in category theory; whilst the category theoretic terminology
provides the names for the monadic classes and operations, it is not
necessary to delve into abstract mathematics to get an intuitive
understanding of how to use the monadic classes.
A monad is constructed on top of a polymorphic type such as @IO@. The
monad itself is defined by instance declarations
associating the type with the some or all of the
monadic classes, @Functor@, @Monad@,
and @MonadPlus@. None of the monadic classes are derivable. In addition
to @IO@, two other types in the Prelude are members of the monadic
classes: lists (@[]@) and @Maybe@.
Mathematically, monads are governed by set of {\em laws} that should hold
for the monadic operations. This idea of laws is not unique to
monads: Haskell includes other operations that are
governed, at least informally, by laws. For example, @x /= y@ and
@not (x == y)@ ought to be the same for any type of values being
compared. However, there is no guarantee of this: both @==@ and @/=@ are
separate methods in the @Eq@ class and there is no way to assure that
@==@ and @=/@ are related in this manner.
In the same sense, the monadic laws presented here are not enforced by
Haskell, but ought be obeyed by any instances of a monadic class.
The monad laws give insight into the underlying structure of monads:
by examining these laws, we hope to give a feel for how monads are
used.
The @Functor@ class, already discussed in section
\ref{tut-type-classes}, defines a
single operation: @fmap@. The map function applies an operation to the
objects inside a container (polymorphic types can be thought of as
containers for values of another type), returning a container of the
same shape.
These laws apply to @fmap@ in the class @Functor@:
\[\ba{lcl}
@fmap id@&=&@id@\\
@fmap (f . g)@&=&@fmap f . fmap g@\\
\ea\]
These laws ensure that the container shape is unchanged by
@fmap@ and that the contents of the container are not re-arranged by
the mapping operation.
The @Monad@ class defines two basic operators: @>>=@ (bind) and @return@.
\bprog
@
infixl 1 >>, >>=
class Monad m where
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
return :: a -> m a
fail :: String -> m a
m >> k = m >>= \_ -> k
@
\eprog
The bind operations, @>>@ and @>>=@, combine two monadic values while
the @return@ operation injects a value into the monad (container).
The signature of @>>=@ helps
us to understand this operation: @ma >>= \v -> mb@
combines a monadic value @ma@ containing values
of type @a@ and a function which operates
on a value @v@ of type @a@, returning the monadic value @mb@. The
result is to combine @ma@ and @mb@ into a
monadic value containing @b@. The @>>@
function is used when the function does not need the value produced by
the first monadic operator.
The precise meaning of binding depends, of course, on the monad. For
example, in the IO monad, @x >>= y@ performs two actions sequentially,
passing the result of the first into the second. For the other
built-in monads, lists and the @Maybe@ type, these monadic operations
can be understood in terms of passing zero or more values from one
calculation to the next. We will see examples of this shortly.
The @do@ syntax provides a simple shorthand for chains of monadic
operations. The essential translation of @do@ is captured in the
following two rules:
\bprog
@
do e1 ; e2 = e1 >> e2
do p <- e1; e2 = e1 >>= \p -> e2
@
\eprog
When the pattern in this second form of @do@ is refutable, pattern
match failure calls the @fail@ operation. This may raise an error (as
in the @IO@ monad) or return a ``zero'' (as in the list monad). Thus
the more complex translation is
\bprog
@
do p <- e1; e2 = e1 >>= (\v -> case v of p -> e2; _ -> fail "s")
@
\eprog
where @"s"@ is a string identifying the location of the @do@ statement
for possible use in an error message. For example, in the I/O monad,
an action such as @'a' <- getChar@ will call @fail@ if the character
typed is not 'a'. This, in turn, terminates the program since in the
I/O monad @fail@ calls @error@.
The laws which govern @>>=@ and @return@ are:
\[\ba{lcl}
@return a >>= k@&=&@k a@ \\
@m >>= return@&=&@m@ \\
@xs >>= return . f@&=&@fmap f xs@\\
@m >>= (\x -> k x >>= h)@&=&@(m >>= k) >>= h@\\
\ea\]
The class @MonadPlus@ is used for monads that have a "zero" element
and a "plus" operation:
\bprog
@
class (Monad m) => MonadPlus m where
mzero :: m a
mplus :: m a -> m a -> m a
@
\eprog
The zero element obeys the following laws:
\[\ba{lcl}
@m >>= \x -> mzero@&=&@mzero@\\
@mzero >>= m@&=&@mzero@\\
\ea\]
For lists, the zero value is @[]@, the empty list. The I/O monad has
no zero element and is not a member of this class.
The laws governing the @mplus@ operator are as follows:
\[\ba{lcl}
@m `mplus` mzero@&=&@m@\\
@mzero `mplus` m@&=&@m@\\
\ea\]
The @mplus@ operator is ordinary list concatenation in the list monad.
\subsection{Built-in Monads}
Given the monadic operations and the laws that govern them, what can
we build? We have already examined the I/O monad in detail so we
start with the two other built-in monads.
For lists, monadic binding involves joining together a set of
calculations for each value in the list. When used with lists, the
signature of @>>=@ becomes:
\bprog
@
(>>=) :: [a] -> (a -> [b]) -> [b]
@
\eprog
That is, given a list of @a@'s and a function that maps an @a@ onto a
list of @b@'s, binding applies this function to each of the @a@'s in
the input and returns all of the generated @b@'s concatenated into a
list. The @return@ function creates a singleton list. These
operations should already be familiar: list comprehensions can easily
be expressed using the monadic operations
defined for lists. These following three
expressions are all different syntax for the same thing:
\bprog
@
[(x,y) | x <- [1,2,3] , y <- [1,2,3], x /= y]
do x <- [1,2,3]
y <- [1,2,3]
True <- return (x /= y)
return (x,y)
[1,2,3] >>= (\ x -> [1,2,3] >>= (\y -> return (x/=y) >>=
(\r -> case r of True -> return (x,y)
_ -> fail "")))
@
\eprog
This definition depends on the definition of @fail@ in this monad as
the empty list. Essentially, each @<-@ is generating a set of values
which is passed on into the remainder of the monadic computation.
Thus @x <- [1,2,3]@ invokes the remainder of the monadic computation
three times, once for each element of the list. The returned
expression, @(x,y)@, will be
evaluated for all possible combinations of bindings that surround it.
In this sense, the list monad can be thought of as describing
functions of multi-valued arguments. For example, this function:
\bprog
@
mvLift2 :: (a -> b -> c) -> [a] -> [b] -> [c]
mvLift2 f x y = do x' <- x
y' <- y
return (f x' y')
@
\eprog
turns an ordinary function of two arguments (@f@) into a function over
multiple values (lists of arguments), returning a value for each possible
combination of the two input arguments. For example,
\[\ba{lcl}
@mvLift2 (+) [1,3] [10,20,30]@ \ \ \ &\red&\ \ \ @[11,21,31,13,23,33]@\\
@mvLift2 (\a b->[a,b]) "ab" "cd"@ \ \ \ &\red&\ \ \ @["ac","ad","bc","bd"]@\\
@mvLift2 (*) [1,2,4] []@\ \ \ &\red&\ \ \ @[]@\\
\ea\]
This function is a specialized version of the @LiftM2@ function in the
monad library. You can think of it as transporting a function from
outside the list monad, @f@, into the list monad in which computations
take on multiple values.
The monad defined for @Maybe@ is similar to the list monad: the value
@Nothing@ serves as @[]@ and @Just x@ as @[x]@.
\subsection{Using Monads}
Explaining the monadic operators and their associated laws doesn't
really show what monads are good for. What they really provide is
{\em modularity}. That is, by defining an operation monadically, we can
hide underlying machinery in a way that allows new features to be
incorporated into the monad transparently. Wadler's paper~\cite{wadler:mffp}
is an excellent example of how monads can be
used to construct modular programs. We will start with a monad taken
directly from this paper, the state monad, and then build a more
complex monad with a similar definition.
Briefly, a state monad built around a state type @S@ looks
like this:
\bprog
@
data SM a = SM (S -> (a,S)) -- The monadic type
instance Monad SM where
-- defines state propagation
SM c1 >>= fc2 = SM (\s0 -> let (r,s1) = c1 s0
SM c2 = fc2 r in
c2 s1)
return k = SM (\s -> (k,s))
-- extracts the state from the monad
readSM :: SM S
readSM = SM (\s -> (s,s))
-- updates the state of the monad
updateSM :: (S -> S) -> SM () -- alters the state
updateSM f = SM (\s -> ((), f s))
-- run a computation in the SM monad
runSM :: S -> SM a -> (a,S)
runSM s0 (SM c) = c s0
@
\eprog
This example defines a new type, @SM@, to be a computation that
implicitly carries a type @S@. That is, a computation of type @SM t@
defines a value of type @t@
while also interacting with (reading and writing) the state of type
@S@. The definition of @SM@ is simple: it consists of functions that take a
state and produce two results: a returned value (of any type) and an
updated state. We can't use a type synonym here: we need a type name
like @SM@ that can be used in instance declarations. The @newtype@
declaration is often used here instead of @data@.
This instance declaration defines the `plumbing' of the monad: how to
sequence two computations and the definition of an empty computation.
Sequencing (the @>>=@ operator) defines a computation (denoted by the
constructor @SM@) that passes an initial
state, @s0@, into @c1@, then passes the value coming out of this
computation, @r@, to the function that returns the second computation,
@c2@. Finally, the state coming out of @c1@ is passed into @c2@ and
the overall result is the result of @c2@.
The definition of @return@ is easier: @return@ doesn't change the
state at all; it only serves to bring a value into the monad.
While @>>=@ and @return@ are the basic monadic sequencing operations,
we also need some {\em monadic primitives}. A monadic primitive is
simply an operation that uses the insides of the monad abstraction and
taps into
the `wheels and gears' that make the monad work. For example, in the
@IO@ monad, operators such as @putChar@ are primitive since they deal
with the inner workings of the @IO@ monad. Similarly, our state monad
uses two primitives: @readSM@ and @updateSM@. Note that these depend
on the inner structure of the monad - a change to the definition of
the @SM@ type would require a change to these primitives.
The definition of @readSM@ and @updateSM@ are simple: @readSM@ brings
the state out of the monad for observation while @updateSM@ allows the
user to alter the state in the monad. (We could also have used
@writeSM@ as a primitive but update is often a more natural way of
dealing with state).
Finally, we need a function that runs computations in the monad,
@runSM@. This takes an initial state and a computation and yields
both the returned value of the computation and the final state.
Looking at the bigger picture, what we are trying to do is define an
overall computation as a series of steps (functions with type
@SM a@), sequenced using @>>=@ and @return@. These steps may interact
with the state (via @readSM@ or @updateSM@) or may ignore the state.
However, the use (or non-use) of the state is hidden: we don't invoke
or sequence our computations differently depending on whether or not
they use @S@.
Rather than present any examples using this simple state monad, we
proceed on to a more complex example that includes the state monad.
We define a small {\em embedded language} of resource-using
calculations.
That is, we build a special purpose language implemented as a set of Haskell
types and functions. Such languages use the basic tools of Haskell,
functions and types, to build a library of operations
and types specifically tailored to a domain of interest.
In this example, consider a computation that requires some sort of
resource. If the resource is available, computation proceeds; when the
resource is unavailable, the computation suspends. We use the type @R@
to denote a computation using resources controlled by our monad.
The definition of @R@ is as follows:
\bprog
@
data R a = R (Resource -> (Resource, Either a (R a)))
@
\eprog
Each computation is a function from available resources to remaining
resources, coupled with either a result, of type @a@, or a
suspended computation, of type @R a@, capturing the work done up
to the point where resources were exhausted.
The @Monad@ instance for @R@ is as follows:
\bprog
@
instance Monad R where
R c1 >>= fc2 = R (\r -> case c1 r of
(r', Left v) -> let R c2 = fc2 v in
c2 r'
(r', Right pc1) -> (r', Right (pc1 >>= fc2)))
return v = R (\r -> (r, (Left v)))
@
\eprog
The @Resource@ type is used in the same manner as the state in
the state monad. This definition reads as follows: to combine two
`resourceful' computations, @c1@ and @fc2@ (a function producing
@c2@), pass the initial resources into @c1@. The result will be
either
\begin{itemize}
\item a value, @v@, and remaining resources, which are used to determine
the next computation (the call @fc2 v@), or
\item a suspended computation, @pc1@, and resources remaining at the
point of suspension.
\end{itemize}
The suspension must take the second computation into consideration:
@pc1@ suspends only the first computation, @c1@, so we must bind @c2@
to this to produce a suspension of the overall computation.
The definition of @return@ leaves the resources unchanged while moving
@v@ into the monad.
This instance declaration defines the basic structure of the monad but
does not determine how resources are used. This monad could be
used to control many types of resource or implement many different
types of resource usage policies. We will demonstrate a very simple
definition of resources as an example: we choose @Resource@ to be an
@Integer@, representing available computation steps:
\bprog
@
type Resource = Integer
@
\eprog
This function takes a step unless no steps are available:
\bprog
@
step :: a -> R a
step v = c where
c = R (\r -> if r /= 0 then (r-1, Left v)
else (r, Right c))
@
\eprog
The @Left@ and @Right@ constructors are part of the @Either@ type.
This function continues computation in @R@ by returning @v@ so long as
there is at least one computational step resource available.
If no steps are available, the @step@ function suspends the current
computation (this suspension is captured in @c@) and passes this
suspended computation back into the monad.
So far, we have the tools to define a sequence of ``resourceful''
computations (the monad) and we can express a form of resource usage
using @step@. Finally, we need to address how computations in this
monad are expressed.
Consider an increment function in our monad:
\bprog
@
inc :: R Integer -> R Integer
inc i = do iValue <- i
step (iValue+1)
@
\eprog
This defines increment as a single step of computation. The @<-@ is
necessary to pull the argument value out of the monad; the type of
@iValue@ is @Integer@ instead of @R Integer@.
This definition isn't particularly satisfying, though, compared to the
standard definition of the increment function. Can we instead ``dress
up'' existing operations like @+@ so that they work in our monadic
world? We'll start with a set of {\tt lifting} functions. These
bring existing functionality into the monad. Consider the definition
of @lift1@ (this is slightly different from the @liftM1@ found in the
@Monad@ library):
\bprog
@
lift1 :: (a -> b) -> (R a -> R b)
lift1 f = \ra1 -> do a1 <- ra1
step (f a1)
@
\eprog
This takes a function of a single argument, @f@, and creates a
function in @R@ that executes the lifted function in a single step.
Using @lift1@, @inc@ becomes
\bprog
@
inc :: R Integer -> R Integer
inc i = lift1 (i+1)
@
\eprog
This is better but still not ideal. First, we add @lift2@:
\bprog
@
lift2 :: (a -> b -> c) -> (R a -> R b -> R c)
lift2 f = \ra1 ra2 -> do a1 <- ra1
a2 <- ra2
step (f a1 a2)
@
\eprog
Notice that this function explicitly sets the order of evaluation in
the lifted function: the computation yielding @a1@ occurs before the
computation for @a2@.
Using @lift2@, we can create a new version of @==@ in the @R@ monad:
\bprog
@
(==*) :: Ord a => R a -> R a -> R Bool
(==*) = lift2 (==)
@
\eprog
We had to use a slightly different name for this new function since
@==@ is already taken but in
some cases we can use the same name for the lifted and unlifted
function. This instance declaration allows
all of the operators in @Num@ to be used in @R@:
\bprog
@
instance Num a => Num (R a) where
(+) = lift2 (+)
(-) = lift2 (-)
negate = lift1 negate
(*) = lift2 (*)
abs = lift1 abs
fromInteger = return . fromInteger
@
\eprog
The @fromInteger@ function is applied implicitly to all integer
constants in a Haskell program (see Section \ref{tut-num-constants});
this definition allows integer constants to have the type @R Integer@.
We can now, finally, write increment in a completely natural style:
\bprog
@
inc :: R Integer -> R Integer
inc x = x + 1
@
\eprog
Note that we cannot lift the @Eq@ class in the same manner as the
@Num@ class: the signature of @==*@ is not compatible with allowable
overloadings of @==@ since the result of @==*@ is @R Bool@ instead of
@Bool@.
To express interesting computations in @R@ we will need a
conditional. Since we can't use @if@ (it requires that the test be of
type @Bool@ instead of @R Bool@), we name the function @ifR@:
\bprog
@
ifR :: R Bool -> R a -> R a -> R a
ifR tst thn els = do t <- tst
if t then thn else els
@
\eprog
Now we're ready for a larger program in the @R@ monad:
\bprog
@
fact :: R Integer -> R Integer
fact x = ifR (x ==* 0) 1 (x * fact (x-1))
@
\eprog
Now this isn't quite the same as an ordinary factorial function but
still quite readable. The idea of providing new definitions for
existing operations like @+@ or @if@ is an essential part of creating
an embedded language in Haskell. Monads are particularly useful for
encapsulating the semantics of these embedded languages in a clean and
modular way.
We're now ready to actually run some programs. This function runs a
program in @M@ given a maximum number of computation steps:
\bprog
@
run :: Resource -> R a -> Maybe a
run s (R p) = case (p s) of
(_, Left v) -> Just v
_ -> Nothing
@
\eprog
We use the @Maybe@ type to deal with the possibility of the
computation not finishing in the allotted number of steps. We can now
compute
\[\ba{lcl}
@run 10 (fact 2)@ \ \ \ &\red&\ \ \ @Just 2@\\
@run 10 (fact 20)@ \ \ \ &\red&\ \ \ @Nothing@\\
\ea\]
Finally, we can add some more interesting functionality to this
monad. Consider the following function:
\bprog
@
(|||) :: R a -> R a -> R a
@
\eprog
This runs two computations in parallel, returning the value of the
first one to complete. One possible definition of this function is:
\bprog
@
c1 ||| c2 = oneStep c1 (\c1' -> c2 ||| c1')
where
oneStep :: R a -> (R a -> R a) -> R a
oneStep (R c1) f =
R (\r -> case c1 1 of
(r', Left v) -> (r+r'-1, Left v)
(r', Right c1') -> -- r' must be 0
let R next = f c1' in
next (r+r'-1))
@
\eprog
This takes a step in @c1@, returning its value of @c1@ complete or, if
@c1@ returns a suspended computation (@c1'@), it evaluates
@c2 ||| c1'@. The @oneStep@ function takes a single step in its
argument, either returning an evaluated value or passing the remainder
of the computation into @f@. The definition of @oneStep@ is simple:
it gives @c1@ a 1 as its resource argument. If a final value is
reached, this is returned, adjusting the returned step count (it is
possible that a computation might return after taking no steps so the
returned resource count isn't necessarily 0). If the computation
suspends, a patched up resource count is passed to the final
continuation.
We can now evaluate expressions like @run 100 (fact (-1) ||| (fact 3))@
without looping since the two calculations are interleaved. (Our
definition of @fact@ loops for @-1@).
Many variations are possible on this basic
structure. For example, we could extend the state to include a trace
of the computation steps. We could also embed this monad inside the
standard @IO@ monad, allowing computations in @M@ to interact with the
outside world.
While this example is perhaps more advanced than others in this tutorial,
it serves to illustrate the power of monads as a tool for defining the
basic semantics of a system. We also present this example as a model
of a small {\em Domain Specific Language}, something Haskell is
particularly good at defining. Many other DSLs have been developed in
Haskell; see {\tt haskell.org} for many more examples. Of particular
interest are Fran, a language of reactive animations, and Haskore, a
language of computer music.
%**~footer
haskell-98-tutorial-sources/moretypes.verb 0100644 0001064 0000062 00000024240 07065467732 017333 0 ustar jcp ftp %**A Gentle Introduction to Haskell: Types, Again
%**~header
\section{Types, Again}
Here we examine some of the more advanced aspects of type
declarations.
\subsection{The Newtype Declaration}
A common programming practice is to define a type whose representation
is identical to an existing one but which has a separate identity in
the type system.
In Haskell, the @newtype@ declaration creates a new type from an
existing one. For example, natural numbers can be represented by
the type @Integer@ using the following declaration:
\bprog
@
newtype Natural = MakeNatural Integer
@
\eprog
This creates an entirely new type, @Natural@, whose only
constructor contains a single @Integer@. The constructor @MakeNatural@
converts between an @Natural@ and an @Integer@:
\bprog
@
toNatural :: Integer -> Natural
toNatural x | x < 0 = error "Can't create negative naturals!"
| otherwise = MakeNatural x
fromNatural :: Natural -> Integer
fromNatural (MakeNatural i) = i
@
\eprog
The
following instance declaration admits @Natural@ to the @Num@ class:
\bprog
@
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)
@
\eprog
Without this declaration, @Natural@ would not be in @Num@. Instances
declared for the old type do not carry over to the new one. Indeed,
the whole purpose of this type is to introduce a different @Num@
instance. This would not be possible if @Natural@ were
defined as a type synonym of @Integer@.
All of this works using a @data@ declaration instead of a
@newtype@ declaration. However, the @data@ declaration
incurs extra overhead in the representation of @Natural@ values. The
use of @newtype@ avoids the extra level of indirection (caused by
laziness) that the @data@ declaration would introduce.
See section
\ref{datatype-renaming} of the report for a more discussion of the
relation between @newtype@, @data@, and @type@ declarations.
\syn{Except for the keyword, the @newtype@ declaration uses the same
syntax as a @data@ declaration with a single constructor containing a
single field. This is appropriate since types defined using @newtype@
are nearly identical to those created by an ordinary @data@
declaration.}
\subsection{Field Labels}
The fields within a Haskell data type can be accessed either
positionally or by name using "field labels".
Consider a data type for a two-dimensional point:
\bprog
@
data Point = Pt Float Float
@
\eprog
The two components of a @Point@ are the first and second arguments to the
constructor @Pt@. A function such as
\bprog
@
pointx :: Point -> Float
pointx (Pt x _) = x
@
\eprog
may be used to refer to the first component of a point in a more
descriptive way, but, for large structures, it becomes tedious to
create such functions by hand.
Constructors in a @data@ declaration may be declared
with associated "field names", enclosed in braces. These field names
identify the components of constructor by name rather than by position.
This is an alternative way to define @Point@:
\bprog
@
data Point = Pt {pointx, pointy :: Float}
@
\eprog
This data type is identical to the earlier definition
of @Point@. The constructor @Pt@ is the same in both cases. However,
this declaration also defines two field names, @pointx@
and @pointy@. These field names can be used as "selector functions" to
extract a component from a structure. In this example, the selectors
are:
\bprog
@
pointx :: Point -> Float
pointy :: Point -> Float
@
\eprog
This is a function using these selectors:
\bprog
@
absPoint :: Point -> Float
absPoint p = sqrt (pointx p * pointx p +
pointy p * pointy p)
@
\eprog
Field labels can also be used to construct new values. The expression
@Pt {pointx=1, pointy=2}@ is identical to @Pt 1 2@. The use of field
names in the declaration of a data constructor does not preclude the
positional style of field access; both
@Pt {pointx=1, pointy=2}@ and @Pt 1 2@ are allowed.
When constructing a value using field names, some fields may be
omitted; these absent fields are undefined.
Pattern matching using field names uses a similar syntax for the
constructor @Pt@:
\bprog
@
absPoint (Pt {pointx = x, pointy = y}) = sqrt (x*x + y*y)
@
\eprog
An update function uses field values in an existing structure to fill
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
@pointx@ replaced by @2@. This is not a destructive update:
the update function merely creates a new copy of the object, filling
in the specified fields with new values.
\syn{The braces used in conjunction with field labels are somewhat
special: Haskell syntax usually allows braces to be omitted using the
"layout rule" (described in Section \ref{tut-layout}). However, the
braces associated with field names must be explicit.}
%Within the braces used to name the fields of a structure, {\em
%punning}---using the same word in two different ways---can be used to
%abbreviate bindings which associate a field name with a local variable
%of the same name. That is, @{pointx}@ abbreviates @{pointx = pointx}@
%in a field list. Thus, the @abs@ function could also be written
%\bprog
%
%abs (Pt {pointx, pointy}) = sqrt (pointx*pointx + pointy*pointy)
%
%\eprog
Field names are not restricted to types with a single constructor
(commonly called `record' types). In a type with multiple
constructors, selection or update operations using field names may
fail at runtime. This is similar to the behavior of the @head@
function when applied to an empty list.
Field labels share the top level namespace with ordinary variables and
class methods.
A field name cannot be used in more than one data type in scope.
However, within a data type, the same field
name can be used in more than one of the constructors so long as it
has the same typing in all cases. For example, in this data type
\bprog
@
data T = C1 {f :: Int, g :: Float}
| C2 {f :: Int, h :: Bool}
@
\eprog
the field name @f@ applies to both constructors in @T@. Thus if
@x@ is of type @T@, then @x {f=5}@ will work for values created by
either of the constructors in @T@.
Field names does not change the basic nature of an algebraic
data type; they are simply a convenient syntax for accessing the
components of a data structure by name rather than by position. They
make constructors with many components
more manageable since fields can be added or removed without changing
every reference to the constructor. For full details of field labels
and their semantics, see Section~\see{field-labels}.
\subsection{Strict Data Constructors}
\label{tut-strict-flag}
Data structures in Haskell are generally "lazy": the
components are not evaluated until
needed. This permits structures that contain elements which, if
evaluated, would lead to an error or fail to terminate. Lazy data
structures enhance the expressiveness of Haskell and are an
essential aspect of the Haskell programming style.
Internally, each field of a lazy data object is wrapped up in a structure
commonly referred to as a "thunk" that encapsulates the computation
defining the field value. This thunk is not entered until
the value is needed; thunks which contain errors ("\bot") do not affect other
elements of a data structure. For
example, the tuple @('a',@"\bot"@)@ is a perfectly legal Haskell
value. The
@'a'@ may be used without disturbing the other component of the tuple.
Most programming languages are
"strict" instead of lazy: that is, all components of a data structure
are reduced to values before being placed in the structure.
There are a number of overheads associated with thunks: they take time to
construct and evaluate, they occupy space in the heap, and they cause
the garbage collector to retain other structures needed for the
evaluation of the thunk.
To avoid these overheads, {\em strictness flags} in @data@ declarations
allow specific fields of a constructor to be evaluated immediately,
selectively suppressing laziness. A field
marked by "@!@" in a @data@ declaration is evaluated when
the structure is created instead of delayed in a thunk.
There are a number of situations where it may be appropriate to use
strictness flags:
\begin{itemize}
\item Structure components that are sure to be evaluated at some
point during program execution.
\item Structure components that are simple to evaluate and never
cause errors.
\item Types in which partially undefined values are not meaningful.
\end{itemize}
For example, the complex number library defines the @Complex@ type as:
\bprog
@
data RealFloat a => Complex a = !a :+ !a
@
\eprog
\syn{note the infix definition of the constructor @:+@.} This definition
marks the two components, the real and imaginary parts, of the complex
number as being strict. This is a more compact representation of
complex numbers but this comes at the expense of making a complex
number with an undefined component, @1 :+ @ "\bot" for example,
totally undefined ("\bot"). As there is no real need for partially
defined complex numbers, it makes sense to use strictness flags to
achieve a more efficient representation.
Strictness flags may be used to address memory leaks: structures
retained by the garbage collector but no longer necessary for computation.
The strictness flag, @!@, can only appear in @data@ declarations.
It cannot be used in other type
signatures or in any other type definitions. There is no
corresponding way to mark function arguments as being strict, although
the same effect can be obtained using the @seq@ or @!$@ functions. See
~\see{strictness-flags} for further details.
It is difficult to present exact guidelines for the use of strictness
flags. They should be used with caution: laziness is one of the
fundamental properties of Haskell and adding strictness flags may lead
to hard to find infinite loops or have other unexpected consequences.
%**~footer
haskell-98-tutorial-sources/numbers.verb 0100644 0001064 0000062 00000023703 07065471023 016746 0 ustar jcp ftp %**A Gentle Introduction to Haskell: Numbers
%**~header
\section{Numbers}
Haskell provides a rich collection of numeric types, based on those of
Scheme~\cite{RRRRS}, which in turn are based on Common
Lisp~\cite{steele:common-lisp}. (Those languages, however, are
dynamically typed.) The standard types include fixed- and
arbitrary-precision integers, ratios (rational numbers) formed from
each integer type, and single- and double-precision real and complex
floating-point. We outline here the basic characteristics of the
numeric type class structure and refer the reader to
\see{numbers} for details.
\subsection{Numeric Class Structure}
The numeric type classes (class @Num@ and those that lie below it)
account for
many of the standard Haskell classes. We also note that @Num@
is a subclass of @Eq@, but not of @Ord@; this is because the order
predicates do not apply to complex numbers. The subclass @Real@
of @Num@, however, is a subclass of @Ord@ as well.
The @Num@ class provides several basic operations common to all
numeric types; these include, among others, addition, subtraction,
negation, multiplication, and absolute value:
\bprog
@
(+), (-), (*) :: (Num a) => a -> a -> a
negate, abs :: (Num a) => a -> a
@
\eprog
\syn{@negate@ is the function applied by Haskell's only prefix operator,
minus; we can't call it @(-)@, because that is the subtraction
function, so this name is provided instead. For example,
@-x*y@ is equivalent to @negate (x*y)@. (Prefix minus has the same
syntactic precedence as infix minus, which, of course, is lower
than that of multiplication.)}
Note that @Num@ does {\em not} provide a division operator; two
different kinds of division operators are provided in two non-overlapping
subclasses of @Num@:
The class @Integral@ provides whole-number division and remainder
operations. The
standard instances of @Integral@ are @Integer@ (unbounded or
mathematical integers, also known as ``bignums'') and @Int@
(bounded, machine integers, with a range equivalent to at least
29-bit signed binary). A particular Haskell implementation might
provide other integral types in addition to these. Note that
@Integral@ is a subclass of @Real@, rather than of @Num@ directly;
this means that there is no attempt to provide Gaussian integers.
All other numeric types fall in the class @Fractional@, which provides
the ordinary division operator @(/)@. The further subclass
@Floating@ contains trigonometric, logarithmic, and exponential functions.
The @RealFrac@ subclass of @Fractional@ and @Real@ provides a function
@properFraction@, which decomposes a number into its whole and
fractional parts, and a collection of functions that round to
integral values by differing rules:
\bprog
@
properFraction :: (Fractional a, Integral b) => a -> (b,a)
truncate, round,
floor, ceiling: :: (Fractional a, Integral b) => a -> b
@
\eprog
The @RealFloat@ subclass of @Floating@ and @RealFrac@ provides
some specialized functions for efficient access to the components
of a floating-point number, the {\em exponent} and {\em significand}.
The standard types @Float@ and @Double@ fall in class @RealFloat@.
\subsection{Constructed Numbers}
Of the standard numeric types, @Int@, @Integer@, @Float@, and @Double@
are primitive. The others are made from these by type constructors.
@Complex@ (found in the library @Complex@) is a type constructor that
makes a complex type in class @Floating@ from a @RealFloat@ type:
\bprog
@
data (RealFloat a) => Complex a = !a :+ !a deriving (Eq, Text)
@
\eprog
The @!@ symbols are strictness flags; these were discussed in Section~
\ref{tut-strict-flag}.
Notice the context @RealFloat a@, which restricts the argument
type; thus, the standard complex types are @Complex Float@ and
@Complex Double@. We can also see from the @data@ declaration
that a complex number is written "x" @:+@ "y"; the arguments are
the cartesian real and imaginary parts, respectively. Since @:+@
is a data constructor, we can use it in pattern matching:
\bprog
@
conjugate :: (RealFloat a) => Complex a -> Complex a
conjugate (x:+y) = x :+ (-y)
@
\eprog
Similarly, the type constructor @Ratio@ (found in the @Rational@
library) makes a rational type in class @RealFrac@ from an instance of
@Integral@.
(@Rational@ is a type synonym for @Ratio Integer@.)
@Ratio@, however, is an abstract type constructor.
Instead of a data constructor like @:+@, rationals use the `@%@' function to
form a ratio from two integers. Instead of pattern matching,
component extraction functions are provided:
\bprog
@
(%) :: (Integral a) => a -> a -> Ratio a
numerator, denominator :: (Integral a) => Ratio a -> a
@
\eprog
Why the difference? Complex numbers in cartesian form are
unique---there are no nontrivial identities involving @:+@. On the
other hand, ratios are not unique, but have a canonical (reduced) form
that the implementation of the abstract data type must maintain; it is
not necessarily the case, for instance, that @numerator (x%y)@ is
equal to @x@, although the real part of @x:+y@ is always @x@.
\subsection{Numeric Coercions and Overloaded Literals}
\label{tut-num-constants}
The Standard Prelude and libraries provide several overloaded functions
that serve as explicit coercions:
\bprog
@
fromInteger :: (Num a) => Integer -> a
fromRational :: (Fractional a) => Rational -> a
toInteger :: (Integral a) => a -> Integer
toRational :: (RealFrac a) => a -> Rational
fromIntegral :: (Integral a, Num b) => a -> b
fromRealFrac :: (RealFrac a, Fractional b) => a -> b
fromIntegral = fromInteger . toInteger
fromRealFrac = fromRational . toRational
@
\eprog
Two of these are implicitly used to provide overloaded numeric literals:
An integer numeral (without a decimal point) is actually equivalent to
an application of @fromInteger@ to the value of the numeral as an
@Integer@. Similarly, a floating numeral (with a decimal point) is
regarded as an application of @fromRational@ to the value of the
numeral as a @Rational@. Thus, @7@ has the type @(Num a) => a@,
and @7.3@ has the type @(Fractional a) => a@. This means that we
can use numeric literals in generic numeric functions, for example:
\bprog
@
halve :: (Fractional a) => a -> a
halve x = x * 0.5
@
\eprog
This rather indirect way of overloading numerals has the additional
advantage that the method of interpreting a numeral as a number
of a given type can be specified in an @Integral@ or @Fractional@
instance declaration (since @fromInteger@ and @fromRational@ are
operators of those classes, respectively). For example, the
@Num@ instance of @(RealFloat a) => Complex a@ contains this method:
\bprog
@
fromInteger x = fromInteger x :+ 0
@
\eprog
This says that a @Complex@ instance of @fromInteger@ is defined to
produce a complex number whose real part is supplied by an appropriate
@RealFloat@ instance of @fromInteger@. In this manner, even
user-defined numeric types (say, quaternions) can make use of
overloaded numerals.
As another example, recall our first definition of @inc@ from Section
\ref{tut-values-etc}:
\bprog
@
inc :: Integer -> Integer
inc n = n+1
@
\eprog
Ignoring the type signature, the most general type of @inc@ is
@(Num a) => a->a@. The explicit type signature is legal,
however, since it is {\em more specific} than the principal type (a
more general type signature would cause a static error). The type
signature has the effect of restricting @inc@'s type, and in this
case would cause something like @inc (1::Float)@ to be ill-typed.
\subsection{Default Numeric Types}
Consider the following function definition:
\bprog
@
rms :: (Floating a) => a -> a -> a
rms x y = sqrt ((x^2 + y^2) * 0.5)
@
\eprog
The exponentiation function @(^)@ (one of three different standard
exponentiation operators with different typings, see \S{6.8.5}) has
the type @(Num a, Integral b) => a -> b -> a@, and since @2@ has the
type @(Num a) => a@, the type of @x^2@ is @(Num a, Integral b) => a@.
This is a problem; there is no way to resolve the overloading
associated with the type variable @b@, since it is in the context, but
has otherwise vanished from the type expression. Essentially, the
programmer has specified that @x@ should be squared, but has not
specified whether it should be squared with an @Int@ or an @Integer@
value of two. Of course, we can fix this:
\bprog
@
rms x y = sqrt ((x ^ (2::Integer) + y ^ (2::Integer)) * 0.5)
@
\eprog
It's obvious that this sort of thing will soon grow tiresome, however.
In fact, this kind of overloading ambiguity is not restricted to
numbers:
\bprog
@
show (read "xyz")
@
\eprog
As what type is the string supposed to be read? This is
more serious than the exponentiation ambiguity, because there, any
@Integral@ instance will do, whereas here, very different behavior
can be expected depending on what instance of @Text@ is used to
resolve the ambiguity.
Because of the difference between the numeric and general cases of the
overloading ambiguity problem, Haskell provides a solution that is
restricted to numbers: Each module may contain a {\em default
declaration,} consisting of the keyword @default@ followed by a
parenthesized, comma-separated list of numeric monotypes (types with
no variables). When an ambiguous type variable is discovered (such as
@b@, above), if at least one of its classes is numeric and all of its
classes are standard, the default list is consulted, and the first
type from the list that will satisfy the context of the type variable
is used. For example, if the default declaration
@default (Int, Float)@ is in effect, the ambiguous exponent above will
be resolved as type @Int@. (See \see{default-decls} for more details.)
The ``default default'' is @(Integer, Double)@, but
@(Integer, Rational, Double)@ may also be appropriate. Very cautious
programmers may prefer @default ()@, which provides no defaults.
%**~footer
haskell-98-tutorial-sources/patterns.verb 0100644 0001064 0000062 00000042372 07065440346 017142 0 ustar jcp ftp %**A Gentle Introduction to Haskell: Patterns
%**~header
\section{Case Expressions and Pattern Matching}
\label{tut-pattern-matching}
Earlier we gave several examples of pattern matching in defining
functions---for example @length@ and @fringe@. In this section we
will look at the pattern-matching process in greater detail
(\see{pattern-matching}).\footnote{Pattern matching in Haskell is
different from that found in logic programming languages such as
Prolog; in particular, it can be viewed as ``one-way'' matching,
whereas Prolog allows ``two-way'' matching (via unification), along
with implicit backtracking in its evaluation mechanism.}
Patterns are not ``first-class;'' there is only a fixed set of
different kinds of patterns. We have already seen several examples of
{\em data constructor} patterns; both @length@ and @fringe@ defined
earlier use such patterns, the former on the constructors of a
``built-in'' type (lists), the latter on a user-defined type (@Tree@).
Indeed, matching is permitted using the constructors of any type,
user-defined or not. This includes tuples, strings, numbers,
characters, etc. For example, here's a contrived function that
matches against a tuple of ``constants:''
\bprog
@
contrived :: ([a], Char, (Int, Float), String, Bool) -> Bool
contrived ([], 'b', (1, 2.0), "hi", True) = False
@
\eprog
This example also demonstrates that {\em nesting} of patterns is
permitted (to arbitrary depth).
Technically speaking, {\em formal parameters}\footnote{The Report
calls these {\em variables}.} are also patterns---it's just that they
{\em never fail to match a value}. As a ``side effect'' of the
successful match, the formal parameter is bound to the value it is
being matched against. For this reason patterns in any one equation
are not allowed to have more than one occurrence of the same formal
parameter (a property called {\em linearity} \see{pattern-matching},
\see{lambda-abstractions}, \see{function-bindings}).
Patterns such as formal parameters that never fail to match are said
to be {\em irrefutable}, in contrast to {\em refutable} patterns which
may fail to match. The pattern used
in the @contrived@ example above is refutable. There are three
other kinds of irrefutable patterns, two of which we will introduce
now (the other we will delay until Section \ref{tut-lazy-patterns}).
\paragraph*{As-patterns.} Sometimes it is convenient to name a
pattern for use on the right-hand side of an equation. For example, a
function that duplicates the first element in a list might be written
as:
\bprog
@
f (x:xs) = x:x:xs
@
\eprog
(Recall that ``@:@'' associates to the right.) Note that @x:xs@ appears
both as a pattern on the left-hand side, and an expression on the
right-hand side. To improve readability, we might prefer to write
@x:xs@ just once, which we can achieve using an {\em as-pattern} as
follows:\footnote{Another advantage to doing this is that a naive
implementation might completely reconstruct @x:xs@ rather than
re-use the value being matched against.}
\bprog
@
f s@@(x:xs) = x:s
@
\eprog
Technically speaking, as-patterns always result in a successful match,
although the sub-pattern (in this case @x:xs@) could, of course, fail.
\paragraph*{Wild-cards.} Another common situation is matching against
a value we really care nothing about. For example, the functions
@head@ and @tail@ defined in Section \ref{tut-polymorphism}
can be rewritten as:
\bprog
@
head (x:_) = x
tail (_:xs) = xs
@
\eprog
in which we have ``advertised'' the fact that we don't care what a
certain part of the input is. Each wild-card independently matches
anything, but in contrast to a formal parameter, each binds
nothing; for this reason more than one is allowed in an equation.
\subsection{Pattern-Matching Semantics}
\label{tut-matching-semantics}
So far we have discussed how individual patterns are matched, how some
are refutable, some are irrefutable, etc. But what drives the overall
process? In what order are the matches attempted? What if none
succeeds? This section addresses these questions.
Pattern matching can either {\em fail}, {\em succeed} or {\em
diverge}. A successful match binds the formal parameters in the
pattern. Divergence occurs when a value needed by the pattern
contains an error ($\bot$). The matching process itself occurs ``top-down,
left-to-right.'' Failure of a pattern anywhere in one equation
results in failure of the whole equation, and the next equation is
then tried. If all equations fail, the value of the function
application is $\bot$, and results in a run-time error.
For example, if @[1,2]@ is matched against @[0,bot]@, then @1@ fails
to match @0@, so the result is a failed match. (Recall that @bot@,
defined earlier, is a variable bound to $\bot$.) But if @[1,2]@ is
matched against @[bot,0]@, then matching @1@ against @bot@ causes
divergence (i.e.~$\bot$).
The other twist to this set of rules is that top-level patterns
may also have a boolean {\em guard}, as in this definition of a
function that forms an abstract version of a number's sign:
\bprog
@
sign x | x > 0 = 1
| x == 0 = 0
| x < 0 = -1
@
\eprog
Note that a sequence of guards may be provided for the same pattern;
as with patterns, they are evaluated top-down, and the first that
evaluates to @True@ results in a successful match.
\subsection{An Example}
The pattern-matching rules can have subtle effects on the meaning of
functions. For example, consider this definition of @take@:
\bprog
@
take 0 _ = []
take _ [] = []
take n (x:xs) = x : take (n-1) xs
@
\eprog
and this slightly different version (the first 2 equations have been
reversed):
\bprog
@
take1 _ [] = []
take1 0 _ = []
take1 n (x:xs) = x : take1 (n-1) xs
@
\eprog
Now note the following:
\[\ba{lcl}
@take 0 bot@ &\ \ \ \red\ \ \ & @[]@ \\
@take1 0 bot@ &\ \ \ \red\ \ \ & \bot \\[.1in]
@take bot []@ &\ \ \ \red\ \ \ & \bot \\
@take1 bot []@ &\ \ \ \red\ \ \ & @[]@
\ea\]
We see that @take@ is ``more defined'' with respect to its second
argument, whereas @take1@ is more defined with respect to its first.
It is difficult to say in this case which definition is better. Just
remember that in certain applications, it may make a difference. (The
Standard Prelude includes a definition corresponding to @take@.)
\subsection{Case Expressions}
\label{tut-case}
Pattern matching provides a way to ``dispatch control'' based on
structural properties of a value. In many circumstances we
don't wish to define a {\em function} every time we need to do this,
but so far we have only shown how to do pattern matching in function
definitions. Haskell's {\em case expression} provides a way to solve
this problem. Indeed, the meaning of pattern matching in function
definitions is specified in the Report in terms of case expressions,
which are considered more primitive. In particular, a function
definition of the form:
\[\ba{l}
"@f@ p_{11} ... p_{1k} @=@ e_{1}" \\
"..." \\
"@f@ p_{n1} ... p_{nk} @=@ e_{n}"
\ea\]
where each "p_{ij}" is a pattern, is semantically equivalent to:
\[ "@f x1 x2@ ... @xk = case (x1, @...@, xk) of@"
\ba[t]{l}
"@(@p_{11}, ..., p_{1k}@) ->@ e_{1}" \\
"..." \\
"@(@p_{n1}, ..., p_{nk}@) ->@ e_{n}"
\ea
\]
where the @xi@ are new identifiers. (For a more general translation
that includes guards, see \see{function-bindings}.) For example, the
definition of @take@ given earlier is equivalent to:
\bprog
@
take m ys = case (m,ys) of
(0,_) -> []
(_,[]) -> []
(n,x:xs) -> x : take (n-1) xs
@
\eprog
A point not made earlier is that, for type correctness, the types of
the right-hand sides of a case expression or set of equations
comprising a function definition must all be the same; more precisely,
they must all share a common principal type.
The pattern-matching rules for case expressions are the same as we
have given for function definitions, so there is really nothing new to
learn here, other than to note the convenience that case expressions
offer. Indeed, there's one use of a case expression that is so common
that it has special syntax: the {\em conditional expression}. In
Haskell, conditional expressions have the familiar form:
\[ @if@\ e_1\ @then@\ e_2\ @else@\ e_3 \]
which is really short-hand for:
\[\ba{ll}
@case@\ e_1\ @of@ & @True ->@\ e_2\\
& @False ->@\ e_3
\ea\]
{}From this expansion it should be clear that $e_1$ must have type
@Bool@, and $e_2$ and $e_3$ must have the same (but otherwise
arbitrary) type. In other words, @if@-@then@-@else@ when viewed
as a function has type @Bool->a->a->a@.
\subsection{Lazy Patterns}
\label{tut-lazy-patterns}
There is one other kind of pattern allowed in Haskell. It is called a
{\em lazy pattern}, and has the form @~@$pat$. Lazy patterns are
{\em irrefutable}: matching a value $v$ against @~@$pat$ always
succeeds, regardless of $pat$. Operationally speaking, if an
identifier in $pat$ is later ``used'' on the right-hand-side, it will
be bound to that portion of the value that would result if $v$ were to
successfully match $pat$, and $\bot$ otherwise.
Lazy patterns are useful in contexts where infinite data structures are being
defined recursively. For example, infinite lists are an excellent
vehicle for writing {\em simulation} programs, and in this context the
infinite lists are often called {\em 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 {\em
requests} to @server@, and @server@ replies to each request with some
kind of {\em response}. This situation is shown pictorially in Figure
\ref{tut-client-fig}. (Note that @client@ also takes an initial message as
argument.)
%**
%**
Figure 2
Using
streams to simulate the message sequences, the Haskell code
corresponding to this diagram is:
\bprog
@
reqs = client init resps
resps = server reqs
@
\eprog
These recursive equations are a direct lexical transliteration of the
diagram.
%*ignore
\begin{figure}
\begin{center}
\mbox{
\epsfbox{fig2.eps}}
\end{center}
\caption{Client-Server Simulation}
\label{tut-client-fig}
\end{figure}
%*endignore
Let us further assume that the structure of the server and client look
something like this:
\bprog
@
client init (resp:resps) = init : client (next resp) resps
server (req:reqs) = process req : server reqs
@
\eprog
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 appropriate
response.
Unfortunately, this program has a serious problem: it will not produce
any output! The problem is that @client@, as used in the recursive
setting of @reqs@ and @resps@, attempts a match on the response list
before it has submitted its first request! In other words, the
pattern matching is being done ``too early.'' One way to fix this is
to redefine @client@ as follows:
\bprog
@
client init resps = init : client (next (head resps)) (tail resps)
@
\eprog
Although workable, this solution does not read as well as that given
earlier. A better solution is to use a lazy pattern:
\bprog
@
client init ~(resp:resps) = init : client (next resp) resps
@
\eprog
Because lazy patterns are irrefutable, the match will immediately
succeed, allowing the initial request to be ``submitted'', in turn
allowing the first response to be generated; the engine is now
``primed'', and the recursion takes care of the rest.
As an example of this program in action, if we define:
\bprog
@
init = 0
next resp = resp
process req = req+1
@
\eprog
then we see that:
\[ @take 10 reqs@\ \ \ \ \red\ \ \ \ @[0,1,2,3,4,5,6,7,8,9]@ \]
As another example of the use of lazy patterns, consider the
definition of Fibonacci given earlier:
\bprog
@
fib = 1 : 1 : [ a+b | (a,b) <- zip fib (tail fib) ]
@
\eprog
We might try rewriting this using an as-pattern:
\bprog
@
fib@@(1:tfib) = 1 : 1 : [ a+b | (a,b) <- zip fib tfib ]
@
\eprog
This version of @fib@ has the (small) advantage of not using @tail@ on
the right-hand side, since it is available in ``destructured'' form on
the left-hand side as @tfib@.
\syn{This kind of equation is called a {\em pattern binding} because
it is a top-level equation in which the entire left-hand side is a
pattern; i.e.\ both @fib@ and @tfib@ become bound within the scope of
the declaration.}
Now, using the same reasoning as earlier, we should be led to
believe that this program will not generate any output. Curiously,
however, it {\em does}, and the reason is simple: in Haskell,
pattern bindings are assumed to have an implicit @~@ in front of them,
reflecting the most common behavior expected of pattern bindings, and
avoiding some anomalous situations which are beyond the scope of this
tutorial. Thus we see that lazy patterns play an important role in
Haskell, if only implicitly.
\subsection{Lexical Scoping and Nested Forms}
\label{tut-nesting}
It is often desirable to create a nested scope within an expression,
for the purpose of creating local bindings not seen elsewhere---i.e.
some kind of ``block-structuring'' form. In Haskell there are two ways
to achieve this:
\paragraph*{Let Expressions.} Haskell's {\em let expressions} are
useful whenever a nested set of bindings is required. As a simple
example, consider:
\bprog
@
let y = a*b
f x = (x+y)/y
in f c + f d
@
\eprog
The set of bindings created by a @let@ expression is {\em mutually
recursive}, and pattern bindings are treated as lazy patterns (i.e.
they carry an implicit @~@). The only kind of declarations permitted
are {\em type signatures}, {\em function bindings}, and {\em pattern
bindings}.
\paragraph*{Where Clauses.} Sometimes it is convenient to scope
bindings over several guarded equations, which requires a {\em where
clause}:
\bprog
@
f x y | y>z = ...
| y==z = ...
| y