New syntax for GADT-style record declarations, and associated refactoring
[ghc-hetmet.git] / docs / users_guide / glasgow_exts.xml
index ec08210..5d1b5cf 100644 (file)
@@ -38,19 +38,20 @@ documentation</ulink> describes all the libraries that come with GHC.
     <indexterm><primary>extensions</primary><secondary>options controlling</secondary>
     </indexterm>
 
-    <para>The language option flag control what variation of the language are
+    <para>The language option flags control what variation of the language are
     permitted.  Leaving out all of them gives you standard Haskell
     98.</para>
 
-    <para>Generally speaking, all the language options are introduced by "<option>-X</option>", 
-    e.g. <option>-XTemplateHaskell</option>.
-    </para>
-
-   <para> All the language options can be turned off by using the prefix "<option>No</option>"; 
-      e.g. "<option>-XNoTemplateHaskell</option>".</para>
-
-   <para> Language options recognised by Cabal can also be enabled using the <literal>LANGUAGE</literal> pragma,
-   thus <literal>{-# LANGUAGE TemplateHaskell #-}</literal> (see <xref linkend="language-pragma"/>>). </para>
+    <para>Language options can be controlled in two ways:
+    <itemizedlist>
+      <listitem><para>Every language option can switched on by a command-line flag "<option>-X...</option>" 
+        (e.g. <option>-XTemplateHaskell</option>), and switched off by the flag "<option>-XNo...</option>"; 
+        (e.g. <option>-XNoTemplateHaskell</option>).</para></listitem>
+      <listitem><para>
+          Language options recognised by Cabal can also be enabled using the <literal>LANGUAGE</literal> pragma,
+          thus <literal>{-# LANGUAGE TemplateHaskell #-}</literal> (see <xref linkend="language-pragma"/>). </para>
+          </listitem>
+      </itemizedlist></para>
 
     <para>The flag <option>-fglasgow-exts</option>
           <indexterm><primary><option>-fglasgow-exts</option></primary></indexterm>
@@ -209,22 +210,20 @@ in a <emphasis>top-level</emphasis> binding.
 in a <emphasis>recursive</emphasis> binding.
 </para></listitem>
 <listitem><para> You may bind unboxed variables in a (non-recursive,
-non-top-level) pattern binding, but any such variable causes the entire
-pattern-match
-to become strict.  For example:
+non-top-level) pattern binding, but you must make any such pattern-match
+strict.  For example, rather than:
 <programlisting>
   data Foo = Foo Int Int#
 
   f x = let (Foo a b, w) = ..rhs.. in ..body..
 </programlisting>
-Since <literal>b</literal> has type <literal>Int#</literal>, the entire pattern
-match
-is strict, and the program behaves as if you had written
+you must write:
 <programlisting>
   data Foo = Foo Int Int#
 
-  f x = case ..rhs.. of { (Foo a b, w) -> ..body.. }
+  f x = let !(Foo a b, w) = ..rhs.. in ..body..
 </programlisting>
+since <literal>b</literal> has type <literal>Int#</literal>.
 </para>
 </listitem>
 </itemizedlist>
@@ -334,6 +333,75 @@ Indeed, the bindings can even be recursive.
 <sect1 id="syntax-extns">
 <title>Syntactic extensions</title>
  
+    <sect2 id="unicode-syntax">
+      <title>Unicode syntax</title>
+      <para>The language
+      extension <option>-XUnicodeSyntax</option><indexterm><primary><option>-XUnicodeSyntax</option></primary></indexterm>
+      enables Unicode characters to be used to stand for certain ASCII
+      character sequences.  The following alternatives are provided:</para>
+
+      <informaltable>
+       <tgroup cols="2" align="left" colsep="1" rowsep="1">
+         <thead>
+           <row>
+             <entry>ASCII</entry>
+              <entry>Unicode alternative</entry>
+             <entry>Code point</entry>
+             <entry>Name</entry>
+           </row>
+         </thead>
+         <tbody>
+           <row>
+             <entry><literal>::</literal></entry>
+             <entry>::</entry> <!-- no special char, apparently -->
+              <entry>0x2237</entry>
+             <entry>PROPORTION</entry>
+           </row>
+          </tbody>
+         <tbody>
+           <row>
+             <entry><literal>=&gt;</literal></entry>
+             <entry>&rArr;</entry>
+             <entry>0x21D2</entry>
+              <entry>RIGHTWARDS DOUBLE ARROW</entry>
+           </row>
+          </tbody>
+         <tbody>
+           <row>
+             <entry><literal>forall</literal></entry>
+             <entry>&forall;</entry>
+             <entry>0x2200</entry>
+              <entry>FOR ALL</entry>
+           </row>
+          </tbody>
+         <tbody>
+           <row>
+             <entry><literal>-&gt;</literal></entry>
+             <entry>&rarr;</entry>
+             <entry>0x2192</entry>
+              <entry>RIGHTWARDS ARROW</entry>
+           </row>
+          </tbody>
+         <tbody>
+           <row>
+             <entry><literal>&lt;-</literal></entry>
+             <entry>&larr;</entry>
+             <entry>0x2190</entry>
+              <entry>LEFTWARDS ARROW</entry>
+           </row>
+          </tbody>
+         <tbody>
+           <row>
+             <entry>..</entry>
+             <entry>&hellip;</entry>
+             <entry>0x22EF</entry>
+             <entry>MIDLINE HORIZONTAL ELLIPSIS</entry>
+           </row>
+          </tbody>
+        </tgroup>
+      </informaltable>
+    </sect2>
+
     <sect2 id="magic-hash">
       <title>The magic hash</title>
       <para>The language extension <option>-XMagicHash</option> allows "&num;" as a
@@ -390,7 +458,7 @@ Indeed, the bindings can even be recursive.
         the syntax by eliminating odd cases
         like <literal>Prelude..</literal>.  For example,
         when <literal>NewQualifiedOperators</literal> is on, it is possible to
-        write the enerated sequence <literal>[Monday..]</literal>
+        write the enumerated sequence <literal>[Monday..]</literal>
         without spaces, whereas in Haskell 98 this would be a
         reference to the operator &lsquo;<literal>.</literal>&lsquo;
         from module <literal>Monday</literal>.</para>
@@ -938,6 +1006,7 @@ This name is not supported by GHC.
        paper <ulink url="http://research.microsoft.com/~simonpj/papers/list-comp">
          Comprehensive comprehensions: comprehensions with "order by" and "group by"</ulink>,
     except that the syntax we use differs slightly from the paper.</para>
+<para>The extension is enabled with the flag <option>-XTransformListComp</option>.</para>
 <para>Here is an example: 
 <programlisting>
 employees = [ ("Simon", "MS", 80)
@@ -2283,16 +2352,46 @@ otherwise is a <emphasis>generalised</emphasis> data type (<xref linkend="gadt"/
 </para></listitem>
 
 <listitem><para>
+As with other type signatures, you can give a single signature for several data constructors.
+In this example we give a single signature for <literal>T1</literal> and <literal>T2</literal>:
+<programlisting>
+  data T a where
+    T1,T2 :: a -> T a
+    T3 :: T a
+</programlisting>
+</para></listitem>
+
+<listitem><para>
 The type signature of
 each constructor is independent, and is implicitly universally quantified as usual. 
-Different constructors may have different universally-quantified type variables
-and different type-class constraints.  
-For example, this is fine:
+In particular, the type variable(s) in the "<literal>data T a where</literal>" header 
+have no scope, and different constructors may have different universally-quantified type variables:
+<programlisting>
+  data T a where        -- The 'a' has no scope
+    T1,T2 :: b -> T b   -- Means forall b. b -> T b
+    T3 :: T a           -- Means forall a. T a
+</programlisting>
+</para></listitem>
+
+<listitem><para>
+A constructor signature may mention type class constraints, which can differ for
+different constructors.  For example, this is fine:
 <programlisting>
   data T a where
-    T1 :: Eq b => b -> T b
+    T1 :: Eq b => b -> b -> T b
     T2 :: (Show c, Ix c) => c -> [c] -> T c
 </programlisting>
+When patten matching, these constraints are made available to discharge constraints
+in the body of the match. For example:
+<programlisting>
+  f :: T a -> String
+  f (T1 x y) | x==y      = "yes"
+             | otherwise = "no"
+  f (T2 a b)             = show a
+</programlisting>
+Note that <literal>f</literal> is not overloaded; the <literal>Eq</literal> constraint arising
+from the use of <literal>==</literal> is discharged by the pattern match on <literal>T1</literal>
+and similarly the <literal>Show</literal> constraint arising from the use of <literal>show</literal>.
 </para></listitem>
 
 <listitem><para>
@@ -2304,12 +2403,12 @@ have no scope.  Indeed, one can write a kind signature instead:
 </programlisting>
 or even a mixture of the two:
 <programlisting>
-  data Foo a :: (* -> *) -> * where ...
+  data Bar a :: (* -> *) -> * where ...
 </programlisting>
 The type variables (if given) may be explicitly kinded, so we could also write the header for <literal>Foo</literal>
 like this:
 <programlisting>
-  data Foo a (b :: * -> *) where ...
+  data Bar a (b :: * -> *) where ...
 </programlisting>
 </para></listitem>
 
@@ -2340,27 +2439,48 @@ declaration.   For example, these two declarations are equivalent
 </para></listitem>
 
 <listitem><para>
+The type signature may have quantified type variables that do not appear
+in the result type:
+<programlisting>
+  data Foo where
+     MkFoo :: a -> (a->Bool) -> Foo
+     Nil   :: Foo
+</programlisting>
+Here the type variable <literal>a</literal> does not appear in the result type
+of either constructor.  
+Although it is universally quantified in the type of the constructor, such
+a type variable is often called "existential".  
+Indeed, the above declaration declares precisely the same type as 
+the <literal>data Foo</literal> in <xref linkend="existential-quantification"/>.
+</para><para>
+The type may contain a class context too, of course:
+<programlisting>
+  data Showable where
+    MkShowable :: Show a => a -> Showable
+</programlisting>
+</para></listitem>
+
+<listitem><para>
 You can use record syntax on a GADT-style data type declaration:
 
 <programlisting>
   data Person where
-      Adult { name :: String, children :: [Person] } :: Person
-      Child { name :: String } :: Person
+      Adult :: { name :: String, children :: [Person] } -> Person
+      Child :: Show a => { name :: !String, funny :: a } -> Person
 </programlisting>
 As usual, for every constructor that has a field <literal>f</literal>, the type of
 field <literal>f</literal> must be the same (modulo alpha conversion).
-</para>
-<para>
-At the moment, record updates are not yet possible with GADT-style declarations, 
-so support is limited to record construction, selection and pattern matching.
-For example
-<programlisting>
-  aPerson = Adult { name = "Fred", children = [] }
+The <literal>Child</literal> constructor above shows that the signature
+may have a context, existentially-quantified variables, and strictness annotations, 
+just as in the non-record case.  (NB: the "type" that follows the double-colon
+is not really a type, because of the record syntax and strictness annotations.
+A "type" of this form can appear only in a constructor signature.)
+</para></listitem>
 
-  shortName :: Person -> Bool
-  hasChildren (Adult { children = kids }) = not (null kids)
-  hasChildren (Child {})                  = False
-</programlisting>
+<listitem><para> 
+Record updates are allowed with GADT-style declarations, 
+only fields that have the following property: the type of the field
+mentions no existential type variables.
 </para></listitem>
 
 <listitem><para> 
@@ -2612,7 +2732,7 @@ GHC always treats the <emphasis>last</emphasis> parameter of the instance
 
 
 <sect2 id="deriving-typeable">
-<title>Deriving clause for classes <literal>Typeable</literal> and <literal>Data</literal></title>
+<title>Deriving clause for extra classes (<literal>Typeable</literal>, <literal>Data</literal>, etc)</title>
 
 <para>
 Haskell 98 allows the programmer to add "<literal>deriving( Eq, Ord )</literal>" to a data type 
@@ -2622,11 +2742,11 @@ classes <literal>Eq</literal>, <literal>Ord</literal>,
 <literal>Enum</literal>, <literal>Ix</literal>, <literal>Bounded</literal>, <literal>Read</literal>, and <literal>Show</literal>.
 </para>
 <para>
-GHC extends this list with two more classes that may be automatically derived 
-(provided the <option>-XDeriveDataTypeable</option> flag is specified):
-<literal>Typeable</literal>, and <literal>Data</literal>.  These classes are defined in the library
-modules <literal>Data.Typeable</literal> and <literal>Data.Generics</literal> respectively, and the
-appropriate class must be in scope before it can be mentioned in the <literal>deriving</literal> clause.
+GHC extends this list with several more classes that may be automatically derived:
+<itemizedlist>
+<listitem><para> With <option>-XDeriveDataTypeable</option>, you can derive instances of the classes
+<literal>Typeable</literal>, and <literal>Data</literal>, defined in the library
+modules <literal>Data.Typeable</literal> and <literal>Data.Generics</literal> respectively.
 </para>
 <para>An instance of <literal>Typeable</literal> can only be derived if the
 data type has seven or fewer type parameters, all of kind <literal>*</literal>.
@@ -2642,6 +2762,26 @@ In other cases, there is nothing to stop the programmer writing a <literal>Typab
 class, whose kind suits that of the data type constructor, and
 then writing the data type instance by hand.
 </para>
+</listitem>
+
+<listitem><para> With <option>-XDeriveFunctor</option>, you can derive instances of 
+the class <literal>Functor</literal>,
+defined in <literal>GHC.Base</literal>.
+</para></listitem>
+
+<listitem><para> With <option>-XDeriveFoldable</option>, you can derive instances of 
+the class <literal>Foldable</literal>,
+defined in <literal>Data.Foldable</literal>.
+</para></listitem>
+
+<listitem><para> With <option>-XDeriveTraversable</option>, you can derive instances of 
+the class <literal>Traversable</literal>,
+defined in <literal>Data.Traversable</literal>.
+</para></listitem>
+</itemizedlist>
+In each case the appropriate class must be in scope before it 
+can be mentioned in the <literal>deriving</literal> clause.
+</para>
 </sect2>
 
 <sect2 id="newtype-deriving">
@@ -3860,37 +4000,71 @@ data instance GMap (Either a b) v = GMapEither (GMap a v) (GMap b v)
       can be any number.
     </para>
     <para>
-      Data and newtype instance declarations are only legit when an
-      appropriate family declaration is in scope - just like class instances
-      require the class declaration to be visible.  Moreover, each instance
+      Data and newtype instance declarations are only permitted when an
+      appropriate family declaration is in scope - just as a class instance declaratoin
+      requires the class declaration to be visible.  Moreover, each instance
       declaration has to conform to the kind determined by its family
       declaration.  This implies that the number of parameters of an instance
       declaration matches the arity determined by the kind of the family.
-      Although, all data families are declared with
-      the <literal>data</literal> keyword, instances can be
-      either <literal>data</literal> or <literal>newtype</literal>s, or a mix
-      of both. 
     </para>
     <para>
+      A data family instance declaration can use the full exprssiveness of
+      ordinary <literal>data</literal> or <literal>newtype</literal> declarations:
+      <itemizedlist>
+      <listitem><para> Although, a data family is <emphasis>introduced</emphasis> with
+      the keyword "<literal>data</literal>", a data family <emphasis>instance</emphasis> can 
+      use either <literal>data</literal> or <literal>newtype</literal>. For example:
+<programlisting>
+data family T a
+data    instance T Int  = T1 Int | T2 Bool
+newtype instance T Char = TC Bool
+</programlisting>
+      </para></listitem>
+      <listitem><para> A <literal>data instance</literal> can use GADT syntax for the data constructors,
+      and indeed can define a GADT.  For example:
+<programlisting>
+data family G a b
+data instance G [a] b where
+   G1 :: c -> G [Int] b
+   G2 :: G [a] Bool
+</programlisting>
+      </para></listitem>
+      <listitem><para> You can use a <literal>deriving</literal> clause on a
+      <literal>data instance</literal> or <literal>newtype instance</literal>
+      declaration.
+      </para></listitem>
+      </itemizedlist>
+    </para>
+
+    <para>
       Even if type families are defined as toplevel declarations, functions
-      that perform different computations for different family instances still
+      that perform different computations for different family instances may still
       need to be defined as methods of type classes.  In particular, the
       following is not possible: 
 <programlisting>
 data family T a
 data instance T Int  = A
 data instance T Char = B
-nonsence :: T a -> Int
-nonsence A = 1             -- WRONG: These two equations together...
-nonsence B = 2             -- ...will produce a type error.
+foo :: T a -> Int
+foo A = 1             -- WRONG: These two equations together...
+foo B = 2             -- ...will produce a type error.
 </programlisting>
-      Given the functionality provided by GADTs (Generalised Algebraic Data
+Instead, you would have to write <literal>foo</literal> as a class operation, thus:
+<programlisting>
+class C a where 
+  foo :: T a -> Int
+instance Foo Int where
+  foo A = 1
+instance Foo Char where
+  foo B = 2
+</programlisting>
+      (Given the functionality provided by GADTs (Generalised Algebraic Data
       Types), it might seem as if a definition, such as the above, should be
       feasible.  However, type families are - in contrast to GADTs - are
       <emphasis>open;</emphasis> i.e., new instances can always be added,
       possibly in other 
       modules.  Supporting pattern matching across different data instances
-      would require a form of extensible case construct. 
+      would require a form of extensible case construct.)
     </para>
 
     <sect4 id="assoc-data-inst">
@@ -5729,6 +5903,8 @@ Wiki page</ulink>.
                  <itemizedlist>
                    <listitem><para> an expression; the spliced expression must
                    have type <literal>Q Exp</literal></para></listitem>
+                   <listitem><para> an type; the spliced expression must
+                   have type <literal>Q Typ</literal></para></listitem>
                    <listitem><para> a list of top-level declarations; the spliced expression must have type <literal>Q [Dec]</literal></para></listitem>
                    </itemizedlist>
                </para>
@@ -5777,7 +5953,7 @@ Wiki page</ulink>.
 (Compared to the original paper, there are many differences of detail.
 The syntax for a declaration splice uses "<literal>$</literal>" not "<literal>splice</literal>".
 The type of the enclosed expression must be  <literal>Q [Dec]</literal>, not  <literal>[Q Dec]</literal>.
-Type splices are not implemented, and neither are pattern splices or quotations.
+Pattern splices and quotations are not implemented.)
 
 </sect2>
 
@@ -6578,13 +6754,24 @@ Because the preprocessor targets Haskell (rather than Core),
 <indexterm><primary>Bang patterns</primary></indexterm>
 </title>
 <para>GHC supports an extension of pattern matching called <emphasis>bang
-patterns</emphasis>.   Bang patterns are under consideration for Haskell Prime.
+patterns</emphasis>, written <literal>!<replaceable>pat</replaceable></literal>.   
+Bang patterns are under consideration for Haskell Prime.
 The <ulink
 url="http://hackage.haskell.org/trac/haskell-prime/wiki/BangPatterns">Haskell
 prime feature description</ulink> contains more discussion and examples
 than the material below.
 </para>
 <para>
+The key change is the addition of a new rule to the 
+<ulink url="http://haskell.org/onlinereport/exps.html#sect3.17.2">semantics of pattern matching in the Haskell 98 report</ulink>.
+Add new bullet 10, saying: Matching the pattern <literal>!</literal><replaceable>pat</replaceable> 
+against a value <replaceable>v</replaceable> behaves as follows:
+<itemizedlist>
+<listitem><para>if <replaceable>v</replaceable> is bottom, the match diverges</para></listitem>
+<listitem><para>otherwise, <replaceable>pat</replaceable> is matched against <replaceable>v</replaceable>  </para></listitem>
+</itemizedlist>
+</para>
+<para>
 Bang patterns are enabled by the flag <option>-XBangPatterns</option>.
 </para>
 
@@ -6615,9 +6802,40 @@ A bang only really has an effect if it precedes a variable or wild-card pattern:
 f3 !(x,y) = [x,y]
 f4 (x,y)  = [x,y]
 </programlisting>
-Here, <literal>f3</literal> and <literal>f4</literal> are identical; putting a bang before a pattern that
+Here, <literal>f3</literal> and <literal>f4</literal> are identical; 
+putting a bang before a pattern that
 forces evaluation anyway does nothing.
-</para><para>
+</para>
+<para>
+There is one (apparent) exception to this general rule that a bang only
+makes a difference when it precedes a variable or wild-card: a bang at the
+top level of a <literal>let</literal> or <literal>where</literal>
+binding makes the binding strict, regardless of the pattern. For example:
+<programlisting>
+let ![x,y] = e in b
+</programlisting>
+is a strict binding: operationally, it evaluates <literal>e</literal>, matches
+it against the pattern <literal>[x,y]</literal>, and then evaluates <literal>b</literal>.
+(We say "apparent" exception because the Right Way to think of it is that the bang
+at the top of a binding is not part of the <emphasis>pattern</emphasis>; rather it
+is part of the syntax of the <emphasis>binding</emphasis>.)
+Nested bangs in a pattern binding behave uniformly with all other forms of 
+pattern matching.  For example
+<programlisting>
+let (!x,[y]) = e in b
+</programlisting>
+is equivalent to this:
+<programlisting>
+let { t = case e of (x,[y]) -> x `seq` (x,y)
+      x = fst t
+      y = snd t }
+in b
+</programlisting>
+The binding is lazy, but when either <literal>x</literal> or <literal>y</literal> is
+evaluated by <literal>b</literal> the entire pattern is matched, including forcing the
+evaluation of <literal>x</literal>.
+</para>
+<para>
 Bang patterns work in <literal>case</literal> expressions too, of course:
 <programlisting>
 g5 x = let y = f x in body
@@ -6627,18 +6845,6 @@ g7 x = case f x of { !y -&gt; body }
 The functions <literal>g5</literal> and <literal>g6</literal> mean exactly the same thing.  
 But <literal>g7</literal> evaluates <literal>(f x)</literal>, binds <literal>y</literal> to the
 result, and then evaluates <literal>body</literal>.
-</para><para>
-Bang patterns work in <literal>let</literal> and <literal>where</literal>
-definitions too. For example:
-<programlisting>
-let ![x,y] = e in b
-</programlisting>
-is a strict pattern: operationally, it evaluates <literal>e</literal>, matches
-it against the pattern <literal>[x,y]</literal>, and then evaluates <literal>b</literal>
-The "<literal>!</literal>" should not be regarded as part of the pattern; after all,
-in a function argument <literal>![x,y]</literal> means the 
-same as <literal>[x,y]</literal>.  Rather, the "<literal>!</literal>" 
-is part of the syntax of <literal>let</literal> bindings.
 </para>
 </sect2>
 
@@ -6824,14 +7030,31 @@ Assertion failures can be caught, see the documentation for the
     <replaceable>word</replaceable>.  The various values for
     <replaceable>word</replaceable> that GHC understands are described
     in the following sections; any pragma encountered with an
-    unrecognised <replaceable>word</replaceable> is (silently)
+    unrecognised <replaceable>word</replaceable> is
     ignored. The layout rule applies in pragmas, so the closing <literal>#-}</literal>
     should start in a column to the right of the opening <literal>{-#</literal>. </para> 
 
-    <para>Certain pragmas are <emphasis>file-header pragmas</emphasis>.  A file-header
-      pragma must precede the <literal>module</literal> keyword in the file.  
+    <para>Certain pragmas are <emphasis>file-header pragmas</emphasis>:
+      <itemizedlist>
+      <listitem><para>
+         A file-header
+         pragma must precede the <literal>module</literal> keyword in the file.
+         </para></listitem>
+      <listitem><para>
       There can be as many file-header pragmas as you please, and they can be
-      preceded or followed by comments.</para>
+      preceded or followed by comments.  
+         </para></listitem>
+      <listitem><para>
+      File-header pragmas are read once only, before
+      pre-processing the file (e.g. with cpp).
+         </para></listitem>
+      <listitem><para>
+         The file-header pragmas are: <literal>{-# LANGUAGE #-}</literal>,
+       <literal>{-# OPTIONS_GHC #-}</literal>, and
+       <literal>{-# INCLUDE #-}</literal>.
+         </para></listitem>
+      </itemizedlist>
+      </para>
 
     <sect2 id="language-pragma">
       <title>LANGUAGE pragma</title>
@@ -7179,7 +7402,7 @@ foo = ...
           please give the GHC team a shout</ulink>.
         </para>
         
-        <para>However, apart from these restrictions, many things are allowed, including expressions which not fully evaluated!
+        <para>However, apart from these restrictions, many things are allowed, including expressions which are not fully evaluated!
         Annotation expressions will be evaluated by the compiler just like Template Haskell splices are. So, this annotation is fine:</para>
         
 <programlisting>
@@ -8120,7 +8343,7 @@ r) ->
 <title>Special built-in functions</title>
 <para>GHC has a few built-in functions with special behaviour.  These
 are now described in the module <ulink
-url="../libraries/base/GHC-Prim.html"><literal>GHC.Prim</literal></ulink>
+url="../libraries/ghc-prim/GHC-Prim.html"><literal>GHC.Prim</literal></ulink>
 in the library documentation.</para>
 </sect1>