diff --git a/report/basic.verb b/report/basic.verb
index c5a242285fe1cb6f20812c9a3aeac9952fa4bd81..60a328f40d33bb64f83197727212cf504a17e6ee 100644
--- a/report/basic.verb
+++ b/report/basic.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/basic.verb,v 1.15 2002/12/03 10:27:21 ross Exp $
+% $Header: /home/cvs/root/haskell-report/report/basic.verb,v 1.16 2002/12/10 11:51:05 simonpj Exp $
 %
 %**<title>The Haskell 98 Report: Predefined Types and Classes</title>
 %*section 6
@@ -8,13 +8,12 @@
 \label{basic-types-and-classes}
 The \Haskell{} Prelude contains predefined classes, types,
 and functions that are implicitly imported into every Haskell
-program.  In this section, we describe the types and classes found in
+program.  In this chapter, we describe the types and classes found in
 the Prelude.
 Most functions are not described in detail here as they
-can easily be understood from their definitions as given in Appendix
-\ref{stdprelude}.
+can easily be understood from their definitions as given in Chapter~\ref{stdprelude}.
 Other predefined types such as arrays, complex numbers, and rationals
-are defined in the \Haskell{} Library Report.
+are defined in Part~\ref{libraries}.
 
 \subsection{Standard Haskell Types}
 \label{basic-types}
@@ -99,7 +98,7 @@ The first constructor is the null list, written `@[]@' (``nil''),
 \index{[]@@{\tt  []} (nil)}%
 and the second is `@:@' (``cons'').
 \indextt{:}
-The module @PreludeList@ (see Appendix~\ref{preludelist}) 
+The module @PreludeList@ (see Section~\ref{preludelist})
 defines many standard list functions.  
 Arithmetic sequences
 \index{arithmetic sequence}
@@ -170,14 +169,14 @@ functional values.  The following simple functions are found in the Prelude:
 The @IO@ type serves as a tag for operations (actions) that interact
 with the outside world.  The @IO@ type is abstract: no constructors are
 visible to the user.  @IO@ is an instance of the @Monad@ and @Functor@
-classes.  Section \ref{io} describes I/O operations.
+classes.  Chapter~\ref{io} describes I/O operations.
 
 @IOError@ is an abstract type representing errors raised by I/O
 operations.  It is an instance of @Show@ and @Eq@.  Values of this type
 are constructed by the various I/O functions and are not presented in
 any further detail in this report.  The Prelude contains a few
-I/O functions (defined in Section~\ref{preludeio}), and the Library
-Report contains many more.
+I/O functions (defined in Section~\ref{preludeio}), and Part~\ref{libraries}
+contains many more.
 \indextycon{IO}
 \indextycon{IOError}
 
@@ -278,7 +277,7 @@ are instances of these classes.
 
 Default class method declarations (Section~\ref{classes}) are provided
 for many of the methods in standard classes.  A comment with each
-@class@ declaration in Appendix~\ref{stdprelude} specifies the
+@class@ declaration in Chapter~\ref{stdprelude} specifies the
 smallest collection of method definitions that, together with the
 default declarations, provide a reasonable definition for all the
 class methods.  If there is no such comment, then all class methods
@@ -389,7 +388,7 @@ class  Show a  where
 The @Read@ and @Show@ classes are used to convert values to
 or from strings. 
 The @Int@ argument to @showsPrec@ and @readsPrec@ gives the operator
-precedence of the enclosing context (see Appendix~\ref{derived-text}).
+precedence of the enclosing context (see Section~\ref{derived-text}).
 
 @showsPrec@ and @showList@ return a @String@-to-@String@
 function, to allow constant-time concatenation of its results using function
@@ -477,7 +476,7 @@ The @enumFrom@... methods are used when translating arithmetic
 sequences (Section~\ref{arithmetic-sequences}).
 
 Instances of @Enum@ may be derived for any enumeration type (types
-whose constructors have no fields); see Appendix~\ref{derived-appendix}.
+whose constructors have no fields); see Chapter~\ref{derived-appendix}.
 
 For any type that is an instance of class @Bounded@ as well as @Enum@, the following
 should hold:
@@ -505,10 +504,10 @@ an implicit bound, thus:
 The following @Prelude@ types are instances of @Enum@: 
 \begin{itemize}
 \item Enumeration types: @()@, @Bool@, and @Ordering@. The
-semantics of these instances is given by Appendix~\ref{derived-appendix}.
+semantics of these instances is given by Chapter~\ref{derived-appendix}.
 For example, @[LT..]@ is the list @[LT,EQ,GT]@.
 
-\item @Char@: the instance is given in Appendix~\ref{stdprelude}, based 
+\item @Char@: the instance is given in Chapter~\ref{stdprelude}, based
 on the primitive functions that convert between a @Char@ and an @Int@.
 For example, @enumFromTo 'a' 'z'@ denotes
 the list of lowercase letters in alphabetical order.
@@ -595,7 +594,7 @@ class  Monad m  where
 @
 \eprog
 The @Monad@ class defines the basic operations over a {\em monad}.
-See Section \ref{io} for more information about monads.
+See Chapter~\ref{io} for more information about monads.
 
 ``@do@'' expressions provide a convenient syntax for writing
 monadic expressions (see Section~\ref{do-expressions}).
diff --git a/report/decls.verb b/report/decls.verb
index a2465bf4dedc720f201ef748ef8cf61fdd195125..ffb2e357c47a37e7de11ec660d3c296e6157d0df 100644
--- a/report/decls.verb
+++ b/report/decls.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/decls.verb,v 1.17 2002/12/03 10:27:21 ross Exp $
+% $Header: /home/cvs/root/haskell-report/report/decls.verb,v 1.18 2002/12/10 11:51:10 simonpj Exp $
 %
 %**<title>The Haskell 98 Report: Declarations</title>
 %*section 4
