1 <?xml version=
"1.0" encoding=
"iso-8859-1"?>
3 <indexterm><primary>language, GHC
</primary></indexterm>
4 <indexterm><primary>extensions, GHC
</primary></indexterm>
5 As with all known Haskell systems, GHC implements some extensions to
6 the language. They are all enabled by options; by default GHC
7 understands only plain Haskell
98.
11 Some of the Glasgow extensions serve to give you access to the
12 underlying facilities with which we implement Haskell. Thus, you can
13 get at the Raw Iron, if you are willing to write some non-portable
14 code at a more primitive level. You need not be
“stuck
”
15 on performance because of the implementation costs of Haskell's
16 “high-level
” features
—you can always code
17 “under
” them. In an extreme case, you can write all your
18 time-critical code in C, and then just glue it together with Haskell!
22 Before you get too carried away working at the lowest level (e.g.,
23 sloshing
<literal>MutableByteArray
#</literal>s around your
24 program), you may wish to check if there are libraries that provide a
25 “Haskellised veneer
” over the features you want. The
26 separate
<ulink url=
"../libraries/index.html">libraries
27 documentation
</ulink> describes all the libraries that come with GHC.
30 <!-- LANGUAGE OPTIONS -->
31 <sect1 id=
"options-language">
32 <title>Language options
</title>
34 <indexterm><primary>language
</primary><secondary>option
</secondary>
36 <indexterm><primary>options
</primary><secondary>language
</secondary>
38 <indexterm><primary>extensions
</primary><secondary>options controlling
</secondary>
41 <para>These flags control what variation of the language are
42 permitted. Leaving out all of them gives you standard Haskell
45 <para>NB. turning on an option that enables special syntax
46 <emphasis>might
</emphasis> cause working Haskell
98 code to fail
47 to compile, perhaps because it uses a variable name which has
48 become a reserved word. So, together with each option below, we
49 list the special syntax which is enabled by this option. We use
50 notation and nonterminal names from the Haskell
98 lexical syntax
51 (see the Haskell
98 Report). There are two classes of special
56 <para>New reserved words and symbols: character sequences
57 which are no longer available for use as identifiers in the
61 <para>Other special syntax: sequences of characters that have
62 a different meaning when this particular option is turned
67 <para>We are only listing syntax changes here that might affect
68 existing working programs (i.e.
"stolen" syntax). Many of these
69 extensions will also enable new context-free syntax, but in all
70 cases programs written to use the new syntax would not be
71 compilable without the option enabled.
</para>
77 <option>-fglasgow-exts
</option>:
78 <indexterm><primary><option>-fglasgow-exts
</option></primary></indexterm>
81 <para>This simultaneously enables all of the extensions to
82 Haskell
98 described in
<xref
83 linkend=
"ghc-language-features"/>, except where otherwise
86 <para>New reserved words:
<literal>forall
</literal> (only in
87 types),
<literal>mdo
</literal>.
</para>
89 <para>Other syntax stolen:
90 <replaceable>varid
</replaceable>{
<literal>#</literal>},
91 <replaceable>char
</replaceable><literal>#</literal>,
92 <replaceable>string
</replaceable><literal>#</literal>,
93 <replaceable>integer
</replaceable><literal>#</literal>,
94 <replaceable>float
</replaceable><literal>#</literal>,
95 <replaceable>float
</replaceable><literal>##</literal>,
96 <literal>(
#</literal>,
<literal>#)
</literal>,
97 <literal>|)
</literal>,
<literal>{|
</literal>.
</para>
103 <option>-ffi
</option> and
<option>-fffi
</option>:
104 <indexterm><primary><option>-ffi
</option></primary></indexterm>
105 <indexterm><primary><option>-fffi
</option></primary></indexterm>
108 <para>This option enables the language extension defined in the
109 Haskell
98 Foreign Function Interface Addendum.
</para>
111 <para>New reserved words:
<literal>foreign
</literal>.
</para>
117 <option>-fno-monomorphism-restriction
</option>,
<option>-fno-mono-pat-binds
</option>:
120 <para> These two flags control how generalisation is done.
121 See
<xref linkend=
"monomorphism"/>.
128 <option>-fextended-default-rules
</option>:
129 <indexterm><primary><option>-fextended-default-rules
</option></primary></indexterm>
132 <para> Use GHCi's extended default rules in a regular module (
<xref linkend=
"extended-default-rules"/>).
133 Independent of the
<option>-fglasgow-exts
</option>
140 <option>-fallow-overlapping-instances
</option>
141 <indexterm><primary><option>-fallow-overlapping-instances
</option></primary></indexterm>
144 <option>-fallow-undecidable-instances
</option>
145 <indexterm><primary><option>-fallow-undecidable-instances
</option></primary></indexterm>
148 <option>-fallow-incoherent-instances
</option>
149 <indexterm><primary><option>-fallow-incoherent-instances
</option></primary></indexterm>
152 <option>-fcontext-stack=N
</option>
153 <indexterm><primary><option>-fcontext-stack
</option></primary></indexterm>
156 <para> See
<xref linkend=
"instance-decls"/>. Only relevant
157 if you also use
<option>-fglasgow-exts
</option>.
</para>
163 <option>-finline-phase
</option>
164 <indexterm><primary><option>-finline-phase
</option></primary></indexterm>
167 <para>See
<xref linkend=
"rewrite-rules"/>. Only relevant if
168 you also use
<option>-fglasgow-exts
</option>.
</para>
174 <option>-farrows
</option>
175 <indexterm><primary><option>-farrows
</option></primary></indexterm>
178 <para>See
<xref linkend=
"arrow-notation"/>. Independent of
179 <option>-fglasgow-exts
</option>.
</para>
181 <para>New reserved words/symbols:
<literal>rec
</literal>,
182 <literal>proc
</literal>,
<literal>-
<</literal>,
183 <literal>>-
</literal>,
<literal>-
<<</literal>,
184 <literal>>>-
</literal>.
</para>
186 <para>Other syntax stolen:
<literal>(|
</literal>,
187 <literal>|)
</literal>.
</para>
193 <option>-fgenerics
</option>
194 <indexterm><primary><option>-fgenerics
</option></primary></indexterm>
197 <para>See
<xref linkend=
"generic-classes"/>. Independent of
198 <option>-fglasgow-exts
</option>.
</para>
203 <term><option>-fno-implicit-prelude
</option></term>
205 <para><indexterm><primary>-fno-implicit-prelude
206 option
</primary></indexterm> GHC normally imports
207 <filename>Prelude.hi
</filename> files for you. If you'd
208 rather it didn't, then give it a
209 <option>-fno-implicit-prelude
</option> option. The idea is
210 that you can then import a Prelude of your own. (But don't
211 call it
<literal>Prelude
</literal>; the Haskell module
212 namespace is flat, and you must not conflict with any
213 Prelude module.)
</para>
215 <para>Even though you have not imported the Prelude, most of
216 the built-in syntax still refers to the built-in Haskell
217 Prelude types and values, as specified by the Haskell
218 Report. For example, the type
<literal>[Int]
</literal>
219 still means
<literal>Prelude.[] Int
</literal>; tuples
220 continue to refer to the standard Prelude tuples; the
221 translation for list comprehensions continues to use
222 <literal>Prelude.map
</literal> etc.
</para>
224 <para>However,
<option>-fno-implicit-prelude
</option> does
225 change the handling of certain built-in syntax: see
<xref
226 linkend=
"rebindable-syntax"/>.
</para>
231 <term><option>-fimplicit-params
</option></term>
233 <para>Enables implicit parameters (see
<xref
234 linkend=
"implicit-parameters"/>). Currently also implied by
235 <option>-fglasgow-exts
</option>.
</para>
238 <literal>?
<replaceable>varid
</replaceable></literal>,
239 <literal>%
<replaceable>varid
</replaceable></literal>.
</para>
244 <term><option>-fscoped-type-variables
</option></term>
246 <para>Enables lexically-scoped type variables (see
<xref
247 linkend=
"scoped-type-variables"/>). Implied by
248 <option>-fglasgow-exts
</option>.
</para>
253 <term><option>-fth
</option></term>
255 <para>Enables Template Haskell (see
<xref
256 linkend=
"template-haskell"/>). This flag must
257 be given explicitly; it is no longer implied by
258 <option>-fglasgow-exts
</option>.
</para>
260 <para>Syntax stolen:
<literal>[|
</literal>,
261 <literal>[e|
</literal>,
<literal>[p|
</literal>,
262 <literal>[d|
</literal>,
<literal>[t|
</literal>,
263 <literal>$(
</literal>,
264 <literal>$
<replaceable>varid
</replaceable></literal>.
</para>
271 <!-- UNBOXED TYPES AND PRIMITIVE OPERATIONS -->
272 <!-- included from primitives.sgml -->
273 <!-- &primitives; -->
274 <sect1 id=
"primitives">
275 <title>Unboxed types and primitive operations
</title>
277 <para>GHC is built on a raft of primitive data types and operations.
278 While you really can use this stuff to write fast code,
279 we generally find it a lot less painful, and more satisfying in the
280 long run, to use higher-level language features and libraries. With
281 any luck, the code you write will be optimised to the efficient
282 unboxed version in any case. And if it isn't, we'd like to know
285 <para>We do not currently have good, up-to-date documentation about the
286 primitives, perhaps because they are mainly intended for internal use.
287 There used to be a long section about them here in the User Guide, but it
288 became out of date, and wrong information is worse than none.
</para>
290 <para>The Real Truth about what primitive types there are, and what operations
291 work over those types, is held in the file
292 <filename>fptools/ghc/compiler/prelude/primops.txt.pp
</filename>.
293 This file is used directly to generate GHC's primitive-operation definitions, so
294 it is always correct! It is also intended for processing into text.
</para>
297 the result of such processing is part of the description of the
299 url=
"http://haskell.cs.yale.edu/ghc/docs/papers/core.ps.gz">External
300 Core language
</ulink>.
301 So that document is a good place to look for a type-set version.
302 We would be very happy if someone wanted to volunteer to produce an SGML
303 back end to the program that processes
<filename>primops.txt
</filename> so that
304 we could include the results here in the User Guide.
</para>
306 <para>What follows here is a brief summary of some main points.
</para>
308 <sect2 id=
"glasgow-unboxed">
313 <indexterm><primary>Unboxed types (Glasgow extension)
</primary></indexterm>
316 <para>Most types in GHC are
<firstterm>boxed
</firstterm>, which means
317 that values of that type are represented by a pointer to a heap
318 object. The representation of a Haskell
<literal>Int
</literal>, for
319 example, is a two-word heap object. An
<firstterm>unboxed
</firstterm>
320 type, however, is represented by the value itself, no pointers or heap
321 allocation are involved.
325 Unboxed types correspond to the
“raw machine
” types you
326 would use in C:
<literal>Int
#</literal> (long int),
327 <literal>Double
#</literal> (double),
<literal>Addr
#</literal>
328 (void *), etc. The
<emphasis>primitive operations
</emphasis>
329 (PrimOps) on these types are what you might expect; e.g.,
330 <literal>(+
#)
</literal> is addition on
331 <literal>Int
#</literal>s, and is the machine-addition that we all
332 know and love
—usually one instruction.
336 Primitive (unboxed) types cannot be defined in Haskell, and are
337 therefore built into the language and compiler. Primitive types are
338 always unlifted; that is, a value of a primitive type cannot be
339 bottom. We use the convention that primitive types, values, and
340 operations have a
<literal>#</literal> suffix.
344 Primitive values are often represented by a simple bit-pattern, such
345 as
<literal>Int
#</literal>,
<literal>Float
#</literal>,
346 <literal>Double
#</literal>. But this is not necessarily the case:
347 a primitive value might be represented by a pointer to a
348 heap-allocated object. Examples include
349 <literal>Array
#</literal>, the type of primitive arrays. A
350 primitive array is heap-allocated because it is too big a value to fit
351 in a register, and would be too expensive to copy around; in a sense,
352 it is accidental that it is represented by a pointer. If a pointer
353 represents a primitive value, then it really does point to that value:
354 no unevaluated thunks, no indirections
…nothing can be at the
355 other end of the pointer than the primitive value.
356 A numerically-intensive program using unboxed types can
357 go a
<emphasis>lot
</emphasis> faster than its
“standard
”
358 counterpart
—we saw a threefold speedup on one example.
362 There are some restrictions on the use of primitive types:
364 <listitem><para>The main restriction
365 is that you can't pass a primitive value to a polymorphic
366 function or store one in a polymorphic data type. This rules out
367 things like
<literal>[Int
#]
</literal> (i.e. lists of primitive
368 integers). The reason for this restriction is that polymorphic
369 arguments and constructor fields are assumed to be pointers: if an
370 unboxed integer is stored in one of these, the garbage collector would
371 attempt to follow it, leading to unpredictable space leaks. Or a
372 <function>seq
</function> operation on the polymorphic component may
373 attempt to dereference the pointer, with disastrous results. Even
374 worse, the unboxed value might be larger than a pointer
375 (
<literal>Double
#</literal> for instance).
378 <listitem><para> You cannot bind a variable with an unboxed type
379 in a
<emphasis>top-level
</emphasis> binding.
381 <listitem><para> You cannot bind a variable with an unboxed type
382 in a
<emphasis>recursive
</emphasis> binding.
384 <listitem><para> You may bind unboxed variables in a (non-recursive,
385 non-top-level) pattern binding, but any such variable causes the entire
387 to become strict. For example:
389 data Foo = Foo Int Int#
391 f x = let (Foo a b, w) = ..rhs.. in ..body..
393 Since
<literal>b
</literal> has type
<literal>Int#
</literal>, the entire pattern
395 is strict, and the program behaves as if you had written
397 data Foo = Foo Int Int#
399 f x = case ..rhs.. of { (Foo a b, w) -
> ..body.. }
408 <sect2 id=
"unboxed-tuples">
409 <title>Unboxed Tuples
413 Unboxed tuples aren't really exported by
<literal>GHC.Exts
</literal>,
414 they're available by default with
<option>-fglasgow-exts
</option>. An
415 unboxed tuple looks like this:
427 where
<literal>e
_1..e
_n
</literal> are expressions of any
428 type (primitive or non-primitive). The type of an unboxed tuple looks
433 Unboxed tuples are used for functions that need to return multiple
434 values, but they avoid the heap allocation normally associated with
435 using fully-fledged tuples. When an unboxed tuple is returned, the
436 components are put directly into registers or on the stack; the
437 unboxed tuple itself does not have a composite representation. Many
438 of the primitive operations listed in
<literal>primops.txt.pp
</literal> return unboxed
440 In particular, the
<literal>IO
</literal> and
<literal>ST
</literal> monads use unboxed
441 tuples to avoid unnecessary allocation during sequences of operations.
445 There are some pretty stringent restrictions on the use of unboxed tuples:
450 Values of unboxed tuple types are subject to the same restrictions as
451 other unboxed types; i.e. they may not be stored in polymorphic data
452 structures or passed to polymorphic functions.
459 No variable can have an unboxed tuple type, nor may a constructor or function
460 argument have an unboxed tuple type. The following are all illegal:
464 data Foo = Foo (# Int, Int #)
466 f :: (# Int, Int #) -
> (# Int, Int #)
469 g :: (# Int, Int #) -
> Int
472 h x = let y = (# x,x #) in ...
479 The typical use of unboxed tuples is simply to return multiple values,
480 binding those multiple results with a
<literal>case
</literal> expression, thus:
482 f x y = (# x+
1, y-
1 #)
483 g x = case f x x of { (# a, b #) -
> a + b }
485 You can have an unboxed tuple in a pattern binding, thus
487 f x = let (# p,q #) = h x in ..body..
489 If the types of
<literal>p
</literal> and
<literal>q
</literal> are not unboxed,
490 the resulting binding is lazy like any other Haskell pattern binding. The
491 above example desugars like this:
493 f x = let t = case h x o f{ (# p,q #) -
> (p,q)
498 Indeed, the bindings can even be recursive.
505 <!-- ====================== SYNTACTIC EXTENSIONS ======================= -->
507 <sect1 id=
"syntax-extns">
508 <title>Syntactic extensions
</title>
510 <!-- ====================== HIERARCHICAL MODULES ======================= -->
512 <sect2 id=
"hierarchical-modules">
513 <title>Hierarchical Modules
</title>
515 <para>GHC supports a small extension to the syntax of module
516 names: a module name is allowed to contain a dot
517 <literal>‘.
’</literal>. This is also known as the
518 “hierarchical module namespace
” extension, because
519 it extends the normally flat Haskell module namespace into a
520 more flexible hierarchy of modules.
</para>
522 <para>This extension has very little impact on the language
523 itself; modules names are
<emphasis>always
</emphasis> fully
524 qualified, so you can just think of the fully qualified module
525 name as
<quote>the module name
</quote>. In particular, this
526 means that the full module name must be given after the
527 <literal>module
</literal> keyword at the beginning of the
528 module; for example, the module
<literal>A.B.C
</literal> must
531 <programlisting>module A.B.C
</programlisting>
534 <para>It is a common strategy to use the
<literal>as
</literal>
535 keyword to save some typing when using qualified names with
536 hierarchical modules. For example:
</para>
539 import qualified Control.Monad.ST.Strict as ST
542 <para>For details on how GHC searches for source and interface
543 files in the presence of hierarchical modules, see
<xref
544 linkend=
"search-path"/>.
</para>
546 <para>GHC comes with a large collection of libraries arranged
547 hierarchically; see the accompanying library documentation.
548 There is an ongoing project to create and maintain a stable set
549 of
<quote>core
</quote> libraries used by several Haskell
550 compilers, and the libraries that GHC comes with represent the
551 current status of that project. For more details, see
<ulink
552 url=
"http://www.haskell.org/~simonmar/libraries/libraries.html">Haskell
553 Libraries
</ulink>.
</para>
557 <!-- ====================== PATTERN GUARDS ======================= -->
559 <sect2 id=
"pattern-guards">
560 <title>Pattern guards
</title>
563 <indexterm><primary>Pattern guards (Glasgow extension)
</primary></indexterm>
564 The discussion that follows is an abbreviated version of Simon Peyton Jones's original
<ulink url=
"http://research.microsoft.com/~simonpj/Haskell/guards.html">proposal
</ulink>. (Note that the proposal was written before pattern guards were implemented, so refers to them as unimplemented.)
568 Suppose we have an abstract data type of finite maps, with a
572 lookup :: FiniteMap -
> Int -
> Maybe Int
575 The lookup returns
<function>Nothing
</function> if the supplied key is not in the domain of the mapping, and
<function>(Just v)
</function> otherwise,
576 where
<varname>v
</varname> is the value that the key maps to. Now consider the following definition:
580 clunky env var1 var2 | ok1
&& ok2 = val1 + val2
581 | otherwise = var1 + var2
592 The auxiliary functions are
596 maybeToBool :: Maybe a -
> Bool
597 maybeToBool (Just x) = True
598 maybeToBool Nothing = False
600 expectJust :: Maybe a -
> a
601 expectJust (Just x) = x
602 expectJust Nothing = error
"Unexpected Nothing"
606 What is
<function>clunky
</function> doing? The guard
<literal>ok1
&&
607 ok2
</literal> checks that both lookups succeed, using
608 <function>maybeToBool
</function> to convert the
<function>Maybe
</function>
609 types to booleans. The (lazily evaluated)
<function>expectJust
</function>
610 calls extract the values from the results of the lookups, and binds the
611 returned values to
<varname>val1
</varname> and
<varname>val2
</varname>
612 respectively. If either lookup fails, then clunky takes the
613 <literal>otherwise
</literal> case and returns the sum of its arguments.
617 This is certainly legal Haskell, but it is a tremendously verbose and
618 un-obvious way to achieve the desired effect. Arguably, a more direct way
619 to write clunky would be to use case expressions:
623 clunky env var1 var1 = case lookup env var1 of
625 Just val1 -
> case lookup env var2 of
627 Just val2 -
> val1 + val2
633 This is a bit shorter, but hardly better. Of course, we can rewrite any set
634 of pattern-matching, guarded equations as case expressions; that is
635 precisely what the compiler does when compiling equations! The reason that
636 Haskell provides guarded equations is because they allow us to write down
637 the cases we want to consider, one at a time, independently of each other.
638 This structure is hidden in the case version. Two of the right-hand sides
639 are really the same (
<function>fail
</function>), and the whole expression
640 tends to become more and more indented.
644 Here is how I would write clunky:
649 | Just val1
<- lookup env var1
650 , Just val2
<- lookup env var2
652 ...other equations for clunky...
656 The semantics should be clear enough. The qualifiers are matched in order.
657 For a
<literal><-
</literal> qualifier, which I call a pattern guard, the
658 right hand side is evaluated and matched against the pattern on the left.
659 If the match fails then the whole guard fails and the next equation is
660 tried. If it succeeds, then the appropriate binding takes place, and the
661 next qualifier is matched, in the augmented environment. Unlike list
662 comprehensions, however, the type of the expression to the right of the
663 <literal><-
</literal> is the same as the type of the pattern to its
664 left. The bindings introduced by pattern guards scope over all the
665 remaining guard qualifiers, and over the right hand side of the equation.
669 Just as with list comprehensions, boolean expressions can be freely mixed
670 with among the pattern guards. For example:
681 Haskell's current guards therefore emerge as a special case, in which the
682 qualifier list has just one element, a boolean expression.
686 <!-- ===================== Recursive do-notation =================== -->
688 <sect2 id=
"mdo-notation">
689 <title>The recursive do-notation
692 <para> The recursive do-notation (also known as mdo-notation) is implemented as described in
693 "A recursive do for Haskell",
694 Levent Erkok, John Launchbury
",
695 Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania.
698 The do-notation of Haskell does not allow <emphasis>recursive bindings</emphasis>,
699 that is, the variables bound in a do-expression are visible only in the textually following
700 code block. Compare this to a let-expression, where bound variables are visible in the entire binding
701 group. It turns out that several applications can benefit from recursive bindings in
702 the do-notation, and this extension provides the necessary syntactic support.
705 Here is a simple (yet contrived) example:
708 import Control.Monad.Fix
710 justOnes = mdo xs <- Just (1:xs)
714 As you can guess <literal>justOnes</literal> will evaluate to <literal>Just [1,1,1,...</literal>.
718 The Control.Monad.Fix library introduces the <literal>MonadFix</literal> class. It's definition is:
721 class Monad m => MonadFix m where
722 mfix :: (a -> m a) -> m a
725 The function <literal>mfix</literal>
726 dictates how the required recursion operation should be performed. If recursive bindings are required for a monad,
727 then that monad must be declared an instance of the <literal>MonadFix</literal> class.
728 For details, see the above mentioned reference.
731 The following instances of <literal>MonadFix</literal> are automatically provided: List, Maybe, IO.
732 Furthermore, the Control.Monad.ST and Control.Monad.ST.Lazy modules provide the instances of the MonadFix class
733 for Haskell's internal state monad (strict and lazy, respectively).
736 There are three important points in using the recursive-do notation:
739 The recursive version of the do-notation uses the keyword <literal>mdo</literal> (rather
740 than <literal>do</literal>).
744 You should <literal>import Control.Monad.Fix</literal>.
745 (Note: Strictly speaking, this import is required only when you need to refer to the name
746 <literal>MonadFix</literal> in your program, but the import is always safe, and the programmers
747 are encouraged to always import this module when using the mdo-notation.)
751 As with other extensions, ghc should be given the flag <literal>-fglasgow-exts</literal>
757 The web page: <ulink url="http://www.cse.ogi.edu/PacSoft/projects/rmb
">http://www.cse.ogi.edu/PacSoft/projects/rmb</ulink>
758 contains up to date information on recursive monadic bindings.
762 Historical note: The old implementation of the mdo-notation (and most
763 of the existing documents) used the name
764 <literal>MonadRec</literal> for the class and the corresponding library.
765 This name is not supported by GHC.
771 <!-- ===================== PARALLEL LIST COMPREHENSIONS =================== -->
773 <sect2 id="parallel-list-comprehensions
">
774 <title>Parallel List Comprehensions</title>
775 <indexterm><primary>list comprehensions</primary><secondary>parallel</secondary>
777 <indexterm><primary>parallel list comprehensions</primary>
780 <para>Parallel list comprehensions are a natural extension to list
781 comprehensions. List comprehensions can be thought of as a nice
782 syntax for writing maps and filters. Parallel comprehensions
783 extend this to include the zipWith family.</para>
785 <para>A parallel list comprehension has multiple independent
786 branches of qualifier lists, each separated by a `|' symbol. For
787 example, the following zips together two lists:</para>
790 [ (x, y) | x <- xs | y <- ys ]
793 <para>The behavior of parallel list comprehensions follows that of
794 zip, in that the resulting list will have the same length as the
795 shortest branch.</para>
797 <para>We can define parallel list comprehensions by translation to
798 regular comprehensions. Here's the basic idea:</para>
800 <para>Given a parallel comprehension of the form: </para>
803 [ e | p1 <- e11, p2 <- e12, ...
804 | q1 <- e21, q2 <- e22, ...
809 <para>This will be translated to: </para>
812 [ e | ((p1,p2), (q1,q2), ...) <- zipN [(p1,p2) | p1 <- e11, p2 <- e12, ...]
813 [(q1,q2) | q1 <- e21, q2 <- e22, ...]
818 <para>where `zipN' is the appropriate zip for the given number of
823 <sect2 id="rebindable-syntax
">
824 <title>Rebindable syntax</title>
827 <para>GHC allows most kinds of built-in syntax to be rebound by
828 the user, to facilitate replacing the <literal>Prelude</literal>
829 with a home-grown version, for example.</para>
831 <para>You may want to define your own numeric class
832 hierarchy. It completely defeats that purpose if the
833 literal "1" means "<literal>Prelude.fromInteger
834 1</literal>", which is what the Haskell Report specifies.
835 So the <option>-fno-implicit-prelude</option> flag causes
836 the following pieces of built-in syntax to refer to
837 <emphasis>whatever is in scope</emphasis>, not the Prelude
842 <para>An integer literal <literal>368</literal> means
843 "<literal>fromInteger (
368::Integer)
</literal>", rather than
844 "<literal>Prelude.fromInteger (
368::Integer)
</literal>".
847 <listitem><para>Fractional literals are handed in just the same way,
848 except that the translation is
849 <literal>fromRational (3.68::Rational)</literal>.
852 <listitem><para>The equality test in an overloaded numeric pattern
853 uses whatever <literal>(==)</literal> is in scope.
856 <listitem><para>The subtraction operation, and the
857 greater-than-or-equal test, in <literal>n+k</literal> patterns
858 use whatever <literal>(-)</literal> and <literal>(>=)</literal> are in scope.
862 <para>Negation (e.g. "<literal>- (f x)
</literal>")
863 means "<literal>negate (f x)
</literal>", both in numeric
864 patterns, and expressions.
868 <para>"Do
" notation is translated using whatever
869 functions <literal>(>>=)</literal>,
870 <literal>(>>)</literal>, and <literal>fail</literal>,
871 are in scope (not the Prelude
872 versions). List comprehensions, mdo (<xref linkend="mdo-notation
"/>), and parallel array
873 comprehensions, are unaffected. </para></listitem>
877 notation (see <xref linkend="arrow-notation
"/>)
878 uses whatever <literal>arr</literal>,
879 <literal>(>>>)</literal>, <literal>first</literal>,
880 <literal>app</literal>, <literal>(|||)</literal> and
881 <literal>loop</literal> functions are in scope. But unlike the
882 other constructs, the types of these functions must match the
883 Prelude types very closely. Details are in flux; if you want
887 In all cases (apart from arrow notation), the static semantics should be that of the desugared form,
888 even if that is a little unexpected. For emample, the
889 static semantics of the literal <literal>368</literal>
890 is exactly that of <literal>fromInteger (368::Integer)</literal>; it's fine for
891 <literal>fromInteger</literal> to have any of the types:
893 fromInteger :: Integer -> Integer
894 fromInteger :: forall a. Foo a => Integer -> a
895 fromInteger :: Num a => a -> Integer
896 fromInteger :: Integer -> Bool -> Bool
900 <para>Be warned: this is an experimental facility, with
901 fewer checks than usual. Use <literal>-dcore-lint</literal>
902 to typecheck the desugared program. If Core Lint is happy
903 you should be all right.</para>
907 <sect2 id="postfix-operators
">
908 <title>Postfix operators</title>
911 GHC allows a small extension to the syntax of left operator sections, which
912 allows you to define postfix operators. The extension is this: the left section
916 is equivalent (from the point of view of both type checking and execution) to the expression
920 (for any expression <literal>e</literal> and operator <literal>(!)</literal>.
921 The strict Haskell 98 interpretation is that the section is equivalent to
925 That is, the operator must be a function of two arguments. GHC allows it to
926 take only one argument, and that in turn allows you to write the function
929 <para>Since this extension goes beyond Haskell 98, it should really be enabled
930 by a flag; but in fact it is enabled all the time. (No Haskell 98 programs
931 change their behaviour, of course.)
933 <para>The extension does not extend to the left-hand side of function
934 definitions; you must define such a function in prefix form.</para>
941 <!-- TYPE SYSTEM EXTENSIONS -->
942 <sect1 id="type-extensions
">
943 <title>Type system extensions</title>
947 <title>Data types and type synonyms</title>
949 <sect3 id="nullary-types
">
950 <title>Data types with no constructors</title>
952 <para>With the <option>-fglasgow-exts</option> flag, GHC lets you declare
953 a data type with no constructors. For example:</para>
957 data T a -- T :: * -> *
960 <para>Syntactically, the declaration lacks the "= constrs
" part. The
961 type can be parameterised over types of any kind, but if the kind is
962 not <literal>*</literal> then an explicit kind annotation must be used
963 (see <xref linkend="sec-kinding
"/>).</para>
965 <para>Such data types have only one value, namely bottom.
966 Nevertheless, they can be useful when defining "phantom types
".</para>
969 <sect3 id="infix-tycons
">
970 <title>Infix type constructors, classes, and type variables</title>
973 GHC allows type constructors, classes, and type variables to be operators, and
974 to be written infix, very much like expressions. More specifically:
977 A type constructor or class can be an operator, beginning with a colon; e.g. <literal>:*:</literal>.
978 The lexical syntax is the same as that for data constructors.
981 Data type and type-synonym declarations can be written infix, parenthesised
982 if you want further arguments. E.g.
984 data a :*: b = Foo a b
985 type a :+: b = Either a b
986 class a :=: b where ...
988 data (a :**: b) x = Baz a b x
989 type (a :++: b) y = Either (a,b) y
993 Types, and class constraints, can be written infix. For example
996 f :: (a :=: b) => a -> b
1000 A type variable can be an (unqualified) operator e.g. <literal>+</literal>.
1001 The lexical syntax is the same as that for variable operators, excluding "(.)
",
1002 "(!)
", and "(*)
". In a binding position, the operator must be
1003 parenthesised. For example:
1005 type T (+) = Int + Int
1009 liftA2 :: Arrow (~>)
1010 => (a -> b -> c) -> (e ~> a) -> (e ~> b) -> (e ~> c)
1016 as for expressions, both for type constructors and type variables; e.g. <literal>Int `Either` Bool</literal>, or
1017 <literal>Int `a` Bool</literal>. Similarly, parentheses work the same; e.g. <literal>(:*:) Int Bool</literal>.
1020 Fixities may be declared for type constructors, or classes, just as for data constructors. However,
1021 one cannot distinguish between the two in a fixity declaration; a fixity declaration
1022 sets the fixity for a data constructor and the corresponding type constructor. For example:
1026 sets the fixity for both type constructor <literal>T</literal> and data constructor <literal>T</literal>,
1027 and similarly for <literal>:*:</literal>.
1028 <literal>Int `a` Bool</literal>.
1031 Function arrow is <literal>infixr</literal> with fixity 0. (This might change; I'm not sure what it should be.)
1038 <sect3 id="type-synonyms
">
1039 <title>Liberalised type synonyms</title>
1042 Type synonyms are like macros at the type level, and
1043 GHC does validity checking on types <emphasis>only after expanding type synonyms</emphasis>.
1044 That means that GHC can be very much more liberal about type synonyms than Haskell 98:
1046 <listitem> <para>You can write a <literal>forall</literal> (including overloading)
1047 in a type synonym, thus:
1049 type Discard a = forall b. Show b => a -> b -> (a, String)
1054 g :: Discard Int -> (Int,String) -- A rank-2 type
1061 You can write an unboxed tuple in a type synonym:
1063 type Pr = (# Int, Int #)
1071 You can apply a type synonym to a forall type:
1073 type Foo a = a -> a -> Bool
1075 f :: Foo (forall b. b->b)
1077 After expanding the synonym, <literal>f</literal> has the legal (in GHC) type:
1079 f :: (forall b. b->b) -> (forall b. b->b) -> Bool
1084 You can apply a type synonym to a partially applied type synonym:
1086 type Generic i o = forall x. i x -> o x
1089 foo :: Generic Id []
1091 After expanding the synonym, <literal>foo</literal> has the legal (in GHC) type:
1093 foo :: forall x. x -> [x]
1101 GHC currently does kind checking before expanding synonyms (though even that
1105 After expanding type synonyms, GHC does validity checking on types, looking for
1106 the following mal-formedness which isn't detected simply by kind checking:
1109 Type constructor applied to a type involving for-alls.
1112 Unboxed tuple on left of an arrow.
1115 Partially-applied type synonym.
1119 this will be rejected:
1121 type Pr = (# Int, Int #)
1126 because GHC does not allow unboxed tuples on the left of a function arrow.
1131 <sect3 id="existential-quantification
">
1132 <title>Existentially quantified data constructors
1136 The idea of using existential quantification in data type declarations
1137 was suggested by Perry, and implemented in Hope+ (Nigel Perry, <emphasis>The Implementation
1138 of Practical Functional Programming Languages</emphasis>, PhD Thesis, University of
1139 London, 1991). It was later formalised by Laufer and Odersky
1140 (<emphasis>Polymorphic type inference and abstract data types</emphasis>,
1141 TOPLAS, 16(5), pp1411-1430, 1994).
1142 It's been in Lennart
1143 Augustsson's <command>hbc</command> Haskell compiler for several years, and
1144 proved very useful. Here's the idea. Consider the declaration:
1150 data Foo = forall a. MkFoo a (a -> Bool)
1157 The data type <literal>Foo</literal> has two constructors with types:
1163 MkFoo :: forall a. a -> (a -> Bool) -> Foo
1170 Notice that the type variable <literal>a</literal> in the type of <function>MkFoo</function>
1171 does not appear in the data type itself, which is plain <literal>Foo</literal>.
1172 For example, the following expression is fine:
1178 [MkFoo 3 even, MkFoo 'c' isUpper] :: [Foo]
1184 Here, <literal>(MkFoo 3 even)</literal> packages an integer with a function
1185 <function>even</function> that maps an integer to <literal>Bool</literal>; and <function>MkFoo 'c'
1186 isUpper</function> packages a character with a compatible function. These
1187 two things are each of type <literal>Foo</literal> and can be put in a list.
1191 What can we do with a value of type <literal>Foo</literal>?. In particular,
1192 what happens when we pattern-match on <function>MkFoo</function>?
1198 f (MkFoo val fn) = ???
1204 Since all we know about <literal>val</literal> and <function>fn</function> is that they
1205 are compatible, the only (useful) thing we can do with them is to
1206 apply <function>fn</function> to <literal>val</literal> to get a boolean. For example:
1213 f (MkFoo val fn) = fn val
1219 What this allows us to do is to package heterogenous values
1220 together with a bunch of functions that manipulate them, and then treat
1221 that collection of packages in a uniform manner. You can express
1222 quite a bit of object-oriented-like programming this way.
1225 <sect4 id="existential
">
1226 <title>Why existential?
1230 What has this to do with <emphasis>existential</emphasis> quantification?
1231 Simply that <function>MkFoo</function> has the (nearly) isomorphic type
1237 MkFoo :: (exists a . (a, a -> Bool)) -> Foo
1243 But Haskell programmers can safely think of the ordinary
1244 <emphasis>universally</emphasis> quantified type given above, thereby avoiding
1245 adding a new existential quantification construct.
1251 <title>Type classes</title>
1254 An easy extension is to allow
1255 arbitrary contexts before the constructor. For example:
1261 data Baz = forall a. Eq a => Baz1 a a
1262 | forall b. Show b => Baz2 b (b -> b)
1268 The two constructors have the types you'd expect:
1274 Baz1 :: forall a. Eq a => a -> a -> Baz
1275 Baz2 :: forall b. Show b => b -> (b -> b) -> Baz
1281 But when pattern matching on <function>Baz1</function> the matched values can be compared
1282 for equality, and when pattern matching on <function>Baz2</function> the first matched
1283 value can be converted to a string (as well as applying the function to it).
1284 So this program is legal:
1291 f (Baz1 p q) | p == q = "Yes
"
1293 f (Baz2 v fn) = show (fn v)
1299 Operationally, in a dictionary-passing implementation, the
1300 constructors <function>Baz1</function> and <function>Baz2</function> must store the
1301 dictionaries for <literal>Eq</literal> and <literal>Show</literal> respectively, and
1302 extract it on pattern matching.
1306 Notice the way that the syntax fits smoothly with that used for
1307 universal quantification earlier.
1312 <sect4 id="existential-records
">
1313 <title>Record Constructors</title>
1316 GHC allows existentials to be used with records syntax as well. For example:
1319 data Counter a = forall self. NewCounter
1321 , _inc :: self -> self
1322 , _display :: self -> IO ()
1326 Here <literal>tag</literal> is a public field, with a well-typed selector
1327 function <literal>tag :: Counter a -> a</literal>. The <literal>self</literal>
1328 type is hidden from the outside; any attempt to apply <literal>_this</literal>,
1329 <literal>_inc</literal> or <literal>_output</literal> as functions will raise a
1330 compile-time error. In other words, <emphasis>GHC defines a record selector function
1331 only for fields whose type does not mention the existentially-quantified variables</emphasis>.
1332 (This example used an underscore in the fields for which record selectors
1333 will not be defined, but that is only programming style; GHC ignores them.)
1337 To make use of these hidden fields, we need to create some helper functions:
1340 inc :: Counter a -> Counter a
1341 inc (NewCounter x i d t) = NewCounter
1342 { _this = i x, _inc = i, _display = d, tag = t }
1344 display :: Counter a -> IO ()
1345 display NewCounter{ _this = x, _display = d } = d x
1348 Now we can define counters with different underlying implementations:
1351 counterA :: Counter String
1352 counterA = NewCounter
1353 { _this = 0, _inc = (1+), _display = print, tag = "A
" }
1355 counterB :: Counter String
1356 counterB = NewCounter
1357 { _this = "", _inc = ('#':), _display = putStrLn, tag = "B
" }
1360 display (inc counterA) -- prints "1"
1361 display (inc (inc counterB)) -- prints "##
"
1364 At the moment, record update syntax is only supported for Haskell 98 data types,
1365 so the following function does <emphasis>not</emphasis> work:
1368 -- This is invalid; use explicit NewCounter instead for now
1369 setTag :: Counter a -> a -> Counter a
1370 setTag obj t = obj{ tag = t }
1379 <title>Restrictions</title>
1382 There are several restrictions on the ways in which existentially-quantified
1383 constructors can be use.
1392 When pattern matching, each pattern match introduces a new,
1393 distinct, type for each existential type variable. These types cannot
1394 be unified with any other type, nor can they escape from the scope of
1395 the pattern match. For example, these fragments are incorrect:
1403 Here, the type bound by <function>MkFoo</function> "escapes
", because <literal>a</literal>
1404 is the result of <function>f1</function>. One way to see why this is wrong is to
1405 ask what type <function>f1</function> has:
1409 f1 :: Foo -> a -- Weird!
1413 What is this "<literal>a
</literal>" in the result type? Clearly we don't mean
1418 f1 :: forall a. Foo -> a -- Wrong!
1422 The original program is just plain wrong. Here's another sort of error
1426 f2 (Baz1 a b) (Baz1 p q) = a==q
1430 It's ok to say <literal>a==b</literal> or <literal>p==q</literal>, but
1431 <literal>a==q</literal> is wrong because it equates the two distinct types arising
1432 from the two <function>Baz1</function> constructors.
1440 You can't pattern-match on an existentially quantified
1441 constructor in a <literal>let</literal> or <literal>where</literal> group of
1442 bindings. So this is illegal:
1446 f3 x = a==b where { Baz1 a b = x }
1449 Instead, use a <literal>case</literal> expression:
1452 f3 x = case x of Baz1 a b -> a==b
1455 In general, you can only pattern-match
1456 on an existentially-quantified constructor in a <literal>case</literal> expression or
1457 in the patterns of a function definition.
1459 The reason for this restriction is really an implementation one.
1460 Type-checking binding groups is already a nightmare without
1461 existentials complicating the picture. Also an existential pattern
1462 binding at the top level of a module doesn't make sense, because it's
1463 not clear how to prevent the existentially-quantified type "escaping
".
1464 So for now, there's a simple-to-state restriction. We'll see how
1472 You can't use existential quantification for <literal>newtype</literal>
1473 declarations. So this is illegal:
1477 newtype T = forall a. Ord a => MkT a
1481 Reason: a value of type <literal>T</literal> must be represented as a
1482 pair of a dictionary for <literal>Ord t</literal> and a value of type
1483 <literal>t</literal>. That contradicts the idea that
1484 <literal>newtype</literal> should have no concrete representation.
1485 You can get just the same efficiency and effect by using
1486 <literal>data</literal> instead of <literal>newtype</literal>. If
1487 there is no overloading involved, then there is more of a case for
1488 allowing an existentially-quantified <literal>newtype</literal>,
1489 because the <literal>data</literal> version does carry an
1490 implementation cost, but single-field existentially quantified
1491 constructors aren't much use. So the simple restriction (no
1492 existential stuff on <literal>newtype</literal>) stands, unless there
1493 are convincing reasons to change it.
1501 You can't use <literal>deriving</literal> to define instances of a
1502 data type with existentially quantified data constructors.
1504 Reason: in most cases it would not make sense. For example:;
1507 data T = forall a. MkT [a] deriving( Eq )
1510 To derive <literal>Eq</literal> in the standard way we would need to have equality
1511 between the single component of two <function>MkT</function> constructors:
1515 (MkT a) == (MkT b) = ???
1518 But <varname>a</varname> and <varname>b</varname> have distinct types, and so can't be compared.
1519 It's just about possible to imagine examples in which the derived instance
1520 would make sense, but it seems altogether simpler simply to prohibit such
1521 declarations. Define your own instances!
1532 <!-- ====================== Generalised algebraic data types ======================= -->
1534 <sect3 id="gadt-style
">
1535 <title>Declaring data types with explicit constructor signatures</title>
1537 <para>GHC allows you to declare an algebraic data type by
1538 giving the type signatures of constructors explicitly. For example:
1542 Just :: a -> Maybe a
1544 The form is called a "GADT-style declaration
"
1545 because Generalised Algebraic Data Types, described in <xref linkend="gadt
"/>,
1546 can only be declared using this form.</para>
1547 <para>Notice that GADT-style syntax generalises existential types (<xref linkend="existential-quantification
"/>).
1548 For example, these two declarations are equivalent:
1550 data Foo = forall a. MkFoo a (a -> Bool)
1551 data Foo' where { MKFoo :: a -> (a->Bool) -> Foo' }
1554 <para>Any data type that can be declared in standard Haskell-98 syntax
1555 can also be declared using GADT-style syntax.
1556 The choice is largely stylistic, but GADT-style declarations differ in one important respect:
1557 they treat class constraints on the data constructors differently.
1558 Specifically, if the constructor is given a type-class context, that
1559 context is made available by pattern matching. For example:
1562 MkSet :: Eq a => [a] -> Set a
1564 makeSet :: Eq a => [a] -> Set a
1565 makeSet xs = MkSet (nub xs)
1567 insert :: a -> Set a -> Set a
1568 insert a (MkSet as) | a `elem` as = MkSet as
1569 | otherwise = MkSet (a:as)
1571 A use of <literal>MkSet</literal> as a constructor (e.g. in the definition of <literal>makeSet</literal>)
1572 gives rise to a <literal>(Eq a)</literal>
1573 constraint, as you would expect. The new feature is that pattern-matching on <literal>MkSet</literal>
1574 (as in the definition of <literal>insert</literal>) makes <emphasis>available</emphasis> an <literal>(Eq a)</literal>
1575 context. In implementation terms, the <literal>MkSet</literal> constructor has a hidden field that stores
1576 the <literal>(Eq a)</literal> dictionary that is passed to <literal>MkSet</literal>; so
1577 when pattern-matching that dictionary becomes available for the right-hand side of the match.
1578 In the example, the equality dictionary is used to satisfy the equality constraint
1579 generated by the call to <literal>elem</literal>, so that the type of
1580 <literal>insert</literal> itself has no <literal>Eq</literal> constraint.
1582 <para>This behaviour contrasts with Haskell 98's peculiar treament of
1583 contexts on a data type declaration (Section 4.2.1 of the Haskell 98 Report).
1584 In Haskell 98 the defintion
1586 data Eq a => Set' a = MkSet' [a]
1588 gives <literal>MkSet'</literal> the same type as <literal>MkSet</literal> above. But instead of
1589 <emphasis>making available</emphasis> an <literal>(Eq a)</literal> constraint, pattern-matching
1590 on <literal>MkSet'</literal> <emphasis>requires</emphasis> an <literal>(Eq a)</literal> constraint!
1591 GHC faithfully implements this behaviour, odd though it is. But for GADT-style declarations,
1592 GHC's behaviour is much more useful, as well as much more intuitive.</para>
1594 For example, a possible application of GHC's behaviour is to reify dictionaries:
1596 data NumInst a where
1597 MkNumInst :: Num a => NumInst a
1599 intInst :: NumInst Int
1602 plus :: NumInst a -> a -> a -> a
1603 plus MkNumInst p q = p + q
1605 Here, a value of type <literal>NumInst a</literal> is equivalent
1606 to an explicit <literal>(Num a)</literal> dictionary.
1610 The rest of this section gives further details about GADT-style data
1615 The result type of each data constructor must begin with the type constructor being defined.
1616 If the result type of all constructors
1617 has the form <literal>T a1 ... an</literal>, where <literal>a1 ... an</literal>
1618 are distinct type variables, then the data type is <emphasis>ordinary</emphasis>;
1619 otherwise is a <emphasis>generalised</emphasis> data type (<xref linkend="gadt
"/>).
1623 The type signature of
1624 each constructor is independent, and is implicitly universally quantified as usual.
1625 Different constructors may have different universally-quantified type variables
1626 and different type-class constraints.
1627 For example, this is fine:
1630 T1 :: Eq b => b -> T b
1631 T2 :: (Show c, Ix c) => c -> [c] -> T c
1636 Unlike a Haskell-98-style
1637 data type declaration, the type variable(s) in the "<literal>data Set a where
</literal>" header
1638 have no scope. Indeed, one can write a kind signature instead:
1640 data Set :: * -> * where ...
1642 or even a mixture of the two:
1644 data Foo a :: (* -> *) -> * where ...
1646 The type variables (if given) may be explicitly kinded, so we could also write the header for <literal>Foo</literal>
1649 data Foo a (b :: * -> *) where ...
1655 You can use strictness annotations, in the obvious places
1656 in the constructor type:
1659 Lit :: !Int -> Term Int
1660 If :: Term Bool -> !(Term a) -> !(Term a) -> Term a
1661 Pair :: Term a -> Term b -> Term (a,b)
1666 You can use a <literal>deriving</literal> clause on a GADT-style data type
1667 declaration. For example, these two declarations are equivalent
1669 data Maybe1 a where {
1670 Nothing1 :: Maybe1 a ;
1671 Just1 :: a -> Maybe1 a
1672 } deriving( Eq, Ord )
1674 data Maybe2 a = Nothing2 | Just2 a
1680 You can use record syntax on a GADT-style data type declaration:
1684 Adult { name :: String, children :: [Person] } :: Person
1685 Child { name :: String } :: Person
1687 As usual, for every constructor that has a field <literal>f</literal>, the type of
1688 field <literal>f</literal> must be the same (modulo alpha conversion).
1691 At the moment, record updates are not yet possible with GADT-style declarations,
1692 so support is limited to record construction, selection and pattern matching.
1695 aPerson = Adult { name = "Fred
", children = [] }
1697 shortName :: Person -> Bool
1698 hasChildren (Adult { children = kids }) = not (null kids)
1699 hasChildren (Child {}) = False
1704 As in the case of existentials declared using the Haskell-98-like record syntax
1705 (<xref linkend="existential-records
"/>),
1706 record-selector functions are generated only for those fields that have well-typed
1708 Here is the example of that section, in GADT-style syntax:
1710 data Counter a where
1711 NewCounter { _this :: self
1712 , _inc :: self -> self
1713 , _display :: self -> IO ()
1718 As before, only one selector function is generated here, that for <literal>tag</literal>.
1719 Nevertheless, you can still use all the field names in pattern matching and record construction.
1721 </itemizedlist></para>
1725 <title>Generalised Algebraic Data Types (GADTs)</title>
1727 <para>Generalised Algebraic Data Types generalise ordinary algebraic data types
1728 by allowing constructors to have richer return types. Here is an example:
1731 Lit :: Int -> Term Int
1732 Succ :: Term Int -> Term Int
1733 IsZero :: Term Int -> Term Bool
1734 If :: Term Bool -> Term a -> Term a -> Term a
1735 Pair :: Term a -> Term b -> Term (a,b)
1737 Notice that the return type of the constructors is not always <literal>Term a</literal>, as is the
1738 case with ordinary data types. This generality allows us to
1739 write a well-typed <literal>eval</literal> function
1740 for these <literal>Terms</literal>:
1744 eval (Succ t) = 1 + eval t
1745 eval (IsZero t) = eval t == 0
1746 eval (If b e1 e2) = if eval b then eval e1 else eval e2
1747 eval (Pair e1 e2) = (eval e1, eval e2)
1749 The key point about GADTs is that <emphasis>pattern matching causes type refinement</emphasis>.
1750 For example, in the right hand side of the equation
1755 the type <literal>a</literal> is refined to <literal>Int</literal>. That's the whole point!
1756 A precise specification of the type rules is beyond what this user manual aspires to,
1757 but the design closely follows that described in
1759 url="http://research.microsoft.com/%
7Esimonpj/papers/gadt/index.htm
">Simple
1760 unification-based type inference for GADTs</ulink>,
1762 The general principle is this: <emphasis>type refinement is only carried out
1763 based on user-supplied type annotations</emphasis>.
1764 So if no type signature is supplied for <literal>eval</literal>, no type refinement happens,
1765 and lots of obscure error messages will
1766 occur. However, the refinement is quite general. For example, if we had:
1768 eval :: Term a -> a -> a
1769 eval (Lit i) j = i+j
1771 the pattern match causes the type <literal>a</literal> to be refined to <literal>Int</literal> (because of the type
1772 of the constructor <literal>Lit</literal>), and that refinement also applies to the type of <literal>j</literal>, and
1773 the result type of the <literal>case</literal> expression. Hence the addition <literal>i+j</literal> is legal.
1776 These and many other examples are given in papers by Hongwei Xi, and
1777 Tim Sheard. There is a longer introduction
1778 <ulink url="http://haskell.org/haskellwiki/GADT
">on the wiki</ulink>,
1780 <ulink url="http://www.informatik.uni-bonn.de/~ralf/publications/With.pdf
">Fun with phantom types</ulink> also has a number of examples. Note that papers
1781 may use different notation to that implemented in GHC.
1784 The rest of this section outlines the extensions to GHC that support GADTs.
1787 A GADT can only be declared using GADT-style syntax (<xref linkend="gadt-style
"/>);
1788 the old Haskell-98 syntax for data declarations always declares an ordinary data type.
1789 The result type of each constructor must begin with the type constructor being defined,
1790 but for a GADT the arguments to the type constructor can be arbitrary monotypes.
1791 For example, in the <literal>Term</literal> data
1792 type above, the type of each constructor must end with <literal>Term ty</literal>, but
1793 the <literal>ty</literal> may not be a type variable (e.g. the <literal>Lit</literal>
1798 You cannot use a <literal>deriving</literal> clause for a GADT; only for
1799 an ordianary data type.
1803 As mentioned in <xref linkend="gadt-style
"/>, record syntax is supported.
1807 Lit { val :: Int } :: Term Int
1808 Succ { num :: Term Int } :: Term Int
1809 Pred { num :: Term Int } :: Term Int
1810 IsZero { arg :: Term Int } :: Term Bool
1811 Pair { arg1 :: Term a
1814 If { cnd :: Term Bool
1819 However, for GADTs there is the following additional constraint:
1820 every constructor that has a field <literal>f</literal> must have
1821 the same result type (modulo alpha conversion)
1822 Hence, in the above example, we cannot merge the <literal>num</literal>
1823 and <literal>arg</literal> fields above into a
1824 single name. Although their field types are both <literal>Term Int</literal>,
1825 their selector functions actually have different types:
1828 num :: Term Int -> Term Int
1829 arg :: Term Bool -> Term Int
1838 <!-- ====================== End of Generalised algebraic data types ======================= -->
1845 <sect2 id="multi-param-type-classes
">
1846 <title>Class declarations</title>
1849 This section, and the next one, documents GHC's type-class extensions.
1850 There's lots of background in the paper <ulink
1851 url="http://research.microsoft.com/~simonpj/Papers/type-class-design-space
" >Type
1852 classes: exploring the design space</ulink > (Simon Peyton Jones, Mark
1853 Jones, Erik Meijer).
1856 All the extensions are enabled by the <option>-fglasgow-exts</option> flag.
1860 <title>Multi-parameter type classes</title>
1862 Multi-parameter type classes are permitted. For example:
1866 class Collection c a where
1867 union :: c a -> c a -> c a
1875 <title>The superclasses of a class declaration</title>
1878 There are no restrictions on the context in a class declaration
1879 (which introduces superclasses), except that the class hierarchy must
1880 be acyclic. So these class declarations are OK:
1884 class Functor (m k) => FiniteMap m k where
1887 class (Monad m, Monad (t m)) => Transform t m where
1888 lift :: m a -> (t m) a
1894 As in Haskell 98, The class hierarchy must be acyclic. However, the definition
1895 of "acyclic
" involves only the superclass relationships. For example,
1901 op :: D b => a -> b -> b
1904 class C a => D a where { ... }
1908 Here, <literal>C</literal> is a superclass of <literal>D</literal>, but it's OK for a
1909 class operation <literal>op</literal> of <literal>C</literal> to mention <literal>D</literal>. (It
1910 would not be OK for <literal>D</literal> to be a superclass of <literal>C</literal>.)
1917 <sect3 id="class-method-types
">
1918 <title>Class method types</title>
1921 Haskell 98 prohibits class method types to mention constraints on the
1922 class type variable, thus:
1925 fromList :: [a] -> s a
1926 elem :: Eq a => a -> s a -> Bool
1928 The type of <literal>elem</literal> is illegal in Haskell 98, because it
1929 contains the constraint <literal>Eq a</literal>, constrains only the
1930 class type variable (in this case <literal>a</literal>).
1931 GHC lifts this restriction.
1938 <sect2 id="functional-dependencies
">
1939 <title>Functional dependencies
1942 <para> Functional dependencies are implemented as described by Mark Jones
1943 in “<ulink url="http://www.cse.ogi.edu/~mpj/pubs/fundeps.html
">Type Classes with Functional Dependencies</ulink>”, Mark P. Jones,
1944 In Proceedings of the 9th European Symposium on Programming,
1945 ESOP 2000, Berlin, Germany, March 2000, Springer-Verlag LNCS 1782,
1949 Functional dependencies are introduced by a vertical bar in the syntax of a
1950 class declaration; e.g.
1952 class (Monad m) => MonadState s m | m -> s where ...
1954 class Foo a b c | a b -> c where ...
1956 There should be more documentation, but there isn't (yet). Yell if you need it.
1959 <sect3><title>Rules for functional dependencies </title>
1961 In a class declaration, all of the class type variables must be reachable (in the sense
1962 mentioned in <xref linkend="type-restrictions
"/>)
1963 from the free variables of each method type.
1967 class Coll s a where
1969 insert :: s -> a -> s
1972 is not OK, because the type of <literal>empty</literal> doesn't mention
1973 <literal>a</literal>. Functional dependencies can make the type variable
1976 class Coll s a | s -> a where
1978 insert :: s -> a -> s
1981 Alternatively <literal>Coll</literal> might be rewritten
1984 class Coll s a where
1986 insert :: s a -> a -> s a
1990 which makes the connection between the type of a collection of
1991 <literal>a</literal>'s (namely <literal>(s a)</literal>) and the element type <literal>a</literal>.
1992 Occasionally this really doesn't work, in which case you can split the
2000 class CollE s => Coll s a where
2001 insert :: s -> a -> s
2008 <title>Background on functional dependencies</title>
2010 <para>The following description of the motivation and use of functional dependencies is taken
2011 from the Hugs user manual, reproduced here (with minor changes) by kind
2012 permission of Mark Jones.
2015 Consider the following class, intended as part of a
2016 library for collection types:
2018 class Collects e ce where
2020 insert :: e -> ce -> ce
2021 member :: e -> ce -> Bool
2023 The type variable e used here represents the element type, while ce is the type
2024 of the container itself. Within this framework, we might want to define
2025 instances of this class for lists or characteristic functions (both of which
2026 can be used to represent collections of any equality type), bit sets (which can
2027 be used to represent collections of characters), or hash tables (which can be
2028 used to represent any collection whose elements have a hash function). Omitting
2029 standard implementation details, this would lead to the following declarations:
2031 instance Eq e => Collects e [e] where ...
2032 instance Eq e => Collects e (e -> Bool) where ...
2033 instance Collects Char BitSet where ...
2034 instance (Hashable e, Collects a ce)
2035 => Collects e (Array Int ce) where ...
2037 All this looks quite promising; we have a class and a range of interesting
2038 implementations. Unfortunately, there are some serious problems with the class
2039 declaration. First, the empty function has an ambiguous type:
2041 empty :: Collects e ce => ce
2043 By "ambiguous
" we mean that there is a type variable e that appears on the left
2044 of the <literal>=></literal> symbol, but not on the right. The problem with
2045 this is that, according to the theoretical foundations of Haskell overloading,
2046 we cannot guarantee a well-defined semantics for any term with an ambiguous
2050 We can sidestep this specific problem by removing the empty member from the
2051 class declaration. However, although the remaining members, insert and member,
2052 do not have ambiguous types, we still run into problems when we try to use
2053 them. For example, consider the following two functions:
2055 f x y = insert x . insert y
2058 for which GHC infers the following types:
2060 f :: (Collects a c, Collects b c) => a -> b -> c -> c
2061 g :: (Collects Bool c, Collects Char c) => c -> c
2063 Notice that the type for f allows the two parameters x and y to be assigned
2064 different types, even though it attempts to insert each of the two values, one
2065 after the other, into the same collection. If we're trying to model collections
2066 that contain only one type of value, then this is clearly an inaccurate
2067 type. Worse still, the definition for g is accepted, without causing a type
2068 error. As a result, the error in this code will not be flagged at the point
2069 where it appears. Instead, it will show up only when we try to use g, which
2070 might even be in a different module.
2073 <sect4><title>An attempt to use constructor classes</title>
2076 Faced with the problems described above, some Haskell programmers might be
2077 tempted to use something like the following version of the class declaration:
2079 class Collects e c where
2081 insert :: e -> c e -> c e
2082 member :: e -> c e -> Bool
2084 The key difference here is that we abstract over the type constructor c that is
2085 used to form the collection type c e, and not over that collection type itself,
2086 represented by ce in the original class declaration. This avoids the immediate
2087 problems that we mentioned above: empty has type <literal>Collects e c => c
2088 e</literal>, which is not ambiguous.
2091 The function f from the previous section has a more accurate type:
2093 f :: (Collects e c) => e -> e -> c e -> c e
2095 The function g from the previous section is now rejected with a type error as
2096 we would hope because the type of f does not allow the two arguments to have
2098 This, then, is an example of a multiple parameter class that does actually work
2099 quite well in practice, without ambiguity problems.
2100 There is, however, a catch. This version of the Collects class is nowhere near
2101 as general as the original class seemed to be: only one of the four instances
2102 for <literal>Collects</literal>
2103 given above can be used with this version of Collects because only one of
2104 them---the instance for lists---has a collection type that can be written in
2105 the form c e, for some type constructor c, and element type e.
2109 <sect4><title>Adding functional dependencies</title>
2112 To get a more useful version of the Collects class, Hugs provides a mechanism
2113 that allows programmers to specify dependencies between the parameters of a
2114 multiple parameter class (For readers with an interest in theoretical
2115 foundations and previous work: The use of dependency information can be seen
2116 both as a generalization of the proposal for `parametric type classes' that was
2117 put forward by Chen, Hudak, and Odersky, or as a special case of Mark Jones's
2118 later framework for "improvement
" of qualified types. The
2119 underlying ideas are also discussed in a more theoretical and abstract setting
2120 in a manuscript [implparam], where they are identified as one point in a
2121 general design space for systems of implicit parameterization.).
2123 To start with an abstract example, consider a declaration such as:
2125 class C a b where ...
2127 which tells us simply that C can be thought of as a binary relation on types
2128 (or type constructors, depending on the kinds of a and b). Extra clauses can be
2129 included in the definition of classes to add information about dependencies
2130 between parameters, as in the following examples:
2132 class D a b | a -> b where ...
2133 class E a b | a -> b, b -> a where ...
2135 The notation <literal>a -> b</literal> used here between the | and where
2136 symbols --- not to be
2137 confused with a function type --- indicates that the a parameter uniquely
2138 determines the b parameter, and might be read as "a determines b.
" Thus D is
2139 not just a relation, but actually a (partial) function. Similarly, from the two
2140 dependencies that are included in the definition of E, we can see that E
2141 represents a (partial) one-one mapping between types.
2144 More generally, dependencies take the form <literal>x1 ... xn -> y1 ... ym</literal>,
2145 where x1, ..., xn, and y1, ..., yn are type variables with n>0 and
2146 m>=0, meaning that the y parameters are uniquely determined by the x
2147 parameters. Spaces can be used as separators if more than one variable appears
2148 on any single side of a dependency, as in <literal>t -> a b</literal>. Note that a class may be
2149 annotated with multiple dependencies using commas as separators, as in the
2150 definition of E above. Some dependencies that we can write in this notation are
2151 redundant, and will be rejected because they don't serve any useful
2152 purpose, and may instead indicate an error in the program. Examples of
2153 dependencies like this include <literal>a -> a </literal>,
2154 <literal>a -> a a </literal>,
2155 <literal>a -> </literal>, etc. There can also be
2156 some redundancy if multiple dependencies are given, as in
2157 <literal>a->b</literal>,
2158 <literal>b->c </literal>, <literal>a->c </literal>, and
2159 in which some subset implies the remaining dependencies. Examples like this are
2160 not treated as errors. Note that dependencies appear only in class
2161 declarations, and not in any other part of the language. In particular, the
2162 syntax for instance declarations, class constraints, and types is completely
2166 By including dependencies in a class declaration, we provide a mechanism for
2167 the programmer to specify each multiple parameter class more precisely. The
2168 compiler, on the other hand, is responsible for ensuring that the set of
2169 instances that are in scope at any given point in the program is consistent
2170 with any declared dependencies. For example, the following pair of instance
2171 declarations cannot appear together in the same scope because they violate the
2172 dependency for D, even though either one on its own would be acceptable:
2174 instance D Bool Int where ...
2175 instance D Bool Char where ...
2177 Note also that the following declaration is not allowed, even by itself:
2179 instance D [a] b where ...
2181 The problem here is that this instance would allow one particular choice of [a]
2182 to be associated with more than one choice for b, which contradicts the
2183 dependency specified in the definition of D. More generally, this means that,
2184 in any instance of the form:
2186 instance D t s where ...
2188 for some particular types t and s, the only variables that can appear in s are
2189 the ones that appear in t, and hence, if the type t is known, then s will be
2190 uniquely determined.
2193 The benefit of including dependency information is that it allows us to define
2194 more general multiple parameter classes, without ambiguity problems, and with
2195 the benefit of more accurate types. To illustrate this, we return to the
2196 collection class example, and annotate the original definition of <literal>Collects</literal>
2197 with a simple dependency:
2199 class Collects e ce | ce -> e where
2201 insert :: e -> ce -> ce
2202 member :: e -> ce -> Bool
2204 The dependency <literal>ce -> e</literal> here specifies that the type e of elements is uniquely
2205 determined by the type of the collection ce. Note that both parameters of
2206 Collects are of kind *; there are no constructor classes here. Note too that
2207 all of the instances of Collects that we gave earlier can be used
2208 together with this new definition.
2211 What about the ambiguity problems that we encountered with the original
2212 definition? The empty function still has type Collects e ce => ce, but it is no
2213 longer necessary to regard that as an ambiguous type: Although the variable e
2214 does not appear on the right of the => symbol, the dependency for class
2215 Collects tells us that it is uniquely determined by ce, which does appear on
2216 the right of the => symbol. Hence the context in which empty is used can still
2217 give enough information to determine types for both ce and e, without
2218 ambiguity. More generally, we need only regard a type as ambiguous if it
2219 contains a variable on the left of the => that is not uniquely determined
2220 (either directly or indirectly) by the variables on the right.
2223 Dependencies also help to produce more accurate types for user defined
2224 functions, and hence to provide earlier detection of errors, and less cluttered
2225 types for programmers to work with. Recall the previous definition for a
2228 f x y = insert x y = insert x . insert y
2230 for which we originally obtained a type:
2232 f :: (Collects a c, Collects b c) => a -> b -> c -> c
2234 Given the dependency information that we have for Collects, however, we can
2235 deduce that a and b must be equal because they both appear as the second
2236 parameter in a Collects constraint with the same first parameter c. Hence we
2237 can infer a shorter and more accurate type for f:
2239 f :: (Collects a c) => a -> a -> c -> c
2241 In a similar way, the earlier definition of g will now be flagged as a type error.
2244 Although we have given only a few examples here, it should be clear that the
2245 addition of dependency information can help to make multiple parameter classes
2246 more useful in practice, avoiding ambiguity problems, and allowing more general
2247 sets of instance declarations.
2253 <sect2 id="instance-decls
">
2254 <title>Instance declarations</title>
2256 <sect3 id="instance-rules
">
2257 <title>Relaxed rules for instance declarations</title>
2259 <para>An instance declaration has the form
2261 instance ( <replaceable>assertion</replaceable><subscript>1</subscript>, ..., <replaceable>assertion</replaceable><subscript>n</subscript>) => <replaceable>class</replaceable> <replaceable>type</replaceable><subscript>1</subscript> ... <replaceable>type</replaceable><subscript>m</subscript> where ...
2263 The part before the "<literal>=
></literal>" is the
2264 <emphasis>context</emphasis>, while the part after the
2265 "<literal>=
></literal>" is the <emphasis>head</emphasis> of the instance declaration.
2269 In Haskell 98 the head of an instance declaration
2270 must be of the form <literal>C (T a1 ... an)</literal>, where
2271 <literal>C</literal> is the class, <literal>T</literal> is a type constructor,
2272 and the <literal>a1 ... an</literal> are distinct type variables.
2273 Furthermore, the assertions in the context of the instance declaration
2274 must be of the form <literal>C a</literal> where <literal>a</literal>
2275 is a type variable that occurs in the head.
2278 The <option>-fglasgow-exts</option> flag loosens these restrictions
2279 considerably. Firstly, multi-parameter type classes are permitted. Secondly,
2280 the context and head of the instance declaration can each consist of arbitrary
2281 (well-kinded) assertions <literal>(C t1 ... tn)</literal> subject only to the
2285 For each assertion in the context:
2287 <listitem><para>No type variable has more occurrences in the assertion than in the head</para></listitem>
2288 <listitem><para>The assertion has fewer constructors and variables (taken together
2289 and counting repetitions) than the head</para></listitem>
2293 <listitem><para>The coverage condition. For each functional dependency,
2294 <replaceable>tvs</replaceable><subscript>left</subscript> <literal>-></literal>
2295 <replaceable>tvs</replaceable><subscript>right</subscript>, of the class,
2296 every type variable in
2297 S(<replaceable>tvs</replaceable><subscript>right</subscript>) must appear in
2298 S(<replaceable>tvs</replaceable><subscript>left</subscript>), where S is the
2299 substitution mapping each type variable in the class declaration to the
2300 corresponding type in the instance declaration.
2303 These restrictions ensure that context reduction terminates: each reduction
2304 step makes the problem smaller by at least one
2305 constructor. For example, the following would make the type checker
2306 loop if it wasn't excluded:
2308 instance C a => C a where ...
2310 For example, these are OK:
2312 instance C Int [a] -- Multiple parameters
2313 instance Eq (S [a]) -- Structured type in head
2315 -- Repeated type variable in head
2316 instance C4 a a => C4 [a] [a]
2317 instance Stateful (ST s) (MutVar s)
2319 -- Head can consist of type variables only
2321 instance (Eq a, Show b) => C2 a b
2323 -- Non-type variables in context
2324 instance Show (s a) => Show (Sized s a)
2325 instance C2 Int a => C3 Bool [a]
2326 instance C2 Int a => C3 [a] b
2330 -- Context assertion no smaller than head
2331 instance C a => C a where ...
2332 -- (C b b) has more more occurrences of b than the head
2333 instance C b b => Foo [b] where ...
2338 The same restrictions apply to instances generated by
2339 <literal>deriving</literal> clauses. Thus the following is accepted:
2341 data MinHeap h a = H a (h a)
2344 because the derived instance
2346 instance (Show a, Show (h a)) => Show (MinHeap h a)
2348 conforms to the above rules.
2352 A useful idiom permitted by the above rules is as follows.
2353 If one allows overlapping instance declarations then it's quite
2354 convenient to have a "default instance
" declaration that applies if
2355 something more specific does not:
2361 <para>You can find lots of background material about the reason for these
2362 restrictions in the paper <ulink
2363 url="http://research.microsoft.com/%
7Esimonpj/papers/fd%
2Dchr/
">
2364 Understanding functional dependencies via Constraint Handling Rules</ulink>.
2368 <sect3 id="undecidable-instances
">
2369 <title>Undecidable instances</title>
2372 Sometimes even the rules of <xref linkend="instance-rules
"/> are too onerous.
2373 For example, sometimes you might want to use the following to get the
2374 effect of a "class synonym
":
2376 class (C1 a, C2 a, C3 a) => C a where { }
2378 instance (C1 a, C2 a, C3 a) => C a where { }
2380 This allows you to write shorter signatures:
2386 f :: (C1 a, C2 a, C3 a) => ...
2388 The restrictions on functional dependencies (<xref
2389 linkend="functional-dependencies
"/>) are particularly troublesome.
2390 It is tempting to introduce type variables in the context that do not appear in
2391 the head, something that is excluded by the normal rules. For example:
2393 class HasConverter a b | a -> b where
2396 data Foo a = MkFoo a
2398 instance (HasConverter a b,Show b) => Show (Foo a) where
2399 show (MkFoo value) = show (convert value)
2401 This is dangerous territory, however. Here, for example, is a program that would make the
2406 instance F [a] [[a]]
2407 instance (D c, F a c) => D [a] -- 'c' is not mentioned in the head
2409 Similarly, it can be tempting to lift the coverage condition:
2411 class Mul a b c | a b -> c where
2412 (.*.) :: a -> b -> c
2414 instance Mul Int Int Int where (.*.) = (*)
2415 instance Mul Int Float Float where x .*. y = fromIntegral x * y
2416 instance Mul a b c => Mul a [b] [c] where x .*. v = map (x.*.) v
2418 The third instance declaration does not obey the coverage condition;
2419 and indeed the (somewhat strange) definition:
2421 f = \ b x y -> if b then x .*. [y] else y
2423 makes instance inference go into a loop, because it requires the constraint
2424 <literal>(Mul a [b] b)</literal>.
2427 Nevertheless, GHC allows you to experiment with more liberal rules. If you use
2428 the experimental flag <option>-fallow-undecidable-instances</option>
2429 <indexterm><primary>-fallow-undecidable-instances
2430 option</primary></indexterm>, you can use arbitrary
2431 types in both an instance context and instance head. Termination is ensured by having a
2432 fixed-depth recursion stack. If you exceed the stack depth you get a
2433 sort of backtrace, and the opportunity to increase the stack depth
2434 with <option>-fcontext-stack=</option><emphasis>N</emphasis>.
2440 <sect3 id="instance-overlap
">
2441 <title>Overlapping instances</title>
2443 In general, <emphasis>GHC requires that that it be unambiguous which instance
2445 should be used to resolve a type-class constraint</emphasis>. This behaviour
2446 can be modified by two flags: <option>-fallow-overlapping-instances</option>
2447 <indexterm><primary>-fallow-overlapping-instances
2448 </primary></indexterm>
2449 and <option>-fallow-incoherent-instances</option>
2450 <indexterm><primary>-fallow-incoherent-instances
2451 </primary></indexterm>, as this section discusses. Both these
2452 flags are dynamic flags, and can be set on a per-module basis, using
2453 an <literal>OPTIONS_GHC</literal> pragma if desired (<xref linkend="source-file-options
"/>).</para>
2455 When GHC tries to resolve, say, the constraint <literal>C Int Bool</literal>,
2456 it tries to match every instance declaration against the
2458 by instantiating the head of the instance declaration. For example, consider
2461 instance context1 => C Int a where ... -- (A)
2462 instance context2 => C a Bool where ... -- (B)
2463 instance context3 => C Int [a] where ... -- (C)
2464 instance context4 => C Int [Int] where ... -- (D)
2466 The instances (A) and (B) match the constraint <literal>C Int Bool</literal>,
2467 but (C) and (D) do not. When matching, GHC takes
2468 no account of the context of the instance declaration
2469 (<literal>context1</literal> etc).
2470 GHC's default behaviour is that <emphasis>exactly one instance must match the
2471 constraint it is trying to resolve</emphasis>.
2472 It is fine for there to be a <emphasis>potential</emphasis> of overlap (by
2473 including both declarations (A) and (B), say); an error is only reported if a
2474 particular constraint matches more than one.
2478 The <option>-fallow-overlapping-instances</option> flag instructs GHC to allow
2479 more than one instance to match, provided there is a most specific one. For
2480 example, the constraint <literal>C Int [Int]</literal> matches instances (A),
2481 (C) and (D), but the last is more specific, and hence is chosen. If there is no
2482 most-specific match, the program is rejected.
2485 However, GHC is conservative about committing to an overlapping instance. For example:
2490 Suppose that from the RHS of <literal>f</literal> we get the constraint
2491 <literal>C Int [b]</literal>. But
2492 GHC does not commit to instance (C), because in a particular
2493 call of <literal>f</literal>, <literal>b</literal> might be instantiate
2494 to <literal>Int</literal>, in which case instance (D) would be more specific still.
2495 So GHC rejects the program. If you add the flag <option>-fallow-incoherent-instances</option>,
2496 GHC will instead pick (C), without complaining about
2497 the problem of subsequent instantiations.
2500 The willingness to be overlapped or incoherent is a property of
2501 the <emphasis>instance declaration</emphasis> itself, controlled by the
2502 presence or otherwise of the <option>-fallow-overlapping-instances</option>
2503 and <option>-fallow-incoherent-instances</option> flags when that mdodule is
2504 being defined. Neither flag is required in a module that imports and uses the
2505 instance declaration. Specifically, during the lookup process:
2508 An instance declaration is ignored during the lookup process if (a) a more specific
2509 match is found, and (b) the instance declaration was compiled with
2510 <option>-fallow-overlapping-instances</option>. The flag setting for the
2511 more-specific instance does not matter.
2514 Suppose an instance declaration does not matche the constraint being looked up, but
2515 does unify with it, so that it might match when the constraint is further
2516 instantiated. Usually GHC will regard this as a reason for not committing to
2517 some other constraint. But if the instance declaration was compiled with
2518 <option>-fallow-incoherent-instances</option>, GHC will skip the "does-it-unify?
"
2519 check for that declaration.
2522 These rules make it possible for a library author to design a library that relies on
2523 overlapping instances without the library client having to know.
2526 If an instance declaration is compiled without
2527 <option>-fallow-overlapping-instances</option>,
2528 then that instance can never be overlapped. This could perhaps be
2529 inconvenient. Perhaps the rule should instead say that the
2530 <emphasis>overlapping</emphasis> instance declaration should be compiled in
2531 this way, rather than the <emphasis>overlapped</emphasis> one. Perhaps overlap
2532 at a usage site should be permitted regardless of how the instance declarations
2533 are compiled, if the <option>-fallow-overlapping-instances</option> flag is
2534 used at the usage site. (Mind you, the exact usage site can occasionally be
2535 hard to pin down.) We are interested to receive feedback on these points.
2537 <para>The <option>-fallow-incoherent-instances</option> flag implies the
2538 <option>-fallow-overlapping-instances</option> flag, but not vice versa.
2543 <title>Type synonyms in the instance head</title>
2546 <emphasis>Unlike Haskell 98, instance heads may use type
2547 synonyms</emphasis>. (The instance "head
" is the bit after the "=
>" in an instance decl.)
2548 As always, using a type synonym is just shorthand for
2549 writing the RHS of the type synonym definition. For example:
2553 type Point = (Int,Int)
2554 instance C Point where ...
2555 instance C [Point] where ...
2559 is legal. However, if you added
2563 instance C (Int,Int) where ...
2567 as well, then the compiler will complain about the overlapping
2568 (actually, identical) instance declarations. As always, type synonyms
2569 must be fully applied. You cannot, for example, write:
2574 instance Monad P where ...
2578 This design decision is independent of all the others, and easily
2579 reversed, but it makes sense to me.
2587 <sect2 id="type-restrictions
">
2588 <title>Type signatures</title>
2590 <sect3><title>The context of a type signature</title>
2592 Unlike Haskell 98, constraints in types do <emphasis>not</emphasis> have to be of
2593 the form <emphasis>(class type-variable)</emphasis> or
2594 <emphasis>(class (type-variable type-variable ...))</emphasis>. Thus,
2595 these type signatures are perfectly OK
2598 g :: Ord (T a ()) => ...
2602 GHC imposes the following restrictions on the constraints in a type signature.
2606 forall tv1..tvn (c1, ...,cn) => type
2609 (Here, we write the "foralls
" explicitly, although the Haskell source
2610 language omits them; in Haskell 98, all the free type variables of an
2611 explicit source-language type signature are universally quantified,
2612 except for the class type variables in a class declaration. However,
2613 in GHC, you can give the foralls if you want. See <xref linkend="universal-quantification
"/>).
2622 <emphasis>Each universally quantified type variable
2623 <literal>tvi</literal> must be reachable from <literal>type</literal></emphasis>.
2625 A type variable <literal>a</literal> is "reachable
" if it it appears
2626 in the same constraint as either a type variable free in in
2627 <literal>type</literal>, or another reachable type variable.
2628 A value with a type that does not obey
2629 this reachability restriction cannot be used without introducing
2630 ambiguity; that is why the type is rejected.
2631 Here, for example, is an illegal type:
2635 forall a. Eq a => Int
2639 When a value with this type was used, the constraint <literal>Eq tv</literal>
2640 would be introduced where <literal>tv</literal> is a fresh type variable, and
2641 (in the dictionary-translation implementation) the value would be
2642 applied to a dictionary for <literal>Eq tv</literal>. The difficulty is that we
2643 can never know which instance of <literal>Eq</literal> to use because we never
2644 get any more information about <literal>tv</literal>.
2648 that the reachability condition is weaker than saying that <literal>a</literal> is
2649 functionally dependent on a type variable free in
2650 <literal>type</literal> (see <xref
2651 linkend="functional-dependencies
"/>). The reason for this is there
2652 might be a "hidden
" dependency, in a superclass perhaps. So
2653 "reachable
" is a conservative approximation to "functionally dependent
".
2654 For example, consider:
2656 class C a b | a -> b where ...
2657 class C a b => D a b where ...
2658 f :: forall a b. D a b => a -> a
2660 This is fine, because in fact <literal>a</literal> does functionally determine <literal>b</literal>
2661 but that is not immediately apparent from <literal>f</literal>'s type.
2667 <emphasis>Every constraint <literal>ci</literal> must mention at least one of the
2668 universally quantified type variables <literal>tvi</literal></emphasis>.
2670 For example, this type is OK because <literal>C a b</literal> mentions the
2671 universally quantified type variable <literal>b</literal>:
2675 forall a. C a b => burble
2679 The next type is illegal because the constraint <literal>Eq b</literal> does not
2680 mention <literal>a</literal>:
2684 forall a. Eq b => burble
2688 The reason for this restriction is milder than the other one. The
2689 excluded types are never useful or necessary (because the offending
2690 context doesn't need to be witnessed at this point; it can be floated
2691 out). Furthermore, floating them out increases sharing. Lastly,
2692 excluding them is a conservative choice; it leaves a patch of
2693 territory free in case we need it later.
2704 <title>For-all hoisting</title>
2706 It is often convenient to use generalised type synonyms (see <xref linkend="type-synonyms
"/>) at the right hand
2707 end of an arrow, thus:
2709 type Discard a = forall b. a -> b -> a
2711 g :: Int -> Discard Int
2714 Simply expanding the type synonym would give
2716 g :: Int -> (forall b. Int -> b -> Int)
2718 but GHC "hoists
" the <literal>forall</literal> to give the isomorphic type
2720 g :: forall b. Int -> Int -> b -> Int
2722 In general, the rule is this: <emphasis>to determine the type specified by any explicit
2723 user-written type (e.g. in a type signature), GHC expands type synonyms and then repeatedly
2724 performs the transformation:</emphasis>
2726 <emphasis>type1</emphasis> -> forall a1..an. <emphasis>context2</emphasis> => <emphasis>type2</emphasis>
2728 forall a1..an. <emphasis>context2</emphasis> => <emphasis>type1</emphasis> -> <emphasis>type2</emphasis>
2730 (In fact, GHC tries to retain as much synonym information as possible for use in
2731 error messages, but that is a usability issue.) This rule applies, of course, whether
2732 or not the <literal>forall</literal> comes from a synonym. For example, here is another
2733 valid way to write <literal>g</literal>'s type signature:
2735 g :: Int -> Int -> forall b. b -> Int
2739 When doing this hoisting operation, GHC eliminates duplicate constraints. For
2742 type Foo a = (?x::Int) => Bool -> a
2747 g :: (?x::Int) => Bool -> Bool -> Int
2755 <sect2 id="implicit-parameters
">
2756 <title>Implicit parameters</title>
2758 <para> Implicit parameters are implemented as described in
2759 "Implicit parameters: dynamic scoping with static types
",
2760 J Lewis, MB Shields, E Meijer, J Launchbury,
2761 27th ACM Symposium on Principles of Programming Languages (POPL'00),
2765 <para>(Most of the following, stil rather incomplete, documentation is
2766 due to Jeff Lewis.)</para>
2768 <para>Implicit parameter support is enabled with the option
2769 <option>-fimplicit-params</option>.</para>
2772 A variable is called <emphasis>dynamically bound</emphasis> when it is bound by the calling
2773 context of a function and <emphasis>statically bound</emphasis> when bound by the callee's
2774 context. In Haskell, all variables are statically bound. Dynamic
2775 binding of variables is a notion that goes back to Lisp, but was later
2776 discarded in more modern incarnations, such as Scheme. Dynamic binding
2777 can be very confusing in an untyped language, and unfortunately, typed
2778 languages, in particular Hindley-Milner typed languages like Haskell,
2779 only support static scoping of variables.
2782 However, by a simple extension to the type class system of Haskell, we
2783 can support dynamic binding. Basically, we express the use of a
2784 dynamically bound variable as a constraint on the type. These
2785 constraints lead to types of the form <literal>(?x::t') => t</literal>, which says "this
2786 function uses a dynamically-bound variable
<literal>?x
</literal>
2787 of type
<literal>t'
</literal>". For
2788 example, the following expresses the type of a sort function,
2789 implicitly parameterized by a comparison function named <literal>cmp</literal>.
2791 sort :: (?cmp :: a -> a -> Bool) => [a] -> [a]
2793 The dynamic binding constraints are just a new form of predicate in the type class system.
2796 An implicit parameter occurs in an expression using the special form <literal>?x</literal>,
2797 where <literal>x</literal> is
2798 any valid identifier (e.g. <literal>ord ?x</literal> is a valid expression).
2799 Use of this construct also introduces a new
2800 dynamic-binding constraint in the type of the expression.
2801 For example, the following definition
2802 shows how we can define an implicitly parameterized sort function in
2803 terms of an explicitly parameterized <literal>sortBy</literal> function:
2805 sortBy :: (a -> a -> Bool) -> [a] -> [a]
2807 sort :: (?cmp :: a -> a -> Bool) => [a] -> [a]
2813 <title>Implicit-parameter type constraints</title>
2815 Dynamic binding constraints behave just like other type class
2816 constraints in that they are automatically propagated. Thus, when a
2817 function is used, its implicit parameters are inherited by the
2818 function that called it. For example, our <literal>sort</literal> function might be used
2819 to pick out the least value in a list:
2821 least :: (?cmp :: a -> a -> Bool) => [a] -> a
2822 least xs = head (sort xs)
2824 Without lifting a finger, the <literal>?cmp</literal> parameter is
2825 propagated to become a parameter of <literal>least</literal> as well. With explicit
2826 parameters, the default is that parameters must always be explicit
2827 propagated. With implicit parameters, the default is to always
2831 An implicit-parameter type constraint differs from other type class constraints in the
2832 following way: All uses of a particular implicit parameter must have
2833 the same type. This means that the type of <literal>(?x, ?x)</literal>
2834 is <literal>(?x::a) => (a,a)</literal>, and not
2835 <literal>(?x::a, ?x::b) => (a, b)</literal>, as would be the case for type
2839 <para> You can't have an implicit parameter in the context of a class or instance
2840 declaration. For example, both these declarations are illegal:
2842 class (?x::Int) => C a where ...
2843 instance (?x::a) => Foo [a] where ...
2845 Reason: exactly which implicit parameter you pick up depends on exactly where
2846 you invoke a function. But the ``invocation'' of instance declarations is done
2847 behind the scenes by the compiler, so it's hard to figure out exactly where it is done.
2848 Easiest thing is to outlaw the offending types.</para>
2850 Implicit-parameter constraints do not cause ambiguity. For example, consider:
2852 f :: (?x :: [a]) => Int -> Int
2855 g :: (Read a, Show a) => String -> String
2858 Here, <literal>g</literal> has an ambiguous type, and is rejected, but <literal>f</literal>
2859 is fine. The binding for <literal>?x</literal> at <literal>f</literal>'s call site is
2860 quite unambiguous, and fixes the type <literal>a</literal>.
2865 <title>Implicit-parameter bindings</title>
2868 An implicit parameter is <emphasis>bound</emphasis> using the standard
2869 <literal>let</literal> or <literal>where</literal> binding forms.
2870 For example, we define the <literal>min</literal> function by binding
2871 <literal>cmp</literal>.
2874 min = let ?cmp = (<=) in least
2878 A group of implicit-parameter bindings may occur anywhere a normal group of Haskell
2879 bindings can occur, except at top level. That is, they can occur in a <literal>let</literal>
2880 (including in a list comprehension, or do-notation, or pattern guards),
2881 or a <literal>where</literal> clause.
2882 Note the following points:
2885 An implicit-parameter binding group must be a
2886 collection of simple bindings to implicit-style variables (no
2887 function-style bindings, and no type signatures); these bindings are
2888 neither polymorphic or recursive.
2891 You may not mix implicit-parameter bindings with ordinary bindings in a
2892 single <literal>let</literal>
2893 expression; use two nested <literal>let</literal>s instead.
2894 (In the case of <literal>where</literal> you are stuck, since you can't nest <literal>where</literal> clauses.)
2898 You may put multiple implicit-parameter bindings in a
2899 single binding group; but they are <emphasis>not</emphasis> treated
2900 as a mutually recursive group (as ordinary <literal>let</literal> bindings are).
2901 Instead they are treated as a non-recursive group, simultaneously binding all the implicit
2902 parameter. The bindings are not nested, and may be re-ordered without changing
2903 the meaning of the program.
2904 For example, consider:
2906 f t = let { ?x = t; ?y = ?x+(1::Int) } in ?x + ?y
2908 The use of <literal>?x</literal> in the binding for <literal>?y</literal> does not "see
"
2909 the binding for <literal>?x</literal>, so the type of <literal>f</literal> is
2911 f :: (?x::Int) => Int -> Int
2919 <sect3><title>Implicit parameters and polymorphic recursion</title>
2922 Consider these two definitions:
2925 len1 xs = let ?acc = 0 in len_acc1 xs
2928 len_acc1 (x:xs) = let ?acc = ?acc + (1::Int) in len_acc1 xs
2933 len2 xs = let ?acc = 0 in len_acc2 xs
2935 len_acc2 :: (?acc :: Int) => [a] -> Int
2937 len_acc2 (x:xs) = let ?acc = ?acc + (1::Int) in len_acc2 xs
2939 The only difference between the two groups is that in the second group
2940 <literal>len_acc</literal> is given a type signature.
2941 In the former case, <literal>len_acc1</literal> is monomorphic in its own
2942 right-hand side, so the implicit parameter <literal>?acc</literal> is not
2943 passed to the recursive call. In the latter case, because <literal>len_acc2</literal>
2944 has a type signature, the recursive call is made to the
2945 <emphasis>polymoprhic</emphasis> version, which takes <literal>?acc</literal>
2946 as an implicit parameter. So we get the following results in GHCi:
2953 Adding a type signature dramatically changes the result! This is a rather
2954 counter-intuitive phenomenon, worth watching out for.
2958 <sect3><title>Implicit parameters and monomorphism</title>
2960 <para>GHC applies the dreaded Monomorphism Restriction (section 4.5.5 of the
2961 Haskell Report) to implicit parameters. For example, consider:
2969 Since the binding for <literal>y</literal> falls under the Monomorphism
2970 Restriction it is not generalised, so the type of <literal>y</literal> is
2971 simply <literal>Int</literal>, not <literal>(?x::Int) => Int</literal>.
2972 Hence, <literal>(f 9)</literal> returns result <literal>9</literal>.
2973 If you add a type signature for <literal>y</literal>, then <literal>y</literal>
2974 will get type <literal>(?x::Int) => Int</literal>, so the occurrence of
2975 <literal>y</literal> in the body of the <literal>let</literal> will see the
2976 inner binding of <literal>?x</literal>, so <literal>(f 9)</literal> will return
2977 <literal>14</literal>.
2982 <!-- ======================= COMMENTED OUT ========================
2984 We intend to remove linear implicit parameters, so I'm at least removing
2985 them from the 6.6 user manual
2987 <sect2 id="linear-implicit-parameters
">
2988 <title>Linear implicit parameters</title>
2990 Linear implicit parameters are an idea developed by Koen Claessen,
2991 Mark Shields, and Simon PJ. They address the long-standing
2992 problem that monads seem over-kill for certain sorts of problem, notably:
2995 <listitem> <para> distributing a supply of unique names </para> </listitem>
2996 <listitem> <para> distributing a supply of random numbers </para> </listitem>
2997 <listitem> <para> distributing an oracle (as in QuickCheck) </para> </listitem>
3001 Linear implicit parameters are just like ordinary implicit parameters,
3002 except that they are "linear
"; that is, they cannot be copied, and
3003 must be explicitly "split
" instead. Linear implicit parameters are
3004 written '<literal>%x</literal>' instead of '<literal>?x</literal>'.
3005 (The '/' in the '%' suggests the split!)
3010 import GHC.Exts( Splittable )
3012 data NameSupply = ...
3014 splitNS :: NameSupply -> (NameSupply, NameSupply)
3015 newName :: NameSupply -> Name
3017 instance Splittable NameSupply where
3021 f :: (%ns :: NameSupply) => Env -> Expr -> Expr
3022 f env (Lam x e) = Lam x' (f env e)
3025 env' = extend env x x'
3026 ...more equations for f...
3028 Notice that the implicit parameter %ns is consumed
3030 <listitem> <para> once by the call to <literal>newName</literal> </para> </listitem>
3031 <listitem> <para> once by the recursive call to <literal>f</literal> </para></listitem>
3035 So the translation done by the type checker makes
3036 the parameter explicit:
3038 f :: NameSupply -> Env -> Expr -> Expr
3039 f ns env (Lam x e) = Lam x' (f ns1 env e)
3041 (ns1,ns2) = splitNS ns
3043 env = extend env x x'
3045 Notice the call to 'split' introduced by the type checker.
3046 How did it know to use 'splitNS'? Because what it really did
3047 was to introduce a call to the overloaded function 'split',
3048 defined by the class <literal>Splittable</literal>:
3050 class Splittable a where
3053 The instance for <literal>Splittable NameSupply</literal> tells GHC how to implement
3054 split for name supplies. But we can simply write
3060 g :: (Splittable a, %ns :: a) => b -> (b,a,a)
3062 The <literal>Splittable</literal> class is built into GHC. It's exported by module
3063 <literal>GHC.Exts</literal>.
3068 <listitem> <para> '<literal>?x</literal>' and '<literal>%x</literal>'
3069 are entirely distinct implicit parameters: you
3070 can use them together and they won't intefere with each other. </para>
3073 <listitem> <para> You can bind linear implicit parameters in 'with' clauses. </para> </listitem>
3075 <listitem> <para>You cannot have implicit parameters (whether linear or not)
3076 in the context of a class or instance declaration. </para></listitem>
3080 <sect3><title>Warnings</title>
3083 The monomorphism restriction is even more important than usual.
3084 Consider the example above:
3086 f :: (%ns :: NameSupply) => Env -> Expr -> Expr
3087 f env (Lam x e) = Lam x' (f env e)
3090 env' = extend env x x'
3092 If we replaced the two occurrences of x' by (newName %ns), which is
3093 usually a harmless thing to do, we get:
3095 f :: (%ns :: NameSupply) => Env -> Expr -> Expr
3096 f env (Lam x e) = Lam (newName %ns) (f env e)
3098 env' = extend env x (newName %ns)
3100 But now the name supply is consumed in <emphasis>three</emphasis> places
3101 (the two calls to newName,and the recursive call to f), so
3102 the result is utterly different. Urk! We don't even have
3106 Well, this is an experimental change. With implicit
3107 parameters we have already lost beta reduction anyway, and
3108 (as John Launchbury puts it) we can't sensibly reason about
3109 Haskell programs without knowing their typing.
3114 <sect3><title>Recursive functions</title>
3115 <para>Linear implicit parameters can be particularly tricky when you have a recursive function
3118 foo :: %x::T => Int -> [Int]
3120 foo n = %x : foo (n-1)
3122 where T is some type in class Splittable.</para>
3124 Do you get a list of all the same T's or all different T's
3125 (assuming that split gives two distinct T's back)?
3127 If you supply the type signature, taking advantage of polymorphic
3128 recursion, you get what you'd probably expect. Here's the
3129 translated term, where the implicit param is made explicit:
3132 foo x n = let (x1,x2) = split x
3133 in x1 : foo x2 (n-1)
3135 But if you don't supply a type signature, GHC uses the Hindley
3136 Milner trick of using a single monomorphic instance of the function
3137 for the recursive calls. That is what makes Hindley Milner type inference
3138 work. So the translation becomes
3142 foom n = x : foom (n-1)
3146 Result: 'x' is not split, and you get a list of identical T's. So the
3147 semantics of the program depends on whether or not foo has a type signature.
3150 You may say that this is a good reason to dislike linear implicit parameters
3151 and you'd be right. That is why they are an experimental feature.
3157 ================ END OF Linear Implicit Parameters commented out -->
3159 <sect2 id="sec-kinding
">
3160 <title>Explicitly-kinded quantification</title>
3163 Haskell infers the kind of each type variable. Sometimes it is nice to be able
3164 to give the kind explicitly as (machine-checked) documentation,
3165 just as it is nice to give a type signature for a function. On some occasions,
3166 it is essential to do so. For example, in his paper "Restricted Data Types in Haskell
" (Haskell Workshop 1999)
3167 John Hughes had to define the data type:
3169 data Set cxt a = Set [a]
3170 | Unused (cxt a -> ())
3172 The only use for the <literal>Unused</literal> constructor was to force the correct
3173 kind for the type variable <literal>cxt</literal>.
3176 GHC now instead allows you to specify the kind of a type variable directly, wherever
3177 a type variable is explicitly bound. Namely:
3179 <listitem><para><literal>data</literal> declarations:
3181 data Set (cxt :: * -> *) a = Set [a]
3182 </screen></para></listitem>
3183 <listitem><para><literal>type</literal> declarations:
3185 type T (f :: * -> *) = f Int
3186 </screen></para></listitem>
3187 <listitem><para><literal>class</literal> declarations:
3189 class (Eq a) => C (f :: * -> *) a where ...
3190 </screen></para></listitem>
3191 <listitem><para><literal>forall</literal>'s in type signatures:
3193 f :: forall (cxt :: * -> *). Set cxt Int
3194 </screen></para></listitem>
3199 The parentheses are required. Some of the spaces are required too, to
3200 separate the lexemes. If you write <literal>(f::*->*)</literal> you
3201 will get a parse error, because "<literal>::*-
>*
</literal>" is a
3202 single lexeme in Haskell.
3206 As part of the same extension, you can put kind annotations in types
3209 f :: (Int :: *) -> Int
3210 g :: forall a. a -> (a :: *)
3214 atype ::= '(' ctype '::' kind ')
3216 The parentheses are required.
3221 <sect2 id="universal-quantification
">
3222 <title>Arbitrary-rank polymorphism
3226 Haskell type signatures are implicitly quantified. The new keyword <literal>forall</literal>
3227 allows us to say exactly what this means. For example:
3235 g :: forall b. (b -> b)
3237 The two are treated identically.
3241 However, GHC's type system supports <emphasis>arbitrary-rank</emphasis>
3242 explicit universal quantification in
3244 For example, all the following types are legal:
3246 f1 :: forall a b. a -> b -> a
3247 g1 :: forall a b. (Ord a, Eq b) => a -> b -> a
3249 f2 :: (forall a. a->a) -> Int -> Int
3250 g2 :: (forall a. Eq a => [a] -> a -> Bool) -> Int -> Int
3252 f3 :: ((forall a. a->a) -> Int) -> Bool -> Bool
3254 Here, <literal>f1</literal> and <literal>g1</literal> are rank-1 types, and
3255 can be written in standard Haskell (e.g. <literal>f1 :: a->b->a</literal>).
3256 The <literal>forall</literal> makes explicit the universal quantification that
3257 is implicitly added by Haskell.
3260 The functions <literal>f2</literal> and <literal>g2</literal> have rank-2 types;
3261 the <literal>forall</literal> is on the left of a function arrow. As <literal>g2</literal>
3262 shows, the polymorphic type on the left of the function arrow can be overloaded.
3265 The function <literal>f3</literal> has a rank-3 type;
3266 it has rank-2 types on the left of a function arrow.
3269 GHC allows types of arbitrary rank; you can nest <literal>forall</literal>s
3270 arbitrarily deep in function arrows. (GHC used to be restricted to rank 2, but
3271 that restriction has now been lifted.)
3272 In particular, a forall-type (also called a "type scheme
"),
3273 including an operational type class context, is legal:
3275 <listitem> <para> On the left of a function arrow </para> </listitem>
3276 <listitem> <para> On the right of a function arrow (see <xref linkend="hoist
"/>) </para> </listitem>
3277 <listitem> <para> As the argument of a constructor, or type of a field, in a data type declaration. For
3278 example, any of the <literal>f1,f2,f3,g1,g2</literal> above would be valid
3279 field type signatures.</para> </listitem>
3280 <listitem> <para> As the type of an implicit parameter </para> </listitem>
3281 <listitem> <para> In a pattern type signature (see <xref linkend="scoped-type-variables
"/>) </para> </listitem>
3283 There is one place you cannot put a <literal>forall</literal>:
3284 you cannot instantiate a type variable with a forall-type. So you cannot
3285 make a forall-type the argument of a type constructor. So these types are illegal:
3287 x1 :: [forall a. a->a]
3288 x2 :: (forall a. a->a, Int)
3289 x3 :: Maybe (forall a. a->a)
3291 Of course <literal>forall</literal> becomes a keyword; you can't use <literal>forall</literal> as
3292 a type variable any more!
3301 In a <literal>data</literal> or <literal>newtype</literal> declaration one can quantify
3302 the types of the constructor arguments. Here are several examples:
3308 data T a = T1 (forall b. b -> b -> b) a
3310 data MonadT m = MkMonad { return :: forall a. a -> m a,
3311 bind :: forall a b. m a -> (a -> m b) -> m b
3314 newtype Swizzle = MkSwizzle (Ord a => [a] -> [a])
3320 The constructors have rank-2 types:
3326 T1 :: forall a. (forall b. b -> b -> b) -> a -> T a
3327 MkMonad :: forall m. (forall a. a -> m a)
3328 -> (forall a b. m a -> (a -> m b) -> m b)
3330 MkSwizzle :: (Ord a => [a] -> [a]) -> Swizzle
3336 Notice that you don't need to use a <literal>forall</literal> if there's an
3337 explicit context. For example in the first argument of the
3338 constructor <function>MkSwizzle</function>, an implicit "<literal>forall a.
</literal>" is
3339 prefixed to the argument type. The implicit <literal>forall</literal>
3340 quantifies all type variables that are not already in scope, and are
3341 mentioned in the type quantified over.
3345 As for type signatures, implicit quantification happens for non-overloaded
3346 types too. So if you write this:
3349 data T a = MkT (Either a b) (b -> b)
3352 it's just as if you had written this:
3355 data T a = MkT (forall b. Either a b) (forall b. b -> b)
3358 That is, since the type variable <literal>b</literal> isn't in scope, it's
3359 implicitly universally quantified. (Arguably, it would be better
3360 to <emphasis>require</emphasis> explicit quantification on constructor arguments
3361 where that is what is wanted. Feedback welcomed.)
3365 You construct values of types <literal>T1, MonadT, Swizzle</literal> by applying
3366 the constructor to suitable values, just as usual. For example,
3377 a3 = MkSwizzle reverse
3380 a4 = let r x = Just x
3387 mkTs :: (forall b. b -> b -> b) -> a -> [T a]
3388 mkTs f x y = [T1 f x, T1 f y]
3394 The type of the argument can, as usual, be more general than the type
3395 required, as <literal>(MkSwizzle reverse)</literal> shows. (<function>reverse</function>
3396 does not need the <literal>Ord</literal> constraint.)
3400 When you use pattern matching, the bound variables may now have
3401 polymorphic types. For example:
3407 f :: T a -> a -> (a, Char)
3408 f (T1 w k) x = (w k x, w 'c' 'd')
3410 g :: (Ord a, Ord b) => Swizzle -> [a] -> (a -> b) -> [b]
3411 g (MkSwizzle s) xs f = s (map f (s xs))
3413 h :: MonadT m -> [m a] -> m [a]
3414 h m [] = return m []
3415 h m (x:xs) = bind m x $ \y ->
3416 bind m (h m xs) $ \ys ->
3423 In the function <function>h</function> we use the record selectors <literal>return</literal>
3424 and <literal>bind</literal> to extract the polymorphic bind and return functions
3425 from the <literal>MonadT</literal> data structure, rather than using pattern
3431 <title>Type inference</title>
3434 In general, type inference for arbitrary-rank types is undecidable.
3435 GHC uses an algorithm proposed by Odersky and Laufer ("Putting type annotations to work
", POPL'96)
3436 to get a decidable algorithm by requiring some help from the programmer.
3437 We do not yet have a formal specification of "some help
" but the rule is this:
3440 <emphasis>For a lambda-bound or case-bound variable, x, either the programmer
3441 provides an explicit polymorphic type for x, or GHC's type inference will assume
3442 that x's type has no foralls in it</emphasis>.
3445 What does it mean to "provide
" an explicit type for x? You can do that by
3446 giving a type signature for x directly, using a pattern type signature
3447 (<xref linkend="scoped-type-variables
"/>), thus:
3449 \ f :: (forall a. a->a) -> (f True, f 'c')
3451 Alternatively, you can give a type signature to the enclosing
3452 context, which GHC can "push down
" to find the type for the variable:
3454 (\ f -> (f True, f 'c')) :: (forall a. a->a) -> (Bool,Char)
3456 Here the type signature on the expression can be pushed inwards
3457 to give a type signature for f. Similarly, and more commonly,
3458 one can give a type signature for the function itself:
3460 h :: (forall a. a->a) -> (Bool,Char)
3461 h f = (f True, f 'c')
3463 You don't need to give a type signature if the lambda bound variable
3464 is a constructor argument. Here is an example we saw earlier:
3466 f :: T a -> a -> (a, Char)
3467 f (T1 w k) x = (w k x, w 'c' 'd')
3469 Here we do not need to give a type signature to <literal>w</literal>, because
3470 it is an argument of constructor <literal>T1</literal> and that tells GHC all
3477 <sect3 id="implicit-quant
">
3478 <title>Implicit quantification</title>
3481 GHC performs implicit quantification as follows. <emphasis>At the top level (only) of
3482 user-written types, if and only if there is no explicit <literal>forall</literal>,
3483 GHC finds all the type variables mentioned in the type that are not already
3484 in scope, and universally quantifies them.</emphasis> For example, the following pairs are
3488 f :: forall a. a -> a
3495 h :: forall b. a -> b -> b
3501 Notice that GHC does <emphasis>not</emphasis> find the innermost possible quantification
3504 f :: (a -> a) -> Int
3506 f :: forall a. (a -> a) -> Int
3508 f :: (forall a. a -> a) -> Int
3511 g :: (Ord a => a -> a) -> Int
3512 -- MEANS the illegal type
3513 g :: forall a. (Ord a => a -> a) -> Int
3515 g :: (forall a. Ord a => a -> a) -> Int
3517 The latter produces an illegal type, which you might think is silly,
3518 but at least the rule is simple. If you want the latter type, you
3519 can write your for-alls explicitly. Indeed, doing so is strongly advised
3526 <sect2 id="impredicative-polymorphism
">
3527 <title>Impredicative polymorphism
3529 <para>GHC supports <emphasis>impredicative polymorphism</emphasis>. This means
3530 that you can call a polymorphic function at a polymorphic type, and
3531 parameterise data structures over polymorphic types. For example:
3533 f :: Maybe (forall a. [a] -> [a]) -> Maybe ([Int], [Char])
3534 f (Just g) = Just (g [3], g "hello
")
3537 Notice here that the <literal>Maybe</literal> type is parameterised by the
3538 <emphasis>polymorphic</emphasis> type <literal>(forall a. [a] ->
3541 <para>The technical details of this extension are described in the paper
3542 <ulink url="http://research.microsoft.com/%
7Esimonpj/papers/boxy
">Boxy types:
3543 type inference for higher-rank types and impredicativity</ulink>,
3544 which appeared at ICFP 2006.
3548 <sect2 id="scoped-type-variables
">
3549 <title>Lexically scoped type variables
3553 GHC supports <emphasis>lexically scoped type variables</emphasis>, without
3554 which some type signatures are simply impossible to write. For example:
3556 f :: forall a. [a] -> [a]
3562 The type signature for <literal>f</literal> brings the type variable <literal>a</literal> into scope; it scopes over
3563 the entire definition of <literal>f</literal>.
3564 In particular, it is in scope at the type signature for <varname>ys</varname>.
3565 In Haskell 98 it is not possible to declare
3566 a type for <varname>ys</varname>; a major benefit of scoped type variables is that
3567 it becomes possible to do so.
3569 <para>Lexically-scoped type variables are enabled by
3570 <option>-fglasgow-exts</option>.
3572 <para>Note: GHC 6.6 contains substantial changes to the way that scoped type
3573 variables work, compared to earlier releases. Read this section
3577 <title>Overview</title>
3579 <para>The design follows the following principles
3581 <listitem><para>A scoped type variable stands for a type <emphasis>variable</emphasis>, and not for
3582 a <emphasis>type</emphasis>. (This is a change from GHC's earlier
3583 design.)</para></listitem>
3584 <listitem><para>Furthermore, distinct lexical type variables stand for distinct
3585 type variables. This means that every programmer-written type signature
3586 (includin one that contains free scoped type variables) denotes a
3587 <emphasis>rigid</emphasis> type; that is, the type is fully known to the type
3588 checker, and no inference is involved.</para></listitem>
3589 <listitem><para>Lexical type variables may be alpha-renamed freely, without
3590 changing the program.</para></listitem>
3594 A <emphasis>lexically scoped type variable</emphasis> can be bound by:
3596 <listitem><para>A declaration type signature (<xref linkend="decl-type-sigs
"/>)</para></listitem>
3597 <listitem><para>An expression type signature (<xref linkend="exp-type-sigs
"/>)</para></listitem>
3598 <listitem><para>A pattern type signature (<xref linkend="pattern-type-sigs
"/>)</para></listitem>
3599 <listitem><para>Class and instance declarations (<xref linkend="cls-inst-scoped-tyvars
"/>)</para></listitem>
3603 In Haskell, a programmer-written type signature is implicitly quantifed over
3604 its free type variables (<ulink
3605 url="http://haskell.org/onlinereport/decls.html#sect4.1
.2">Section
3607 of the Haskel Report).
3608 Lexically scoped type variables affect this implicit quantification rules
3609 as follows: any type variable that is in scope is <emphasis>not</emphasis> universally
3610 quantified. For example, if type variable <literal>a</literal> is in scope,
3613 (e :: a -> a) means (e :: a -> a)
3614 (e :: b -> b) means (e :: forall b. b->b)
3615 (e :: a -> b) means (e :: forall b. a->b)
3623 <sect3 id="decl-type-sigs
">
3624 <title>Declaration type signatures</title>
3625 <para>A declaration type signature that has <emphasis>explicit</emphasis>
3626 quantification (using <literal>forall</literal>) brings into scope the
3627 explicitly-quantified
3628 type variables, in the definition of the named function(s). For example:
3630 f :: forall a. [a] -> [a]
3631 f (x:xs) = xs ++ [ x :: a ]
3633 The "<literal>forall a
</literal>" brings "<literal>a
</literal>" into scope in
3634 the definition of "<literal>f
</literal>".
3636 <para>This only happens if the quantification in <literal>f</literal>'s type
3637 signature is explicit. For example:
3640 g (x:xs) = xs ++ [ x :: a ]
3642 This program will be rejected, because "<literal>a
</literal>" does not scope
3643 over the definition of "<literal>f
</literal>", so "<literal>x::a
</literal>"
3644 means "<literal>x::forall a. a
</literal>" by Haskell's usual implicit
3645 quantification rules.
3649 <sect3 id="exp-type-sigs
">
3650 <title>Expression type signatures</title>
3652 <para>An expression type signature that has <emphasis>explicit</emphasis>
3653 quantification (using <literal>forall</literal>) brings into scope the
3654 explicitly-quantified
3655 type variables, in the annotated expression. For example:
3657 f = runST ( (op >>= \(x :: STRef s Int) -> g x) :: forall s. ST s Bool )
3659 Here, the type signature <literal>forall a. ST s Bool</literal> brings the
3660 type variable <literal>s</literal> into scope, in the annotated expression
3661 <literal>(op >>= \(x :: STRef s Int) -> g x)</literal>.
3666 <sect3 id="pattern-type-sigs
">
3667 <title>Pattern type signatures</title>
3669 A type signature may occur in any pattern; this is a <emphasis>pattern type
3670 signature</emphasis>.
3673 -- f and g assume that 'a' is already in scope
3674 f = \(x::Int, y::a) -> x
3676 h ((x,y) :: (Int,Bool)) = (y,x)
3678 In the case where all the type variables in the pattern type sigature are
3679 already in scope (i.e. bound by the enclosing context), matters are simple: the
3680 signature simply constrains the type of the pattern in the obvious way.
3683 There is only one situation in which you can write a pattern type signature that
3684 mentions a type variable that is not already in scope, namely in pattern match
3685 of an existential data constructor. For example:
3687 data T = forall a. MkT [a]
3690 k (MkT [t::a]) = MkT t3
3694 Here, the pattern type signature <literal>(t::a)</literal> mentions a lexical type
3695 variable that is not already in scope. Indeed, it cannot already be in scope,
3696 because it is bound by the pattern match. GHC's rule is that in this situation
3697 (and only then), a pattern type signature can mention a type variable that is
3698 not already in scope; the effect is to bring it into scope, standing for the
3699 existentially-bound type variable.
3702 If this seems a little odd, we think so too. But we must have
3703 <emphasis>some</emphasis> way to bring such type variables into scope, else we
3704 could not name existentially-bound type variables in subequent type signatures.
3707 This is (now) the <emphasis>only</emphasis> situation in which a pattern type
3708 signature is allowed to mention a lexical variable that is not already in
3710 For example, both <literal>f</literal> and <literal>g</literal> would be
3711 illegal if <literal>a</literal> was not already in scope.
3717 <!-- ==================== Commented out part about result type signatures
3719 <sect3 id="result-type-sigs
">
3720 <title>Result type signatures</title>
3723 The result type of a function, lambda, or case expression alternative can be given a signature, thus:
3726 {- f assumes that 'a' is already in scope -}
3727 f x y :: [a] = [x,y,x]
3729 g = \ x :: [Int] -> [3,4]
3731 h :: forall a. [a] -> a
3735 The final <literal>:: [a]</literal> after the patterns of <literal>f</literal> gives the type of
3736 the result of the function. Similarly, the body of the lambda in the RHS of
3737 <literal>g</literal> is <literal>[Int]</literal>, and the RHS of the case
3738 alternative in <literal>h</literal> is <literal>a</literal>.
3740 <para> A result type signature never brings new type variables into scope.</para>
3742 There are a couple of syntactic wrinkles. First, notice that all three
3743 examples would parse quite differently with parentheses:
3745 {- f assumes that 'a' is already in scope -}
3746 f x (y :: [a]) = [x,y,x]
3748 g = \ (x :: [Int]) -> [3,4]
3750 h :: forall a. [a] -> a
3754 Now the signature is on the <emphasis>pattern</emphasis>; and
3755 <literal>h</literal> would certainly be ill-typed (since the pattern
3756 <literal>(y:ys)</literal> cannot have the type <literal>a</literal>.
3758 Second, to avoid ambiguity, the type after the “<literal>::</literal>” in a result
3759 pattern signature on a lambda or <literal>case</literal> must be atomic (i.e. a single
3760 token or a parenthesised type of some sort). To see why,
3761 consider how one would parse this:
3770 <sect3 id="cls-inst-scoped-tyvars
">
3771 <title>Class and instance declarations</title>
3774 The type variables in the head of a <literal>class</literal> or <literal>instance</literal> declaration
3775 scope over the methods defined in the <literal>where</literal> part. For example:
3792 <sect2 id="deriving-typeable
">
3793 <title>Deriving clause for classes <literal>Typeable</literal> and <literal>Data</literal></title>
3796 Haskell 98 allows the programmer to add "<literal>deriving( Eq, Ord )
</literal>" to a data type
3797 declaration, to generate a standard instance declaration for classes specified in the <literal>deriving</literal> clause.
3798 In Haskell 98, the only classes that may appear in the <literal>deriving</literal> clause are the standard
3799 classes <literal>Eq</literal>, <literal>Ord</literal>,
3800 <literal>Enum</literal>, <literal>Ix</literal>, <literal>Bounded</literal>, <literal>Read</literal>, and <literal>Show</literal>.
3803 GHC extends this list with two more classes that may be automatically derived
3804 (provided the <option>-fglasgow-exts</option> flag is specified):
3805 <literal>Typeable</literal>, and <literal>Data</literal>. These classes are defined in the library
3806 modules <literal>Data.Typeable</literal> and <literal>Data.Generics</literal> respectively, and the
3807 appropriate class must be in scope before it can be mentioned in the <literal>deriving</literal> clause.
3809 <para>An instance of <literal>Typeable</literal> can only be derived if the
3810 data type has seven or fewer type parameters, all of kind <literal>*</literal>.
3811 The reason for this is that the <literal>Typeable</literal> class is derived using the scheme
3813 <ulink url="http://research.microsoft.com/%
7Esimonpj/papers/hmap/gmap2.ps
">
3814 Scrap More Boilerplate: Reflection, Zips, and Generalised Casts
3816 (Section 7.4 of the paper describes the multiple <literal>Typeable</literal> classes that
3817 are used, and only <literal>Typeable1</literal> up to
3818 <literal>Typeable7</literal> are provided in the library.)
3819 In other cases, there is nothing to stop the programmer writing a <literal>TypableX</literal>
3820 class, whose kind suits that of the data type constructor, and
3821 then writing the data type instance by hand.
3825 <sect2 id="newtype-deriving
">
3826 <title>Generalised derived instances for newtypes</title>
3829 When you define an abstract type using <literal>newtype</literal>, you may want
3830 the new type to inherit some instances from its representation. In
3831 Haskell 98, you can inherit instances of <literal>Eq</literal>, <literal>Ord</literal>,
3832 <literal>Enum</literal> and <literal>Bounded</literal> by deriving them, but for any
3833 other classes you have to write an explicit instance declaration. For
3834 example, if you define
3837 newtype Dollars = Dollars Int
3840 and you want to use arithmetic on <literal>Dollars</literal>, you have to
3841 explicitly define an instance of <literal>Num</literal>:
3844 instance Num Dollars where
3845 Dollars a + Dollars b = Dollars (a+b)
3848 All the instance does is apply and remove the <literal>newtype</literal>
3849 constructor. It is particularly galling that, since the constructor
3850 doesn't appear at run-time, this instance declaration defines a
3851 dictionary which is <emphasis>wholly equivalent</emphasis> to the <literal>Int</literal>
3852 dictionary, only slower!
3856 <sect3> <title> Generalising the deriving clause </title>
3858 GHC now permits such instances to be derived instead, so one can write
3860 newtype Dollars = Dollars Int deriving (Eq,Show,Num)
3863 and the implementation uses the <emphasis>same</emphasis> <literal>Num</literal> dictionary
3864 for <literal>Dollars</literal> as for <literal>Int</literal>. Notionally, the compiler
3865 derives an instance declaration of the form
3868 instance Num Int => Num Dollars
3871 which just adds or removes the <literal>newtype</literal> constructor according to the type.
3875 We can also derive instances of constructor classes in a similar
3876 way. For example, suppose we have implemented state and failure monad
3877 transformers, such that
3880 instance Monad m => Monad (State s m)
3881 instance Monad m => Monad (Failure m)
3883 In Haskell 98, we can define a parsing monad by
3885 type Parser tok m a = State [tok] (Failure m) a
3888 which is automatically a monad thanks to the instance declarations
3889 above. With the extension, we can make the parser type abstract,
3890 without needing to write an instance of class <literal>Monad</literal>, via
3893 newtype Parser tok m a = Parser (State [tok] (Failure m) a)
3896 In this case the derived instance declaration is of the form
3898 instance Monad (State [tok] (Failure m)) => Monad (Parser tok m)
3901 Notice that, since <literal>Monad</literal> is a constructor class, the
3902 instance is a <emphasis>partial application</emphasis> of the new type, not the
3903 entire left hand side. We can imagine that the type declaration is
3904 ``eta-converted'' to generate the context of the instance
3909 We can even derive instances of multi-parameter classes, provided the
3910 newtype is the last class parameter. In this case, a ``partial
3911 application'' of the class appears in the <literal>deriving</literal>
3912 clause. For example, given the class
3915 class StateMonad s m | m -> s where ...
3916 instance Monad m => StateMonad s (State s m) where ...
3918 then we can derive an instance of <literal>StateMonad</literal> for <literal>Parser</literal>s by
3920 newtype Parser tok m a = Parser (State [tok] (Failure m) a)
3921 deriving (Monad, StateMonad [tok])
3924 The derived instance is obtained by completing the application of the
3925 class to the new type:
3928 instance StateMonad [tok] (State [tok] (Failure m)) =>
3929 StateMonad [tok] (Parser tok m)
3934 As a result of this extension, all derived instances in newtype
3935 declarations are treated uniformly (and implemented just by reusing
3936 the dictionary for the representation type), <emphasis>except</emphasis>
3937 <literal>Show</literal> and <literal>Read</literal>, which really behave differently for
3938 the newtype and its representation.
3942 <sect3> <title> A more precise specification </title>
3944 Derived instance declarations are constructed as follows. Consider the
3945 declaration (after expansion of any type synonyms)
3948 newtype T v1...vn = T' (t vk+1...vn) deriving (c1...cm)
3954 The <literal>ci</literal> are partial applications of
3955 classes of the form <literal>C t1'...tj'</literal>, where the arity of <literal>C</literal>
3956 is exactly <literal>j+1</literal>. That is, <literal>C</literal> lacks exactly one type argument.
3959 The <literal>k</literal> is chosen so that <literal>ci (T v1...vk)</literal> is well-kinded.
3962 The type <literal>t</literal> is an arbitrary type.
3965 The type variables <literal>vk+1...vn</literal> do not occur in <literal>t</literal>,
3966 nor in the <literal>ci</literal>, and
3969 None of the <literal>ci</literal> is <literal>Read</literal>, <literal>Show</literal>,
3970 <literal>Typeable</literal>, or <literal>Data</literal>. These classes
3971 should not "look through
" the type or its constructor. You can still
3972 derive these classes for a newtype, but it happens in the usual way, not
3973 via this new mechanism.
3976 Then, for each <literal>ci</literal>, the derived instance
3979 instance ci t => ci (T v1...vk)
3981 As an example which does <emphasis>not</emphasis> work, consider
3983 newtype NonMonad m s = NonMonad (State s m s) deriving Monad
3985 Here we cannot derive the instance
3987 instance Monad (State s m) => Monad (NonMonad m)
3990 because the type variable <literal>s</literal> occurs in <literal>State s m</literal>,
3991 and so cannot be "eta-converted
" away. It is a good thing that this
3992 <literal>deriving</literal> clause is rejected, because <literal>NonMonad m</literal> is
3993 not, in fact, a monad --- for the same reason. Try defining
3994 <literal>>>=</literal> with the correct type: you won't be able to.
3998 Notice also that the <emphasis>order</emphasis> of class parameters becomes
3999 important, since we can only derive instances for the last one. If the
4000 <literal>StateMonad</literal> class above were instead defined as
4003 class StateMonad m s | m -> s where ...
4006 then we would not have been able to derive an instance for the
4007 <literal>Parser</literal> type above. We hypothesise that multi-parameter
4008 classes usually have one "main
" parameter for which deriving new
4009 instances is most interesting.
4011 <para>Lastly, all of this applies only for classes other than
4012 <literal>Read</literal>, <literal>Show</literal>, <literal>Typeable</literal>,
4013 and <literal>Data</literal>, for which the built-in derivation applies (section
4014 4.3.3. of the Haskell Report).
4015 (For the standard classes <literal>Eq</literal>, <literal>Ord</literal>,
4016 <literal>Ix</literal>, and <literal>Bounded</literal> it is immaterial whether
4017 the standard method is used or the one described here.)
4023 <sect2 id="stand-alone-deriving
">
4024 <title>Stand-alone deriving declarations</title>
4027 GHC now allows stand-alone <literal>deriving</literal> declarations:
4031 data Foo = Bar Int | Baz String
4036 <para>Deriving instances of multi-parameter type classes for newtypes is
4037 also allowed:</para>
4040 newtype Foo a = MkFoo (State Int a)
4042 deriving (MonadState Int) for Foo
4050 <sect2 id="typing-binds
">
4051 <title>Generalised typing of mutually recursive bindings</title>
4054 The Haskell Report specifies that a group of bindings (at top level, or in a
4055 <literal>let</literal> or <literal>where</literal>) should be sorted into
4056 strongly-connected components, and then type-checked in dependency order
4057 (<ulink url="http://haskell.org/onlinereport/decls.html#sect4.5
.1">Haskell
4058 Report, Section 4.5.1</ulink>).
4059 As each group is type-checked, any binders of the group that
4061 an explicit type signature are put in the type environment with the specified
4063 and all others are monomorphic until the group is generalised
4064 (<ulink url="http://haskell.org/onlinereport/decls.html#sect4.5
.2">Haskell Report, Section 4.5.2</ulink>).
4067 <para>Following a suggestion of Mark Jones, in his paper
4068 <ulink url="http://www.cse.ogi.edu/~mpj/thih/
">Typing Haskell in
4070 GHC implements a more general scheme. If <option>-fglasgow-exts</option> is
4072 <emphasis>the dependency analysis ignores references to variables that have an explicit
4073 type signature</emphasis>.
4074 As a result of this refined dependency analysis, the dependency groups are smaller, and more bindings will
4075 typecheck. For example, consider:
4077 f :: Eq a => a -> Bool
4078 f x = (x == x) || g True || g "Yes
"
4080 g y = (y <= y) || f True
4082 This is rejected by Haskell 98, but under Jones's scheme the definition for
4083 <literal>g</literal> is typechecked first, separately from that for
4084 <literal>f</literal>,
4085 because the reference to <literal>f</literal> in <literal>g</literal>'s right
4086 hand side is ingored by the dependency analysis. Then <literal>g</literal>'s
4087 type is generalised, to get
4089 g :: Ord a => a -> Bool
4091 Now, the defintion for <literal>f</literal> is typechecked, with this type for
4092 <literal>g</literal> in the type environment.
4096 The same refined dependency analysis also allows the type signatures of
4097 mutually-recursive functions to have different contexts, something that is illegal in
4098 Haskell 98 (Section 4.5.2, last sentence). With
4099 <option>-fglasgow-exts</option>
4100 GHC only insists that the type signatures of a <emphasis>refined</emphasis> group have identical
4101 type signatures; in practice this means that only variables bound by the same
4102 pattern binding must have the same context. For example, this is fine:
4104 f :: Eq a => a -> Bool
4105 f x = (x == x) || g True
4107 g :: Ord a => a -> Bool
4108 g y = (y <= y) || f True
4114 <!-- ==================== End of type system extensions ================= -->
4116 <!-- ====================== TEMPLATE HASKELL ======================= -->
4118 <sect1 id="template-haskell
">
4119 <title>Template Haskell</title>
4121 <para>Template Haskell allows you to do compile-time meta-programming in
4124 the main technical innovations is discussed in "<ulink
4125 url=
"http://research.microsoft.com/~simonpj/papers/meta-haskell">
4126 Template Meta-programming for Haskell
</ulink>" (Proc Haskell Workshop 2002).
4129 There is a Wiki page about
4130 Template Haskell at <ulink url="http://haskell.org/haskellwiki/Template_Haskell
">
4131 http://www.haskell.org/th/</ulink>, and that is the best place to look for
4135 url="http://www.haskell.org/ghc/docs/latest/html/libraries/index.html
">online
4136 Haskell library reference material</ulink>
4137 (search for the type ExpQ).
4138 [Temporary: many changes to the original design are described in
4139 <ulink url="http://research.microsoft.com/~simonpj/tmp/notes2.ps
">"http://research.microsoft.com/~simonpj/tmp/notes2.ps
"</ulink>.