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 can all be enabled or disabled by commandline flags
7 or language pragmas. By default GHC understands the most recent Haskell
8 version it supports, plus a handful of extensions.
12 Some of the Glasgow extensions serve to give you access to the
13 underlying facilities with which we implement Haskell. Thus, you can
14 get at the Raw Iron, if you are willing to write some non-portable
15 code at a more primitive level. You need not be
“stuck
”
16 on performance because of the implementation costs of Haskell's
17 “high-level
” features
—you can always code
18 “under
” them. In an extreme case, you can write all your
19 time-critical code in C, and then just glue it together with Haskell!
23 Before you get too carried away working at the lowest level (e.g.,
24 sloshing
<literal>MutableByteArray
#</literal>s around your
25 program), you may wish to check if there are libraries that provide a
26 “Haskellised veneer
” over the features you want. The
27 separate
<ulink url=
"../libraries/index.html">libraries
28 documentation
</ulink> describes all the libraries that come with GHC.
31 <!-- LANGUAGE OPTIONS -->
32 <sect1 id=
"options-language">
33 <title>Language options
</title>
35 <indexterm><primary>language
</primary><secondary>option
</secondary>
37 <indexterm><primary>options
</primary><secondary>language
</secondary>
39 <indexterm><primary>extensions
</primary><secondary>options controlling
</secondary>
42 <para>The language option flags control what variation of the language are
45 <para>Language options can be controlled in two ways:
47 <listitem><para>Every language option can switched on by a command-line flag
"<option>-X...</option>"
48 (e.g.
<option>-XTemplateHaskell
</option>), and switched off by the flag
"<option>-XNo...</option>";
49 (e.g.
<option>-XNoTemplateHaskell
</option>).
</para></listitem>
51 Language options recognised by Cabal can also be enabled using the
<literal>LANGUAGE
</literal> pragma,
52 thus
<literal>{-# LANGUAGE TemplateHaskell #-}
</literal> (see
<xref linkend=
"language-pragma"/>).
</para>
54 </itemizedlist></para>
56 <para>The flag
<option>-fglasgow-exts
</option>
57 <indexterm><primary><option>-fglasgow-exts
</option></primary></indexterm>
58 is equivalent to enabling the following extensions:
59 &what_glasgow_exts_does;
60 Enabling these options is the
<emphasis>only
</emphasis>
61 effect of
<option>-fglasgow-exts
</option>.
62 We are trying to move away from this portmanteau flag,
63 and towards enabling features individually.
</para>
67 <!-- UNBOXED TYPES AND PRIMITIVE OPERATIONS -->
68 <sect1 id=
"primitives">
69 <title>Unboxed types and primitive operations
</title>
71 <para>GHC is built on a raft of primitive data types and operations;
72 "primitive" in the sense that they cannot be defined in Haskell itself.
73 While you really can use this stuff to write fast code,
74 we generally find it a lot less painful, and more satisfying in the
75 long run, to use higher-level language features and libraries. With
76 any luck, the code you write will be optimised to the efficient
77 unboxed version in any case. And if it isn't, we'd like to know
80 <para>All these primitive data types and operations are exported by the
81 library
<literal>GHC.Prim
</literal>, for which there is
82 <ulink url=
"&libraryGhcPrimLocation;/GHC-Prim.html">detailed online documentation
</ulink>.
83 (This documentation is generated from the file
<filename>compiler/prelude/primops.txt.pp
</filename>.)
87 If you want to mention any of the primitive data types or operations in your
88 program, you must first import
<literal>GHC.Prim
</literal> to bring them
89 into scope. Many of them have names ending in
"#", and to mention such
90 names you need the
<option>-XMagicHash
</option> extension (
<xref linkend=
"magic-hash"/>).
93 <para>The primops make extensive use of
<link linkend=
"glasgow-unboxed">unboxed types
</link>
94 and
<link linkend=
"unboxed-tuples">unboxed tuples
</link>, which
95 we briefly summarise here.
</para>
97 <sect2 id=
"glasgow-unboxed">
98 <title>Unboxed types
</title>
101 <indexterm><primary>Unboxed types (Glasgow extension)
</primary></indexterm>
104 <para>Most types in GHC are
<firstterm>boxed
</firstterm>, which means
105 that values of that type are represented by a pointer to a heap
106 object. The representation of a Haskell
<literal>Int
</literal>, for
107 example, is a two-word heap object. An
<firstterm>unboxed
</firstterm>
108 type, however, is represented by the value itself, no pointers or heap
109 allocation are involved.
113 Unboxed types correspond to the
“raw machine
” types you
114 would use in C:
<literal>Int
#</literal> (long int),
115 <literal>Double
#</literal> (double),
<literal>Addr
#</literal>
116 (void *), etc. The
<emphasis>primitive operations
</emphasis>
117 (PrimOps) on these types are what you might expect; e.g.,
118 <literal>(+
#)
</literal> is addition on
119 <literal>Int
#</literal>s, and is the machine-addition that we all
120 know and love
—usually one instruction.
124 Primitive (unboxed) types cannot be defined in Haskell, and are
125 therefore built into the language and compiler. Primitive types are
126 always unlifted; that is, a value of a primitive type cannot be
127 bottom. We use the convention (but it is only a convention)
128 that primitive types, values, and
129 operations have a
<literal>#</literal> suffix (see
<xref linkend=
"magic-hash"/>).
130 For some primitive types we have special syntax for literals, also
131 described in the
<link linkend=
"magic-hash">same section
</link>.
135 Primitive values are often represented by a simple bit-pattern, such
136 as
<literal>Int
#</literal>,
<literal>Float
#</literal>,
137 <literal>Double
#</literal>. But this is not necessarily the case:
138 a primitive value might be represented by a pointer to a
139 heap-allocated object. Examples include
140 <literal>Array
#</literal>, the type of primitive arrays. A
141 primitive array is heap-allocated because it is too big a value to fit
142 in a register, and would be too expensive to copy around; in a sense,
143 it is accidental that it is represented by a pointer. If a pointer
144 represents a primitive value, then it really does point to that value:
145 no unevaluated thunks, no indirections
…nothing can be at the
146 other end of the pointer than the primitive value.
147 A numerically-intensive program using unboxed types can
148 go a
<emphasis>lot
</emphasis> faster than its
“standard
”
149 counterpart
—we saw a threefold speedup on one example.
153 There are some restrictions on the use of primitive types:
155 <listitem><para>The main restriction
156 is that you can't pass a primitive value to a polymorphic
157 function or store one in a polymorphic data type. This rules out
158 things like
<literal>[Int
#]
</literal> (i.e. lists of primitive
159 integers). The reason for this restriction is that polymorphic
160 arguments and constructor fields are assumed to be pointers: if an
161 unboxed integer is stored in one of these, the garbage collector would
162 attempt to follow it, leading to unpredictable space leaks. Or a
163 <function>seq
</function> operation on the polymorphic component may
164 attempt to dereference the pointer, with disastrous results. Even
165 worse, the unboxed value might be larger than a pointer
166 (
<literal>Double
#</literal> for instance).
169 <listitem><para> You cannot define a newtype whose representation type
170 (the argument type of the data constructor) is an unboxed type. Thus,
176 <listitem><para> You cannot bind a variable with an unboxed type
177 in a
<emphasis>top-level
</emphasis> binding.
179 <listitem><para> You cannot bind a variable with an unboxed type
180 in a
<emphasis>recursive
</emphasis> binding.
182 <listitem><para> You may bind unboxed variables in a (non-recursive,
183 non-top-level) pattern binding, but you must make any such pattern-match
184 strict. For example, rather than:
186 data Foo = Foo Int Int#
188 f x = let (Foo a b, w) = ..rhs.. in ..body..
192 data Foo = Foo Int Int#
194 f x = let !(Foo a b, w) = ..rhs.. in ..body..
196 since
<literal>b
</literal> has type
<literal>Int#
</literal>.
204 <sect2 id=
"unboxed-tuples">
205 <title>Unboxed tuples
</title>
208 Unboxed tuples aren't really exported by
<literal>GHC.Exts
</literal>;
209 they are a syntactic extension enabled by the language flag
<option>-XUnboxedTuples
</option>. An
210 unboxed tuple looks like this:
222 where
<literal>e
_1..e
_n
</literal> are expressions of any
223 type (primitive or non-primitive). The type of an unboxed tuple looks
228 Note that when unboxed tuples are enabled,
229 <literal>(#
</literal> is a single lexeme, so for example when using
230 operators like
<literal>#
</literal> and
<literal>#-
</literal> you need
231 to write
<literal>( # )
</literal> and
<literal>( #- )
</literal> rather than
232 <literal>(#)
</literal> and
<literal>(#-)
</literal>.
236 Unboxed tuples are used for functions that need to return multiple
237 values, but they avoid the heap allocation normally associated with
238 using fully-fledged tuples. When an unboxed tuple is returned, the
239 components are put directly into registers or on the stack; the
240 unboxed tuple itself does not have a composite representation. Many
241 of the primitive operations listed in
<literal>primops.txt.pp
</literal> return unboxed
243 In particular, the
<literal>IO
</literal> and
<literal>ST
</literal> monads use unboxed
244 tuples to avoid unnecessary allocation during sequences of operations.
248 There are some restrictions on the use of unboxed tuples:
253 Values of unboxed tuple types are subject to the same restrictions as
254 other unboxed types; i.e. they may not be stored in polymorphic data
255 structures or passed to polymorphic functions.
261 The typical use of unboxed tuples is simply to return multiple values,
262 binding those multiple results with a
<literal>case
</literal> expression, thus:
264 f x y = (# x+
1, y-
1 #)
265 g x = case f x x of { (# a, b #) -
> a + b }
267 You can have an unboxed tuple in a pattern binding, thus
269 f x = let (# p,q #) = h x in ..body..
271 If the types of
<literal>p
</literal> and
<literal>q
</literal> are not unboxed,
272 the resulting binding is lazy like any other Haskell pattern binding. The
273 above example desugars like this:
275 f x = let t = case h x of { (# p,q #) -
> (p,q) }
280 Indeed, the bindings can even be recursive.
291 <!-- ====================== SYNTACTIC EXTENSIONS ======================= -->
293 <sect1 id=
"syntax-extns">
294 <title>Syntactic extensions
</title>
296 <sect2 id=
"unicode-syntax">
297 <title>Unicode syntax
</title>
299 extension
<option>-XUnicodeSyntax
</option><indexterm><primary><option>-XUnicodeSyntax
</option></primary></indexterm>
300 enables Unicode characters to be used to stand for certain ASCII
301 character sequences. The following alternatives are provided:
</para>
304 <tgroup cols=
"2" align=
"left" colsep=
"1" rowsep=
"1">
308 <entry>Unicode alternative
</entry>
309 <entry>Code point
</entry>
315 to find the DocBook entities for these characters, find
316 the Unicode code point (e.g. 0x2237), and grep for it in
317 /usr/share/sgml/docbook/xml-dtd-*/ent/* (or equivalent on
318 your system. Some of these Unicode code points don't have
319 equivalent DocBook entities.
324 <entry><literal>::
</literal></entry>
325 <entry>::
</entry> <!-- no special char, apparently -->
326 <entry>0x2237</entry>
327 <entry>PROPORTION
</entry>
332 <entry><literal>=
></literal></entry>
333 <entry>⇒</entry>
334 <entry>0x21D2</entry>
335 <entry>RIGHTWARDS DOUBLE ARROW
</entry>
340 <entry><literal>forall
</literal></entry>
341 <entry>∀</entry>
342 <entry>0x2200</entry>
343 <entry>FOR ALL
</entry>
348 <entry><literal>-
></literal></entry>
349 <entry>→</entry>
350 <entry>0x2192</entry>
351 <entry>RIGHTWARDS ARROW
</entry>
356 <entry><literal><-
</literal></entry>
357 <entry>←</entry>
358 <entry>0x2190</entry>
359 <entry>LEFTWARDS ARROW
</entry>
366 <entry>↢</entry>
367 <entry>0x2919</entry>
368 <entry>LEFTWARDS ARROW-TAIL
</entry>
375 <entry>↣</entry>
376 <entry>0x291A</entry>
377 <entry>RIGHTWARDS ARROW-TAIL
</entry>
383 <entry>-
<<</entry>
385 <entry>0x291B</entry>
386 <entry>LEFTWARDS DOUBLE ARROW-TAIL
</entry>
392 <entry>>>-
</entry>
394 <entry>0x291C</entry>
395 <entry>RIGHTWARDS DOUBLE ARROW-TAIL
</entry>
402 <entry>★</entry>
403 <entry>0x2605</entry>
404 <entry>BLACK STAR
</entry>
412 <sect2 id=
"magic-hash">
413 <title>The magic hash
</title>
414 <para>The language extension
<option>-XMagicHash
</option> allows
"#" as a
415 postfix modifier to identifiers. Thus,
"x#" is a valid variable, and
"T#" is
416 a valid type constructor or data constructor.
</para>
418 <para>The hash sign does not change semantics at all. We tend to use variable
419 names ending in
"#" for unboxed values or types (e.g.
<literal>Int
#</literal>),
420 but there is no requirement to do so; they are just plain ordinary variables.
421 Nor does the
<option>-XMagicHash
</option> extension bring anything into scope.
422 For example, to bring
<literal>Int
#</literal> into scope you must
423 import
<literal>GHC.Prim
</literal> (see
<xref linkend=
"primitives"/>);
424 the
<option>-XMagicHash
</option> extension
425 then allows you to
<emphasis>refer
</emphasis> to the
<literal>Int
#</literal>
426 that is now in scope. Note that with this option, the meaning of
<literal>x
#y =
0</literal>
427 is changed: it defines a function
<literal>x
#</literal> taking a single argument
<literal>y
</literal>;
428 to define the operator
<literal>#</literal>, put a space:
<literal>x
# y =
0</literal>.
431 <para> The
<option>-XMagicHash
</option> also enables some new forms of literals (see
<xref linkend=
"glasgow-unboxed"/>):
433 <listitem><para> <literal>'x'
#</literal> has type
<literal>Char
#</literal></para> </listitem>
434 <listitem><para> <literal>"foo
"#</literal> has type
<literal>Addr
#</literal></para> </listitem>
435 <listitem><para> <literal>3#</literal> has type
<literal>Int
#</literal>. In general,
436 any Haskell integer lexeme followed by a
<literal>#</literal> is an
<literal>Int
#</literal> literal, e.g.
437 <literal>-
0x3A#</literal> as well as
<literal>32#</literal>.
</para></listitem>
438 <listitem><para> <literal>3##</literal> has type
<literal>Word
#</literal>. In general,
439 any non-negative Haskell integer lexeme followed by
<literal>##</literal>
440 is a
<literal>Word
#</literal>.
</para> </listitem>
441 <listitem><para> <literal>3.2#</literal> has type
<literal>Float
#</literal>.
</para> </listitem>
442 <listitem><para> <literal>3.2##</literal> has type
<literal>Double
#</literal></para> </listitem>
447 <sect2 id=
"negative-literals">
448 <title>Negative literals
</title>
450 The literal
<literal>-
123</literal> is, according to
451 Haskell98 and Haskell
2010, desugared as
452 <literal>negate (fromInteger
123)
</literal>.
453 The language extension
<option>-XNegativeLiterals
</option>
454 means that it is instead desugared as
455 <literal>fromInteger (-
123)
</literal>.
459 This can make a difference when the positive and negative range of
460 a numeric data type don't match up. For example,
461 in
8-bit arithmetic -
128 is representable, but +
128 is not.
462 So
<literal>negate (fromInteger
128)
</literal> will elicit an
463 unexpected integer-literal-overflow message.
467 <sect2 id=
"num-decimals">
468 <title>Fractional looking integer literals
</title>
470 Haskell
2010 and Haskell
98 define floating literals with
471 the syntax
<literal>1.2e6
</literal>. These literals have the
472 type
<literal>Fractional a =
> a
</literal>.
476 The language extension
<option>-XNumDecimals
</option> allows
477 you to also use the floating literal syntax for instances of
478 <literal>Integral
</literal>, and have values like
479 <literal>(
1.2e6 :: Num a =
> a)
</literal>
484 <!-- ====================== HIERARCHICAL MODULES ======================= -->
487 <sect2 id=
"hierarchical-modules">
488 <title>Hierarchical Modules
</title>
490 <para>GHC supports a small extension to the syntax of module
491 names: a module name is allowed to contain a dot
492 <literal>‘.
’</literal>. This is also known as the
493 “hierarchical module namespace
” extension, because
494 it extends the normally flat Haskell module namespace into a
495 more flexible hierarchy of modules.
</para>
497 <para>This extension has very little impact on the language
498 itself; modules names are
<emphasis>always
</emphasis> fully
499 qualified, so you can just think of the fully qualified module
500 name as
<quote>the module name
</quote>. In particular, this
501 means that the full module name must be given after the
502 <literal>module
</literal> keyword at the beginning of the
503 module; for example, the module
<literal>A.B.C
</literal> must
506 <programlisting>module A.B.C
</programlisting>
509 <para>It is a common strategy to use the
<literal>as
</literal>
510 keyword to save some typing when using qualified names with
511 hierarchical modules. For example:
</para>
514 import qualified Control.Monad.ST.Strict as ST
517 <para>For details on how GHC searches for source and interface
518 files in the presence of hierarchical modules, see
<xref
519 linkend=
"search-path"/>.
</para>
521 <para>GHC comes with a large collection of libraries arranged
522 hierarchically; see the accompanying
<ulink
523 url=
"../libraries/index.html">library
524 documentation
</ulink>. More libraries to install are available
526 url=
"http://hackage.haskell.org/packages/hackage.html">HackageDB
</ulink>.
</para>
529 <!-- ====================== PATTERN GUARDS ======================= -->
531 <sect2 id=
"pattern-guards">
532 <title>Pattern guards
</title>
535 <indexterm><primary>Pattern guards (Glasgow extension)
</primary></indexterm>
536 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.)
540 Suppose we have an abstract data type of finite maps, with a
544 lookup :: FiniteMap -
> Int -
> Maybe Int
547 The lookup returns
<function>Nothing
</function> if the supplied key is not in the domain of the mapping, and
<function>(Just v)
</function> otherwise,
548 where
<varname>v
</varname> is the value that the key maps to. Now consider the following definition:
552 clunky env var1 var2 | ok1
&& ok2 = val1 + val2
553 | otherwise = var1 + var2
564 The auxiliary functions are
568 maybeToBool :: Maybe a -
> Bool
569 maybeToBool (Just x) = True
570 maybeToBool Nothing = False
572 expectJust :: Maybe a -
> a
573 expectJust (Just x) = x
574 expectJust Nothing = error
"Unexpected Nothing"
578 What is
<function>clunky
</function> doing? The guard
<literal>ok1
&&
579 ok2
</literal> checks that both lookups succeed, using
580 <function>maybeToBool
</function> to convert the
<function>Maybe
</function>
581 types to booleans. The (lazily evaluated)
<function>expectJust
</function>
582 calls extract the values from the results of the lookups, and binds the
583 returned values to
<varname>val1
</varname> and
<varname>val2
</varname>
584 respectively. If either lookup fails, then clunky takes the
585 <literal>otherwise
</literal> case and returns the sum of its arguments.
589 This is certainly legal Haskell, but it is a tremendously verbose and
590 un-obvious way to achieve the desired effect. Arguably, a more direct way
591 to write clunky would be to use case expressions:
595 clunky env var1 var2 = case lookup env var1 of
597 Just val1 -
> case lookup env var2 of
599 Just val2 -
> val1 + val2
605 This is a bit shorter, but hardly better. Of course, we can rewrite any set
606 of pattern-matching, guarded equations as case expressions; that is
607 precisely what the compiler does when compiling equations! The reason that
608 Haskell provides guarded equations is because they allow us to write down
609 the cases we want to consider, one at a time, independently of each other.
610 This structure is hidden in the case version. Two of the right-hand sides
611 are really the same (
<function>fail
</function>), and the whole expression
612 tends to become more and more indented.
616 Here is how I would write clunky:
621 | Just val1
<- lookup env var1
622 , Just val2
<- lookup env var2
624 ...other equations for clunky...
628 The semantics should be clear enough. The qualifiers are matched in order.
629 For a
<literal><-
</literal> qualifier, which I call a pattern guard, the
630 right hand side is evaluated and matched against the pattern on the left.
631 If the match fails then the whole guard fails and the next equation is
632 tried. If it succeeds, then the appropriate binding takes place, and the
633 next qualifier is matched, in the augmented environment. Unlike list
634 comprehensions, however, the type of the expression to the right of the
635 <literal><-
</literal> is the same as the type of the pattern to its
636 left. The bindings introduced by pattern guards scope over all the
637 remaining guard qualifiers, and over the right hand side of the equation.
641 Just as with list comprehensions, boolean expressions can be freely mixed
642 with among the pattern guards. For example:
653 Haskell's current guards therefore emerge as a special case, in which the
654 qualifier list has just one element, a boolean expression.
658 <!-- ===================== View patterns =================== -->
660 <sect2 id=
"view-patterns">
665 View patterns are enabled by the flag
<literal>-XViewPatterns
</literal>.
666 More information and examples of view patterns can be found on the
667 <ulink url=
"http://ghc.haskell.org/trac/ghc/wiki/ViewPatterns">Wiki
672 View patterns are somewhat like pattern guards that can be nested inside
673 of other patterns. They are a convenient way of pattern-matching
674 against values of abstract types. For example, in a programming language
675 implementation, we might represent the syntax of the types of the
684 view :: Typ -
> TypView
686 -- additional operations for constructing Typ's ...
689 The representation of Typ is held abstract, permitting implementations
690 to use a fancy representation (e.g., hash-consing to manage sharing).
692 Without view patterns, using this signature a little inconvenient:
694 size :: Typ -
> Integer
695 size t = case view t of
697 Arrow t1 t2 -
> size t1 + size t2
700 It is necessary to iterate the case, rather than using an equational
701 function definition. And the situation is even worse when the matching
702 against
<literal>t
</literal> is buried deep inside another pattern.
706 View patterns permit calling the view function inside the pattern and
707 matching against the result:
709 size (view -
> Unit) =
1
710 size (view -
> Arrow t1 t2) = size t1 + size t2
713 That is, we add a new form of pattern, written
714 <replaceable>expression
</replaceable> <literal>-
></literal>
715 <replaceable>pattern
</replaceable> that means
"apply the expression to
716 whatever we're trying to match against, and then match the result of
717 that application against the pattern". The expression can be any Haskell
718 expression of function type, and view patterns can be used wherever
723 The semantics of a pattern
<literal>(
</literal>
724 <replaceable>exp
</replaceable> <literal>-
></literal>
725 <replaceable>pat
</replaceable> <literal>)
</literal> are as follows:
731 <para>The variables bound by the view pattern are the variables bound by
732 <replaceable>pat
</replaceable>.
736 Any variables in
<replaceable>exp
</replaceable> are bound occurrences,
737 but variables bound
"to the left" in a pattern are in scope. This
738 feature permits, for example, one argument to a function to be used in
739 the view of another argument. For example, the function
740 <literal>clunky
</literal> from
<xref linkend=
"pattern-guards" /> can be
741 written using view patterns as follows:
744 clunky env (lookup env -
> Just val1) (lookup env -
> Just val2) = val1 + val2
745 ...other equations for clunky...
750 More precisely, the scoping rules are:
754 In a single pattern, variables bound by patterns to the left of a view
755 pattern expression are in scope. For example:
757 example :: Maybe ((String -
> Integer,Integer), String) -
> Bool
758 example Just ((f,_), f -
> 4) = True
761 Additionally, in function definitions, variables bound by matching earlier curried
762 arguments may be used in view pattern expressions in later arguments:
764 example :: (String -
> Integer) -
> String -
> Bool
765 example f (f -
> 4) = True
767 That is, the scoping is the same as it would be if the curried arguments
768 were collected into a tuple.
774 In mutually recursive bindings, such as
<literal>let
</literal>,
775 <literal>where
</literal>, or the top level, view patterns in one
776 declaration may not mention variables bound by other declarations. That
777 is, each declaration must be self-contained. For example, the following
778 program is not allowed:
784 (For some amplification on this design choice see
785 <ulink url=
"http://ghc.haskell.org/trac/ghc/ticket/4061">Trac #
4061</ulink>.)
794 <listitem><para> Typing: If
<replaceable>exp
</replaceable> has type
795 <replaceable>T1
</replaceable> <literal>-
></literal>
796 <replaceable>T2
</replaceable> and
<replaceable>pat
</replaceable> matches
797 a
<replaceable>T2
</replaceable>, then the whole view pattern matches a
798 <replaceable>T1
</replaceable>.
801 <listitem><para> Matching: To the equations in Section
3.17.3 of the
802 <ulink url=
"http://www.haskell.org/onlinereport/">Haskell
98
803 Report
</ulink>, add the following:
805 case v of { (e -
> p) -
> e1 ; _ -
> e2 }
807 case (e v) of { p -
> e1 ; _ -
> e2 }
809 That is, to match a variable
<replaceable>v
</replaceable> against a pattern
810 <literal>(
</literal> <replaceable>exp
</replaceable>
811 <literal>-
></literal> <replaceable>pat
</replaceable>
812 <literal>)
</literal>, evaluate
<literal>(
</literal>
813 <replaceable>exp
</replaceable> <replaceable> v
</replaceable>
814 <literal>)
</literal> and match the result against
815 <replaceable>pat
</replaceable>.
818 <listitem><para> Efficiency: When the same view function is applied in
819 multiple branches of a function definition or a case expression (e.g.,
820 in
<literal>size
</literal> above), GHC makes an attempt to collect these
821 applications into a single nested case expression, so that the view
822 function is only applied once. Pattern compilation in GHC follows the
823 matrix algorithm described in Chapter
4 of
<ulink
824 url=
"http://research.microsoft.com/~simonpj/Papers/slpj-book-1987/">The
825 Implementation of Functional Programming Languages
</ulink>. When the
826 top rows of the first column of a matrix are all view patterns with the
827 "same" expression, these patterns are transformed into a single nested
828 case. This includes, for example, adjacent view patterns that line up
831 f ((view -
> A, p1), p2) = e1
832 f ((view -
> B, p3), p4) = e2
836 <para> The current notion of when two view pattern expressions are
"the
837 same" is very restricted: it is not even full syntactic equality.
838 However, it does include variables, literals, applications, and tuples;
839 e.g., two instances of
<literal>view (
"hi",
"there")
</literal> will be
840 collected. However, the current implementation does not compare up to
841 alpha-equivalence, so two instances of
<literal>(x, view x -
>
842 y)
</literal> will not be coalesced.
852 <!-- ===================== n+k patterns =================== -->
854 <sect2 id=
"n-k-patterns">
855 <title>n+k patterns
</title>
856 <indexterm><primary><option>-XNPlusKPatterns
</option></primary></indexterm>
859 <literal>n+k
</literal> pattern support is disabled by default. To enable
860 it, you can use the
<option>-XNPlusKPatterns
</option> flag.
865 <!-- ===================== Traditional record syntax =================== -->
867 <sect2 id=
"traditional-record-syntax">
868 <title>Traditional record syntax
</title>
869 <indexterm><primary><option>-XNoTraditionalRecordSyntax
</option></primary></indexterm>
872 Traditional record syntax, such as
<literal>C {f = x}
</literal>, is enabled by default.
873 To disable it, you can use the
<option>-XNoTraditionalRecordSyntax
</option> flag.
878 <!-- ===================== Recursive do-notation =================== -->
880 <sect2 id=
"recursive-do-notation">
881 <title>The recursive do-notation
885 The do-notation of Haskell
98 does not allow
<emphasis>recursive bindings
</emphasis>,
886 that is, the variables bound in a do-expression are visible only in the textually following
887 code block. Compare this to a let-expression, where bound variables are visible in the entire binding
892 It turns out that such recursive bindings do indeed make sense for a variety of monads, but
893 not all. In particular, recursion in this sense requires a fixed-point operator for the underlying
894 monad, captured by the
<literal>mfix
</literal> method of the
<literal>MonadFix
</literal> class, defined in
<literal>Control.Monad.Fix
</literal> as follows:
896 class Monad m =
> MonadFix m where
897 mfix :: (a -
> m a) -
> m a
900 <literal>Maybe
</literal>,
<literal>[]
</literal> (list),
<literal>ST
</literal> (both strict and lazy versions),
901 <literal>IO
</literal>, and many other monads have
<literal>MonadFix
</literal> instances. On the negative
902 side, the continuation monad, with the signature
<literal>(a -
> r) -
> r
</literal>, does not.
906 For monads that do belong to the
<literal>MonadFix
</literal> class, GHC provides
907 an extended version of the do-notation that allows recursive bindings.
908 The
<option>-XRecursiveDo
</option> (language pragma:
<literal>RecursiveDo
</literal>)
909 provides the necessary syntactic support, introducing the keywords
<literal>mdo
</literal> and
910 <literal>rec
</literal> for higher and lower levels of the notation respectively. Unlike
911 bindings in a
<literal>do
</literal> expression, those introduced by
<literal>mdo
</literal> and
<literal>rec
</literal>
912 are recursively defined, much like in an ordinary let-expression. Due to the new
913 keyword
<literal>mdo
</literal>, we also call this notation the
<emphasis>mdo-notation
</emphasis>.
917 Here is a simple (albeit contrived) example:
919 {-# LANGUAGE RecursiveDo #-}
920 justOnes = mdo { xs
<- Just (
1:xs)
921 ; return (map negate xs) }
925 {-# LANGUAGE RecursiveDo #-}
926 justOnes = do { rec { xs
<- Just (
1:xs) }
927 ; return (map negate xs) }
929 As you can guess
<literal>justOnes
</literal> will evaluate to
<literal>Just [-
1,-
1,-
1,...
</literal>.
933 GHC's implementation the mdo-notation closely follows the original translation as described in the paper
934 <ulink url=
"https://sites.google.com/site/leventerkok/recdo.pdf">A recursive do for Haskell
</ulink>, which
935 in turn is based on the work
<ulink url=
"http://sites.google.com/site/leventerkok/erkok-thesis.pdf">Value Recursion
936 in Monadic Computations
</ulink>. Furthermore, GHC extends the syntax described in the former paper
937 with a lower level syntax flagged by the
<literal>rec
</literal> keyword, as we describe next.
941 <title>Recursive binding groups
</title>
944 The flag
<option>-XRecursiveDo
</option> also introduces a new keyword
<literal>rec
</literal>, which wraps a
945 mutually-recursive group of monadic statements inside a
<literal>do
</literal> expression, producing a single statement.
946 Similar to a
<literal>let
</literal> statement inside a
<literal>do
</literal>, variables bound in
947 the
<literal>rec
</literal> are visible throughout the
<literal>rec
</literal> group, and below it. For example, compare
949 do { a
<- getChar do { a
<- getChar
950 ; let { r1 = f a r2 ; rec { r1
<- f a r2
951 ; ; r2 = g r1 } ; ; r2
<- g r1 }
952 ; return (r1 ++ r2) } ; return (r1 ++ r2) }
954 In both cases,
<literal>r1
</literal> and
<literal>r2
</literal> are available both throughout
955 the
<literal>let
</literal> or
<literal>rec
</literal> block, and in the statements that follow it.
956 The difference is that
<literal>let
</literal> is non-monadic, while
<literal>rec
</literal> is monadic.
957 (In Haskell
<literal>let
</literal> is really
<literal>letrec
</literal>, of course.)
961 The semantics of
<literal>rec
</literal> is fairly straightforward. Whenever GHC finds a
<literal>rec
</literal>
962 group, it will compute its set of bound variables, and will introduce an appropriate call
963 to the underlying monadic value-recursion operator
<literal>mfix
</literal>, belonging to the
964 <literal>MonadFix
</literal> class. Here is an example:
966 rec { b
<- f a c ===
> (b,c)
<- mfix (\ ~(b,c) -
> do { b
<- f a c
967 ; c
<- f b a } ; c
<- f b a
970 As usual, the meta-variables
<literal>b
</literal>,
<literal>c
</literal> etc., can be arbitrary patterns.
971 In general, the statement
<literal>rec
<replaceable>ss
</replaceable></literal> is desugared to the statement
973 <replaceable>vs
</replaceable> <- mfix (\ ~
<replaceable>vs
</replaceable> -
> do {
<replaceable>ss
</replaceable>; return
<replaceable>vs
</replaceable> })
975 where
<replaceable>vs
</replaceable> is a tuple of the variables bound by
<replaceable>ss
</replaceable>.
979 Note in particular that the translation for a
<literal>rec
</literal> block only involves wrapping a call
980 to
<literal>mfix
</literal>: it performs no other analysis on the bindings. The latter is the task
981 for the
<literal>mdo
</literal> notation, which is described next.
986 <title>The
<literal>mdo
</literal> notation
</title>
989 A
<literal>rec
</literal>-block tells the compiler where precisely the recursive knot should be tied. It turns out that
990 the placement of the recursive knots can be rather delicate: in particular, we would like the knots to be wrapped
991 around as minimal groups as possible. This process is known as
<emphasis>segmentation
</emphasis>, and is described
992 in detail in Secton
3.2 of
<ulink url=
"https://sites.google.com/site/leventerkok/recdo.pdf">A recursive do for
993 Haskell
</ulink>. Segmentation improves polymorphism and reduces the size of the recursive knot. Most importantly, it avoids
994 unnecessary interference caused by a fundamental issue with the so-called
<emphasis>right-shrinking
</emphasis>
995 axiom for monadic recursion. In brief, most monads of interest (IO, strict state, etc.) do
<emphasis>not
</emphasis>
996 have recursion operators that satisfy this axiom, and thus not performing segmentation can cause unnecessary
997 interference, changing the termination behavior of the resulting translation.
998 (Details can be found in Sections
3.1 and
7.2.2 of
999 <ulink url=
"http://sites.google.com/site/leventerkok/erkok-thesis.pdf">Value Recursion in Monadic Computations
</ulink>.)
1003 The
<literal>mdo
</literal> notation removes the burden of placing
1004 explicit
<literal>rec
</literal> blocks in the code. Unlike an
1005 ordinary
<literal>do
</literal> expression, in which variables bound by
1006 statements are only in scope for later statements, variables bound in
1007 an
<literal>mdo
</literal> expression are in scope for all statements
1008 of the expression. The compiler then automatically identifies minimal
1009 mutually recursively dependent segments of statements, treating them as
1010 if the user had wrapped a
<literal>rec
</literal> qualifier around them.
1014 The definition is syntactic:
1019 A generator
<replaceable>g
</replaceable>
1020 <emphasis>depends
</emphasis> on a textually following generator
1021 <replaceable>g'
</replaceable>, if
1026 <replaceable>g'
</replaceable> defines a variable that
1027 is used by
<replaceable>g
</replaceable>, or
1032 <replaceable>g'
</replaceable> textually appears between
1033 <replaceable>g
</replaceable> and
1034 <replaceable>g''
</replaceable>, where
<replaceable>g
</replaceable>
1035 depends on
<replaceable>g''
</replaceable>.
1042 A
<emphasis>segment
</emphasis> of a given
1043 <literal>mdo
</literal>-expression is a minimal sequence of generators
1044 such that no generator of the sequence depends on an outside
1045 generator. As a special case, although it is not a generator,
1046 the final expression in an
<literal>mdo
</literal>-expression is
1047 considered to form a segment by itself.
1052 Segments in this sense are
1053 related to
<emphasis>strongly-connected components
</emphasis> analysis,
1054 with the exception that bindings in a segment cannot be reordered and
1059 Here is an example
<literal>mdo
</literal>-expression, and its translation to
<literal>rec
</literal> blocks:
1061 mdo { a
<- getChar ===
> do { a
<- getChar
1062 ; b
<- f a c ; rec { b
<- f a c
1063 ; c
<- f b a ; ; c
<- f b a }
1064 ; z
<- h a b ; z
<- h a b
1065 ; d
<- g d e ; rec { d
<- g d e
1066 ; e
<- g a z ; ; e
<- g a z }
1067 ; putChar c } ; putChar c }
1069 Note that a given
<literal>mdo
</literal> expression can cause the creation of multiple
<literal>rec
</literal> blocks.
1070 If there are no recursive dependencies,
<literal>mdo
</literal> will introduce no
<literal>rec
</literal> blocks. In this
1071 latter case an
<literal>mdo
</literal> expression is precisely the same as a
<literal>do
</literal> expression, as one
1076 In summary, given an
<literal>mdo
</literal> expression, GHC first performs segmentation, introducing
1077 <literal>rec
</literal> blocks to wrap over minimal recursive groups. Then, each resulting
1078 <literal>rec
</literal> is desugared, using a call to
<literal>Control.Monad.Fix.mfix
</literal> as described
1079 in the previous section. The original
<literal>mdo
</literal>-expression typechecks exactly when the desugared
1080 version would do so.
1084 Here are some other important points in using the recursive-do notation:
1089 It is enabled with the flag
<literal>-XRecursiveDo
</literal>, or the
<literal>LANGUAGE RecursiveDo
</literal>
1090 pragma. (The same flag enables both
<literal>mdo
</literal>-notation, and the use of
<literal>rec
</literal>
1091 blocks inside
<literal>do
</literal> expressions.)
1096 <literal>rec
</literal> blocks can also be used inside
<literal>mdo
</literal>-expressions, which will be
1097 treated as a single statement. However, it is good style to either use
<literal>mdo
</literal> or
1098 <literal>rec
</literal> blocks in a single expression.
1103 If recursive bindings are required for a monad, then that monad must be declared an instance of
1104 the
<literal>MonadFix
</literal> class.
1109 The following instances of
<literal>MonadFix
</literal> are automatically provided: List, Maybe, IO.
1110 Furthermore, the
<literal>Control.Monad.ST
</literal> and
<literal>Control.Monad.ST.Lazy
</literal>
1111 modules provide the instances of the
<literal>MonadFix
</literal> class for Haskell's internal
1112 state monad (strict and lazy, respectively).
1117 Like
<literal>let
</literal> and
<literal>where
</literal> bindings, name shadowing is not allowed within
1118 an
<literal>mdo
</literal>-expression or a
<literal>rec
</literal>-block; that is, all the names bound in
1119 a single
<literal>rec
</literal> must be distinct. (GHC will complain if this is not the case.)
1130 <!-- ===================== PARALLEL LIST COMPREHENSIONS =================== -->
1132 <sect2 id=
"parallel-list-comprehensions">
1133 <title>Parallel List Comprehensions
</title>
1134 <indexterm><primary>list comprehensions
</primary><secondary>parallel
</secondary>
1136 <indexterm><primary>parallel list comprehensions
</primary>
1139 <para>Parallel list comprehensions are a natural extension to list
1140 comprehensions. List comprehensions can be thought of as a nice
1141 syntax for writing maps and filters. Parallel comprehensions
1142 extend this to include the zipWith family.
</para>
1144 <para>A parallel list comprehension has multiple independent
1145 branches of qualifier lists, each separated by a `|' symbol. For
1146 example, the following zips together two lists:
</para>
1149 [ (x, y) | x
<- xs | y
<- ys ]
1152 <para>The behaviour of parallel list comprehensions follows that of
1153 zip, in that the resulting list will have the same length as the
1154 shortest branch.
</para>
1156 <para>We can define parallel list comprehensions by translation to
1157 regular comprehensions. Here's the basic idea:
</para>
1159 <para>Given a parallel comprehension of the form:
</para>
1162 [ e | p1
<- e11, p2
<- e12, ...
1163 | q1
<- e21, q2
<- e22, ...
1168 <para>This will be translated to:
</para>
1171 [ e | ((p1,p2), (q1,q2), ...)
<- zipN [(p1,p2) | p1
<- e11, p2
<- e12, ...]
1172 [(q1,q2) | q1
<- e21, q2
<- e22, ...]
1177 <para>where `zipN' is the appropriate zip for the given number of
1182 <!-- ===================== TRANSFORM LIST COMPREHENSIONS =================== -->
1184 <sect2 id=
"generalised-list-comprehensions">
1185 <title>Generalised (SQL-Like) List Comprehensions
</title>
1186 <indexterm><primary>list comprehensions
</primary><secondary>generalised
</secondary>
1188 <indexterm><primary>extended list comprehensions
</primary>
1190 <indexterm><primary>group
</primary></indexterm>
1191 <indexterm><primary>sql
</primary></indexterm>
1194 <para>Generalised list comprehensions are a further enhancement to the
1195 list comprehension syntactic sugar to allow operations such as sorting
1196 and grouping which are familiar from SQL. They are fully described in the
1197 paper
<ulink url=
"http://research.microsoft.com/~simonpj/papers/list-comp">
1198 Comprehensive comprehensions: comprehensions with
"order by" and
"group by"</ulink>,
1199 except that the syntax we use differs slightly from the paper.
</para>
1200 <para>The extension is enabled with the flag
<option>-XTransformListComp
</option>.
</para>
1201 <para>Here is an example:
1203 employees = [ (
"Simon",
"MS",
80)
1204 , (
"Erik",
"MS",
100)
1205 , (
"Phil",
"Ed",
40)
1206 , (
"Gordon",
"Ed",
45)
1207 , (
"Paul",
"Yale",
60)]
1209 output = [ (the dept, sum salary)
1210 | (name, dept, salary)
<- employees
1211 , then group by dept using groupWith
1212 , then sortWith by (sum salary)
1215 In this example, the list
<literal>output
</literal> would take on
1219 [(
"Yale",
60), (
"Ed",
85), (
"MS",
180)]
1222 <para>There are three new keywords:
<literal>group
</literal>,
<literal>by
</literal>, and
<literal>using
</literal>.
1223 (The functions
<literal>sortWith
</literal> and
<literal>groupWith
</literal> are not keywords; they are ordinary
1224 functions that are exported by
<literal>GHC.Exts
</literal>.)
</para>
1226 <para>There are five new forms of comprehension qualifier,
1227 all introduced by the (existing) keyword
<literal>then
</literal>:
1235 This statement requires that
<literal>f
</literal> have the type
<literal>
1236 forall a. [a] -
> [a]
</literal>. You can see an example of its use in the
1237 motivating example, as this form is used to apply
<literal>take
5</literal>.
1248 This form is similar to the previous one, but allows you to create a function
1249 which will be passed as the first argument to f. As a consequence f must have
1250 the type
<literal>forall a. (a -
> t) -
> [a] -
> [a]
</literal>. As you can see
1251 from the type, this function lets f
"project out
" some information
1252 from the elements of the list it is transforming.
</para>
1254 <para>An example is shown in the opening example, where
<literal>sortWith
</literal>
1255 is supplied with a function that lets it find out the
<literal>sum salary
</literal>
1256 for any item in the list comprehension it transforms.
</para>
1264 then group by e using f
1267 <para>This is the most general of the grouping-type statements. In this form,
1268 f is required to have type
<literal>forall a. (a -
> t) -
> [a] -
> [[a]]
</literal>.
1269 As with the
<literal>then f by e
</literal> case above, the first argument
1270 is a function supplied to f by the compiler which lets it compute e on every
1271 element of the list being transformed. However, unlike the non-grouping case,
1272 f additionally partitions the list into a number of sublists: this means that
1273 at every point after this statement, binders occurring before it in the comprehension
1274 refer to
<emphasis>lists
</emphasis> of possible values, not single values. To help understand
1275 this, let's look at an example:
</para>
1278 -- This works similarly to groupWith in GHC.Exts, but doesn't sort its input first
1279 groupRuns :: Eq b =
> (a -
> b) -
> [a] -
> [[a]]
1280 groupRuns f = groupBy (\x y -
> f x == f y)
1282 output = [ (the x, y)
1283 | x
<- ([
1.
.3] ++ [
1.
.2])
1285 , then group by x using groupRuns ]
1288 <para>This results in the variable
<literal>output
</literal> taking on the value below:
</para>
1291 [(
1, [
4,
5,
6]), (
2, [
4,
5,
6]), (
3, [
4,
5,
6]), (
1, [
4,
5,
6]), (
2, [
4,
5,
6])]
1294 <para>Note that we have used the
<literal>the
</literal> function to change the type
1295 of x from a list to its original numeric type. The variable y, in contrast, is left
1296 unchanged from the list form introduced by the grouping.
</para>
1306 <para>With this form of the group statement, f is required to simply have the type
1307 <literal>forall a. [a] -
> [[a]]
</literal>, which will be used to group up the
1308 comprehension so far directly. An example of this form is as follows:
</para>
1314 , then group using inits]
1317 <para>This will yield a list containing every prefix of the word
"hello" written out
5 times:
</para>
1320 [
"",
"h",
"he",
"hel",
"hell",
"hello",
"helloh",
"hellohe",
"hellohel",
"hellohell",
"hellohello",
"hellohelloh",...]
1328 <!-- ===================== MONAD COMPREHENSIONS ===================== -->
1330 <sect2 id=
"monad-comprehensions">
1331 <title>Monad comprehensions
</title>
1332 <indexterm><primary>monad comprehensions
</primary></indexterm>
1335 Monad comprehensions generalise the list comprehension notation,
1336 including parallel comprehensions
1337 (
<xref linkend=
"parallel-list-comprehensions"/>) and
1338 transform comprehensions (
<xref linkend=
"generalised-list-comprehensions"/>)
1339 to work for any monad.
1342 <para>Monad comprehensions support:
</para>
1351 [ x + y | x
<- Just
1, y
<- Just
2 ]
1355 Bindings are translated with the
<literal>(
>>=)
</literal> and
1356 <literal>return
</literal> functions to the usual do-notation:
1372 [ x | x
<- [
1.
.10], x
<=
5 ]
1376 Guards are translated with the
<literal>guard
</literal> function,
1377 which requires a
<literal>MonadPlus
</literal> instance:
1389 Transform statements (as with
<literal>-XTransformListComp
</literal>):
1393 [ x+y | x
<- [
1.
.10], y
<- [
1..x], then take
2 ]
1401 do (x,y)
<- take
2 (do x
<- [
1.
.10]
1410 Group statements (as with
<literal>-XTransformListComp
</literal>):
1414 [ x | x
<- [
1,
1,
2,
2,
3], then group by x using GHC.Exts.groupWith ]
1415 [ x | x
<- [
1,
1,
2,
2,
3], then group using myGroup ]
1421 Parallel statements (as with
<literal>-XParallelListComp
</literal>):
1425 [ (x+y) | x
<- [
1.
.10]
1431 Parallel statements are translated using the
1432 <literal>mzip
</literal> function, which requires a
1433 <literal>MonadZip
</literal> instance defined in
1434 <ulink url=
"&libraryBaseLocation;/Control-Monad-Zip.html"><literal>Control.Monad.Zip
</literal></ulink>:
1438 do (x,y)
<- mzip (do x
<- [
1.
.10]
1440 (do y
<- [
11.
.20]
1449 All these features are enabled by default if the
1450 <literal>MonadComprehensions
</literal> extension is enabled. The types
1451 and more detailed examples on how to use comprehensions are explained
1452 in the previous chapters
<xref
1453 linkend=
"generalised-list-comprehensions"/> and
<xref
1454 linkend=
"parallel-list-comprehensions"/>. In general you just have
1455 to replace the type
<literal>[a]
</literal> with the type
1456 <literal>Monad m =
> m a
</literal> for monad comprehensions.
1460 Note: Even though most of these examples are using the list monad,
1461 monad comprehensions work for any monad.
1462 The
<literal>base
</literal> package offers all necessary instances for
1463 lists, which make
<literal>MonadComprehensions
</literal> backward
1464 compatible to built-in, transform and parallel list comprehensions.
1466 <para> More formally, the desugaring is as follows. We write
<literal>D[ e | Q]
</literal>
1467 to mean the desugaring of the monad comprehension
<literal>[ e | Q]
</literal>:
1471 Lists of qualifiers: Q,R,S
1475 D[ e | p
<- e, Q ] = e
>>= \p -
> D[ e | Q ]
1476 D[ e | e, Q ] = guard e
>> \p -
> D[ e | Q ]
1477 D[ e | let d, Q ] = let d in D[ e | Q ]
1479 -- Parallel comprehensions (iterate for multiple parallel branches)
1480 D[ e | (Q | R), S ] = mzip D[ Qv | Q ] D[ Rv | R ]
>>= \(Qv,Rv) -
> D[ e | S ]
1482 -- Transform comprehensions
1483 D[ e | Q then f, R ] = f D[ Qv | Q ]
>>= \Qv -
> D[ e | R ]
1485 D[ e | Q then f by b, R ] = f (\Qv -
> b) D[ Qv | Q ]
>>= \Qv -
> D[ e | R ]
1487 D[ e | Q then group using f, R ] = f D[ Qv | Q ]
>>= \ys -
>
1488 case (fmap selQv1 ys, ..., fmap selQvn ys) of
1491 D[ e | Q then group by b using f, R ] = f (\Qv -
> b) D[ Qv | Q ]
>>= \ys -
>
1492 case (fmap selQv1 ys, ..., fmap selQvn ys) of
1495 where Qv is the tuple of variables bound by Q (and used subsequently)
1496 selQvi is a selector mapping Qv to the ith component of Qv
1498 Operator Standard binding Expected type
1499 --------------------------------------------------------------------
1500 return GHC.Base t1 -
> m t2
1501 (
>>=) GHC.Base m1 t1 -
> (t2 -
> m2 t3) -
> m3 t3
1502 (
>>) GHC.Base m1 t1 -
> m2 t2 -
> m3 t3
1503 guard Control.Monad t1 -
> m t2
1504 fmap GHC.Base forall a b. (a-
>b) -
> n a -
> n b
1505 mzip Control.Monad.Zip forall a b. m a -
> m b -
> m (a,b)
1507 The comprehension should typecheck when its desugaring would typecheck.
1510 Monad comprehensions support rebindable syntax (
<xref linkend=
"rebindable-syntax"/>).
1512 syntax, the operators from the
"standard binding" module are used; with
1513 rebindable syntax, the operators are looked up in the current lexical scope.
1514 For example, parallel comprehensions will be typechecked and desugared
1515 using whatever
"<literal>mzip</literal>" is in scope.
1518 The rebindable operators must have the
"Expected type" given in the
1519 table above. These types are surprisingly general. For example, you can
1520 use a bind operator with the type
1522 (
>>=) :: T x y a -
> (a -
> T y z b) -
> T x z b
1524 In the case of transform comprehensions, notice that the groups are
1525 parameterised over some arbitrary type
<literal>n
</literal> (provided it
1526 has an
<literal>fmap
</literal>, as well as
1527 the comprehension being over an arbitrary monad.
1531 <!-- ===================== REBINDABLE SYNTAX =================== -->
1533 <sect2 id=
"rebindable-syntax">
1534 <title>Rebindable syntax and the implicit Prelude import
</title>
1536 <para><indexterm><primary>-XNoImplicitPrelude
1537 option
</primary></indexterm> GHC normally imports
1538 <filename>Prelude.hi
</filename> files for you. If you'd
1539 rather it didn't, then give it a
1540 <option>-XNoImplicitPrelude
</option> option. The idea is
1541 that you can then import a Prelude of your own. (But don't
1542 call it
<literal>Prelude
</literal>; the Haskell module
1543 namespace is flat, and you must not conflict with any
1544 Prelude module.)
</para>
1546 <para>Suppose you are importing a Prelude of your own
1547 in order to define your own numeric class
1548 hierarchy. It completely defeats that purpose if the
1549 literal
"1" means
"<literal>Prelude.fromInteger
1550 1</literal>", which is what the Haskell Report specifies.
1551 So the
<option>-XRebindableSyntax
</option>
1553 the following pieces of built-in syntax to refer to
1554 <emphasis>whatever is in scope
</emphasis>, not the Prelude
1558 <para>An integer literal
<literal>368</literal> means
1559 "<literal>fromInteger (368::Integer)</literal>", rather than
1560 "<literal>Prelude.fromInteger (368::Integer)</literal>".
1563 <listitem><para>Fractional literals are handed in just the same way,
1564 except that the translation is
1565 <literal>fromRational (
3.68::Rational)
</literal>.
1568 <listitem><para>The equality test in an overloaded numeric pattern
1569 uses whatever
<literal>(==)
</literal> is in scope.
1572 <listitem><para>The subtraction operation, and the
1573 greater-than-or-equal test, in
<literal>n+k
</literal> patterns
1574 use whatever
<literal>(-)
</literal> and
<literal>(
>=)
</literal> are in scope.
1578 <para>Negation (e.g.
"<literal>- (f x)</literal>")
1579 means
"<literal>negate (f x)</literal>", both in numeric
1580 patterns, and expressions.
1584 <para>Conditionals (e.g.
"<literal>if</literal> e1 <literal>then</literal> e2 <literal>else</literal> e3")
1585 means
"<literal>ifThenElse</literal> e1 e2 e3". However
<literal>case
</literal> expressions are unaffected.
1589 <para>"Do" notation is translated using whatever
1590 functions
<literal>(
>>=)
</literal>,
1591 <literal>(
>>)
</literal>, and
<literal>fail
</literal>,
1592 are in scope (not the Prelude
1593 versions). List comprehensions, mdo (
<xref linkend=
"recursive-do-notation"/>), and parallel array
1594 comprehensions, are unaffected.
</para></listitem>
1598 notation (see
<xref linkend=
"arrow-notation"/>)
1599 uses whatever
<literal>arr
</literal>,
1600 <literal>(
>>>)
</literal>,
<literal>first
</literal>,
1601 <literal>app
</literal>,
<literal>(|||)
</literal> and
1602 <literal>loop
</literal> functions are in scope. But unlike the
1603 other constructs, the types of these functions must match the
1604 Prelude types very closely. Details are in flux; if you want
1608 <option>-XRebindableSyntax
</option> implies
<option>-XNoImplicitPrelude
</option>.
1611 In all cases (apart from arrow notation), the static semantics should be that of the desugared form,
1612 even if that is a little unexpected. For example, the
1613 static semantics of the literal
<literal>368</literal>
1614 is exactly that of
<literal>fromInteger (
368::Integer)
</literal>; it's fine for
1615 <literal>fromInteger
</literal> to have any of the types:
1617 fromInteger :: Integer -
> Integer
1618 fromInteger :: forall a. Foo a =
> Integer -
> a
1619 fromInteger :: Num a =
> a -
> Integer
1620 fromInteger :: Integer -
> Bool -
> Bool
1624 <para>Be warned: this is an experimental facility, with
1625 fewer checks than usual. Use
<literal>-dcore-lint
</literal>
1626 to typecheck the desugared program. If Core Lint is happy
1627 you should be all right.
</para>
1631 <sect2 id=
"postfix-operators">
1632 <title>Postfix operators
</title>
1635 The
<option>-XPostfixOperators
</option> flag enables a small
1636 extension to the syntax of left operator sections, which allows you to
1637 define postfix operators. The extension is this: the left section
1641 is equivalent (from the point of view of both type checking and execution) to the expression
1645 (for any expression
<literal>e
</literal> and operator
<literal>(!)
</literal>.
1646 The strict Haskell
98 interpretation is that the section is equivalent to
1650 That is, the operator must be a function of two arguments. GHC allows it to
1651 take only one argument, and that in turn allows you to write the function
1654 <para>The extension does not extend to the left-hand side of function
1655 definitions; you must define such a function in prefix form.
</para>
1659 <sect2 id=
"tuple-sections">
1660 <title>Tuple sections
</title>
1663 The
<option>-XTupleSections
</option> flag enables Python-style partially applied
1664 tuple constructors. For example, the following program
1668 is considered to be an alternative notation for the more unwieldy alternative
1672 You can omit any combination of arguments to the tuple, as in the following
1674 (,
"I", , ,
"Love", ,
1337)
1678 \a b c d -
> (a,
"I", b, c,
"Love", d,
1337)
1683 If you have
<link linkend=
"unboxed-tuples">unboxed tuples
</link> enabled, tuple sections
1684 will also be available for them, like so
1688 Because there is no unboxed unit tuple, the following expression
1692 continues to stand for the unboxed singleton tuple data constructor.
1697 <sect2 id=
"lambda-case">
1698 <title>Lambda-case
</title>
1700 The
<option>-XLambdaCase
</option> flag enables expressions of the form
1702 \case { p1 -
> e1; ...; pN -
> eN }
1704 which is equivalent to
1706 \freshName -
> case freshName of { p1 -
> e1; ...; pN -
> eN }
1708 Note that
<literal>\case
</literal> starts a layout, so you can write
1718 <sect2 id=
"empty-case">
1719 <title>Empty case alternatives
</title>
1721 The
<option>-XEmptyCase
</option> flag enables
1722 case expressions, or lambda-case expressions, that have no alternatives,
1725 case e of { } -- No alternatives
1727 \case { } -- -XLambdaCase is also required
1729 This can be useful when you know that the expression being scrutinised
1730 has no non-bottom values. For example:
1736 With dependently-typed features it is more useful
1737 (see
<ulink url=
"http://ghc.haskell.org/trac/ghc/ticket/2431">Trac
</ulink>).
1738 For example, consider these two candidate definitions of
<literal>absurd
</literal>:
1743 absurd :: True :~: False -
> a
1744 absurd x = error
"absurd" -- (A)
1745 absurd x = case x of {} -- (B)
1747 We much prefer (B). Why? Because GHC can figure out that
<literal>(True :~: False)
</literal>
1748 is an empty type. So (B) has no partiality and GHC should be able to compile with
1749 <option>-fwarn-incomplete-patterns
</option>. (Though the pattern match checking is not
1750 yet clever enough to do that.)
1751 On the other hand (A) looks dangerous, and GHC doesn't check to make
1752 sure that, in fact, the function can never get called.
1756 <sect2 id=
"multi-way-if">
1757 <title>Multi-way if-expressions
</title>
1759 With
<option>-XMultiWayIf
</option> flag GHC accepts conditional expressions
1760 with multiple branches:
1762 if | guard1 -
> expr1
1766 which is roughly equivalent to
1775 <para>Multi-way if expressions introduce a new layout context. So the
1776 example above is equivalent to:
1778 if { | guard1 -
> expr1
1783 The following behaves as expected:
1785 if | guard1 -
> if | guard2 -
> expr2
1789 because layout translates it as
1791 if { | guard1 -
> if { | guard2 -
> expr2
1797 Layout with multi-way if works in the same way as other layout
1798 contexts, except that the semi-colons between guards in a multi-way if
1799 are optional. So it is not necessary to line up all the guards at the
1800 same column; this is consistent with the way guards work in function
1801 definitions and case expressions.
1805 <sect2 id=
"disambiguate-fields">
1806 <title>Record field disambiguation
</title>
1808 In record construction and record pattern matching
1809 it is entirely unambiguous which field is referred to, even if there are two different
1810 data types in scope with a common field name. For example:
1813 data S = MkS { x :: Int, y :: Bool }
1818 data T = MkT { x :: Int }
1820 ok1 (MkS { x = n }) = n+
1 -- Unambiguous
1821 ok2 n = MkT { x = n+
1 } -- Unambiguous
1823 bad1 k = k { x =
3 } -- Ambiguous
1824 bad2 k = x k -- Ambiguous
1826 Even though there are two
<literal>x
</literal>'s in scope,
1827 it is clear that the
<literal>x
</literal> in the pattern in the
1828 definition of
<literal>ok1
</literal> can only mean the field
1829 <literal>x
</literal> from type
<literal>S
</literal>. Similarly for
1830 the function
<literal>ok2
</literal>. However, in the record update
1831 in
<literal>bad1
</literal> and the record selection in
<literal>bad2
</literal>
1832 it is not clear which of the two types is intended.
1835 Haskell
98 regards all four as ambiguous, but with the
1836 <option>-XDisambiguateRecordFields
</option> flag, GHC will accept
1837 the former two. The rules are precisely the same as those for instance
1838 declarations in Haskell
98, where the method names on the left-hand side
1839 of the method bindings in an instance declaration refer unambiguously
1840 to the method of that class (provided they are in scope at all), even
1841 if there are other variables in scope with the same name.
1842 This reduces the clutter of qualified names when you import two
1843 records from different modules that use the same field name.
1849 Field disambiguation can be combined with punning (see
<xref linkend=
"record-puns"/>). For example:
1854 ok3 (MkS { x }) = x+
1 -- Uses both disambiguation and punning
1859 With
<option>-XDisambiguateRecordFields
</option> you can use
<emphasis>unqualified
</emphasis>
1860 field names even if the corresponding selector is only in scope
<emphasis>qualified
</emphasis>
1861 For example, assuming the same module
<literal>M
</literal> as in our earlier example, this is legal:
1864 import qualified M -- Note qualified
1866 ok4 (M.MkS { x = n }) = n+
1 -- Unambiguous
1868 Since the constructor
<literal>MkS
</literal> is only in scope qualified, you must
1869 name it
<literal>M.MkS
</literal>, but the field
<literal>x
</literal> does not need
1870 to be qualified even though
<literal>M.x
</literal> is in scope but
<literal>x
</literal>
1871 is not. (In effect, it is qualified by the constructor.)
1878 <!-- ===================== Record puns =================== -->
1880 <sect2 id=
"record-puns">
1885 Record puns are enabled by the flag
<literal>-XNamedFieldPuns
</literal>.
1889 When using records, it is common to write a pattern that binds a
1890 variable with the same name as a record field, such as:
1893 data C = C {a :: Int}
1899 Record punning permits the variable name to be elided, so one can simply
1906 to mean the same pattern as above. That is, in a record pattern, the
1907 pattern
<literal>a
</literal> expands into the pattern
<literal>a =
1908 a
</literal> for the same name
<literal>a
</literal>.
1915 Record punning can also be used in an expression, writing, for example,
1921 let a =
1 in C {a = a}
1923 The expansion is purely syntactic, so the expanded right-hand side
1924 expression refers to the nearest enclosing variable that is spelled the
1925 same as the field name.
1929 Puns and other patterns can be mixed in the same record:
1931 data C = C {a :: Int, b :: Int}
1932 f (C {a, b =
4}) = a
1937 Puns can be used wherever record patterns occur (e.g. in
1938 <literal>let
</literal> bindings or at the top-level).
1942 A pun on a qualified field name is expanded by stripping off the module qualifier.
1949 f (M.C {M.a = a}) = a
1951 (This is useful if the field selector
<literal>a
</literal> for constructor
<literal>M.C
</literal>
1952 is only in scope in qualified form.)
1960 <!-- ===================== Record wildcards =================== -->
1962 <sect2 id=
"record-wildcards">
1963 <title>Record wildcards
1967 Record wildcards are enabled by the flag
<literal>-XRecordWildCards
</literal>.
1968 This flag implies
<literal>-XDisambiguateRecordFields
</literal>.
1972 For records with many fields, it can be tiresome to write out each field
1973 individually in a record pattern, as in
1975 data C = C {a :: Int, b :: Int, c :: Int, d :: Int}
1976 f (C {a =
1, b = b, c = c, d = d}) = b + c + d
1981 Record wildcard syntax permits a
"<literal>..</literal>" in a record
1982 pattern, where each elided field
<literal>f
</literal> is replaced by the
1983 pattern
<literal>f = f
</literal>. For example, the above pattern can be
1986 f (C {a =
1, ..}) = b + c + d
1994 Wildcards can be mixed with other patterns, including puns
1995 (
<xref linkend=
"record-puns"/>); for example, in a pattern
<literal>C {a
1996 =
1, b, ..})
</literal>. Additionally, record wildcards can be used
1997 wherever record patterns occur, including in
<literal>let
</literal>
1998 bindings and at the top-level. For example, the top-level binding
2002 defines
<literal>b
</literal>,
<literal>c
</literal>, and
2003 <literal>d
</literal>.
2007 Record wildcards can also be used in expressions, writing, for example,
2009 let {a =
1; b =
2; c =
3; d =
4} in C {..}
2013 let {a =
1; b =
2; c =
3; d =
4} in C {a=a, b=b, c=c, d=d}
2015 The expansion is purely syntactic, so the record wildcard
2016 expression refers to the nearest enclosing variables that are spelled
2017 the same as the omitted field names.
2021 The
"<literal>..</literal>" expands to the missing
2022 <emphasis>in-scope
</emphasis> record fields.
2023 Specifically the expansion of
"<literal>C {..}</literal>" includes
2024 <literal>f
</literal> if and only if:
2027 <literal>f
</literal> is a record field of constructor
<literal>C
</literal>.
2030 The record field
<literal>f
</literal> is in scope somehow (either qualified or unqualified).
2033 In the case of expressions (but not patterns),
2034 the variable
<literal>f
</literal> is in scope unqualified,
2035 apart from the binding of the record selector itself.
2041 data R = R { a,b,c :: Int }
2046 The
<literal>R{..}
</literal> expands to
<literal>R{M.a=a}
</literal>,
2047 omitting
<literal>b
</literal> since the record field is not in scope,
2048 and omitting
<literal>c
</literal> since the variable
<literal>c
</literal>
2049 is not in scope (apart from the binding of the
2050 record selector
<literal>c
</literal>, of course).
2057 <!-- ===================== Local fixity declarations =================== -->
2059 <sect2 id=
"local-fixity-declarations">
2060 <title>Local Fixity Declarations
2063 <para>A careful reading of the Haskell
98 Report reveals that fixity
2064 declarations (
<literal>infix
</literal>,
<literal>infixl
</literal>, and
2065 <literal>infixr
</literal>) are permitted to appear inside local bindings
2066 such those introduced by
<literal>let
</literal> and
2067 <literal>where
</literal>. However, the Haskell Report does not specify
2068 the semantics of such bindings very precisely.
2071 <para>In GHC, a fixity declaration may accompany a local binding:
2078 and the fixity declaration applies wherever the binding is in scope.
2079 For example, in a
<literal>let
</literal>, it applies in the right-hand
2080 sides of other
<literal>let
</literal>-bindings and the body of the
2081 <literal>let
</literal>C. Or, in recursive
<literal>do
</literal>
2082 expressions (
<xref linkend=
"recursive-do-notation"/>), the local fixity
2083 declarations of a
<literal>let
</literal> statement scope over other
2084 statements in the group, just as the bound name does.
2088 Moreover, a local fixity declaration *must* accompany a local binding of
2089 that name: it is not possible to revise the fixity of name bound
2092 let infixr
9 $ in ...
2095 Because local fixity declarations are technically Haskell
98, no flag is
2096 necessary to enable them.
2100 <sect2 id=
"package-imports">
2101 <title>Package-qualified imports
</title>
2103 <para>With the
<option>-XPackageImports
</option> flag, GHC allows
2104 import declarations to be qualified by the package name that the
2105 module is intended to be imported from. For example:
</para>
2108 import
"network" Network.Socket
2111 <para>would import the module
<literal>Network.Socket
</literal> from
2112 the package
<literal>network
</literal> (any version). This may
2113 be used to disambiguate an import when the same module is
2114 available from multiple packages, or is present in both the
2115 current package being built and an external package.
</para>
2117 <para>The special package name
<literal>this
</literal> can be used to
2118 refer to the current package being built.
</para>
2120 <para>Note: you probably don't need to use this feature, it was
2121 added mainly so that we can build backwards-compatible versions of
2122 packages when APIs change. It can lead to fragile dependencies in
2123 the common case: modules occasionally move from one package to
2124 another, rendering any package-qualified imports broken.
</para>
2127 <sect2 id=
"safe-imports-ext">
2128 <title>Safe imports
</title>
2130 <para>With the
<option>-XSafe
</option>,
<option>-XTrustworthy
</option>
2131 and
<option>-XUnsafe
</option> language flags, GHC extends
2132 the import declaration syntax to take an optional
<literal>safe
</literal>
2133 keyword after the
<literal>import
</literal> keyword. This feature
2134 is part of the Safe Haskell GHC extension. For example:
</para>
2137 import safe qualified Network.Socket as NS
2140 <para>would import the module
<literal>Network.Socket
</literal>
2141 with compilation only succeeding if Network.Socket can be
2142 safely imported. For a description of when a import is
2143 considered safe see
<xref linkend=
"safe-haskell"/></para>
2147 <sect2 id=
"explicit-namespaces">
2148 <title>Explicit namespaces in import/export
</title>
2150 <para> In an import or export list, such as
2152 module M( f, (++) ) where ...
2156 the entities
<literal>f
</literal> and
<literal>(++)
</literal> are
<emphasis>values
</emphasis>.
2157 However, with type operators (
<xref linkend=
"type-operators"/>) it becomes possible
2158 to declare
<literal>(++)
</literal> as a
<emphasis>type constructor
</emphasis>. In that
2159 case, how would you export or import it?
2162 The
<option>-XExplicitNamespaces
</option> extension allows you to prefix the name of
2163 a type constructor in an import or export list with
"<literal>type</literal>" to
2164 disambiguate this case, thus:
2166 module M( f, type (++) ) where ...
2167 import N( f, type (++) )
2169 module N( f, type (++) ) where
2170 data family a ++ b = L a | R b
2172 The extension
<option>-XExplicitNamespaces
</option>
2173 is implied by
<option>-XTypeOperators
</option> and (for some reason) by
<option>-XTypeFamilies
</option>.
2177 <sect2 id=
"syntax-stolen">
2178 <title>Summary of stolen syntax
</title>
2180 <para>Turning on an option that enables special syntax
2181 <emphasis>might
</emphasis> cause working Haskell
98 code to fail
2182 to compile, perhaps because it uses a variable name which has
2183 become a reserved word. This section lists the syntax that is
2184 "stolen" by language extensions.
2186 notation and nonterminal names from the Haskell
98 lexical syntax
2187 (see the Haskell
98 Report).
2188 We only list syntax changes here that might affect
2189 existing working programs (i.e.
"stolen" syntax). Many of these
2190 extensions will also enable new context-free syntax, but in all
2191 cases programs written to use the new syntax would not be
2192 compilable without the option enabled.
</para>
2194 <para>There are two classes of special
2199 <para>New reserved words and symbols: character sequences
2200 which are no longer available for use as identifiers in the
2204 <para>Other special syntax: sequences of characters that have
2205 a different meaning when this particular option is turned
2210 The following syntax is stolen:
2215 <literal>forall
</literal>
2216 <indexterm><primary><literal>forall
</literal></primary></indexterm>
2219 Stolen (in types) by:
<option>-XExplicitForAll
</option>, and hence by
2220 <option>-XScopedTypeVariables
</option>,
2221 <option>-XLiberalTypeSynonyms
</option>,
2222 <option>-XRankNTypes
</option>,
2223 <option>-XExistentialQuantification
</option>
2229 <literal>mdo
</literal>
2230 <indexterm><primary><literal>mdo
</literal></primary></indexterm>
2233 Stolen by:
<option>-XRecursiveDo
</option>
2239 <literal>foreign
</literal>
2240 <indexterm><primary><literal>foreign
</literal></primary></indexterm>
2243 Stolen by:
<option>-XForeignFunctionInterface
</option>
2249 <literal>rec
</literal>,
2250 <literal>proc
</literal>,
<literal>-
<</literal>,
2251 <literal>>-
</literal>,
<literal>-
<<</literal>,
2252 <literal>>>-
</literal>, and
<literal>(|
</literal>,
2253 <literal>|)
</literal> brackets
2254 <indexterm><primary><literal>proc
</literal></primary></indexterm>
2257 Stolen by:
<option>-XArrows
</option>
2263 <literal>?
<replaceable>varid
</replaceable></literal>,
2264 <literal>%
<replaceable>varid
</replaceable></literal>
2265 <indexterm><primary>implicit parameters
</primary></indexterm>
2268 Stolen by:
<option>-XImplicitParams
</option>
2274 <literal>[|
</literal>,
2275 <literal>[e|
</literal>,
<literal>[p|
</literal>,
2276 <literal>[d|
</literal>,
<literal>[t|
</literal>,
2277 <literal>$(
</literal>,
2278 <literal>$
<replaceable>varid
</replaceable></literal>
2279 <indexterm><primary>Template Haskell
</primary></indexterm>
2282 Stolen by:
<option>-XTemplateHaskell
</option>
2288 <literal>[:
<replaceable>varid
</replaceable>|
</literal>
2289 <indexterm><primary>quasi-quotation
</primary></indexterm>
2292 Stolen by:
<option>-XQuasiQuotes
</option>
2298 <replaceable>varid
</replaceable>{
<literal>#</literal>},
2299 <replaceable>char
</replaceable><literal>#</literal>,
2300 <replaceable>string
</replaceable><literal>#</literal>,
2301 <replaceable>integer
</replaceable><literal>#</literal>,
2302 <replaceable>float
</replaceable><literal>#</literal>,
2303 <replaceable>float
</replaceable><literal>##</literal>
2306 Stolen by:
<option>-XMagicHash
</option>
2312 <literal>(
#</literal>,
<literal>#)
</literal>
2315 Stolen by:
<option>-XUnboxedTuples
</option>
2321 <replaceable>varid
</replaceable><literal>!
</literal><replaceable>varid
</replaceable>
2324 Stolen by:
<option>-XBangPatterns
</option>
2333 <!-- TYPE SYSTEM EXTENSIONS -->
2334 <sect1 id=
"data-type-extensions">
2335 <title>Extensions to data types and type synonyms
</title>
2337 <sect2 id=
"nullary-types">
2338 <title>Data types with no constructors
</title>
2340 <para>With the
<option>-XEmptyDataDecls
</option> flag (or equivalent LANGUAGE pragma),
2341 GHC lets you declare a data type with no constructors. For example:
</para>
2345 data T a -- T :: * -
> *
2348 <para>Syntactically, the declaration lacks the
"= constrs" part. The
2349 type can be parameterised over types of any kind, but if the kind is
2350 not
<literal>*
</literal> then an explicit kind annotation must be used
2351 (see
<xref linkend=
"kinding"/>).
</para>
2353 <para>Such data types have only one value, namely bottom.
2354 Nevertheless, they can be useful when defining
"phantom types".
</para>
2357 <sect2 id=
"datatype-contexts">
2358 <title>Data type contexts
</title>
2360 <para>Haskell allows datatypes to be given contexts, e.g.
</para>
2363 data Eq a =
> Set a = NilSet | ConsSet a (Set a)
2366 <para>give constructors with types:
</para>
2370 ConsSet :: Eq a =
> a -
> Set a -
> Set a
2373 <para>This is widely considered a misfeature, and is going to be removed from
2374 the language. In GHC, it is controlled by the deprecated extension
2375 <literal>DatatypeContexts
</literal>.
</para>
2378 <sect2 id=
"infix-tycons">
2379 <title>Infix type constructors, classes, and type variables
</title>
2382 GHC allows type constructors, classes, and type variables to be operators, and
2383 to be written infix, very much like expressions. More specifically:
2386 A type constructor or class can be an operator, beginning with a colon; e.g.
<literal>:*:
</literal>.
2387 The lexical syntax is the same as that for data constructors.
2390 Data type and type-synonym declarations can be written infix, parenthesised
2391 if you want further arguments. E.g.
2393 data a :*: b = Foo a b
2394 type a :+: b = Either a b
2395 class a :=: b where ...
2397 data (a :**: b) x = Baz a b x
2398 type (a :++: b) y = Either (a,b) y
2402 Types, and class constraints, can be written infix. For example
2405 f :: (a :=: b) =
> a -
> b
2410 as for expressions, both for type constructors and type variables; e.g.
<literal>Int `Either` Bool
</literal>, or
2411 <literal>Int `a` Bool
</literal>. Similarly, parentheses work the same; e.g.
<literal>(:*:) Int Bool
</literal>.
2414 Fixities may be declared for type constructors, or classes, just as for data constructors. However,
2415 one cannot distinguish between the two in a fixity declaration; a fixity declaration
2416 sets the fixity for a data constructor and the corresponding type constructor. For example:
2420 sets the fixity for both type constructor
<literal>T
</literal> and data constructor
<literal>T
</literal>,
2421 and similarly for
<literal>:*:
</literal>.
2422 <literal>Int `a` Bool
</literal>.
2425 Function arrow is
<literal>infixr
</literal> with fixity
0. (This might change; I'm not sure what it should be.)
2432 <sect2 id=
"type-operators">
2433 <title>Type operators
</title>
2435 In types, an operator symbol like
<literal>(+)
</literal> is normally treated as a type
2436 <emphasis>variable
</emphasis>, just like
<literal>a
</literal>. Thus in Haskell
98 you can say
2438 type T (+) = ((+), (+))
2439 -- Just like: type T a = (a,a)
2444 As you can see, using operators in this way is not very useful, and Haskell
98 does not even
2445 allow you to write them infix.
2448 The language
<option>-XTypeOperators
</option> changes this behaviour:
2451 Operator symbols become type
<emphasis>constructors
</emphasis> rather than
2452 type
<emphasis>variables
</emphasis>.
2455 Operator symbols in types can be written infix, both in definitions and uses.
2458 data a + b = Plus a b
2459 type Foo = Int + Bool
2463 There is now some potential ambiguity in import and export lists; for example
2464 if you write
<literal>import M( (+) )
</literal> do you mean the
2465 <emphasis>function
</emphasis> <literal>(+)
</literal> or the
2466 <emphasis>type constructor
</emphasis> <literal>(+)
</literal>?
2467 The default is the former, but with
<option>-XExplicitNamespaces
</option> (which is implied
2468 by
<option>-XExplicitTypeOperators
</option>) GHC allows you to specify the latter
2469 by preceding it with the keyword
<literal>type
</literal>, thus:
2471 import M( type (+) )
2473 See
<xref linkend=
"explicit-namespaces"/>.
2476 The fixity of a type operator may be set using the usual fixity declarations
2477 but, as in
<xref linkend=
"infix-tycons"/>, the function and type constructor share
2484 <sect2 id=
"type-synonyms">
2485 <title>Liberalised type synonyms
</title>
2488 Type synonyms are like macros at the type level, but Haskell
98 imposes many rules
2489 on individual synonym declarations.
2490 With the
<option>-XLiberalTypeSynonyms
</option> extension,
2491 GHC does validity checking on types
<emphasis>only after expanding type synonyms
</emphasis>.
2492 That means that GHC can be very much more liberal about type synonyms than Haskell
98.
2495 <listitem> <para>You can write a
<literal>forall
</literal> (including overloading)
2496 in a type synonym, thus:
2498 type Discard a = forall b. Show b =
> a -
> b -
> (a, String)
2503 g :: Discard Int -
> (Int,String) -- A rank-
2 type
2510 If you also use
<option>-XUnboxedTuples
</option>,
2511 you can write an unboxed tuple in a type synonym:
2513 type Pr = (# Int, Int #)
2521 You can apply a type synonym to a forall type:
2523 type Foo a = a -
> a -
> Bool
2525 f :: Foo (forall b. b-
>b)
2527 After expanding the synonym,
<literal>f
</literal> has the legal (in GHC) type:
2529 f :: (forall b. b-
>b) -
> (forall b. b-
>b) -
> Bool
2534 You can apply a type synonym to a partially applied type synonym:
2536 type Generic i o = forall x. i x -
> o x
2539 foo :: Generic Id []
2541 After expanding the synonym,
<literal>foo
</literal> has the legal (in GHC) type:
2543 foo :: forall x. x -
> [x]
2551 GHC currently does kind checking before expanding synonyms (though even that
2555 After expanding type synonyms, GHC does validity checking on types, looking for
2556 the following mal-formedness which isn't detected simply by kind checking:
2559 Type constructor applied to a type involving for-alls (if
<literal>XImpredicativeTypes
</literal>
2563 Partially-applied type synonym.
2566 So, for example, this will be rejected:
2568 type Pr = forall a. a
2573 because GHC does not allow type constructors applied to for-all types.
2578 <sect2 id=
"existential-quantification">
2579 <title>Existentially quantified data constructors
2583 The idea of using existential quantification in data type declarations
2584 was suggested by Perry, and implemented in Hope+ (Nigel Perry,
<emphasis>The Implementation
2585 of Practical Functional Programming Languages
</emphasis>, PhD Thesis, University of
2586 London,
1991). It was later formalised by Laufer and Odersky
2587 (
<emphasis>Polymorphic type inference and abstract data types
</emphasis>,
2588 TOPLAS,
16(
5), pp1411-
1430,
1994).
2589 It's been in Lennart
2590 Augustsson's
<command>hbc
</command> Haskell compiler for several years, and
2591 proved very useful. Here's the idea. Consider the declaration:
2597 data Foo = forall a. MkFoo a (a -
> Bool)
2604 The data type
<literal>Foo
</literal> has two constructors with types:
2610 MkFoo :: forall a. a -
> (a -
> Bool) -
> Foo
2617 Notice that the type variable
<literal>a
</literal> in the type of
<function>MkFoo
</function>
2618 does not appear in the data type itself, which is plain
<literal>Foo
</literal>.
2619 For example, the following expression is fine:
2625 [MkFoo
3 even, MkFoo 'c' isUpper] :: [Foo]
2631 Here,
<literal>(MkFoo
3 even)
</literal> packages an integer with a function
2632 <function>even
</function> that maps an integer to
<literal>Bool
</literal>; and
<function>MkFoo 'c'
2633 isUpper
</function> packages a character with a compatible function. These
2634 two things are each of type
<literal>Foo
</literal> and can be put in a list.
2638 What can we do with a value of type
<literal>Foo
</literal>?. In particular,
2639 what happens when we pattern-match on
<function>MkFoo
</function>?
2645 f (MkFoo val fn) = ???
2651 Since all we know about
<literal>val
</literal> and
<function>fn
</function> is that they
2652 are compatible, the only (useful) thing we can do with them is to
2653 apply
<function>fn
</function> to
<literal>val
</literal> to get a boolean. For example:
2660 f (MkFoo val fn) = fn val
2666 What this allows us to do is to package heterogeneous values
2667 together with a bunch of functions that manipulate them, and then treat
2668 that collection of packages in a uniform manner. You can express
2669 quite a bit of object-oriented-like programming this way.
2672 <sect3 id=
"existential">
2673 <title>Why existential?
2677 What has this to do with
<emphasis>existential
</emphasis> quantification?
2678 Simply that
<function>MkFoo
</function> has the (nearly) isomorphic type
2684 MkFoo :: (exists a . (a, a -
> Bool)) -
> Foo
2690 But Haskell programmers can safely think of the ordinary
2691 <emphasis>universally
</emphasis> quantified type given above, thereby avoiding
2692 adding a new existential quantification construct.
2697 <sect3 id=
"existential-with-context">
2698 <title>Existentials and type classes
</title>
2701 An easy extension is to allow
2702 arbitrary contexts before the constructor. For example:
2708 data Baz = forall a. Eq a =
> Baz1 a a
2709 | forall b. Show b =
> Baz2 b (b -
> b)
2715 The two constructors have the types you'd expect:
2721 Baz1 :: forall a. Eq a =
> a -
> a -
> Baz
2722 Baz2 :: forall b. Show b =
> b -
> (b -
> b) -
> Baz
2728 But when pattern matching on
<function>Baz1
</function> the matched values can be compared
2729 for equality, and when pattern matching on
<function>Baz2
</function> the first matched
2730 value can be converted to a string (as well as applying the function to it).
2731 So this program is legal:
2738 f (Baz1 p q) | p == q =
"Yes"
2740 f (Baz2 v fn) = show (fn v)
2746 Operationally, in a dictionary-passing implementation, the
2747 constructors
<function>Baz1
</function> and
<function>Baz2
</function> must store the
2748 dictionaries for
<literal>Eq
</literal> and
<literal>Show
</literal> respectively, and
2749 extract it on pattern matching.
2754 <sect3 id=
"existential-records">
2755 <title>Record Constructors
</title>
2758 GHC allows existentials to be used with records syntax as well. For example:
2761 data Counter a = forall self. NewCounter
2763 , _inc :: self -
> self
2764 , _display :: self -
> IO ()
2768 Here
<literal>tag
</literal> is a public field, with a well-typed selector
2769 function
<literal>tag :: Counter a -
> a
</literal>. The
<literal>self
</literal>
2770 type is hidden from the outside; any attempt to apply
<literal>_this
</literal>,
2771 <literal>_inc
</literal> or
<literal>_display
</literal> as functions will raise a
2772 compile-time error. In other words,
<emphasis>GHC defines a record selector function
2773 only for fields whose type does not mention the existentially-quantified variables
</emphasis>.
2774 (This example used an underscore in the fields for which record selectors
2775 will not be defined, but that is only programming style; GHC ignores them.)
2779 To make use of these hidden fields, we need to create some helper functions:
2782 inc :: Counter a -
> Counter a
2783 inc (NewCounter x i d t) = NewCounter
2784 { _this = i x, _inc = i, _display = d, tag = t }
2786 display :: Counter a -
> IO ()
2787 display NewCounter{ _this = x, _display = d } = d x
2790 Now we can define counters with different underlying implementations:
2793 counterA :: Counter String
2794 counterA = NewCounter
2795 { _this =
0, _inc = (
1+), _display = print, tag =
"A" }
2797 counterB :: Counter String
2798 counterB = NewCounter
2799 { _this =
"", _inc = ('#':), _display = putStrLn, tag =
"B" }
2802 display (inc counterA) -- prints
"1"
2803 display (inc (inc counterB)) -- prints
"##"
2806 Record update syntax is supported for existentials (and GADTs):
2808 setTag :: Counter a -
> a -
> Counter a
2809 setTag obj t = obj{ tag = t }
2811 The rule for record update is this:
<emphasis>
2812 the types of the updated fields may
2813 mention only the universally-quantified type variables
2814 of the data constructor. For GADTs, the field may mention only types
2815 that appear as a simple type-variable argument in the constructor's result
2816 type
</emphasis>. For example:
2818 data T a b where { T1 { f1::a, f2::b, f3::(b,c) } :: T a b } -- c is existential
2819 upd1 t x = t { f1=x } -- OK: upd1 :: T a b -
> a' -
> T a' b
2820 upd2 t x = t { f3=x } -- BAD (f3's type mentions c, which is
2821 -- existentially quantified)
2823 data G a b where { G1 { g1::a, g2::c } :: G a [c] }
2824 upd3 g x = g { g1=x } -- OK: upd3 :: G a b -
> c -
> G c b
2825 upd4 g x = g { g2=x } -- BAD (f2's type mentions c, which is not a simple
2826 -- type-variable argument in G1's result type)
2834 <title>Restrictions
</title>
2837 There are several restrictions on the ways in which existentially-quantified
2838 constructors can be use.
2847 When pattern matching, each pattern match introduces a new,
2848 distinct, type for each existential type variable. These types cannot
2849 be unified with any other type, nor can they escape from the scope of
2850 the pattern match. For example, these fragments are incorrect:
2858 Here, the type bound by
<function>MkFoo
</function> "escapes", because
<literal>a
</literal>
2859 is the result of
<function>f1
</function>. One way to see why this is wrong is to
2860 ask what type
<function>f1
</function> has:
2864 f1 :: Foo -
> a -- Weird!
2868 What is this
"<literal>a</literal>" in the result type? Clearly we don't mean
2873 f1 :: forall a. Foo -
> a -- Wrong!
2877 The original program is just plain wrong. Here's another sort of error
2881 f2 (Baz1 a b) (Baz1 p q) = a==q
2885 It's ok to say
<literal>a==b
</literal> or
<literal>p==q
</literal>, but
2886 <literal>a==q
</literal> is wrong because it equates the two distinct types arising
2887 from the two
<function>Baz1
</function> constructors.
2895 You can't pattern-match on an existentially quantified
2896 constructor in a
<literal>let
</literal> or
<literal>where
</literal> group of
2897 bindings. So this is illegal:
2901 f3 x = a==b where { Baz1 a b = x }
2904 Instead, use a
<literal>case
</literal> expression:
2907 f3 x = case x of Baz1 a b -
> a==b
2910 In general, you can only pattern-match
2911 on an existentially-quantified constructor in a
<literal>case
</literal> expression or
2912 in the patterns of a function definition.
2914 The reason for this restriction is really an implementation one.
2915 Type-checking binding groups is already a nightmare without
2916 existentials complicating the picture. Also an existential pattern
2917 binding at the top level of a module doesn't make sense, because it's
2918 not clear how to prevent the existentially-quantified type
"escaping".
2919 So for now, there's a simple-to-state restriction. We'll see how
2927 You can't use existential quantification for
<literal>newtype
</literal>
2928 declarations. So this is illegal:
2932 newtype T = forall a. Ord a =
> MkT a
2936 Reason: a value of type
<literal>T
</literal> must be represented as a
2937 pair of a dictionary for
<literal>Ord t
</literal> and a value of type
2938 <literal>t
</literal>. That contradicts the idea that
2939 <literal>newtype
</literal> should have no concrete representation.
2940 You can get just the same efficiency and effect by using
2941 <literal>data
</literal> instead of
<literal>newtype
</literal>. If
2942 there is no overloading involved, then there is more of a case for
2943 allowing an existentially-quantified
<literal>newtype
</literal>,
2944 because the
<literal>data
</literal> version does carry an
2945 implementation cost, but single-field existentially quantified
2946 constructors aren't much use. So the simple restriction (no
2947 existential stuff on
<literal>newtype
</literal>) stands, unless there
2948 are convincing reasons to change it.
2956 You can't use
<literal>deriving
</literal> to define instances of a
2957 data type with existentially quantified data constructors.
2959 Reason: in most cases it would not make sense. For example:;
2962 data T = forall a. MkT [a] deriving( Eq )
2965 To derive
<literal>Eq
</literal> in the standard way we would need to have equality
2966 between the single component of two
<function>MkT
</function> constructors:
2970 (MkT a) == (MkT b) = ???
2973 But
<varname>a
</varname> and
<varname>b
</varname> have distinct types, and so can't be compared.
2974 It's just about possible to imagine examples in which the derived instance
2975 would make sense, but it seems altogether simpler simply to prohibit such
2976 declarations. Define your own instances!
2987 <!-- ====================== Generalised algebraic data types ======================= -->
2989 <sect2 id=
"gadt-style">
2990 <title>Declaring data types with explicit constructor signatures
</title>
2992 <para>When the
<literal>GADTSyntax
</literal> extension is enabled,
2993 GHC allows you to declare an algebraic data type by
2994 giving the type signatures of constructors explicitly. For example:
2998 Just :: a -
> Maybe a
3000 The form is called a
"GADT-style declaration"
3001 because Generalised Algebraic Data Types, described in
<xref linkend=
"gadt"/>,
3002 can only be declared using this form.
</para>
3003 <para>Notice that GADT-style syntax generalises existential types (
<xref linkend=
"existential-quantification"/>).
3004 For example, these two declarations are equivalent:
3006 data Foo = forall a. MkFoo a (a -
> Bool)
3007 data Foo' where { MKFoo :: a -
> (a-
>Bool) -
> Foo' }
3010 <para>Any data type that can be declared in standard Haskell-
98 syntax
3011 can also be declared using GADT-style syntax.
3012 The choice is largely stylistic, but GADT-style declarations differ in one important respect:
3013 they treat class constraints on the data constructors differently.
3014 Specifically, if the constructor is given a type-class context, that
3015 context is made available by pattern matching. For example:
3018 MkSet :: Eq a =
> [a] -
> Set a
3020 makeSet :: Eq a =
> [a] -
> Set a
3021 makeSet xs = MkSet (nub xs)
3023 insert :: a -
> Set a -
> Set a
3024 insert a (MkSet as) | a `elem` as = MkSet as
3025 | otherwise = MkSet (a:as)
3027 A use of
<literal>MkSet
</literal> as a constructor (e.g. in the definition of
<literal>makeSet
</literal>)
3028 gives rise to a
<literal>(Eq a)
</literal>
3029 constraint, as you would expect. The new feature is that pattern-matching on
<literal>MkSet
</literal>
3030 (as in the definition of
<literal>insert
</literal>) makes
<emphasis>available
</emphasis> an
<literal>(Eq a)
</literal>
3031 context. In implementation terms, the
<literal>MkSet
</literal> constructor has a hidden field that stores
3032 the
<literal>(Eq a)
</literal> dictionary that is passed to
<literal>MkSet
</literal>; so
3033 when pattern-matching that dictionary becomes available for the right-hand side of the match.
3034 In the example, the equality dictionary is used to satisfy the equality constraint
3035 generated by the call to
<literal>elem
</literal>, so that the type of
3036 <literal>insert
</literal> itself has no
<literal>Eq
</literal> constraint.
3039 For example, one possible application is to reify dictionaries:
3041 data NumInst a where
3042 MkNumInst :: Num a =
> NumInst a
3044 intInst :: NumInst Int
3047 plus :: NumInst a -
> a -
> a -
> a
3048 plus MkNumInst p q = p + q
3050 Here, a value of type
<literal>NumInst a
</literal> is equivalent
3051 to an explicit
<literal>(Num a)
</literal> dictionary.
3054 All this applies to constructors declared using the syntax of
<xref linkend=
"existential-with-context"/>.
3055 For example, the
<literal>NumInst
</literal> data type above could equivalently be declared
3059 = Num a =
> MkNumInst (NumInst a)
3061 Notice that, unlike the situation when declaring an existential, there is
3062 no
<literal>forall
</literal>, because the
<literal>Num
</literal> constrains the
3063 data type's universally quantified type variable
<literal>a
</literal>.
3064 A constructor may have both universal and existential type variables: for example,
3065 the following two declarations are equivalent:
3068 = forall b. (Num a, Eq b) =
> MkT1 a b
3070 MkT2 :: (Num a, Eq b) =
> a -
> b -
> T2 a
3073 <para>All this behaviour contrasts with Haskell
98's peculiar treatment of
3074 contexts on a data type declaration (Section
4.2.1 of the Haskell
98 Report).
3075 In Haskell
98 the definition
3077 data Eq a =
> Set' a = MkSet' [a]
3079 gives
<literal>MkSet'
</literal> the same type as
<literal>MkSet
</literal> above. But instead of
3080 <emphasis>making available
</emphasis> an
<literal>(Eq a)
</literal> constraint, pattern-matching
3081 on
<literal>MkSet'
</literal> <emphasis>requires
</emphasis> an
<literal>(Eq a)
</literal> constraint!
3082 GHC faithfully implements this behaviour, odd though it is. But for GADT-style declarations,
3083 GHC's behaviour is much more useful, as well as much more intuitive.
3087 The rest of this section gives further details about GADT-style data
3092 The result type of each data constructor must begin with the type constructor being defined.
3093 If the result type of all constructors
3094 has the form
<literal>T a1 ... an
</literal>, where
<literal>a1 ... an
</literal>
3095 are distinct type variables, then the data type is
<emphasis>ordinary
</emphasis>;
3096 otherwise is a
<emphasis>generalised
</emphasis> data type (
<xref linkend=
"gadt"/>).
3100 As with other type signatures, you can give a single signature for several data constructors.
3101 In this example we give a single signature for
<literal>T1
</literal> and
<literal>T2
</literal>:
3110 The type signature of
3111 each constructor is independent, and is implicitly universally quantified as usual.
3112 In particular, the type variable(s) in the
"<literal>data T a where</literal>" header
3113 have no scope, and different constructors may have different universally-quantified type variables:
3115 data T a where -- The 'a' has no scope
3116 T1,T2 :: b -
> T b -- Means forall b. b -
> T b
3117 T3 :: T a -- Means forall a. T a
3122 A constructor signature may mention type class constraints, which can differ for
3123 different constructors. For example, this is fine:
3126 T1 :: Eq b =
> b -
> b -
> T b
3127 T2 :: (Show c, Ix c) =
> c -
> [c] -
> T c
3129 When pattern matching, these constraints are made available to discharge constraints
3130 in the body of the match. For example:
3133 f (T1 x y) | x==y =
"yes"
3137 Note that
<literal>f
</literal> is not overloaded; the
<literal>Eq
</literal> constraint arising
3138 from the use of
<literal>==
</literal> is discharged by the pattern match on
<literal>T1
</literal>
3139 and similarly the
<literal>Show
</literal> constraint arising from the use of
<literal>show
</literal>.
3143 Unlike a Haskell-
98-style
3144 data type declaration, the type variable(s) in the
"<literal>data Set a where</literal>" header
3145 have no scope. Indeed, one can write a kind signature instead:
3147 data Set :: * -
> * where ...
3149 or even a mixture of the two:
3151 data Bar a :: (* -
> *) -
> * where ...
3153 The type variables (if given) may be explicitly kinded, so we could also write the header for
<literal>Foo
</literal>
3156 data Bar a (b :: * -
> *) where ...
3162 You can use strictness annotations, in the obvious places
3163 in the constructor type:
3166 Lit :: !Int -
> Term Int
3167 If :: Term Bool -
> !(Term a) -
> !(Term a) -
> Term a
3168 Pair :: Term a -
> Term b -
> Term (a,b)
3173 You can use a
<literal>deriving
</literal> clause on a GADT-style data type
3174 declaration. For example, these two declarations are equivalent
3176 data Maybe1 a where {
3177 Nothing1 :: Maybe1 a ;
3178 Just1 :: a -
> Maybe1 a
3179 } deriving( Eq, Ord )
3181 data Maybe2 a = Nothing2 | Just2 a
3187 The type signature may have quantified type variables that do not appear
3191 MkFoo :: a -
> (a-
>Bool) -
> Foo
3194 Here the type variable
<literal>a
</literal> does not appear in the result type
3195 of either constructor.
3196 Although it is universally quantified in the type of the constructor, such
3197 a type variable is often called
"existential".
3198 Indeed, the above declaration declares precisely the same type as
3199 the
<literal>data Foo
</literal> in
<xref linkend=
"existential-quantification"/>.
3201 The type may contain a class context too, of course:
3204 MkShowable :: Show a =
> a -
> Showable
3209 You can use record syntax on a GADT-style data type declaration:
3213 Adult :: { name :: String, children :: [Person] } -
> Person
3214 Child :: Show a =
> { name :: !String, funny :: a } -
> Person
3216 As usual, for every constructor that has a field
<literal>f
</literal>, the type of
3217 field
<literal>f
</literal> must be the same (modulo alpha conversion).
3218 The
<literal>Child
</literal> constructor above shows that the signature
3219 may have a context, existentially-quantified variables, and strictness annotations,
3220 just as in the non-record case. (NB: the
"type" that follows the double-colon
3221 is not really a type, because of the record syntax and strictness annotations.
3222 A
"type" of this form can appear only in a constructor signature.)
3226 Record updates are allowed with GADT-style declarations,
3227 only fields that have the following property: the type of the field
3228 mentions no existential type variables.
3232 As in the case of existentials declared using the Haskell-
98-like record syntax
3233 (
<xref linkend=
"existential-records"/>),
3234 record-selector functions are generated only for those fields that have well-typed
3236 Here is the example of that section, in GADT-style syntax:
3238 data Counter a where
3239 NewCounter :: { _this :: self
3240 , _inc :: self -
> self
3241 , _display :: self -
> IO ()
3245 As before, only one selector function is generated here, that for
<literal>tag
</literal>.
3246 Nevertheless, you can still use all the field names in pattern matching and record construction.
3250 In a GADT-style data type declaration there is no obvious way to specify that a data constructor
3251 should be infix, which makes a difference if you derive
<literal>Show
</literal> for the type.
3252 (Data constructors declared infix are displayed infix by the derived
<literal>show
</literal>.)
3253 So GHC implements the following design: a data constructor declared in a GADT-style data type
3254 declaration is displayed infix by
<literal>Show
</literal> iff (a) it is an operator symbol,
3255 (b) it has two arguments, (c) it has a programmer-supplied fixity declaration. For example
3259 (:--:) :: Int -
> Bool -
> T Int
3262 </itemizedlist></para>
3266 <title>Generalised Algebraic Data Types (GADTs)
</title>
3268 <para>Generalised Algebraic Data Types generalise ordinary algebraic data types
3269 by allowing constructors to have richer return types. Here is an example:
3272 Lit :: Int -
> Term Int
3273 Succ :: Term Int -
> Term Int
3274 IsZero :: Term Int -
> Term Bool
3275 If :: Term Bool -
> Term a -
> Term a -
> Term a
3276 Pair :: Term a -
> Term b -
> Term (a,b)
3278 Notice that the return type of the constructors is not always
<literal>Term a
</literal>, as is the
3279 case with ordinary data types. This generality allows us to
3280 write a well-typed
<literal>eval
</literal> function
3281 for these
<literal>Terms
</literal>:
3285 eval (Succ t) =
1 + eval t
3286 eval (IsZero t) = eval t ==
0
3287 eval (If b e1 e2) = if eval b then eval e1 else eval e2
3288 eval (Pair e1 e2) = (eval e1, eval e2)
3290 The key point about GADTs is that
<emphasis>pattern matching causes type refinement
</emphasis>.
3291 For example, in the right hand side of the equation
3296 the type
<literal>a
</literal> is refined to
<literal>Int
</literal>. That's the whole point!
3297 A precise specification of the type rules is beyond what this user manual aspires to,
3298 but the design closely follows that described in
3300 url=
"http://research.microsoft.com/%7Esimonpj/papers/gadt/">Simple
3301 unification-based type inference for GADTs
</ulink>,
3303 The general principle is this:
<emphasis>type refinement is only carried out
3304 based on user-supplied type annotations
</emphasis>.
3305 So if no type signature is supplied for
<literal>eval
</literal>, no type refinement happens,
3306 and lots of obscure error messages will
3307 occur. However, the refinement is quite general. For example, if we had:
3309 eval :: Term a -
> a -
> a
3310 eval (Lit i) j = i+j
3312 the pattern match causes the type
<literal>a
</literal> to be refined to
<literal>Int
</literal> (because of the type
3313 of the constructor
<literal>Lit
</literal>), and that refinement also applies to the type of
<literal>j
</literal>, and
3314 the result type of the
<literal>case
</literal> expression. Hence the addition
<literal>i+j
</literal> is legal.
3317 These and many other examples are given in papers by Hongwei Xi, and
3318 Tim Sheard. There is a longer introduction
3319 <ulink url=
"http://www.haskell.org/haskellwiki/GADT">on the wiki
</ulink>,
3321 <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
3322 may use different notation to that implemented in GHC.
3325 The rest of this section outlines the extensions to GHC that support GADTs. The extension is enabled with
3326 <option>-XGADTs
</option>. The
<option>-XGADTs
</option> flag also sets
<option>-XRelaxedPolyRec
</option>.
3329 A GADT can only be declared using GADT-style syntax (
<xref linkend=
"gadt-style"/>);
3330 the old Haskell-
98 syntax for data declarations always declares an ordinary data type.
3331 The result type of each constructor must begin with the type constructor being defined,
3332 but for a GADT the arguments to the type constructor can be arbitrary monotypes.
3333 For example, in the
<literal>Term
</literal> data
3334 type above, the type of each constructor must end with
<literal>Term ty
</literal>, but
3335 the
<literal>ty
</literal> need not be a type variable (e.g. the
<literal>Lit
</literal>
3340 It is permitted to declare an ordinary algebraic data type using GADT-style syntax.
3341 What makes a GADT into a GADT is not the syntax, but rather the presence of data constructors
3342 whose result type is not just
<literal>T a b
</literal>.
3346 You cannot use a
<literal>deriving
</literal> clause for a GADT; only for
3347 an ordinary data type.
3351 As mentioned in
<xref linkend=
"gadt-style"/>, record syntax is supported.
3355 Lit :: { val :: Int } -
> Term Int
3356 Succ :: { num :: Term Int } -
> Term Int
3357 Pred :: { num :: Term Int } -
> Term Int
3358 IsZero :: { arg :: Term Int } -
> Term Bool
3359 Pair :: { arg1 :: Term a
3362 If :: { cnd :: Term Bool
3367 However, for GADTs there is the following additional constraint:
3368 every constructor that has a field
<literal>f
</literal> must have
3369 the same result type (modulo alpha conversion)
3370 Hence, in the above example, we cannot merge the
<literal>num
</literal>
3371 and
<literal>arg
</literal> fields above into a
3372 single name. Although their field types are both
<literal>Term Int
</literal>,
3373 their selector functions actually have different types:
3376 num :: Term Int -
> Term Int
3377 arg :: Term Bool -
> Term Int
3382 When pattern-matching against data constructors drawn from a GADT,
3383 for example in a
<literal>case
</literal> expression, the following rules apply:
3385 <listitem><para>The type of the scrutinee must be rigid.
</para></listitem>
3386 <listitem><para>The type of the entire
<literal>case
</literal> expression must be rigid.
</para></listitem>
3387 <listitem><para>The type of any free variable mentioned in any of
3388 the
<literal>case
</literal> alternatives must be rigid.
</para></listitem>
3390 A type is
"rigid" if it is completely known to the compiler at its binding site. The easiest
3391 way to ensure that a variable a rigid type is to give it a type signature.
3392 For more precise details see
<ulink url=
"http://research.microsoft.com/%7Esimonpj/papers/gadt">
3393 Simple unification-based type inference for GADTs
3394 </ulink>. The criteria implemented by GHC are given in the Appendix.
3404 <!-- ====================== End of Generalised algebraic data types ======================= -->
3406 <sect1 id=
"deriving">
3407 <title>Extensions to the
"deriving" mechanism
</title>
3409 <sect2 id=
"deriving-inferred">
3410 <title>Inferred context for deriving clauses
</title>
3413 The Haskell Report is vague about exactly when a
<literal>deriving
</literal> clause is
3416 data T0 f a = MkT0 a deriving( Eq )
3417 data T1 f a = MkT1 (f a) deriving( Eq )
3418 data T2 f a = MkT2 (f (f a)) deriving( Eq )
3420 The natural generated
<literal>Eq
</literal> code would result in these instance declarations:
3422 instance Eq a =
> Eq (T0 f a) where ...
3423 instance Eq (f a) =
> Eq (T1 f a) where ...
3424 instance Eq (f (f a)) =
> Eq (T2 f a) where ...
3426 The first of these is obviously fine. The second is still fine, although less obviously.
3427 The third is not Haskell
98, and risks losing termination of instances.
3430 GHC takes a conservative position: it accepts the first two, but not the third. The rule is this:
3431 each constraint in the inferred instance context must consist only of type variables,
3432 with no repetitions.
3435 This rule is applied regardless of flags. If you want a more exotic context, you can write
3436 it yourself, using the
<link linkend=
"stand-alone-deriving">standalone deriving mechanism
</link>.
3440 <sect2 id=
"stand-alone-deriving">
3441 <title>Stand-alone deriving declarations
</title>
3444 GHC now allows stand-alone
<literal>deriving
</literal> declarations, enabled by
<literal>-XStandaloneDeriving
</literal>:
3446 data Foo a = Bar a | Baz String
3448 deriving instance Eq a =
> Eq (Foo a)
3450 The syntax is identical to that of an ordinary instance declaration apart from (a) the keyword
3451 <literal>deriving
</literal>, and (b) the absence of the
<literal>where
</literal> part.
3452 Note the following points:
3455 You must supply an explicit context (in the example the context is
<literal>(Eq a)
</literal>),
3456 exactly as you would in an ordinary instance declaration.
3457 (In contrast, in a
<literal>deriving
</literal> clause
3458 attached to a data type declaration, the context is inferred.)
3462 A
<literal>deriving instance
</literal> declaration
3463 must obey the same rules concerning form and termination as ordinary instance declarations,
3464 controlled by the same flags; see
<xref linkend=
"instance-decls"/>.
3468 Unlike a
<literal>deriving
</literal>
3469 declaration attached to a
<literal>data
</literal> declaration, the instance can be more specific
3470 than the data type (assuming you also use
3471 <literal>-XFlexibleInstances
</literal>,
<xref linkend=
"instance-rules"/>). Consider
3474 data Foo a = Bar a | Baz String
3476 deriving instance Eq a =
> Eq (Foo [a])
3477 deriving instance Eq a =
> Eq (Foo (Maybe a))
3479 This will generate a derived instance for
<literal>(Foo [a])
</literal> and
<literal>(Foo (Maybe a))
</literal>,
3480 but other types such as
<literal>(Foo (Int,Bool))
</literal> will not be an instance of
<literal>Eq
</literal>.
3484 Unlike a
<literal>deriving
</literal>
3485 declaration attached to a
<literal>data
</literal> declaration,
3486 GHC does not restrict the form of the data type. Instead, GHC simply generates the appropriate
3487 boilerplate code for the specified class, and typechecks it. If there is a type error, it is
3488 your problem. (GHC will show you the offending code if it has a type error.)
3489 The merit of this is that you can derive instances for GADTs and other exotic
3490 data types, providing only that the boilerplate code does indeed typecheck. For example:
3496 deriving instance Show (T a)
3498 In this example, you cannot say
<literal>... deriving( Show )
</literal> on the
3499 data type declaration for
<literal>T
</literal>,
3500 because
<literal>T
</literal> is a GADT, but you
<emphasis>can
</emphasis> generate
3501 the instance declaration using stand-alone deriving.
3506 <para>The stand-alone syntax is generalised for newtypes in exactly the same
3507 way that ordinary
<literal>deriving
</literal> clauses are generalised (
<xref linkend=
"newtype-deriving"/>).
3510 newtype Foo a = MkFoo (State Int a)
3512 deriving instance MonadState Int Foo
3514 GHC always treats the
<emphasis>last
</emphasis> parameter of the instance
3515 (
<literal>Foo
</literal> in this example) as the type whose instance is being derived.
3517 </itemizedlist></para>
3522 <sect2 id=
"deriving-typeable">
3523 <title>Deriving clause for extra classes (
<literal>Typeable
</literal>,
<literal>Data
</literal>, etc)
</title>
3526 Haskell
98 allows the programmer to add
"<literal>deriving( Eq, Ord )</literal>" to a data type
3527 declaration, to generate a standard instance declaration for classes specified in the
<literal>deriving
</literal> clause.
3528 In Haskell
98, the only classes that may appear in the
<literal>deriving
</literal> clause are the standard
3529 classes
<literal>Eq
</literal>,
<literal>Ord
</literal>,
3530 <literal>Enum
</literal>,
<literal>Ix
</literal>,
<literal>Bounded
</literal>,
<literal>Read
</literal>, and
<literal>Show
</literal>.
3533 GHC extends this list with several more classes that may be automatically derived:
3535 <listitem><para> With
<option>-XDeriveDataTypeable
</option>, you can derive instances of the classes
3536 <literal>Typeable
</literal>, and
<literal>Data
</literal>, defined in the library
3537 modules
<literal>Data.Typeable
</literal> and
<literal>Data.Data
</literal> respectively.
3539 <para>Since GHC
7.8.1,
<literal>Typeable
</literal> is kind-polymorphic (see
3540 <xref linkend=
"kind-polymorphism"/>) and can be derived for any datatype and
3541 type class. Instances for datatypes can be derived by attaching a
3542 <literal>deriving Typeable
</literal> clause to the datatype declaration, or by
3543 using standalone deriving (see
<xref linkend=
"stand-alone-deriving"/>).
3544 Instances for type classes can only be derived using standalone deriving.
3545 For data families,
<literal>Typeable
</literal> should only be derived for the
3546 uninstantiated family type; each instance will then automatically have a
3547 <literal>Typeable
</literal> instance too.
3548 See also
<xref linkend=
"auto-derive-typeable"/>.
3551 Also since GHC
7.8.1, handwritten (ie. not derived) instances of
3552 <literal>Typeable
</literal> are forbidden, and will result in an error.
3556 <listitem><para> With
<option>-XDeriveGeneric
</option>, you can derive
3557 instances of the classes
<literal>Generic
</literal> and
3558 <literal>Generic1
</literal>, defined in
<literal>GHC.Generics
</literal>.
3559 You can use these to define generic functions,
3560 as described in
<xref linkend=
"generic-programming"/>.
3563 <listitem><para> With
<option>-XDeriveFunctor
</option>, you can derive instances of
3564 the class
<literal>Functor
</literal>,
3565 defined in
<literal>GHC.Base
</literal>.
3568 <listitem><para> With
<option>-XDeriveFoldable
</option>, you can derive instances of
3569 the class
<literal>Foldable
</literal>,
3570 defined in
<literal>Data.Foldable
</literal>.
3573 <listitem><para> With
<option>-XDeriveTraversable
</option>, you can derive instances of
3574 the class
<literal>Traversable
</literal>,
3575 defined in
<literal>Data.Traversable
</literal>.
3578 In each case the appropriate class must be in scope before it
3579 can be mentioned in the
<literal>deriving
</literal> clause.
3583 <sect2 id=
"auto-derive-typeable">
3584 <title>Automatically deriving
<literal>Typeable
</literal> instances
</title>
3587 The flag
<option>-XAutoDeriveTypeable
</option> triggers the generation
3588 of derived
<literal>Typeable
</literal> instances for every datatype and type
3589 class declaration in the module it is used. It will also generate
3590 <literal>Typeable
</literal> instances for any promoted data constructors
3591 (
<xref linkend=
"promotion"/>). This flag implies
3592 <option>-XDeriveDataTypeable
</option> (
<xref linkend=
"deriving-typeable"/>).
3597 <sect2 id=
"newtype-deriving">
3598 <title>Generalised derived instances for newtypes
</title>
3601 When you define an abstract type using
<literal>newtype
</literal>, you may want
3602 the new type to inherit some instances from its representation. In
3603 Haskell
98, you can inherit instances of
<literal>Eq
</literal>,
<literal>Ord
</literal>,
3604 <literal>Enum
</literal> and
<literal>Bounded
</literal> by deriving them, but for any
3605 other classes you have to write an explicit instance declaration. For
3606 example, if you define
3609 newtype Dollars = Dollars Int
3612 and you want to use arithmetic on
<literal>Dollars
</literal>, you have to
3613 explicitly define an instance of
<literal>Num
</literal>:
3616 instance Num Dollars where
3617 Dollars a + Dollars b = Dollars (a+b)
3620 All the instance does is apply and remove the
<literal>newtype
</literal>
3621 constructor. It is particularly galling that, since the constructor
3622 doesn't appear at run-time, this instance declaration defines a
3623 dictionary which is
<emphasis>wholly equivalent
</emphasis> to the
<literal>Int
</literal>
3624 dictionary, only slower!
3628 <sect3 id=
"generalized-newtype-deriving"> <title> Generalising the deriving clause
</title>
3630 GHC now permits such instances to be derived instead,
3631 using the flag
<option>-XGeneralizedNewtypeDeriving
</option>,
3634 newtype Dollars = Dollars Int deriving (Eq,Show,Num)
3637 and the implementation uses the
<emphasis>same
</emphasis> <literal>Num
</literal> dictionary
3638 for
<literal>Dollars
</literal> as for
<literal>Int
</literal>. Notionally, the compiler
3639 derives an instance declaration of the form
3642 instance Num Int =
> Num Dollars
3645 which just adds or removes the
<literal>newtype
</literal> constructor according to the type.
3649 We can also derive instances of constructor classes in a similar
3650 way. For example, suppose we have implemented state and failure monad
3651 transformers, such that
3654 instance Monad m =
> Monad (State s m)
3655 instance Monad m =
> Monad (Failure m)
3657 In Haskell
98, we can define a parsing monad by
3659 type Parser tok m a = State [tok] (Failure m) a
3662 which is automatically a monad thanks to the instance declarations
3663 above. With the extension, we can make the parser type abstract,
3664 without needing to write an instance of class
<literal>Monad
</literal>, via
3667 newtype Parser tok m a = Parser (State [tok] (Failure m) a)
3670 In this case the derived instance declaration is of the form
3672 instance Monad (State [tok] (Failure m)) =
> Monad (Parser tok m)
3675 Notice that, since
<literal>Monad
</literal> is a constructor class, the
3676 instance is a
<emphasis>partial application
</emphasis> of the new type, not the
3677 entire left hand side. We can imagine that the type declaration is
3678 "eta-converted" to generate the context of the instance
3683 We can even derive instances of multi-parameter classes, provided the
3684 newtype is the last class parameter. In this case, a ``partial
3685 application'' of the class appears in the
<literal>deriving
</literal>
3686 clause. For example, given the class
3689 class StateMonad s m | m -
> s where ...
3690 instance Monad m =
> StateMonad s (State s m) where ...
3692 then we can derive an instance of
<literal>StateMonad
</literal> for
<literal>Parser
</literal>s by
3694 newtype Parser tok m a = Parser (State [tok] (Failure m) a)
3695 deriving (Monad, StateMonad [tok])
3698 The derived instance is obtained by completing the application of the
3699 class to the new type:
3702 instance StateMonad [tok] (State [tok] (Failure m)) =
>
3703 StateMonad [tok] (Parser tok m)
3708 As a result of this extension, all derived instances in newtype
3709 declarations are treated uniformly (and implemented just by reusing
3710 the dictionary for the representation type),
<emphasis>except
</emphasis>
3711 <literal>Show
</literal> and
<literal>Read
</literal>, which really behave differently for
3712 the newtype and its representation.
3716 <sect3> <title> A more precise specification
</title>
3718 Derived instance declarations are constructed as follows. Consider the
3719 declaration (after expansion of any type synonyms)
3722 newtype T v1...vn = T' (t vk+
1...vn) deriving (c1...cm)
3728 The
<literal>ci
</literal> are partial applications of
3729 classes of the form
<literal>C t1'...tj'
</literal>, where the arity of
<literal>C
</literal>
3730 is exactly
<literal>j+
1</literal>. That is,
<literal>C
</literal> lacks exactly one type argument.
3733 The
<literal>k
</literal> is chosen so that
<literal>ci (T v1...vk)
</literal> is well-kinded.
3736 The type
<literal>t
</literal> is an arbitrary type.
3739 The type variables
<literal>vk+
1...vn
</literal> do not occur in
<literal>t
</literal>,
3740 nor in the
<literal>ci
</literal>, and
3743 None of the
<literal>ci
</literal> is
<literal>Read
</literal>,
<literal>Show
</literal>,
3744 <literal>Typeable
</literal>, or
<literal>Data
</literal>. These classes
3745 should not
"look through" the type or its constructor. You can still
3746 derive these classes for a newtype, but it happens in the usual way, not
3747 via this new mechanism.
3750 It is safe to coerce each of the methods of
<literal>ci
</literal>. That is,
3751 the missing last argument to each of the
<literal>ci
</literal> is not used
3752 at a nominal role in any of the
<literal>ci
</literal>'s methods.
3753 (See
<xref linkend=
"roles"/>.)
</para></listitem>
3755 Then, for each
<literal>ci
</literal>, the derived instance
3758 instance ci t =
> ci (T v1...vk)
3760 As an example which does
<emphasis>not
</emphasis> work, consider
3762 newtype NonMonad m s = NonMonad (State s m s) deriving Monad
3764 Here we cannot derive the instance
3766 instance Monad (State s m) =
> Monad (NonMonad m)
3769 because the type variable
<literal>s
</literal> occurs in
<literal>State s m
</literal>,
3770 and so cannot be
"eta-converted" away. It is a good thing that this
3771 <literal>deriving
</literal> clause is rejected, because
<literal>NonMonad m
</literal> is
3772 not, in fact, a monad --- for the same reason. Try defining
3773 <literal>>>=
</literal> with the correct type: you won't be able to.
3777 Notice also that the
<emphasis>order
</emphasis> of class parameters becomes
3778 important, since we can only derive instances for the last one. If the
3779 <literal>StateMonad
</literal> class above were instead defined as
3782 class StateMonad m s | m -
> s where ...
3785 then we would not have been able to derive an instance for the
3786 <literal>Parser
</literal> type above. We hypothesise that multi-parameter
3787 classes usually have one
"main" parameter for which deriving new
3788 instances is most interesting.
3790 <para>Lastly, all of this applies only for classes other than
3791 <literal>Read
</literal>,
<literal>Show
</literal>,
<literal>Typeable
</literal>,
3792 and
<literal>Data
</literal>, for which the built-in derivation applies (section
3793 4.3.3. of the Haskell Report).
3794 (For the standard classes
<literal>Eq
</literal>,
<literal>Ord
</literal>,
3795 <literal>Ix
</literal>, and
<literal>Bounded
</literal> it is immaterial whether
3796 the standard method is used or the one described here.)
3803 <!-- TYPE SYSTEM EXTENSIONS -->
3804 <sect1 id=
"type-class-extensions">
3805 <title>Class and instances declarations
</title>
3807 <sect2 id=
"multi-param-type-classes">
3808 <title>Class declarations
</title>
3811 This section, and the next one, documents GHC's type-class extensions.
3812 There's lots of background in the paper
<ulink
3813 url=
"http://research.microsoft.com/~simonpj/Papers/type-class-design-space/">Type
3814 classes: exploring the design space
</ulink> (Simon Peyton Jones, Mark
3815 Jones, Erik Meijer).
3819 <title>Multi-parameter type classes
</title>
3821 Multi-parameter type classes are permitted, with flag
<option>-XMultiParamTypeClasses
</option>.
3826 class Collection c a where
3827 union :: c a -
> c a -
> c a
3834 <sect3 id=
"superclass-rules">
3835 <title>The superclasses of a class declaration
</title>
3838 In Haskell
98 the context of a class declaration (which introduces superclasses)
3839 must be simple; that is, each predicate must consist of a class applied to
3840 type variables. The flag
<option>-XFlexibleContexts
</option>
3841 (
<xref linkend=
"flexible-contexts"/>)
3842 lifts this restriction,
3843 so that the only restriction on the context in a class declaration is
3844 that the class hierarchy must be acyclic. So these class declarations are OK:
3848 class Functor (m k) =
> FiniteMap m k where
3851 class (Monad m, Monad (t m)) =
> Transform t m where
3852 lift :: m a -
> (t m) a
3858 As in Haskell
98, The class hierarchy must be acyclic. However, the definition
3859 of
"acyclic" involves only the superclass relationships. For example,
3865 op :: D b =
> a -
> b -
> b
3868 class C a =
> D a where { ... }
3872 Here,
<literal>C
</literal> is a superclass of
<literal>D
</literal>, but it's OK for a
3873 class operation
<literal>op
</literal> of
<literal>C
</literal> to mention
<literal>D
</literal>. (It
3874 would not be OK for
<literal>D
</literal> to be a superclass of
<literal>C
</literal>.)
3877 With the extension that adds a
<link linkend=
"constraint-kind">kind of constraints
</link>,
3878 you can write more exotic superclass definitions. The superclass cycle check is even more
3879 liberal in these case. For example, this is OK:
3883 meth :: cls c =
> c -
> c
3885 class A B c =
> B c where
3888 A superclass context for a class
<literal>C
</literal> is allowed if, after expanding
3889 type synonyms to their right-hand-sides, and uses of classes (other than
<literal>C
</literal>)
3890 to their superclasses,
<literal>C
</literal> does not occur syntactically in the context.
3897 <sect3 id=
"class-method-types">
3898 <title>Class method types
</title>
3901 Haskell
98 prohibits class method types to mention constraints on the
3902 class type variable, thus:
3905 fromList :: [a] -
> s a
3906 elem :: Eq a =
> a -
> s a -
> Bool
3908 The type of
<literal>elem
</literal> is illegal in Haskell
98, because it
3909 contains the constraint
<literal>Eq a
</literal>, constrains only the
3910 class type variable (in this case
<literal>a
</literal>).
3911 GHC lifts this restriction (flag
<option>-XConstrainedClassMethods
</option>).
3918 <sect3 id=
"class-default-signatures">
3919 <title>Default method signatures
</title>
3922 Haskell
98 allows you to define a default implementation when declaring a class:
3928 The type of the
<literal>enum
</literal> method is
<literal>[a]
</literal>, and
3929 this is also the type of the default method. You can lift this restriction
3930 and give another type to the default method using the flag
3931 <option>-XDefaultSignatures
</option>. For instance, if you have written a
3932 generic implementation of enumeration in a class
<literal>GEnum
</literal>
3933 with method
<literal>genum
</literal> in terms of
<literal>GHC.Generics
</literal>,
3934 you can specify a default method that uses that generic implementation:
3938 default enum :: (Generic a, GEnum (Rep a)) =
> [a]
3941 We reuse the keyword
<literal>default
</literal> to signal that a signature
3942 applies to the default method only; when defining instances of the
3943 <literal>Enum
</literal> class, the original type
<literal>[a]
</literal> of
3944 <literal>enum
</literal> still applies. When giving an empty instance, however,
3945 the default implementation
<literal>map to genum
</literal> is filled-in,
3946 and type-checked with the type
3947 <literal>(Generic a, GEnum (Rep a)) =
> [a]
</literal>.
3951 We use default signatures to simplify generic programming in GHC
3952 (
<xref linkend=
"generic-programming"/>).
3958 <sect3 id=
"nullary-type-classes">
3959 <title>Nullary type classes
</title>
3960 Nullary (no parameter) type classes are enabled with
<option>-XNullaryTypeClasses
</option>.
3961 Since there are no available parameters, there can be at most one instance
3962 of a nullary class. A nullary type class might be used to document some assumption
3963 in a type signature (such as reliance on the Riemann hypothesis) or add some
3964 globally configurable settings in a program. For example,
3967 class RiemannHypothesis where
3970 -- Deterministic version of the Miller test
3971 -- correctness depends on the generalized Riemann hypothesis
3972 isPrime :: RiemannHypothesis =
> Integer -
> Bool
3973 isPrime n = assumeRH (...)
3976 The type signature of
<literal>isPrime
</literal> informs users that its correctness
3977 depends on an unproven conjecture. If the function is used, the user has
3978 to acknowledge the dependence with:
3981 instance RiemannHypothesis where
3988 <sect2 id=
"functional-dependencies">
3989 <title>Functional dependencies
3992 <para> Functional dependencies are implemented as described by Mark Jones
3993 in
“<ulink url=
"http://citeseer.ist.psu.edu/jones00type.html">Type Classes with Functional Dependencies
</ulink>”, Mark P. Jones,
3994 In Proceedings of the
9th European Symposium on Programming,
3995 ESOP
2000, Berlin, Germany, March
2000, Springer-Verlag LNCS
1782,
3999 Functional dependencies are introduced by a vertical bar in the syntax of a
4000 class declaration; e.g.
4002 class (Monad m) =
> MonadState s m | m -
> s where ...
4004 class Foo a b c | a b -
> c where ...
4006 There should be more documentation, but there isn't (yet). Yell if you need it.
4009 <sect3><title>Rules for functional dependencies
</title>
4011 In a class declaration, all of the class type variables must be reachable (in the sense
4012 mentioned in
<xref linkend=
"flexible-contexts"/>)
4013 from the free variables of each method type.
4017 class Coll s a where
4019 insert :: s -
> a -
> s
4022 is not OK, because the type of
<literal>empty
</literal> doesn't mention
4023 <literal>a
</literal>. Functional dependencies can make the type variable
4026 class Coll s a | s -
> a where
4028 insert :: s -
> a -
> s
4031 Alternatively
<literal>Coll
</literal> might be rewritten
4034 class Coll s a where
4036 insert :: s a -
> a -
> s a
4040 which makes the connection between the type of a collection of
4041 <literal>a
</literal>'s (namely
<literal>(s a)
</literal>) and the element type
<literal>a
</literal>.
4042 Occasionally this really doesn't work, in which case you can split the
4050 class CollE s =
> Coll s a where
4051 insert :: s -
> a -
> s
4058 <title>Background on functional dependencies
</title>
4060 <para>The following description of the motivation and use of functional dependencies is taken
4061 from the Hugs user manual, reproduced here (with minor changes) by kind
4062 permission of Mark Jones.
4065 Consider the following class, intended as part of a
4066 library for collection types:
4068 class Collects e ce where
4070 insert :: e -
> ce -
> ce
4071 member :: e -
> ce -
> Bool
4073 The type variable e used here represents the element type, while ce is the type
4074 of the container itself. Within this framework, we might want to define
4075 instances of this class for lists or characteristic functions (both of which
4076 can be used to represent collections of any equality type), bit sets (which can
4077 be used to represent collections of characters), or hash tables (which can be
4078 used to represent any collection whose elements have a hash function). Omitting
4079 standard implementation details, this would lead to the following declarations:
4081 instance Eq e =
> Collects e [e] where ...
4082 instance Eq e =
> Collects e (e -
> Bool) where ...
4083 instance Collects Char BitSet where ...
4084 instance (Hashable e, Collects a ce)
4085 =
> Collects e (Array Int ce) where ...
4087 All this looks quite promising; we have a class and a range of interesting
4088 implementations. Unfortunately, there are some serious problems with the class
4089 declaration. First, the empty function has an ambiguous type:
4091 empty :: Collects e ce =
> ce
4093 By
"ambiguous" we mean that there is a type variable e that appears on the left
4094 of the
<literal>=
></literal> symbol, but not on the right. The problem with
4095 this is that, according to the theoretical foundations of Haskell overloading,