@@ -9,7 +9,7 @@
 \index{binding}
 \label{declarations}
 
-In this section, we describe the syntax and informal semantics of \Haskell{}
+In this chapter, we describe the syntax and informal semantics of \Haskell{}
 {\em declarations}.
 % including their translations into
 % the \Haskell{} kernel where appropriate.
@@ -66,7 +66,7 @@ fixity	-> @infixl@ | @infixr@ | @infix@
 
 The declarations in the syntactic category "topdecls" are only allowed
 at the top level of a \Haskell{} module (see
-Section~\ref{modules}), whereas "decls" may be used either at the top level or
+Chapter~\ref{modules}), whereas "decls" may be used either at the top level or
 in nested scopes (i.e.~those within a @let@ or @where@ construct).
 
 For exposition, we divide the declarations into
@@ -295,7 +295,7 @@ These special syntactic forms always denote the built-in type constructors
 for functions, tuples, and lists, regardless of what is in scope.
 In a similar way, the prefix type constructors @(->)@, @[]@, @()@, @(,)@, 
 and so on, always denote the built-in type constructors; they 
-cannot be qualified, nor mentioned in import or export lists (Section~\ref{modules}).
+cannot be qualified, nor mentioned in import or export lists (Chapter~\ref{modules}).
 (Hence the special production, ``gtycon'', above.)
 
 Although the list and tuple types have special syntax, their semantics 
@@ -377,7 +377,7 @@ case the concrete syntax contains no @=>@.
 \subsubsection{Semantics of Types and Classes}
 \label{type-semantics}
 
-In this subsection, we provide informal details of the type system.
+In this section, we provide informal details of the type system.
 % the formal semantics is described in Appendix~\ref{static-semantics}
 (Wadler and Blott \cite{wadler:classes} and Jones
 \cite{jones:cclasses} discuss type
@@ -1090,7 +1090,7 @@ valid only if @[a]@ is an instance of @Foo@ under the assumptions
 instance of @Foo@ under the stronger assumption @Num a@.
 
 Further examples of 
-@instance@ declarations may be found in Appendix~\ref{stdprelude}.
+@instance@ declarations may be found in Chapter~\ref{stdprelude}.
 
 \subsubsection{Derived Instances}
 \index{derived instance}
@@ -1125,7 +1125,7 @@ and @Read@\indexdi{Read},
 all mentioned in Figure~\ref{standard-classes}, page~\pageref{standard-classes}.
 The
 precise details of how the derived instances are generated for each of
-these classes are provided in Appendix~\ref{derived-appendix}, including
+these classes are provided in Chapter~\ref{derived-appendix}, including
 a specification of when such derived instances are possible. 
 %(which is important for the following discussion).
 Classes defined by the standard libraries may also be derivable.
@@ -1172,7 +1172,7 @@ A problem inherent with \Haskell{}-style overloading is the
 possibility of an {\em ambiguous type}.
 \index{ambiguous type}
 For example, using the
-@read@ and @show@ functions defined in Appendix~\ref{derived-appendix},
+@read@ and @show@ functions defined in Chapter~\ref{derived-appendix},
 and supposing that just @Int@ and @Bool@ are members of @Read@ and
 @Show@, then the expression
 \bprog
@@ -1215,7 +1215,7 @@ which disambiguates the type.
 Occasionally, an otherwise ambiguous expression needs to be made
 the same type as some variable, rather than being given a fixed
 type with an expression type-signature.  This is the purpose
-of the function @asTypeOf@ (Appendix~\ref{stdprelude}):
+of the function @asTypeOf@ (Chapter~\ref{stdprelude}):
 "x" @`asTypeOf`@ "y" has the value of "x", but "x" and "y" are
 forced to have the same type.  For example,
 \bprog
diff --git a/report/derived.verb b/report/derived.verb
index aaf42b84ae8c5b26c091293d792a7be5a1c6ce80..e31b84b376228893042a242408eab4b17a3a377d 100644
--- a/report/derived.verb
+++ b/report/derived.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/derived.verb,v 1.11 2002/12/03 10:27:22 ross Exp $
+% $Header: /home/cvs/root/haskell-report/report/derived.verb,v 1.12 2002/12/10 11:51:10 simonpj Exp $
 %
 % The paragraph describing the formats of standard representations might
 % be deleted, since the info is already in the Prelude.  
@@ -19,7 +19,7 @@ automatically in conjunction with a @data@ or @newtype@ declaration.
 The body of a derived instance declaration is derived syntactically from
 the definition of the associated type.  Derived instances are
 possible only for classes known to the compiler: those defined in
-either the Prelude or a standard library.  In this appendix, we
+either the Prelude or a standard library.  In this chapter, we
 describe the derivation of classes defined by the Prelude.
 
 If "T" is an algebraic datatype declared by:\index{algebraic datatype}
@@ -126,7 +126,7 @@ instances for each of the derivable Prelude classes are now given.
 Free variables and constructors used in these translations
 always refer to entities defined by the @Prelude@.
 
-\subsection{Derived instances of @Eq@ and @Ord@.}
+\subsection{Derived instances of @Eq@ and @Ord@}
 \indexdi{Eq}
 \indexdi{Ord}
 The class methods automatically introduced by derived instances
@@ -159,7 +159,7 @@ These examples illustrate this property:
 @
 \eprog
 All derived operations of class @Eq@ and @Ord@ are strict in both arguments.
-For example, "@False <=@ \bot" is "\bot", even though @False@ is the first constructor
+For example, "@False < @\bot" is "\bot", even though @False@ is the first constructor
 of the @Bool@ type.
 
 \subsection{Derived instances of @Enum@}
@@ -210,7 +210,7 @@ we would have:
 @
 \eprog
 
-\subsection{Derived instances of @Bounded@.}
+\subsection{Derived instances of @Bounded@}
 \indexdi{Bounded}
 The @Bounded@ class introduces the class
 methods 
@@ -235,7 +235,7 @@ would generate the following @Bounded@ instance:
 @
 \eprog
 
-\subsection{Derived instances of @Read@ and @Show@.}
+\subsection{Derived instances of @Read@ and @Show@}
 \label{derived-text}
 \indexdi{Read}
 \indexdi{Show}
@@ -316,7 +316,7 @@ using non-standard denotations.  This is especially useful for strings
 @readsPrec@ will parse any valid representation of the standard types 
 apart from strings, for which only quoted strings are accepted, and other lists,
 for which only the bracketed form @[@\ldots@]@ is accepted. See
-Appendix~\ref{stdprelude} for full details.
+Chapter~\ref{stdprelude} for full details.
 
 The result of @show@ is a syntactically correct \Haskell{} expression
 containing only constants, given the fixity declarations in force at
diff --git a/report/exps.verb b/report/exps.verb
index 256f54267018e3a7f620d59b8947c5261eba91b2..9dc0b5e649aee5f6bd58824c0019a4ba6b8ccc4b 100644
--- a/report/exps.verb
+++ b/report/exps.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/exps.verb,v 1.18 2002/12/03 01:17:14 ross Exp $
+% $Header: /home/cvs/root/haskell-report/report/exps.verb,v 1.19 2002/12/10 11:51:10 simonpj Exp $
 %
 %*section 3
 %**<title>The Haskell 98 Report: Expressions</title>
@@ -7,7 +7,7 @@
 \section{Expressions}\index{expression}
 \label{expressions}
 
-In this section, we describe the syntax and informal semantics of
+In this chapter, we describe the syntax and informal semantics of
 \Haskell{} {\em expressions}, including their translations into the
 \Haskell{} kernel, where appropriate.  Except in the case of @let@
 expressions, these translations preserve both the static and dynamic
@@ -440,7 +440,7 @@ but @(+a+b)@ is not; the latter may legally be written as @(+(a+b))@.
 As another example, the expression
 \bprog
 @
-  (let x = 10 in x +)
+  (let n = 10 in n +)
 @
 \eprog
 is invalid because, by the let/lambda meta-rule (Section~\ref{expressions}),
@@ -544,7 +544,7 @@ gconsym -> @:@
 "k>=1".  The list constructor is @:@, and the empty list is denoted @[]@.
 Standard operations on
 lists are given in the Prelude (see Section~\ref{basic-lists}, and
-Appendix~\ref{stdprelude} notably Section~\ref{preludelist}).
+Chapter~\ref{stdprelude} notably Section~\ref{preludelist}).
 
 \outline{
 \paragraph*{Translation:}  
@@ -580,7 +580,7 @@ of arbitrary length "k>=2".  The constructor for an "n"-tuple is denoted by
 @(,@\ldots@,)@, where there are "n-1" commas.  Thus @(a,b,c)@ and
 @(,,) a b c@ denote the same value.
 Standard operations on tuples are given
-in the Prelude (see Section~\ref{basic-tuples} and Appendix~\ref{stdprelude}).
+in the Prelude (see Section~\ref{basic-tuples} and Chapter~\ref{stdprelude}).
 
 \outline{
 \paragraph*{Translation:}  
@@ -762,7 +762,7 @@ nested, lexically-scoped,
 mutually-recursive list of declarations (@let@ is often called @letrec@ in
 other languages).  The scope of the declarations is the expression "e"
 and the right hand side of the declarations.  Declarations are
-described in Section~\ref{declarations}.  Pattern bindings are matched
+described in Chapter~\ref{declarations}.  Pattern bindings are matched
 lazily; an implicit @~@ makes these patterns
 irrefutable.\index{irrefutable pattern}
 For example, 
@@ -1593,14 +1593,14 @@ $e'$ @ }@ \\
 &{\rm where $K$ and $K'$ are distinct @data@ constructors of arity $n$ and $m$, respectively}\\[4pt]
 %\\
 (q)&@case (@$K$@ @$e_1$@ @$\ldots$@ @$e_n$@) of { @$K$@ @$x_1$@ @$\ldots$@ @$x_n$@ -> @$e$@; _ -> @$e'$@ }@\\
-&$=~(@\@x_1 \ldots x_n@ -> @e)~e_1 ~\ldots~ e_n$\\
+&$=$@ (\@$x_1~\ldots~x_n$@ -> @$e$@) @$e_1~\ldots~e_n$\\
 &{\rm where $K$ is a @data@ constructor of arity $n$}\\[4pt]
 
 (r)&@case@~$\bot$~@of { @$K$@ @$x_1$@ @$\ldots$@ @$x_n$@ -> @$e$@; _ -> @$e'$@ }@ ~$=$~ $\bot$ \\
 &{\rm where $K$ is a @data@ constructor of arity $n$}\\[4pt]
 
 (s)&@case @$v$@ of { @$x$@+@$k$@ -> @$e$@; _ -> @$e'$@ }@\\
-&$=$@ if @$v$@ >= @$k$@ then @(@\@$x$@ -> @$e$)~($v$@-@$k$)@ else @$e'$\\
+&$=$@ if @$v$@ >= @$k$@ then (\@$x$@ -> @$e$@) (@$v$@-@$k$@) else @$e'$\\
 &{\rm where $k$ is a numeric literal}\\
 \end{tabular}
 }
diff --git a/report/haskell.bbl b/report/haskell.bbl
index c5019988969e00efdc214560778442cb2bd3491b..7b0629dd20ef2a51da8f49b4d489afda43ea7005 100644
--- a/report/haskell.bbl
+++ b/report/haskell.bbl
@@ -10,7 +10,7 @@ J.~Backus.
 \newblock {\em CACM}, 21(8):613--641, August 1978.
 
 \bibitem{curry&feys:book}
-H.B. Curry and R.~Feys.
+H.B.~Curry and R.~Feys.
 \newblock {\em Combinatory Logic}.
 \newblock North-Holland Pub. Co., Amsterdam, 1958.
 
@@ -21,7 +21,7 @@ L.~Damas and R.~Milner.
   Programming Languages}, pages 207--212, Albuquerque, N.M., January 1982.
 
 \bibitem{faxen:static}
-K-F. Fax\'en
+K-F.~Fax\'en
 \newblock A static semantics for Haskell
 \newblock {\em Journal of Functional Programming}, 2002.
 
@@ -37,13 +37,13 @@ P.~Hudak, J.~Fasel, and J.~Peterson.
 \newblock Technical Report YALEU/DCS/RR-901, Yale University, May 1996.
 
 \bibitem{jones:cclasses}
-Mark~P. Jones.
+Mark~P.~Jones.
 \newblock A system of constructor classes: overloading and implicit
   higher-order polymorphism.
 \newblock {\em Journal of Functional Programming}, 5(1), January 1995.
 
 \bibitem{jones:thih}
-Mark~P. Jones.
+Mark~P.~Jones.
 \newblock Typing Haskell in Haskell.
 \newblock {\em Haskell Workshop}, Paris, October 1999.
 
@@ -54,7 +54,7 @@ P.~Penfield, Jr.
   Francisco, September 1981.
 
 \bibitem{peyton-jones:book}
-S.L. Peyton~Jones.
+S.L.~Peyton~Jones.
 \newblock {\em The Implementation of Functional Programming Languages}.
 \newblock Prentice-Hall International, Englewood Cliffs, New Jersey, 1987.
 
diff --git a/report/haskell.idx b/report/haskell.idx
index 9ec13874f8d37d6ae4a98686430d2301b935e680..30cff08c8a12dad45450c307a12ebb5d896d2d4f 100644
--- a/report/haskell.idx
+++ b/report/haskell.idx
@@ -304,7 +304,7 @@
 \indexentry{abstract datatype}{44}
 \indexentry{field label}{44}
 \indexentry{strictness flag}{45}
-\indexentry{!@{\tt  !}}{45}
+\indexentry{"!@{\tt  {\char'041}}}{45}
 \indexentry{type synonym}{45}
 \indexentry{topdecl@{\em topdecl} (\mbox{\tt type})}{45}
 \indexentry{simpletype@{\it  simpletype}}{45}
@@ -395,7 +395,7 @@
 \indexentry{>=@{\tt  >=}}{55}
 \indexentry{elem@{\tt  elem}}{55}
 \indexentry{notElem@{\tt  notElem}}{55}
-\indexentry{&&@{\tt  \&\&}@{\tt  &&@{\tt  \&\&}}}{55}
+\indexentry{&&@{\tt  \&\&}}{55}
 \indexentry{"|"|@{\tt  {\char'174}{\char'174}}}{55}
 \indexentry{>>@{\tt  >>}}{55}
 \indexentry{>>=@{\tt  >>=}}{55}
@@ -505,7 +505,7 @@
 \indexentry{Ordering@{\tt  Ordering} (datatype)}{81}
 \indexentry{maybe@{\tt  maybe}}{81}
 \indexentry{either@{\tt  either}}{81}
-\indexentry{$!@{\tt  $!}}{81}
+\indexentry{$"!@{\tt  {\char'044}{\char'041}}}{81}
 \indexentry{seq@{\tt  seq}}{81}
 \indexentry{strictness flags}{82}
 \indexentry{Eq@{\tt  Eq} (class)}{82}
@@ -1172,13 +1172,13 @@
 \indexentry{algebraic datatype}{141}
 \indexentry{Eq@{\tt  Eq} (class)!derived instance}{142}
 \indexentry{Ord@{\tt  Ord} (class)!derived instance}{142}
-\indexentry{==@{\tt ==}}{142}
-\indexentry{/=@{\tt /=}}{142}
+\indexentry{==@{\tt  ==}}{142}
+\indexentry{/=@{\tt  /=}}{142}
 \indexentry{compare@{\tt  compare}}{142}
-\indexentry{<@{\tt <}}{142}
-\indexentry{<=@{\tt <=}}{142}
-\indexentry{>@{\tt >}}{142}
-\indexentry{>=@{\tt >=}}{142}
+\indexentry{<@{\tt  <}}{142}
+\indexentry{<=@{\tt  <=}}{142}
+\indexentry{>@{\tt  >}}{142}
+\indexentry{>=@{\tt  >=}}{142}
 \indexentry{max@{\tt  max}}{142}
 \indexentry{min@{\tt  min}}{142}
 \indexentry{Enum@{\tt  Enum} (class)!derived instance}{142}
@@ -1204,7 +1204,7 @@
 \indexentry{Rational@{\tt  Rational} (type synonym)}{151}
 \indexentry{Ratio@{\tt  Ratio} (datatype)}{151}
 \indexentry{Rational@{\tt  Rational} (type synonym)}{151}
-\indexentry{%@{\tt {\char'045}}}{151}
+\indexentry{%@{\tt  {\char'045}}}{151}
 \indexentry{numerator@{\tt  numerator}}{151}
 \indexentry{denominator@{\tt  denominator}}{151}
 \indexentry{Ratio@{\tt  Ratio} (module)}{153}
@@ -1351,7 +1351,7 @@
 \indexentry{ixmap@{\tt  ixmap}}{173}
 \indexentry{Array@{\tt  Array} (datatype)}{174}
 \indexentry{array@{\tt  array}}{174}
-\indexentry{!@{\tt {\char'041}}}{174}
+\indexentry{"!@{\tt  {\char'041}}}{174}
 \indexentry{bounds@{\tt  bounds}}{174}
 \indexentry{indices@{\tt  indices}}{174}
 \indexentry{elems@{\tt  elems}}{174}
@@ -1444,7 +1444,7 @@
 \indexentry{find@{\tt  find}}{182}
 \indexentry{nub@{\tt  nub}}{182}
 \indexentry{delete@{\tt  delete}}{182}
-\indexentry{(\\)@{\tt  (\\)}}{182}
+\indexentry{\\\\@{\tt  {\char'134}{\char'134}}}{182}
 \indexentry{union@{\tt  union}}{182}
 \indexentry{intersect@{\tt  intersect}}{182}
 \indexentry{intersperse@{\tt  intersperse}}{183}
@@ -1890,11 +1890,11 @@
 \indexentry{ClockTime@{\tt  ClockTime} (datatype)}{234}
 \indexentry{Month@{\tt  Month} (datatype)}{234}
 \indexentry{Day@{\tt  Day} (datatype)}{234}
-\indexentry{ctDay@{\tt  ctDay}}{234}
-\indexentry{ctHour@{\tt  ctHour}}{234}
-\indexentry{ctMin@{\tt  ctMin}}{234}
-\indexentry{ctIsDST@{\tt  ctIsDST}}{234}
-\indexentry{CalendarTime@{\tt  CalendarTime} (datatype)}{234}
+\indexentry{ctDay@{\tt  ctDay}}{235}
+\indexentry{ctHour@{\tt  ctHour}}{235}
+\indexentry{ctMin@{\tt  ctMin}}{235}
+\indexentry{ctIsDST@{\tt  ctIsDST}}{235}
+\indexentry{CalendarTime@{\tt  CalendarTime} (datatype)}{235}
 \indexentry{tdYear@{\tt  tdYear}}{235}
 \indexentry{tdMonth@{\tt  tdMonth}}{235}
 \indexentry{tdDay@{\tt  tdDay}}{235}
@@ -2018,8 +2018,8 @@
 \indexentry{type renaming|see{{\tt newtype} declaration}}{249}
 \indexentry{type signature!for an expression|see{expression type-signature}}{249}
 \indexentry{(aaa)@{\tt ()}|see{trivial type and unit expression}}{249}
-\indexentry{-@{\tt -}|hseealso{negation}}{249}
-\indexentry{+@{\tt +}|hseealso{\mbox{$\it n\makebox{\tt +}k$} pattern}}{249}
+\indexentry{-@{\tt  -}|hseealso{negation}}{249}
+\indexentry{+@{\tt  +}|hseealso{\mbox{$\it n\makebox{\tt +}k$} pattern}}{249}
 \indexentry{\\@{\tt {\char'134}}|see{lambda abstraction}}{249}
 \indexentry{~@{\tt {\char'176}}|see{irrefutable pattern}}{249}
 \indexentry{derived instance|hseealso{instance declaration}}{249}
diff --git a/report/haskell.verb b/report/haskell.verb
index a97b47ed3ab3baf8026fe73b394704026889917f..6a74040aa58e38e707c76298f0e124bf759c69c4 100644
--- a/report/haskell.verb
+++ b/report/haskell.verb
@@ -362,7 +362,7 @@ Simon Peyton Jones (editor)
 \begin{center} \emph{Copyright notice.} \end{center}
 
 The authors and publisher intend this Report to belong to the entire Haskell
-community, and grants permission to copy and distribute it for any
+community, and grant permission to copy and distribute it for any
 purpose, provided that it is reproduced in its
 entirety, including this Notice. Modified versions of this Report may
 also be copied and distributed for any 
@@ -411,6 +411,7 @@ that it does not claim to be a definition of the language Haskell 98.
 % ------------------------- Part II: libraries report -----------------------------------
 
 \part{The Haskell 98 Libraries}
+\label{libraries}
 
 \input{ratio}\startnewsection
 \input{complex}\startnewsection
diff --git a/report/haskell98-bugs.html b/report/haskell98-bugs.html
index 2e773dc1087637423285276da55f31c348936d30..4af0d149038afcf7022547984d0cd360a62ef83c 100644
--- a/report/haskell98-bugs.html
+++ b/report/haskell98-bugs.html
@@ -1848,6 +1848,9 @@ in dir." the following extra sentence:
 <p>
 "Each entry in the returned list is named relative to the directory dir, not as an absolute path."
 
+<p><li> [Dec 2002] <strong>Page 70, Section 14, The <tt>Time</tt> library; and page 72, section 14.1</strong>.
+Add <tt>ctSec</tt> to the export list for Time (in two places).
+
 <p><li> [Apr 2001] <strong>Page 78, Section 16, The <tt>CPUTime</tt> library</strong>.
 Add <tt>cpuTimePrecision</tt> to the export list.
 
diff --git a/report/intro.verb b/report/intro.verb
index b5583c7640179d5c51831c699a3f05c8cc9afcb3..4e3a21e94230c7d7a388256baf39b417f227ffe2 100644
--- a/report/intro.verb
+++ b/report/intro.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/intro.verb,v 1.6 2002/12/03 11:14:41 ross Exp $
+% $Header: /home/cvs/root/haskell-report/report/intro.verb,v 1.7 2002/12/10 11:51:11 simonpj Exp $
 %
 %**<title>The Haskell 98 Report: Introduction</title>
 %*section 1
@@ -69,23 +69,23 @@ In this section, we describe the abstract syntactic and semantic structure of
 rest of the report.
 \begin{enumerate}
 \item At the topmost level a \Haskell{} program is a set
-of {\em modules}, described in Section~\ref{modules}.  Modules provide
+of {\em modules}, described in Chapter~\ref{modules}.  Modules provide
 a way to control namespaces
 and to re-use software in large programs.
 
 \item The top level of a module consists of a collection of
 {\em declarations}, of which there are several kinds, all described
-in Section~\ref{declarations}.  Declarations
+in Chapter~\ref{declarations}.  Declarations
 define things such as ordinary values, datatypes, type
 classes, and fixity information.
 
 \item At the next lower level are {\em expressions}, described
-in Section~\ref{expressions}.  An expression denotes a {\em value}
+in Chapter~\ref{expressions}.  An expression denotes a {\em value}
 and has a {\em static type}; expressions are at the heart of
 \Haskell{} programming ``in the small.''
 
 \item At the bottom level is \Haskell{}'s {\em
-lexical structure}, defined in Section~\ref{lexical-structure}.  The
+lexical structure}, defined in Chapter~\ref{lexical-structure}.  The
 lexical structure captures the concrete
 representation of \Haskell{} programs in text files.
 
@@ -93,12 +93,12 @@ representation of \Haskell{} programs in text files.
 This report proceeds bottom-up with respect
 to \Haskell{}'s syntactic structure.
 
-The sections not mentioned above are
-Section~\ref{basic-types-and-classes}, which
+The chapters not mentioned above are
+Chapter~\ref{basic-types-and-classes}, which
 describes the standard built-in datatypes and classes in \Haskell{}, and
-Section~\ref{io}, which discusses the I/O facility in \Haskell{}
+Chapter~\ref{io}, which discusses the I/O facility in \Haskell{}
 (i.e.~how \Haskell{} programs communicate with the outside world).
-Also, there are several appendices describing the Prelude,
+Also, there are several chapters describing the Prelude,
 the concrete syntax, literate programming, the specification of derived
 instances, and pragmas supported by most \Haskell{} compilers.
 
diff --git a/report/io-13.verb b/report/io-13.verb
index 3d5d5567322b4ada8c9835a5848575ecef6a0ef7..6b403c89540125d1c7fa3d6cea9b586debd9b6b0 100644
--- a/report/io-13.verb
+++ b/report/io-13.verb
@@ -41,6 +41,7 @@ corresponding to sequencing operators (such as the semicolon) in imperative
 languages.
 
 \subsection{Standard I/O Functions}
+\label{standard-io-functions}
 Although \Haskell{} provides fairly sophisticated I/O facilities, as
 defined in the @IO@ library, it is possible to write many
 \Haskell{} programs using only the few simple functions that are
@@ -286,7 +287,7 @@ The @fail@ method of the @IO@ instance of the @Monad@ class (Section~\ref{monad-
 \eprog
 \indextt{fail}%
 The exceptions raised by the I/O functions in the Prelude are defined
-in the Library Report.
+in Chapter~\ref{IO}.
 
 %**~footer
 
diff --git a/report/io.verb b/report/io.verb
index c8462e7b8c388055aadd9a1d2bdd145a50873c9d..940237656b9bd42d7d2acb813ed69c3514e91752 100644
--- a/report/io.verb
+++ b/report/io.verb
@@ -199,7 +199,7 @@ implementation-dependent, but they should normally be the same if they
 have the same absolute path name and neither has been renamed, for
 example.
 
-{\em Warning}: the @readFile@ operation (Section 7.1 of the Haskell Language Report)
+{\em Warning}: the @readFile@ operation (Section~\ref{standard-io-functions})
 holds a semi-closed handle on the file until the entire contents of the file have been
 consumed.  It follows that an attempt to write to a file (using @writeFile@, for example)
 that was earlier opened by @readFile@ will usually result in 
@@ -480,8 +480,8 @@ within "t" milliseconds.
 Computation @hReady@~"hdl"\indextt{hReady} indicates whether at least one item is
 available for input from handle "hdl".
 
-{\em Error reporting}.
-The @hWaitForInput@ and @hReady@ computations fail with
+{\em Error reporting}:
+the @hWaitForInput@ and @hReady@ computations fail with
 @isEOFError@ if the end of file has been reached.
 
 \subsubsection{Reading Input}
@@ -493,10 +493,10 @@ Computation @hGetLine@~"hdl"\indextt{hGetLine} reads a line from the file or
 channel managed by "hdl". The Prelude's @getLine@ is a shorthand
 for @hGetLine stdin@.
 
-{\em Error reporting}.
-The @hGetChar@ computation fails with
+{\em Error reporting}:
+the @hGetChar@ computation fails with
 @isEOFError@ if the end of file has been reached.
-The @hGetLine@ fails with @isEOFError@ if the end of file is encountered
+The @hGetLine@ computation fails with @isEOFError@ if the end of file is encountered
 when reading the {\em first} character of the line. If @hGetLine@ encounters
 end-of-file at any other point while reading in a line, it is treated as
 a line terminator and the (partial) line is returned.
diff --git a/report/ix.verb b/report/ix.verb
index d921764290e79c02e0b2b21b0fbe20eda203d8b6..be1ffd1c5311760f2b686547687b23c476cf75a7 100644
--- a/report/ix.verb
+++ b/report/ix.verb
@@ -7,7 +7,7 @@
 }
 The @Ix@ class is used to map a contiguous subrange of values in a
 type onto integers.  It is used primarily for array indexing (see
-Section~\ref{arrays}).  
+Chapter~\ref{arrays}).
 The @Ix@ class contains the methods @range@\indextt{range},
 @index@\indextt{index}, and @inRange@\indextt{inRange}. 
 The @index@ operation maps a bounding pair, which defines the lower
@@ -35,8 +35,7 @@ operations:
 \index{Ix@@{\tt Ix}!derived instance}
 
 It is possible to derive an instance of @Ix@ automatically, using
-a @deriving@ clause on a @data@ declaration (Section~4.3.3
-of the Language Report).
+a @deriving@ clause on a @data@ declaration (Section~\ref{derived-decls}).
 Such derived instance declarations for the class @Ix@ are only possible
 for enumerations\index{enumeration} (i.e.~datatypes having
 only nullary constructors) and single-constructor datatypes,
diff --git a/report/lexemes.verb b/report/lexemes.verb
index 08b13a82c939c8a3bca37e0911050236909812e9..657bb8e75941277812ba4ac8b7e999cbc5e69e7c 100644
--- a/report/lexemes.verb
+++ b/report/lexemes.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/lexemes.verb,v 1.12 2002/12/02 14:53:30 simonpj Exp $
+% $Header: /home/cvs/root/haskell-report/report/lexemes.verb,v 1.13 2002/12/10 11:51:11 simonpj Exp $
 %
 %*section 2
 %**<title>Haskell 98 Lexical Structure</title>
@@ -32,7 +32,7 @@
 %% \end{quote}
 
 \noindent
-In this section, 
+In this chapter, 
 we describe the low-level lexical structure of \Haskell{}.
 Most of the details may be skipped in a first reading of
 the report.
@@ -135,7 +135,7 @@ sequences ``@{-@'' and ``@-}@'' have no special significance, and, in a
 nested comment, a sequence of dashes has no special significance.
 
 Nested comments are also used for compiler pragmas, as explained in
-Appendix \ref{pragmas}.
+Chapter~\ref{pragmas}.
 
 If some code is commented out using a nested comment, then any
 occurrence of @{-@ or @-}@ within a string or within an end-of-line
@@ -227,7 +227,7 @@ A name may optionally be {\em qualified} in certain
 circumstances by prepending them with a module identifier.  This
 applies to variable, constructor, type constructor and type class
 names, but not type variables or module names.  Qualified
-names are discussed in detail in Section~\ref{modules}.
+names are discussed in detail in Chapter~\ref{modules}.
 @@@
 qvarid   -> [modid @.@] varid
 qconid   -> [modid @.@] conid
diff --git a/report/list.verb b/report/list.verb
index 641bbcbe8b7670b2f16d9ce6b64c812252f77e22..4012153298dc49610d5eec76c4ca273f8bac6254 100644
--- a/report/list.verb
+++ b/report/list.verb
@@ -33,7 +33,7 @@ or Nothing, if there is no such element.
 There are a number of ``set'' operations defined over the @List@ type.
 @nub@ (meaning ``essence'') removes duplicates elements from a list.
 @delete@, @(\\)@, @union@ and @intersect@ (and their @By@ variants) 
-preserve the invariant their result
+preserve the invariant that their result
 does not contain duplicates, provided that their first argument
 contains no duplicates.
 
diff --git a/report/modules.verb b/report/modules.verb
index e9415f12846d4b8e2e7d209421a37dc0650911b7..cde75e3f98fd7a18c2ef0bd7b5951ccccdabeb90 100644
--- a/report/modules.verb
+++ b/report/modules.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/modules.verb,v 1.18 2002/12/02 14:53:30 simonpj Exp $
+% $Header: /home/cvs/root/haskell-report/report/modules.verb,v 1.19 2002/12/10 11:51:11 simonpj Exp $
 %
 %**<title>The Haskell 98 Report: Modules</title>
 %*section 5
@@ -9,7 +9,7 @@
 \index{module}
 
 A module defines a collection of values, datatypes, type synonyms,
-classes, etc.~(see Section~\ref{declarations}), in an environment created
+classes, etc.~(see Chapter~\ref{declarations}), in an environment created
 by a set of {\em imports} (resources brought into scope from other modules).
 It {\em exports} some of these resources, making them available to
 other modules.  
@@ -22,7 +22,7 @@ which, by convention, must be called @Main@\indexmodule{Main} and must
 export the value @main@\indextt{main}.  The {\em value} of the program
 is the value of the identifier @main@ in module @Main@,
 which must be a computation of type $@IO@~\tau$ for some type $\tau$
-(see Section~\ref{io}).  When the program is executed, the computation
+(see Chapter~\ref{io}).  When the program is executed, the computation
 @main@ is performed, and its result (of type $\tau$) is discarded.
 
 Modules may reference other modules via explicit
@@ -75,14 +75,14 @@ beginning with a capital letter; i.e.~"modid").
 There is one distinguished module, @Prelude@, which is imported into
 all modules by default (see Section~\ref{standard-prelude}), plus a
 set of standard library modules that may be imported as required
-(see the \Haskell{} Library Report).
+(see Part~\ref{libraries}).
 
 \subsection{Module Structure} 
 \label{module-implementations}
 
 A module defines a mutually
 recursive scope containing declarations for value bindings, data
-types, type synonyms, classes, etc. (see Section~\ref{declarations}).
+types, type synonyms, classes, etc. (see Chapter~\ref{declarations}).
 
 @@@
 module -> @module@ modid [exports] @where@ body
@@ -108,7 +108,7 @@ begins with a header: the keyword
 parentheses) to be exported.  The header is followed by a possibly-empty
 list of @import@ declarations ("impdecls", Section~\ref{import}) that specify modules to be imported,
 optionally restricting the imported bindings.  
-This is followed by a possibly-empty list of top-level declarations ("topdecls", Section~\ref{declarations}).  
+This is followed by a possibly-empty list of top-level declarations ("topdecls", Chapter~\ref{declarations}).
 
 An abbreviated form of module, consisting only 
 of\index{abbreviated module}
@@ -658,7 +658,7 @@ many predefined library modules, which provide less frequently used
 functions and types.  For example, arrays, 
 tables, and most of the input/output are all part of the standard
 libraries.    These are 
-defined in the Haskell Library Report.
+defined in Part~\ref{libraries}
 Separating
 libraries from the Prelude has the advantage of reducing the size and
 complexity of the Prelude, allowing it to be more easily assimilated,
@@ -683,16 +683,16 @@ just like those from any other module.
 
 The semantics of the entities in @Prelude@ is specified by a reference
 implementation of @Prelude@ written in \Haskell{}, given in
-Appendix~\ref{stdprelude}.  Some datatypes (such as @Int@) and
+Chapter~\ref{stdprelude}.  Some datatypes (such as @Int@) and
 functions (such as @Int@ addition) cannot be specified directly in
 \Haskell{}.  Since the treatment of such entities depends on the
-implementation, they are not formally defined in the appendix.
+implementation, they are not formally defined in Chapter~\ref{stdprelude}.
 The implementation of
 @Prelude@ is also incomplete in its treatment of tuples: there should
 be an infinite family of tuples and their instance declarations, but the
 implementation only gives a scheme.
 
-Appendix~\ref{stdprelude} defines the module @Prelude@ using
+Chapter~\ref{stdprelude} defines the module @Prelude@ using
 several other modules: @PreludeList@, @PreludeIO@, and so on.
 These modules are {\em not} part of Haskell 98, and they cannot be imported
 separately.  They are simply 
diff --git a/report/pragmas.verb b/report/pragmas.verb
index e801f0fd585ef86b5950bf7b648b16ffce3476af..2473ec1e2abccf7a5c7bf9d9098b8ca0d813813e 100644
--- a/report/pragmas.verb
+++ b/report/pragmas.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/pragmas.verb,v 1.5 2002/12/03 01:17:14 ross Exp $
+% $Header: /home/cvs/root/haskell-report/report/pragmas.verb,v 1.6 2002/12/10 11:51:11 simonpj Exp $
 %
 %**<title>The Haskell 98 Report: Compiler Pragmas</title>
 %**~header
@@ -11,7 +11,7 @@ Some compiler implementations support compiler {\em pragmas}, which are
 used to give additional instructions or hints to the compiler, but which
 do not form part of the \Haskell{} language proper and do not change a
 program's semantics.  This
-section summarizes this existing practice.  An implementation is not
+chapter summarizes this existing practice.  An implementation is not
 required to respect any pragma, but the pragma should be ignored if an
 implementation is not prepared to handle it.  
 Lexically, pragmas appear as comments, except that the enclosing
diff --git a/report/standard-prelude.verb b/report/standard-prelude.verb
index 4eab3176da62763d995d2f03efca373a4367091b..050f9e35b92098c9904fc7a49a0ea2660803d21f 100644
--- a/report/standard-prelude.verb
+++ b/report/standard-prelude.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/standard-prelude.verb,v 1.3 2002/12/02 14:53:30 simonpj Exp $
+% $Header: /home/cvs/root/haskell-report/report/standard-prelude.verb,v 1.4 2002/12/10 11:51:11 simonpj Exp $
 %
 %**<title>The Haskell 98 Report: Standard Prelude</title>
 %**~header
@@ -28,8 +28,8 @@ nor are these three modules available for import separately.
 Only the exports of module @Prelude@ are significant.
 
 Some of these modules import Library modules, such as @Char@, @Monad@, @IO@,
-and @Numeric@.  These modules are described fully in the accompanying
-Haskell 98 Library Report.  These imports are not, of course, part of the specification
+and @Numeric@.  These modules are described fully in Part~\ref{libraries}.
+These imports are not, of course, part of the specification
 of the @Prelude@.  That is, an implementation is free to import more, or less,
 of the Library modules, as it pleases.
 
diff --git a/report/syntax-iso.verb b/report/syntax-iso.verb
index 5d8fa96827bdbd0fbfca446f96ad7217dc6030a5..fbe1b6be096f62a0978e8c85332394b8912812d3 100644
--- a/report/syntax-iso.verb
+++ b/report/syntax-iso.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/syntax-iso.verb,v 1.10 2002/12/02 14:53:30 simonpj Exp $
+% $Header: /home/cvs/root/haskell-report/report/syntax-iso.verb,v 1.11 2002/12/10 11:51:11 simonpj Exp $
 %
 %**<title>Haskell 98 Syntax</title>
 %**~header
@@ -354,7 +354,7 @@ The program text is recovered
 by taking only those lines beginning with ``@>@'', 
 and replacing the leading ``@>@'' with a space.
 Layout and comments apply
-exactly as described in Appendix~\ref{syntax} in the resulting text.
+exactly as described in Chapter~\ref{syntax} in the resulting text.
 
 To capture some cases where one omits an ``@>@'' by mistake, it is an
 error for a program line to appear adjacent to a non-blank comment line,
diff --git a/report/syntax-lexical.verb b/report/syntax-lexical.verb
index 9d79c6ec02ea1e4b2ec960591a38fd78e9a016af..3bf8ab5e8f5502d987fa4bb4ccc9a83f4431145c 100644
--- a/report/syntax-lexical.verb
+++ b/report/syntax-lexical.verb
@@ -1,5 +1,5 @@
 %
-% $Header: /home/cvs/root/haskell-report/report/syntax-lexical.verb,v 1.8 2002/12/02 11:22:02 simonpj Exp $
+% $Header: /home/cvs/root/haskell-report/report/syntax-lexical.verb,v 1.9 2002/12/10 11:51:11 simonpj Exp $
 % 
 
 @@@
@@ -28,7 +28,7 @@ opencom		-> @{-@
 closecom	-> @-}@
 ncomment	-> opencom ANYseq \{ncomment ANYseq\} closecom
 ANYseq		-> \{ANY\}_{\langle{}\{ANY\} ( opencom | closecom ) \{ANY\}\rangle{}}
-ANY		-> grahic | whitechar
+ANY		-> graphic | whitechar
 any		-> graphic | space | tab
 graphic		-> small | large | symbol | digit | special | @:@ | @"@ | @'@