2 single: language, GHC extensions
4 As with all known Haskell systems, GHC implements some extensions to the
5 standard Haskell language. They can all be enabled or disabled by command line
6 flags or language pragmas. By default GHC understands the most recent Haskell
7 version it supports, plus a handful of extensions.
9 Some of the Glasgow extensions serve to give you access to the
10 underlying facilities with which we implement Haskell. Thus, you can get
11 at the Raw Iron, if you are willing to write some non-portable code at a
12 more primitive level. You need not be “stuck” on performance because of
13 the implementation costs of Haskell's "high-level" features—you can
14 always code "under" them. In an extreme case, you can write all your
15 time-critical code in C, and then just glue it together with Haskell!
17 Before you get too carried away working at the lowest level (e.g.,
18 sloshing ``MutableByteArray#``\ s around your program), you may wish to
19 check if there are libraries that provide a "Haskellised veneer" over
20 the features you want. The separate
21 `libraries documentation <../libraries/index.html>`__ describes all the
22 libraries that come with GHC.
30 single: language; option
31 single: options; language
32 single: extensions; options controlling
34 The language extensions control what variation of the language are
37 Language options can be controlled in two ways:
39 - Every language option can switched on by a command-line flag
40 "``-X...``" (e.g. ``-XTemplateHaskell``), and switched off by the
41 flag "``-XNo...``"; (e.g. ``-XNoTemplateHaskell``).
43 - Language options recognised by Cabal can also be enabled using the
44 ``LANGUAGE`` pragma, thus ``{-# LANGUAGE TemplateHaskell #-}`` (see
45 :ref:`language-pragma`).
47 GHC supports these language options:
52 Although not recommended, the deprecated :ghc-flag:`-fglasgow-exts` flag enables
53 a large swath of the extensions supported by GHC at once.
55 .. ghc-flag:: -fglasgow-exts
56 :shortdesc: Deprecated. Enable most language extensions;
57 see :ref:`options-language` for exactly which ones.
59 :reverse: -fno-glasgow-exts
62 The flag ``-fglasgow-exts`` is equivalent to enabling the following extensions:
64 .. include:: what_glasgow_exts_does.rst
66 Enabling these options is the *only* effect of ``-fglasgow-exts``. We are trying
67 to move away from this portmanteau flag, and towards enabling features
72 Unboxed types and primitive operations
73 ======================================
75 GHC is built on a raft of primitive data types and operations;
76 "primitive" in the sense that they cannot be defined in Haskell itself.
77 While you really can use this stuff to write fast code, we generally
78 find it a lot less painful, and more satisfying in the long run, to use
79 higher-level language features and libraries. With any luck, the code
80 you write will be optimised to the efficient unboxed version in any
81 case. And if it isn't, we'd like to know about it.
83 All these primitive data types and operations are exported by the
84 library ``GHC.Prim``, for which there is
85 :ghc-prim-ref:`detailed online documentation <GHC.Prim.>`. (This
86 documentation is generated from the file ``compiler/prelude/primops.txt.pp``.)
88 If you want to mention any of the primitive data types or operations in
89 your program, you must first import ``GHC.Prim`` to bring them into
90 scope. Many of them have names ending in ``#``, and to mention such names
91 you need the :extension:`MagicHash` extension.
93 The primops make extensive use of `unboxed types <#glasgow-unboxed>`__
94 and `unboxed tuples <#unboxed-tuples>`__, which we briefly summarise
102 Most types in GHC are boxed, which means that values of that type are
103 represented by a pointer to a heap object. The representation of a
104 Haskell ``Int``, for example, is a two-word heap object. An unboxed
105 type, however, is represented by the value itself, no pointers or heap
106 allocation are involved.
108 Unboxed types correspond to the “raw machine” types you would use in C:
109 ``Int#`` (long int), ``Double#`` (double), ``Addr#`` (void \*), etc. The
110 *primitive operations* (PrimOps) on these types are what you might
111 expect; e.g., ``(+#)`` is addition on ``Int#``\ s, and is the
112 machine-addition that we all know and love—usually one instruction.
114 Primitive (unboxed) types cannot be defined in Haskell, and are
115 therefore built into the language and compiler. Primitive types are
116 always unlifted; that is, a value of a primitive type cannot be bottom.
117 (Note: a "boxed" type means that a value is represented by a pointer to a heap
118 object; a "lifted" type means that terms of that type may be bottom. See
119 the next paragraph for an example.)
120 We use the convention (but it is only a convention) that primitive
121 types, values, and operations have a ``#`` suffix (see
122 :ref:`magic-hash`). For some primitive types we have special syntax for
123 literals, also described in the `same section <#magic-hash>`__.
125 Primitive values are often represented by a simple bit-pattern, such as
126 ``Int#``, ``Float#``, ``Double#``. But this is not necessarily the case:
127 a primitive value might be represented by a pointer to a heap-allocated
128 object. Examples include ``Array#``, the type of primitive arrays. Thus,
129 ``Array#`` is an unlifted, boxed type. A
130 primitive array is heap-allocated because it is too big a value to fit
131 in a register, and would be too expensive to copy around; in a sense, it
132 is accidental that it is represented by a pointer. If a pointer
133 represents a primitive value, then it really does point to that value:
134 no unevaluated thunks, no indirections. Nothing can be at the other end
135 of the pointer than the primitive value. A numerically-intensive program
136 using unboxed types can go a *lot* faster than its “standard”
137 counterpart—we saw a threefold speedup on one example.
142 Because unboxed types are represented without the use of pointers, we
143 cannot store them in use a polymorphic datatype at an unboxed type.
144 For example, the ``Just`` node
145 of ``Just 42#`` would have to be different from the ``Just`` node of
146 ``Just 42``; the former stores an integer directly, while the latter
147 stores a pointer. GHC currently does not support this variety of ``Just``
148 nodes (nor for any other datatype). Accordingly, the *kind* of an unboxed
149 type is different from the kind of a boxed type.
151 The Haskell Report describes that ``*`` (spelled ``Type`` and imported from
152 ``Data.Kind`` in the GHC dialect of Haskell) is the kind of ordinary datatypes,
153 such as ``Int``. Furthermore, type constructors can have kinds with arrows; for
154 example, ``Maybe`` has kind ``Type -> Type``. Unboxed types have a kind that
155 specifies their runtime representation. For example, the type ``Int#`` has kind
156 ``TYPE 'IntRep`` and ``Double#`` has kind ``TYPE 'DoubleRep``. These kinds say
157 that the runtime representation of an ``Int#`` is a machine integer, and the
158 runtime representation of a ``Double#`` is a machine double-precision floating
159 point. In contrast, the kind ``Type`` is actually just a synonym for ``TYPE
160 'LiftedRep``. More details of the ``TYPE`` mechanisms appear in the `section
161 on runtime representation polymorphism <#runtime-rep>`__.
163 Given that ``Int#``'s kind is not ``Type``, it then it follows that ``Maybe
164 Int#`` is disallowed. Similarly, because type variables tend to be of kind
165 ``Type`` (for example, in ``(.) :: (b -> c) -> (a -> b) -> a -> c``, all the
166 type variables have kind ``Type``), polymorphism tends not to work over
167 primitive types. Stepping back, this makes some sense, because a polymorphic
168 function needs to manipulate the pointers to its data, and most primitive types
171 There are some restrictions on the use of primitive types:
173 - You cannot define a newtype whose representation type (the argument
174 type of the data constructor) is an unboxed type. Thus, this is
181 - You cannot bind a variable with an unboxed type in a *top-level*
184 - You cannot bind a variable with an unboxed type in a *recursive*
187 - You may bind unboxed variables in a (non-recursive, non-top-level)
188 pattern binding, but you must make any such pattern-match strict.
189 (Failing to do so emits a warning :ghc-flag:`-Wunbanged-strict-patterns`.)
190 For example, rather than:
194 data Foo = Foo Int Int#
196 f x = let (Foo a b, w) = ..rhs.. in ..body..
202 data Foo = Foo Int Int#
204 f x = let !(Foo a b, w) = ..rhs.. in ..body..
206 since ``b`` has type ``Int#``.
213 .. extension:: UnboxedTuples
214 :shortdesc: Enable the use of unboxed tuple syntax.
219 Unboxed tuples aren't really exported by ``GHC.Exts``; they are a
220 syntactic extension (:extension:`UnboxedTuples`). An
221 unboxed tuple looks like this: ::
225 where ``e_1..e_n`` are expressions of any type (primitive or
226 non-primitive). The type of an unboxed tuple looks the same.
228 Note that when unboxed tuples are enabled, ``(#`` is a single lexeme, so
229 for example when using operators like ``#`` and ``#-`` you need to write
230 ``( # )`` and ``( #- )`` rather than ``(#)`` and ``(#-)``.
232 Unboxed tuples are used for functions that need to return multiple
233 values, but they avoid the heap allocation normally associated with
234 using fully-fledged tuples. When an unboxed tuple is returned, the
235 components are put directly into registers or on the stack; the unboxed
236 tuple itself does not have a composite representation. Many of the
237 primitive operations listed in ``primops.txt.pp`` return unboxed tuples.
238 In particular, the ``IO`` and ``ST`` monads use unboxed tuples to avoid
239 unnecessary allocation during sequences of operations.
241 There are some restrictions on the use of unboxed tuples:
243 - The typical use of unboxed tuples is simply to return multiple
244 values, binding those multiple results with a ``case`` expression,
249 f x y = (# x+1, y-1 #)
250 g x = case f x x of { (# a, b #) -> a + b }
252 You can have an unboxed tuple in a pattern binding, thus
256 f x = let (# p,q #) = h x in ..body..
258 If the types of ``p`` and ``q`` are not unboxed, the resulting
259 binding is lazy like any other Haskell pattern binding. The above
260 example desugars like this:
264 f x = let t = case h x of { (# p,q #) -> (p,q) }
269 Indeed, the bindings can even be recursive.
276 .. extension:: UnboxedSums
277 :shortdesc: Enable unboxed sums.
281 Enable the use of unboxed sum syntax.
283 `-XUnboxedSums` enables new syntax for anonymous, unboxed sum types. The syntax
284 for an unboxed sum type with N alternatives is ::
286 (# t_1 | t_2 | ... | t_N #)
288 where ``t_1`` ... ``t_N`` are types (which can be unlifted, including unboxed
291 Unboxed tuples can be used for multi-arity alternatives. For example: ::
293 (# (# Int, String #) | Bool #)
295 The term level syntax is similar. Leading and preceding bars (`|`) indicate which
296 alternative it is. Here are two terms of the type shown above: ::
298 (# (# 1, "foo" #) | #) -- first alternative
300 (# | True #) -- second alternative
302 The pattern syntax reflects the term syntax: ::
305 (# (# i, str #) | #) -> ...
308 Unboxed sums are "unboxed" in the sense that, instead of allocating sums in the
309 heap and representing values as pointers, unboxed sums are represented as their
310 components, just like unboxed tuples. These "components" depend on alternatives
311 of a sum type. Like unboxed tuples, unboxed sums are lazy in their lifted
314 The code generator tries to generate as compact layout as possible for each
315 unboxed sum. In the best case, size of an unboxed sum is size of its biggest
316 alternative plus one word (for a tag). The algorithm for generating the memory
317 layout for a sum type works like this:
319 - All types are classified as one of these classes: 32bit word, 64bit word,
320 32bit float, 64bit float, pointer.
322 - For each alternative of the sum type, a layout that consists of these fields
323 is generated. For example, if an alternative has ``Int``, ``Float#`` and
324 ``String`` fields, the layout will have an 32bit word, 32bit float and
327 - Layout fields are then overlapped so that the final layout will be as compact
328 as possible. For example, suppose we have the unboxed sum: ::
330 (# (# Word32#, String, Float# #)
331 | (# Float#, Float#, Maybe Int #) #)
333 The final layout will be something like ::
335 Int32, Float32, Float32, Word32, Pointer
337 The first ``Int32`` is for the tag. There are two ``Float32`` fields because
338 floating point types can't overlap with other types, because of limitations of
339 the code generator that we're hoping to overcome in the future. The second
340 alternative needs two ``Float32`` fields: The ``Word32`` field is for the
341 ``Word32#`` in the first alternative. The ``Pointer`` field is shared between
342 ``String`` and ``Maybe Int`` values of the alternatives.
344 As another example, this is the layout for the unboxed version of ``Maybe a``
345 type, ``(# (# #) | a #)``: ::
349 The ``Pointer`` field is not used when tag says that it's ``Nothing``.
350 Otherwise ``Pointer`` points to the value in ``Just``. As mentioned
351 above, this type is lazy in its lifted field. Therefore, the type ::
353 data Maybe' a = Maybe' (# (# #) | a #)
355 is *precisely* isomorphic to the type ``Maybe a``, although its memory
356 representation is different.
358 In the degenerate case where all the alternatives have zero width, such
359 as the ``Bool``-like ``(# (# #) | (# #) #)``, the unboxed sum layout only
360 has an ``Int32`` tag field (i.e., the whole thing is represented by an integer).
372 .. extension:: UnicodeSyntax
373 :shortdesc: Enable unicode syntax.
377 Enable the use of Unicode characters in place of their equivalent ASCII
380 The language extension :extension:`UnicodeSyntax` enables
381 Unicode characters to be used to stand for certain ASCII character
382 sequences. The following alternatives are provided:
384 +--------------+---------------+-------------+-----------------------------------------+
385 | ASCII | Unicode | Code point | Name |
386 | | alternative | | |
387 +==============+===============+=============+=========================================+
388 | ``::`` | ∷ | 0x2237 | PROPORTION |
389 +--------------+---------------+-------------+-----------------------------------------+
390 | ``=>`` | ⇒ | 0x21D2 | RIGHTWARDS DOUBLE ARROW |
391 +--------------+---------------+-------------+-----------------------------------------+
392 | ``->`` | → | 0x2192 | RIGHTWARDS ARROW |
393 +--------------+---------------+-------------+-----------------------------------------+
394 | ``<-`` | ← | 0x2190 | LEFTWARDS ARROW |
395 +--------------+---------------+-------------+-----------------------------------------+
396 | ``>-`` | ⤚ | 0x291a | RIGHTWARDS ARROW-TAIL |
397 +--------------+---------------+-------------+-----------------------------------------+
398 | ``-<`` | ⤙ | 0x2919 | LEFTWARDS ARROW-TAIL |
399 +--------------+---------------+-------------+-----------------------------------------+
400 | ``>>-`` | ⤜ | 0x291C | RIGHTWARDS DOUBLE ARROW-TAIL |
401 +--------------+---------------+-------------+-----------------------------------------+
402 | ``-<<`` | ⤛ | 0x291B | LEFTWARDS DOUBLE ARROW-TAIL |
403 +--------------+---------------+-------------+-----------------------------------------+
404 | ``*`` | ★ | 0x2605 | BLACK STAR |
405 +--------------+---------------+-------------+-----------------------------------------+
406 | ``forall`` | ∀ | 0x2200 | FOR ALL |
407 +--------------+---------------+-------------+-----------------------------------------+
408 | ``(|`` | ⦇ | 0x2987 | Z NOTATION LEFT IMAGE BRACKET |
409 +--------------+---------------+-------------+-----------------------------------------+
410 | ``|)`` | ⦈ | 0x2988 | Z NOTATION RIGHT IMAGE BRACKET |
411 +--------------+---------------+-------------+-----------------------------------------+
412 | ``[|`` | ⟦ | 0x27E6 | MATHEMATICAL LEFT WHITE SQUARE BRACKET |
413 +--------------+---------------+-------------+-----------------------------------------+
414 | ``|]`` | ⟧ | 0x27E7 | MATHEMATICAL RIGHT WHITE SQUARE BRACKET |
415 +--------------+---------------+-------------+-----------------------------------------+
422 .. extension:: MagicHash
423 :shortdesc: Allow ``#`` as a postfix modifier on identifiers.
427 Enables the use of the hash character (``#``) as an identifier suffix.
429 The language extension :extension:`MagicHash` allows ``#`` as a postfix modifier
430 to identifiers. Thus, ``x#`` is a valid variable, and ``T#`` is a valid type
431 constructor or data constructor.
433 The hash sign does not change semantics at all. We tend to use variable
434 names ending in "#" for unboxed values or types (e.g. ``Int#``), but
435 there is no requirement to do so; they are just plain ordinary
436 variables. Nor does the :extension:`MagicHash` extension bring anything into
437 scope. For example, to bring ``Int#`` into scope you must import
438 ``GHC.Prim`` (see :ref:`primitives`); the :extension:`MagicHash` extension then
439 allows you to *refer* to the ``Int#`` that is now in scope. Note that
440 with this option, the meaning of ``x#y = 0`` is changed: it defines a
441 function ``x#`` taking a single argument ``y``; to define the operator
442 ``#``, put a space: ``x # y = 0``.
444 The :extension:`MagicHash` also enables some new forms of literals (see
445 :ref:`glasgow-unboxed`):
447 - ``'x'#`` has type ``Char#``
449 - ``"foo"#`` has type ``Addr#``
451 - ``3#`` has type ``Int#``. In general, any Haskell integer lexeme
452 followed by a ``#`` is an ``Int#`` literal, e.g. ``-0x3A#`` as well as
455 - ``3##`` has type ``Word#``. In general, any non-negative Haskell
456 integer lexeme followed by ``##`` is a ``Word#``.
458 - ``3.2#`` has type ``Float#``.
460 - ``3.2##`` has type ``Double#``
462 .. _negative-literals:
467 .. extension:: NegativeLiterals
468 :shortdesc: Enable support for negative literals.
472 Enable the use of un-parenthesized negative numeric literals.
474 The literal ``-123`` is, according to Haskell98 and Haskell 2010,
475 desugared as ``negate (fromInteger 123)``. The language extension
476 :extension:`NegativeLiterals` means that it is instead desugared as
477 ``fromInteger (-123)``.
479 This can make a difference when the positive and negative range of a
480 numeric data type don't match up. For example, in 8-bit arithmetic -128
481 is representable, but +128 is not. So ``negate (fromInteger 128)`` will
482 elicit an unexpected integer-literal-overflow message.
486 Fractional looking integer literals
487 -----------------------------------
489 .. extension:: NumDecimals
490 :shortdesc: Enable support for 'fractional' integer literals.
494 Allow the use of floating-point literal syntax for integral types.
496 Haskell 2010 and Haskell 98 define floating literals with the syntax
497 ``1.2e6``. These literals have the type ``Fractional a => a``.
499 The language extension :extension:`NumDecimals` allows you to also use the
500 floating literal syntax for instances of ``Integral``, and have values
501 like ``(1.2e6 :: Num a => a)``
505 Binary integer literals
506 -----------------------
508 .. extension:: BinaryLiterals
509 :shortdesc: Enable support for binary literals.
513 Allow the use of binary notation in integer literals.
515 Haskell 2010 and Haskell 98 allows for integer literals to be given in
516 decimal, octal (prefixed by ``0o`` or ``0O``), or hexadecimal notation
517 (prefixed by ``0x`` or ``0X``).
519 The language extension :extension:`BinaryLiterals` adds support for expressing
520 integer literals in binary notation with the prefix ``0b`` or ``0B``. For
521 instance, the binary integer literal ``0b11001001`` will be desugared into
522 ``fromInteger 201`` when :extension:`BinaryLiterals` is enabled.
524 .. _hex-float-literals:
526 Hexadecimal floating point literals
527 -----------------------------------
529 .. extension:: HexFloatLiterals
530 :shortdesc: Enable support for :ref:`hexadecimal floating point literals <hex-float-literals>`.
534 Allow writing floating point literals using hexadecimal notation.
536 The hexadecimal notation for floating point literals is useful when you
537 need to specify floating point constants precisely, as the literal notation
538 corresponds closely to the underlying bit-encoding of the number.
540 In this notation floating point numbers are written using hexadecimal digits,
541 and so the digits are interpreted using base 16, rather then the usual 10.
542 This means that digits left of the decimal point correspond to positive
543 powers of 16, while the ones to the right correspond to negative ones.
545 You may also write an explicit exponent, which is similar to the exponent
546 in decimal notation with the following differences:
547 - the exponent begins with ``p`` instead of ``e``
548 - the exponent is written in base ``10`` (**not** 16)
549 - the base of the exponent is ``2`` (**not** 16).
551 In terms of the underlying bit encoding, each hexadecimal digit corresponds
552 to 4 bits, and you may think of the exponent as "moving" the floating point
553 by one bit left (negative) or right (positive). Here are some examples:
555 - ``0x0.1`` is the same as ``1/16``
556 - ``0x0.01`` is the same as ``1/256``
557 - ``0xF.FF`` is the same as ``15 + 15/16 + 15/256``
558 - ``0x0.1p4`` is the same as ``1``
559 - ``0x0.1p-4`` is the same as ``1/256``
560 - ``0x0.1p12`` is the same as ``256``
565 .. _numeric-underscores:
570 .. extension:: NumericUnderscores
571 :shortdesc: Enable support for :ref:`numeric underscores <numeric-underscores>`.
575 Allow the use of underscores in numeric literals.
577 GHC allows for numeric literals to be given in decimal, octal, hexadecimal,
578 binary, or float notation.
580 The language extension :extension:`NumericUnderscores` adds support for expressing
581 underscores in numeric literals.
582 For instance, the numeric literal ``1_000_000`` will be parsed into
583 ``1000000`` when :extension:`NumericUnderscores` is enabled.
584 That is, underscores in numeric literals are ignored when
585 :extension:`NumericUnderscores` is enabled.
586 See also :ghc-ticket:`14473`.
594 billion = 1_000_000_000
595 lightspeed = 299_792_458
600 red_mask = 0xff_00_00
604 bit8th = 0b01_0000_0000
605 packbits = 0b1_11_01_0000_0_111
606 bigbits = 0b1100_1011__1110_1111__0101_0011
609 pi = 3.141_592_653_589_793
610 faraday = 96_485.332_89
611 avogadro = 6.022_140_857e+23
614 isUnderMillion = (< 1_000_000)
617 | x > 0x3ff_ffff = 0x3ff_ffff
620 test8bit x = (0b01_0000_0000 .&. x) /= 0
626 x0 = 1_000_000 -- valid
627 x1 = 1__000000 -- valid
628 x2 = 1000000_ -- invalid
629 x3 = _1000000 -- invalid
632 e1 = 0.000_1 -- valid
633 e2 = 0_.0001 -- invalid
634 e3 = _0.0001 -- invalid
635 e4 = 0._0001 -- invalid
636 e5 = 0.0001_ -- invalid
640 f2 = 1__e+23 -- valid
641 f3 = 1e_+23 -- invalid
644 g1 = 1e+_23 -- invalid
645 g2 = 1e+23_ -- invalid
648 h1 = 0xff_ff -- valid
649 h2 = 0x_ffff -- valid
650 h3 = 0x__ffff -- valid
651 h4 = _0xffff -- invalid
658 .. extension:: NoPatternGuards
659 :shortdesc: Disable pattern guards.
660 Implied by :extension:`Haskell98`.
662 :implied by: :extension:`Haskell98`
665 Disable `pattern guards
666 <http://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-460003.13>`__.
673 .. extension:: ViewPatterns
674 :shortdesc: Enable view patterns.
678 Allow use of view pattern syntax.
680 View patterns are enabled by the language extension :extension:`ViewPatterns`. More
681 information and examples of view patterns can be found on the
682 :ghc-wiki:`Wiki page <ViewPatterns>`.
684 View patterns are somewhat like pattern guards that can be nested inside
685 of other patterns. They are a convenient way of pattern-matching against
686 values of abstract types. For example, in a programming language
687 implementation, we might represent the syntax of the types of the
688 language as follows: ::
695 view :: Typ -> TypView
697 -- additional operations for constructing Typ's ...
699 The representation of Typ is held abstract, permitting implementations
700 to use a fancy representation (e.g., hash-consing to manage sharing).
701 Without view patterns, using this signature is a little inconvenient: ::
703 size :: Typ -> Integer
704 size t = case view t of
706 Arrow t1 t2 -> size t1 + size t2
708 It is necessary to iterate the case, rather than using an equational
709 function definition. And the situation is even worse when the matching
710 against ``t`` is buried deep inside another pattern.
712 View patterns permit calling the view function inside the pattern and
713 matching against the result: ::
715 size (view -> Unit) = 1
716 size (view -> Arrow t1 t2) = size t1 + size t2
718 That is, we add a new form of pattern, written ⟨expression⟩ ``->``
719 ⟨pattern⟩ that means "apply the expression to whatever we're trying to
720 match against, and then match the result of that application against the
721 pattern". The expression can be any Haskell expression of function type,
722 and view patterns can be used wherever patterns are used.
724 The semantics of a pattern ``(`` ⟨exp⟩ ``->`` ⟨pat⟩ ``)`` are as
728 The variables bound by the view pattern are the variables bound by
731 Any variables in ⟨exp⟩ are bound occurrences, but variables bound "to
732 the left" in a pattern are in scope. This feature permits, for
733 example, one argument to a function to be used in the view of another
734 argument. For example, the function ``clunky`` from
735 :ref:`pattern-guards` can be written using view patterns as follows: ::
737 clunky env (lookup env -> Just val1) (lookup env -> Just val2) = val1 + val2
738 ...other equations for clunky...
740 More precisely, the scoping rules are:
742 - In a single pattern, variables bound by patterns to the left of a
743 view pattern expression are in scope. For example: ::
745 example :: Maybe ((String -> Integer,Integer), String) -> Bool
746 example (Just ((f,_), f -> 4)) = True
748 Additionally, in function definitions, variables bound by matching
749 earlier curried arguments may be used in view pattern expressions
750 in later arguments: ::
752 example :: (String -> Integer) -> String -> Bool
753 example f (f -> 4) = True
755 That is, the scoping is the same as it would be if the curried
756 arguments were collected into a tuple.
758 - In mutually recursive bindings, such as ``let``, ``where``, or the
759 top level, view patterns in one declaration may not mention
760 variables bound by other declarations. That is, each declaration
761 must be self-contained. For example, the following program is not
767 (For some amplification on this design choice see :ghc-ticket:`4061`.
769 - Typing: If ⟨exp⟩ has type ⟨T1⟩ ``->`` ⟨T2⟩ and ⟨pat⟩ matches a ⟨T2⟩,
770 then the whole view pattern matches a ⟨T1⟩.
772 - Matching: To the equations in Section 3.17.3 of the `Haskell 98
773 Report <http://www.haskell.org/onlinereport/>`__, add the following: ::
775 case v of { (e -> p) -> e1 ; _ -> e2 }
777 case (e v) of { p -> e1 ; _ -> e2 }
779 That is, to match a variable ⟨v⟩ against a pattern ``(`` ⟨exp⟩ ``->``
780 ⟨pat⟩ ``)``, evaluate ``(`` ⟨exp⟩ ⟨v⟩ ``)`` and match the result
783 - Efficiency: When the same view function is applied in multiple
784 branches of a function definition or a case expression (e.g., in
785 ``size`` above), GHC makes an attempt to collect these applications
786 into a single nested case expression, so that the view function is
787 only applied once. Pattern compilation in GHC follows the matrix
788 algorithm described in Chapter 4 of `The Implementation of Functional
790 Languages <http://research.microsoft.com/~simonpj/Papers/slpj-book-1987/>`__.
791 When the top rows of the first column of a matrix are all view
792 patterns with the "same" expression, these patterns are transformed
793 into a single nested case. This includes, for example, adjacent view
794 patterns that line up in a tuple, as in
798 f ((view -> A, p1), p2) = e1
799 f ((view -> B, p3), p4) = e2
801 The current notion of when two view pattern expressions are "the
802 same" is very restricted: it is not even full syntactic equality.
803 However, it does include variables, literals, applications, and
804 tuples; e.g., two instances of ``view ("hi", "there")`` will be
805 collected. However, the current implementation does not compare up to
806 alpha-equivalence, so two instances of ``(x, view x -> y)`` will not
814 .. extension:: NPlusKPatterns
815 :shortdesc: Enable support for ``n+k`` patterns.
816 Implied by :extension:`Haskell98`.
818 :implied by: :extension:`Haskell98`
821 Enable use of ``n+k`` patterns.
823 .. _recursive-do-notation:
825 The recursive do-notation
826 -------------------------
828 .. extension:: RecursiveDo
829 :shortdesc: Enable recursive do (mdo) notation.
833 Allow the use of recursive ``do`` notation.
835 The do-notation of Haskell 98 does not allow *recursive bindings*, that
836 is, the variables bound in a do-expression are visible only in the
837 textually following code block. Compare this to a let-expression, where
838 bound variables are visible in the entire binding group.
840 It turns out that such recursive bindings do indeed make sense for a
841 variety of monads, but not all. In particular, recursion in this sense
842 requires a fixed-point operator for the underlying monad, captured by
843 the ``mfix`` method of the ``MonadFix`` class, defined in
844 ``Control.Monad.Fix`` as follows: ::
846 class Monad m => MonadFix m where
847 mfix :: (a -> m a) -> m a
849 Haskell's ``Maybe``, ``[]`` (list), ``ST`` (both strict and lazy
850 versions), ``IO``, and many other monads have ``MonadFix`` instances. On
851 the negative side, the continuation monad, with the signature
852 ``(a -> r) -> r``, does not.
854 For monads that do belong to the ``MonadFix`` class, GHC provides an
855 extended version of the do-notation that allows recursive bindings. The
856 :extension:`RecursiveDo` (language pragma: ``RecursiveDo``) provides the
857 necessary syntactic support, introducing the keywords ``mdo`` and
858 ``rec`` for higher and lower levels of the notation respectively. Unlike
859 bindings in a ``do`` expression, those introduced by ``mdo`` and ``rec``
860 are recursively defined, much like in an ordinary let-expression. Due to
861 the new keyword ``mdo``, we also call this notation the *mdo-notation*.
863 Here is a simple (albeit contrived) example:
867 {-# LANGUAGE RecursiveDo #-}
868 justOnes = mdo { xs <- Just (1:xs)
869 ; return (map negate xs) }
875 {-# LANGUAGE RecursiveDo #-}
876 justOnes = do { rec { xs <- Just (1:xs) }
877 ; return (map negate xs) }
879 As you can guess ``justOnes`` will evaluate to ``Just [-1,-1,-1,...``.
881 GHC's implementation the mdo-notation closely follows the original
882 translation as described in the paper `A recursive do for
883 Haskell <http://leventerkok.github.io/papers/recdo.pdf>`__, which
884 in turn is based on the work `Value Recursion in Monadic
885 Computations <http://leventerkok.github.io/papers/erkok-thesis.pdf>`__.
886 Furthermore, GHC extends the syntax described in the former paper with a
887 lower level syntax flagged by the ``rec`` keyword, as we describe next.
889 Recursive binding groups
890 ~~~~~~~~~~~~~~~~~~~~~~~~
892 The extension :extension:`RecursiveDo` also introduces a new keyword ``rec``, which
893 wraps a mutually-recursive group of monadic statements inside a ``do``
894 expression, producing a single statement. Similar to a ``let`` statement
895 inside a ``do``, variables bound in the ``rec`` are visible throughout
896 the ``rec`` group, and below it. For example, compare
900 do { a <- getChar do { a <- getChar
901 ; let { r1 = f a r2 ; rec { r1 <- f a r2
902 ; ; r2 = g r1 } ; ; r2 <- g r1 }
903 ; return (r1 ++ r2) } ; return (r1 ++ r2) }
905 In both cases, ``r1`` and ``r2`` are available both throughout the
906 ``let`` or ``rec`` block, and in the statements that follow it. The
907 difference is that ``let`` is non-monadic, while ``rec`` is monadic. (In
908 Haskell ``let`` is really ``letrec``, of course.)
910 The semantics of ``rec`` is fairly straightforward. Whenever GHC finds a
911 ``rec`` group, it will compute its set of bound variables, and will
912 introduce an appropriate call to the underlying monadic value-recursion
913 operator ``mfix``, belonging to the ``MonadFix`` class. Here is an
918 rec { b <- f a c ===> (b,c) <- mfix (\ ~(b,c) -> do { b <- f a c
919 ; c <- f b a } ; c <- f b a
922 As usual, the meta-variables ``b``, ``c`` etc., can be arbitrary
923 patterns. In general, the statement ``rec ss`` is desugared to the
928 vs <- mfix (\ ~vs -> do { ss; return vs })
930 where ``vs`` is a tuple of the variables bound by ``ss``.
932 Note in particular that the translation for a ``rec`` block only
933 involves wrapping a call to ``mfix``: it performs no other analysis on
934 the bindings. The latter is the task for the ``mdo`` notation, which is
940 A ``rec``-block tells the compiler where precisely the recursive knot
941 should be tied. It turns out that the placement of the recursive knots
942 can be rather delicate: in particular, we would like the knots to be
943 wrapped around as minimal groups as possible. This process is known as
944 *segmentation*, and is described in detail in Section 3.2 of `A
946 Haskell <http://leventerkok.github.io/papers/recdo.pdf>`__.
947 Segmentation improves polymorphism and reduces the size of the recursive
948 knot. Most importantly, it avoids unnecessary interference caused by a
949 fundamental issue with the so-called *right-shrinking* axiom for monadic
950 recursion. In brief, most monads of interest (IO, strict state, etc.) do
951 *not* have recursion operators that satisfy this axiom, and thus not
952 performing segmentation can cause unnecessary interference, changing the
953 termination behavior of the resulting translation. (Details can be found
954 in Sections 3.1 and 7.2.2 of `Value Recursion in Monadic
955 Computations <http://leventerkok.github.io/papers/erkok-thesis.pdf>`__.)
957 The ``mdo`` notation removes the burden of placing explicit ``rec``
958 blocks in the code. Unlike an ordinary ``do`` expression, in which
959 variables bound by statements are only in scope for later statements,
960 variables bound in an ``mdo`` expression are in scope for all statements
961 of the expression. The compiler then automatically identifies minimal
962 mutually recursively dependent segments of statements, treating them as
963 if the user had wrapped a ``rec`` qualifier around them.
965 The definition is syntactic:
967 - A generator ⟨g⟩ *depends* on a textually following generator ⟨g'⟩, if
969 - ⟨g'⟩ defines a variable that is used by ⟨g⟩, or
971 - ⟨g'⟩ textually appears between ⟨g⟩ and ⟨g''⟩, where ⟨g⟩ depends on
974 - A *segment* of a given ``mdo``-expression is a minimal sequence of
975 generators such that no generator of the sequence depends on an
976 outside generator. As a special case, although it is not a generator,
977 the final expression in an ``mdo``-expression is considered to form a
980 Segments in this sense are related to *strongly-connected components*
981 analysis, with the exception that bindings in a segment cannot be
982 reordered and must be contiguous.
984 Here is an example ``mdo``-expression, and its translation to ``rec``
989 mdo { a <- getChar ===> do { a <- getChar
990 ; b <- f a c ; rec { b <- f a c
991 ; c <- f b a ; ; c <- f b a }
992 ; z <- h a b ; z <- h a b
993 ; d <- g d e ; rec { d <- g d e
994 ; e <- g a z ; ; e <- g a z }
995 ; putChar c } ; putChar c }
997 Note that a given ``mdo`` expression can cause the creation of multiple
998 ``rec`` blocks. If there are no recursive dependencies, ``mdo`` will
999 introduce no ``rec`` blocks. In this latter case an ``mdo`` expression
1000 is precisely the same as a ``do`` expression, as one would expect.
1002 In summary, given an ``mdo`` expression, GHC first performs
1003 segmentation, introducing ``rec`` blocks to wrap over minimal recursive
1004 groups. Then, each resulting ``rec`` is desugared, using a call to
1005 ``Control.Monad.Fix.mfix`` as described in the previous section. The
1006 original ``mdo``-expression typechecks exactly when the desugared
1007 version would do so.
1009 Here are some other important points in using the recursive-do notation:
1011 - It is enabled with the extension :extension:`RecursiveDo`, or the
1012 ``LANGUAGE RecursiveDo`` pragma. (The same extension enables both
1013 ``mdo``-notation, and the use of ``rec`` blocks inside ``do``
1016 - ``rec`` blocks can also be used inside ``mdo``-expressions, which
1017 will be treated as a single statement. However, it is good style to
1018 either use ``mdo`` or ``rec`` blocks in a single expression.
1020 - If recursive bindings are required for a monad, then that monad must
1021 be declared an instance of the ``MonadFix`` class.
1023 - The following instances of ``MonadFix`` are automatically provided:
1024 List, Maybe, IO. Furthermore, the ``Control.Monad.ST`` and
1025 ``Control.Monad.ST.Lazy`` modules provide the instances of the
1026 ``MonadFix`` class for Haskell's internal state monad (strict and
1027 lazy, respectively).
1029 - Like ``let`` and ``where`` bindings, name shadowing is not allowed
1030 within an ``mdo``-expression or a ``rec``-block; that is, all the
1031 names bound in a single ``rec`` must be distinct. (GHC will complain
1032 if this is not the case.)
1036 Applicative do-notation
1037 -----------------------
1040 single: Applicative do-notation
1041 single: do-notation; Applicative
1043 .. extension:: ApplicativeDo
1044 :shortdesc: Enable Applicative do-notation desugaring
1048 Allow use of ``Applicative`` ``do`` notation.
1050 The language option :extension:`ApplicativeDo` enables an alternative translation for
1051 the do-notation, which uses the operators ``<$>``, ``<*>``, along with ``join``
1052 as far as possible. There are two main reasons for wanting to do this:
1054 - We can use do-notation with types that are an instance of ``Applicative`` and
1055 ``Functor``, but not ``Monad``
1056 - In some monads, using the applicative operators is more efficient than monadic
1057 bind. For example, it may enable more parallelism.
1059 Applicative do-notation desugaring preserves the original semantics, provided
1060 that the ``Applicative`` instance satisfies ``<*> = ap`` and ``pure = return``
1061 (these are true of all the common monadic types). Thus, you can normally turn on
1062 :extension:`ApplicativeDo` without fear of breaking your program. There is one pitfall
1063 to watch out for; see :ref:`applicative-do-pitfall`.
1065 There are no syntactic changes with :extension:`ApplicativeDo`. The only way it shows
1066 up at the source level is that you can have a ``do`` expression that doesn't
1067 require a ``Monad`` constraint. For example, in GHCi: ::
1069 Prelude> :set -XApplicativeDo
1070 Prelude> :t \m -> do { x <- m; return (not x) }
1071 \m -> do { x <- m; return (not x) }
1072 :: Functor f => f Bool -> f Bool
1074 This example only requires ``Functor``, because it is translated into ``(\x ->
1075 not x) <$> m``. A more complex example requires ``Applicative``, ::
1077 Prelude> :t \m -> do { x <- m 'a'; y <- m 'b'; return (x || y) }
1078 \m -> do { x <- m 'a'; y <- m 'b'; return (x || y) }
1079 :: Applicative f => (Char -> f Bool) -> f Bool
1081 Here GHC has translated the expression into ::
1083 (\x y -> x || y) <$> m 'a' <*> m 'b'
1085 It is possible to see the actual translation by using :ghc-flag:`-ddump-ds`, but be
1086 warned, the output is quite verbose.
1088 Note that if the expression can't be translated into uses of ``<$>``, ``<*>``
1089 only, then it will incur a ``Monad`` constraint as usual. This happens when
1090 there is a dependency on a value produced by an earlier statement in the
1093 Prelude> :t \m -> do { x <- m True; y <- m x; return (x || y) }
1094 \m -> do { x <- m True; y <- m x; return (x || y) }
1095 :: Monad m => (Bool -> m Bool) -> m Bool
1097 Here, ``m x`` depends on the value of ``x`` produced by the first statement, so
1098 the expression cannot be translated using ``<*>``.
1100 In general, the rule for when a ``do`` statement incurs a ``Monad`` constraint
1101 is as follows. If the do-expression has the following form: ::
1103 do p1 <- E1; ...; pn <- En; return E
1105 where none of the variables defined by ``p1...pn`` are mentioned in ``E1...En``,
1106 and ``p1...pn`` are all variables or lazy patterns,
1107 then the expression will only require ``Applicative``. Otherwise, the expression
1108 will require ``Monad``. The block may return a pure expression ``E`` depending
1109 upon the results ``p1...pn`` with either ``return`` or ``pure``.
1111 Note: the final statement must match one of these patterns exactly:
1118 otherwise GHC cannot recognise it as a ``return`` statement, and the
1119 transformation to use ``<$>`` that we saw above does not apply. In
1120 particular, slight variations such as ``return . Just $ x`` or ``let x
1121 = e in return x`` would not be recognised.
1123 If the final statement is not of one of these forms, GHC falls back to
1124 standard ``do`` desugaring, and the expression will require a
1125 ``Monad`` constraint.
1127 When the statements of a ``do`` expression have dependencies between
1128 them, and ``ApplicativeDo`` cannot infer an ``Applicative`` type, it
1129 uses a heuristic algorithm to try to use ``<*>`` as much as possible.
1130 This algorithm usually finds the best solution, but in rare complex
1131 cases it might miss an opportunity. There is an algorithm that finds
1132 the optimal solution, provided as an option:
1134 .. ghc-flag:: -foptimal-applicative-do
1135 :shortdesc: Use a slower but better algorithm for ApplicativeDo
1137 :reverse: -fno-optimal-applicative-do
1138 :category: optimization
1142 Enables an alternative algorithm for choosing where to use ``<*>``
1143 in conjunction with the ``ApplicativeDo`` language extension.
1144 This algorithm always finds the optimal solution, but it is
1145 expensive: ``O(n^3)``, so this option can lead to long compile
1146 times when there are very large ``do`` expressions (over 100
1147 statements). The default ``ApplicativeDo`` algorithm is ``O(n^2)``.
1150 .. _applicative-do-strict:
1156 A strict pattern match in a bind statement prevents
1157 ``ApplicativeDo`` from transforming that statement to use
1158 ``Applicative``. This is because the transformation would change the
1159 semantics by making the expression lazier.
1161 For example, this code will require a ``Monad`` constraint::
1163 > :t \m -> do { (x:xs) <- m; return x }
1164 \m -> do { (x:xs) <- m; return x } :: Monad m => m [b] -> m b
1166 but making the pattern match lazy allows it to have a ``Functor`` constraint::
1168 > :t \m -> do { ~(x:xs) <- m; return x }
1169 \m -> do { ~(x:xs) <- m; return x } :: Functor f => f [b] -> f b
1171 A "strict pattern match" is any pattern match that can fail. For
1172 example, ``()``, ``(x:xs)``, ``!z``, and ``C x`` are strict patterns,
1173 but ``x`` and ``~(1,2)`` are not. For the purposes of
1174 ``ApplicativeDo``, a pattern match against a ``newtype`` constructor
1175 is considered strict.
1177 When there's a strict pattern match in a sequence of statements,
1178 ``ApplicativeDo`` places a ``>>=`` between that statement and the one
1179 that follows it. The sequence may be transformed to use ``<*>``
1180 elsewhere, but the strict pattern match and the following statement
1181 will always be connected with ``>>=``, to retain the same strictness
1182 semantics as the standard do-notation. If you don't want this, simply
1183 put a ``~`` on the pattern match to make it lazy.
1185 .. _applicative-do-pitfall:
1187 Things to watch out for
1188 ~~~~~~~~~~~~~~~~~~~~~~~
1190 Your code should just work as before when :extension:`ApplicativeDo` is enabled,
1191 provided you use conventional ``Applicative`` instances. However, if you define
1192 a ``Functor`` or ``Applicative`` instance using do-notation, then it will likely
1193 get turned into an infinite loop by GHC. For example, if you do this: ::
1195 instance Functor MyType where
1196 fmap f m = do x <- m; return (f x)
1198 Then applicative desugaring will turn it into ::
1200 instance Functor MyType where
1201 fmap f m = fmap (\x -> f x) m
1203 And the program will loop at runtime. Similarly, an ``Applicative`` instance
1206 instance Applicative MyType where
1208 x <*> y = do f <- x; a <- y; return (f a)
1210 will result in an infinte loop when ``<*>`` is called.
1212 Just as you wouldn't define a ``Monad`` instance using the do-notation, you
1213 shouldn't define ``Functor`` or ``Applicative`` instance using do-notation (when
1214 using ``ApplicativeDo``) either. The correct way to define these instances in
1215 terms of ``Monad`` is to use the ``Monad`` operations directly, e.g. ::
1217 instance Functor MyType where
1218 fmap f m = m >>= return . f
1220 instance Applicative MyType where
1225 .. _parallel-list-comprehensions:
1227 Parallel List Comprehensions
1228 ----------------------------
1231 single: list comprehensions; parallel
1232 single: parallel list comprehensions
1234 .. extension:: ParallelListComp
1235 :shortdesc: Enable parallel list comprehensions.
1239 Allow parallel list comprehension syntax.
1241 Parallel list comprehensions are a natural extension to list
1242 comprehensions. List comprehensions can be thought of as a nice syntax
1243 for writing maps and filters. Parallel comprehensions extend this to
1244 include the ``zipWith`` family.
1246 A parallel list comprehension has multiple independent branches of
1247 qualifier lists, each separated by a ``|`` symbol. For example, the
1248 following zips together two lists: ::
1250 [ (x, y) | x <- xs | y <- ys ]
1252 The behaviour of parallel list comprehensions follows that of zip, in
1253 that the resulting list will have the same length as the shortest
1256 We can define parallel list comprehensions by translation to regular
1257 comprehensions. Here's the basic idea:
1259 Given a parallel comprehension of the form: ::
1261 [ e | p1 <- e11, p2 <- e12, ...
1262 | q1 <- e21, q2 <- e22, ...
1266 This will be translated to: ::
1268 [ e | ((p1,p2), (q1,q2), ...) <- zipN [(p1,p2) | p1 <- e11, p2 <- e12, ...]
1269 [(q1,q2) | q1 <- e21, q2 <- e22, ...]
1273 where ``zipN`` is the appropriate zip for the given number of branches.
1275 .. _generalised-list-comprehensions:
1277 Generalised (SQL-like) List Comprehensions
1278 ------------------------------------------
1281 single: list comprehensions; generalised
1282 single: extended list comprehensions
1286 .. extension:: TransformListComp
1287 :shortdesc: Enable generalised list comprehensions.
1291 Allow use of generalised list (SQL-like) comprehension syntax. This
1292 introduces the ``group``, ``by``, and ``using`` keywords.
1294 Generalised list comprehensions are a further enhancement to the list
1295 comprehension syntactic sugar to allow operations such as sorting and
1296 grouping which are familiar from SQL. They are fully described in the
1297 paper `Comprehensive comprehensions: comprehensions with "order by" and
1298 "group by" <https://www.microsoft.com/en-us/research/wp-content/uploads/2007/09/list-comp.pdf>`__,
1299 except that the syntax we use differs slightly from the paper.
1301 The extension is enabled with the extension :extension:`TransformListComp`.
1307 employees = [ ("Simon", "MS", 80)
1308 , ("Erik", "MS", 100)
1309 , ("Phil", "Ed", 40)
1310 , ("Gordon", "Ed", 45)
1311 , ("Paul", "Yale", 60) ]
1313 output = [ (the dept, sum salary)
1314 | (name, dept, salary) <- employees
1315 , then group by dept using groupWith
1316 , then sortWith by (sum salary)
1319 In this example, the list ``output`` would take on the value:
1323 [("Yale", 60), ("Ed", 85), ("MS", 180)]
1325 There are three new keywords: ``group``, ``by``, and ``using``. (The
1326 functions ``sortWith`` and ``groupWith`` are not keywords; they are
1327 ordinary functions that are exported by ``GHC.Exts``.)
1329 There are five new forms of comprehension qualifier, all introduced by
1330 the (existing) keyword ``then``:
1336 This statement requires that
1339 forall a. [a] -> [a]
1340 . You can see an example of its use in the motivating example, as
1341 this form is used to apply
1348 This form is similar to the previous one, but allows you to create a
1349 function which will be passed as the first argument to f. As a
1350 consequence f must have the type
1351 ``forall a. (a -> t) -> [a] -> [a]``. As you can see from the type,
1352 this function lets f "project out" some information from the elements
1353 of the list it is transforming.
1355 An example is shown in the opening example, where ``sortWith`` is
1356 supplied with a function that lets it find out the ``sum salary`` for
1357 any item in the list comprehension it transforms.
1361 then group by e using f
1363 This is the most general of the grouping-type statements. In this
1364 form, f is required to have type
1365 ``forall a. (a -> t) -> [a] -> [[a]]``. As with the ``then f by e``
1366 case above, the first argument is a function supplied to f by the
1367 compiler which lets it compute e on every element of the list being
1368 transformed. However, unlike the non-grouping case, f additionally
1369 partitions the list into a number of sublists: this means that at
1370 every point after this statement, binders occurring before it in the
1371 comprehension refer to *lists* of possible values, not single values.
1372 To help understand this, let's look at an example:
1376 -- This works similarly to groupWith in GHC.Exts, but doesn't sort its input first
1377 groupRuns :: Eq b => (a -> b) -> [a] -> [[a]]
1378 groupRuns f = groupBy (\x y -> f x == f y)
1380 output = [ (the x, y)
1381 | x <- ([1..3] ++ [1..2])
1383 , then group by x using groupRuns ]
1385 This results in the variable ``output`` taking on the value below:
1389 [(1, [4, 5, 6]), (2, [4, 5, 6]), (3, [4, 5, 6]), (1, [4, 5, 6]), (2, [4, 5, 6])]
1391 Note that we have used the ``the`` function to change the type of x
1392 from a list to its original numeric type. The variable y, in
1393 contrast, is left unchanged from the list form introduced by the
1400 With this form of the group statement, f is required to simply have
1401 the type ``forall a. [a] -> [[a]]``, which will be used to group up
1402 the comprehension so far directly. An example of this form is as
1410 , then group using inits]
1412 This will yield a list containing every prefix of the word "hello"
1413 written out 5 times:
1417 ["","h","he","hel","hell","hello","helloh","hellohe","hellohel","hellohell","hellohello","hellohelloh",...]
1419 .. _monad-comprehensions:
1421 Monad comprehensions
1422 --------------------
1425 single: monad comprehensions
1427 .. extension:: MonadComprehensions
1428 :shortdesc: Enable monad comprehensions.
1432 Enable list comprehension syntax for arbitrary monads.
1434 Monad comprehensions generalise the list comprehension notation,
1435 including parallel comprehensions (:ref:`parallel-list-comprehensions`)
1436 and transform comprehensions (:ref:`generalised-list-comprehensions`) to
1439 Monad comprehensions support:
1443 [ x + y | x <- Just 1, y <- Just 2 ]
1445 Bindings are translated with the ``(>>=)`` and ``return`` functions
1446 to the usual do-notation: ::
1454 [ x | x <- [1..10], x <= 5 ]
1456 Guards are translated with the ``guard`` function, which requires a
1457 ``MonadPlus`` instance: ::
1463 - Transform statements (as with :extension:`TransformListComp`): ::
1465 [ x+y | x <- [1..10], y <- [1..x], then take 2 ]
1467 This translates to: ::
1469 do (x,y) <- take 2 (do x <- [1..10]
1474 - Group statements (as with :extension:`TransformListComp`):
1478 [ x | x <- [1,1,2,2,3], then group by x using GHC.Exts.groupWith ]
1479 [ x | x <- [1,1,2,2,3], then group using myGroup ]
1481 - Parallel statements (as with :extension:`ParallelListComp`):
1485 [ (x+y) | x <- [1..10]
1489 Parallel statements are translated using the ``mzip`` function, which
1490 requires a ``MonadZip`` instance defined in
1491 :base-ref:`Control.Monad.Zip.`:
1495 do (x,y) <- mzip (do x <- [1..10]
1501 All these features are enabled by default if the :extension:`MonadComprehensions`
1502 extension is enabled. The types and more detailed examples on how to use
1503 comprehensions are explained in the previous chapters
1504 :ref:`generalised-list-comprehensions` and
1505 :ref:`parallel-list-comprehensions`. In general you just have to replace
1506 the type ``[a]`` with the type ``Monad m => m a`` for monad
1510 Even though most of these examples are using the list monad, monad
1511 comprehensions work for any monad. The ``base`` package offers all
1512 necessary instances for lists, which make :extension:`MonadComprehensions`
1513 backward compatible to built-in, transform and parallel list
1516 More formally, the desugaring is as follows. We write ``D[ e | Q]`` to
1517 mean the desugaring of the monad comprehension ``[ e | Q]``:
1519 .. code-block:: none
1523 Lists of qualifiers: Q,R,S
1527 D[ e | p <- e, Q ] = e >>= \p -> D[ e | Q ]
1528 D[ e | e, Q ] = guard e >> \p -> D[ e | Q ]
1529 D[ e | let d, Q ] = let d in D[ e | Q ]
1531 -- Parallel comprehensions (iterate for multiple parallel branches)
1532 D[ e | (Q | R), S ] = mzip D[ Qv | Q ] D[ Rv | R ] >>= \(Qv,Rv) -> D[ e | S ]
1534 -- Transform comprehensions
1535 D[ e | Q then f, R ] = f D[ Qv | Q ] >>= \Qv -> D[ e | R ]
1537 D[ e | Q then f by b, R ] = f (\Qv -> b) D[ Qv | Q ] >>= \Qv -> D[ e | R ]
1539 D[ e | Q then group using f, R ] = f D[ Qv | Q ] >>= \ys ->
1540 case (fmap selQv1 ys, ..., fmap selQvn ys) of
1543 D[ e | Q then group by b using f, R ] = f (\Qv -> b) D[ Qv | Q ] >>= \ys ->
1544 case (fmap selQv1 ys, ..., fmap selQvn ys) of
1547 where Qv is the tuple of variables bound by Q (and used subsequently)
1548 selQvi is a selector mapping Qv to the ith component of Qv
1550 Operator Standard binding Expected type
1551 --------------------------------------------------------------------
1552 return GHC.Base t1 -> m t2
1553 (>>=) GHC.Base m1 t1 -> (t2 -> m2 t3) -> m3 t3
1554 (>>) GHC.Base m1 t1 -> m2 t2 -> m3 t3
1555 guard Control.Monad t1 -> m t2
1556 fmap GHC.Base forall a b. (a->b) -> n a -> n b
1557 mzip Control.Monad.Zip forall a b. m a -> m b -> m (a,b)
1559 The comprehension should typecheck when its desugaring would typecheck,
1560 except that (as discussed in :ref:`generalised-list-comprehensions`) in the
1561 "then ``f``" and "then group using ``f``" clauses, when the "by ``b``" qualifier
1562 is omitted, argument ``f`` should have a polymorphic type. In particular, "then
1563 ``Data.List.sort``" and "then group using ``Data.List.group``" are
1564 insufficiently polymorphic.
1566 Monad comprehensions support rebindable syntax
1567 (:ref:`rebindable-syntax`). Without rebindable syntax, the operators
1568 from the "standard binding" module are used; with rebindable syntax, the
1569 operators are looked up in the current lexical scope. For example,
1570 parallel comprehensions will be typechecked and desugared using whatever
1571 "``mzip``" is in scope.
1573 The rebindable operators must have the "Expected type" given in the
1574 table above. These types are surprisingly general. For example, you can
1575 use a bind operator with the type
1579 (>>=) :: T x y a -> (a -> T y z b) -> T x z b
1581 In the case of transform comprehensions, notice that the groups are
1582 parameterised over some arbitrary type ``n`` (provided it has an
1583 ``fmap``, as well as the comprehension being over an arbitrary monad.
1585 .. _monadfail-desugaring:
1587 New monadic failure desugaring mechanism
1588 ----------------------------------------
1590 .. extension:: MonadFailDesugaring
1591 :shortdesc: Enable monadfail desugaring.
1595 Use the ``MonadFail.fail`` instead of the legacy ``Monad.fail`` function
1596 when desugaring refutable patterns in ``do`` blocks.
1598 The ``-XMonadFailDesugaring`` extension switches the desugaring of
1599 ``do``-blocks to use ``MonadFail.fail`` instead of ``Monad.fail``.
1601 This extension is enabled by default since GHC 8.6.1, under the
1602 `MonadFail Proposal (MFP)
1603 <https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail>`__.
1605 This extension is temporary, and will be deprecated in a future release.
1607 .. _rebindable-syntax:
1609 Rebindable syntax and the implicit Prelude import
1610 -------------------------------------------------
1612 .. extension:: NoImplicitPrelude
1613 :shortdesc: Don't implicitly ``import Prelude``.
1614 Implied by :extension:`RebindableSyntax`.
1618 Don't import ``Prelude`` by default.
1620 GHC normally imports ``Prelude.hi`` files for
1621 you. If you'd rather it didn't, then give it a ``-XNoImplicitPrelude``
1622 option. The idea is that you can then import a Prelude of your own. (But
1623 don't call it ``Prelude``; the Haskell module namespace is flat, and you
1624 must not conflict with any Prelude module.)
1626 .. extension:: RebindableSyntax
1627 :shortdesc: Employ rebindable syntax.
1628 Implies :extension:`NoImplicitPrelude`.
1630 :implies: :extension:`NoImplicitPrelude`
1633 Enable rebinding of a variety of usually-built-in operations.
1635 Suppose you are importing a Prelude of your own in order to define your
1636 own numeric class hierarchy. It completely defeats that purpose if the
1637 literal "1" means "``Prelude.fromInteger 1``", which is what the Haskell
1638 Report specifies. So the :extension:`RebindableSyntax` extension causes the
1639 following pieces of built-in syntax to refer to *whatever is in scope*,
1640 not the Prelude versions:
1642 - An integer literal ``368`` means "``fromInteger (368::Integer)``",
1643 rather than "``Prelude.fromInteger (368::Integer)``".
1645 - Fractional literals are handled in just the same way, except that the
1646 translation is ``fromRational (3.68::Rational)``.
1648 - String literals are also handled the same way, except that the
1649 translation is ``fromString ("368"::String)``.
1651 - The equality test in an overloaded numeric pattern uses whatever
1652 ``(==)`` is in scope.
1654 - The subtraction operation, and the greater-than-or-equal test, in
1655 ``n+k`` patterns use whatever ``(-)`` and ``(>=)`` are in scope.
1657 - Negation (e.g. "``- (f x)``") means "``negate (f x)``", both in
1658 numeric patterns, and expressions.
1660 - Conditionals (e.g. "``if`` e1 ``then`` e2 ``else`` e3") means
1661 "``ifThenElse`` e1 e2 e3". However ``case`` expressions are
1664 - "Do" notation is translated using whatever functions ``(>>=)``,
1665 ``(>>)``, and ``fail``, are in scope (not the Prelude versions). List
1666 comprehensions, ``mdo`` (:ref:`recursive-do-notation`), and parallel
1667 array comprehensions, are unaffected.
1669 - Arrow notation (see :ref:`arrow-notation`) uses whatever ``arr``,
1670 ``(>>>)``, ``first``, ``app``, ``(|||)`` and ``loop`` functions are
1671 in scope. But unlike the other constructs, the types of these
1672 functions must match the Prelude types very closely. Details are in
1673 flux; if you want to use this, ask!
1675 - List notation, such as ``[x,y]`` or ``[m..n]`` can also be treated
1676 via rebindable syntax if you use `-XOverloadedLists`;
1677 see :ref:`overloaded-lists`.
1679 - An overloaded label "``#foo``" means "``fromLabel @"foo"``", rather than
1680 "``GHC.OverloadedLabels.fromLabel @"foo"``" (see :ref:`overloaded-labels`).
1682 :extension:`RebindableSyntax` implies :extension:`NoImplicitPrelude`.
1684 In all cases (apart from arrow notation), the static semantics should be
1685 that of the desugared form, even if that is a little unexpected. For
1686 example, the static semantics of the literal ``368`` is exactly that of
1687 ``fromInteger (368::Integer)``; it's fine for ``fromInteger`` to have
1688 any of the types: ::
1690 fromInteger :: Integer -> Integer
1691 fromInteger :: forall a. Foo a => Integer -> a
1692 fromInteger :: Num a => a -> Integer
1693 fromInteger :: Integer -> Bool -> Bool
1695 Be warned: this is an experimental facility, with fewer checks than
1696 usual. Use ``-dcore-lint`` to typecheck the desugared program. If Core
1697 Lint is happy you should be all right.
1699 Things unaffected by :extension:`RebindableSyntax`
1700 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1702 :extension:`RebindableSyntax` does not apply to any code generated from a
1703 ``deriving`` clause or declaration. To see why, consider the following code: ::
1705 {-# LANGUAGE RebindableSyntax, OverloadedStrings #-}
1706 newtype Text = Text String
1708 fromString :: String -> Text
1711 data Foo = Foo deriving Show
1713 This will generate code to the effect of: ::
1715 instance Show Foo where
1716 showsPrec _ Foo = showString "Foo"
1718 But because :extension:`RebindableSyntax` and :extension:`OverloadedStrings`
1719 are enabled, the ``"Foo"`` string literal would now be of type ``Text``, not
1720 ``String``, which ``showString`` doesn't accept! This causes the generated
1721 ``Show`` instance to fail to typecheck. It's hard to imagine any scenario where
1722 it would be desirable have :extension:`RebindableSyntax` behavior within
1723 derived code, so GHC simply ignores :extension:`RebindableSyntax` entirely
1724 when checking derived code.
1726 .. _postfix-operators:
1731 .. extension:: PostfixOperators
1732 :shortdesc: Enable postfix operators.
1736 Allow the use of post-fix operators
1738 The :extension:`PostfixOperators` extension enables a small extension to the syntax
1739 of left operator sections, which allows you to define postfix operators.
1740 The extension is this: the left section ::
1744 is equivalent (from the point of view of both type checking and
1745 execution) to the expression ::
1749 (for any expression ``e`` and operator ``(!)``. The strict Haskell 98
1750 interpretation is that the section is equivalent to ::
1754 That is, the operator must be a function of two arguments. GHC allows it
1755 to take only one argument, and that in turn allows you to write the
1758 The extension does not extend to the left-hand side of function
1759 definitions; you must define such a function in prefix form.
1766 .. extension:: TupleSections
1767 :shortdesc: Enable tuple sections.
1771 Allow the use of tuple section syntax
1773 The :extension:`TupleSections` extension enables partially applied
1774 tuple constructors. For example, the following program ::
1778 is considered to be an alternative notation for the more unwieldy
1783 You can omit any combination of arguments to the tuple, as in the
1786 (, "I", , , "Love", , 1337)
1788 which translates to ::
1790 \a b c d -> (a, "I", b, c, "Love", d, 1337)
1792 If you have `unboxed tuples <#unboxed-tuples>`__ enabled, tuple sections
1793 will also be available for them, like so ::
1797 Because there is no unboxed unit tuple, the following expression ::
1801 continues to stand for the unboxed singleton tuple data constructor.
1808 .. extension:: LambdaCase
1809 :shortdesc: Enable lambda-case expressions.
1813 Allow the use of lambda-case syntax.
1815 The :extension:`LambdaCase` extension enables expressions of the form ::
1817 \case { p1 -> e1; ...; pN -> eN }
1819 which is equivalent to ::
1821 \freshName -> case freshName of { p1 -> e1; ...; pN -> eN }
1823 Note that ``\case`` starts a layout, so you can write ::
1832 Empty case alternatives
1833 -----------------------
1835 .. extension:: EmptyCase
1836 :shortdesc: Allow empty case alternatives.
1840 Allow empty case expressions.
1842 The :extension:`EmptyCase` extension enables case expressions, or lambda-case
1843 expressions, that have no alternatives, thus: ::
1845 case e of { } -- No alternatives
1849 \case { } -- -XLambdaCase is also required
1851 This can be useful when you know that the expression being scrutinised
1852 has no non-bottom values. For example:
1860 With dependently-typed features it is more useful (see :ghc-ticket:`2431`). For
1861 example, consider these two candidate definitions of ``absurd``:
1868 absurd :: True :~: False -> a
1869 absurd x = error "absurd" -- (A)
1870 absurd x = case x of {} -- (B)
1872 We much prefer (B). Why? Because GHC can figure out that
1873 ``(True :~: False)`` is an empty type. So (B) has no partiality and GHC
1874 is able to compile with :ghc-flag:`-Wincomplete-patterns` and
1875 :ghc-flag:`-Werror`. On the other hand (A) looks dangerous, and GHC doesn't
1876 check to make sure that, in fact, the function can never get called.
1880 Multi-way if-expressions
1881 ------------------------
1883 .. extension:: MultiWayIf
1884 :shortdesc: Enable multi-way if-expressions.
1888 Allow the use of multi-way-``if`` syntax.
1890 With :extension:`MultiWayIf` extension GHC accepts conditional expressions with
1891 multiple branches: ::
1893 if | guard1 -> expr1
1897 which is roughly equivalent to ::
1904 Multi-way if expressions introduce a new layout context. So the example
1905 above is equivalent to: ::
1907 if { | guard1 -> expr1
1912 The following behaves as expected: ::
1914 if | guard1 -> if | guard2 -> expr2
1918 because layout translates it as ::
1920 if { | guard1 -> if { | guard2 -> expr2
1926 Layout with multi-way if works in the same way as other layout contexts,
1927 except that the semi-colons between guards in a multi-way if are
1928 optional. So it is not necessary to line up all the guards at the same
1929 column; this is consistent with the way guards work in function
1930 definitions and case expressions.
1932 .. _local-fixity-declarations:
1934 Local Fixity Declarations
1935 -------------------------
1937 A careful reading of the Haskell 98 Report reveals that fixity
1938 declarations (``infix``, ``infixl``, and ``infixr``) are permitted to
1939 appear inside local bindings such those introduced by ``let`` and
1940 ``where``. However, the Haskell Report does not specify the semantics of
1941 such bindings very precisely.
1943 In GHC, a fixity declaration may accompany a local binding: ::
1950 and the fixity declaration applies wherever the binding is in scope. For
1951 example, in a ``let``, it applies in the right-hand sides of other
1952 ``let``-bindings and the body of the ``let``\ C. Or, in recursive ``do``
1953 expressions (:ref:`recursive-do-notation`), the local fixity
1954 declarations of a ``let`` statement scope over other statements in the
1955 group, just as the bound name does.
1957 Moreover, a local fixity declaration *must* accompany a local binding
1958 of that name: it is not possible to revise the fixity of name bound
1961 let infixr 9 $ in ...
1963 Because local fixity declarations are technically Haskell 98, no extension is
1964 necessary to enable them.
1966 .. _package-imports:
1968 Import and export extensions
1969 ----------------------------
1971 Hiding things the imported module doesn't export
1972 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1974 Technically in Haskell 2010 this is illegal: ::
1980 import A hiding( g ) -- A does not export g
1983 The ``import A hiding( g )`` in module ``B`` is technically an error
1985 5.3.1 <http://www.haskell.org/onlinereport/haskell2010/haskellch5.html#x11-1020005.3.1>`__)
1986 because ``A`` does not export ``g``. However GHC allows it, in the
1987 interests of supporting backward compatibility; for example, a newer
1988 version of ``A`` might export ``g``, and you want ``B`` to work in
1991 The warning :ghc-flag:`-Wdodgy-imports`, which is off by default but included
1992 with :ghc-flag:`-W`, warns if you hide something that the imported module does
1995 .. _package-qualified-imports:
1997 Package-qualified imports
1998 ~~~~~~~~~~~~~~~~~~~~~~~~~
2000 .. extension:: PackageImports
2001 :shortdesc: Enable package-qualified imports.
2005 Allow the use of package-qualified ``import`` syntax.
2007 With the :extension:`PackageImports` extension, GHC allows import declarations to be
2008 qualified by the package name that the module is intended to be imported
2009 from. For example: ::
2011 import "network" Network.Socket
2013 would import the module ``Network.Socket`` from the package ``network``
2014 (any version). This may be used to disambiguate an import when the same
2015 module is available from multiple packages, or is present in both the
2016 current package being built and an external package.
2018 The special package name ``this`` can be used to refer to the current
2019 package being built.
2022 You probably don't need to use this feature, it was added mainly so that we
2023 can build backwards-compatible versions of packages when APIs change. It can
2024 lead to fragile dependencies in the common case: modules occasionally move
2025 from one package to another, rendering any package-qualified imports broken.
2026 See also :ref:`package-thinning-and-renaming` for an alternative way of
2027 disambiguating between module names.
2029 .. _safe-imports-ext:
2035 :shortdesc: Enable the :ref:`Safe Haskell <safe-haskell>` Safe mode.
2040 Declare the Safe Haskell state of the current module.
2042 .. extension:: Trustworthy
2043 :shortdesc: Enable the :ref:`Safe Haskell <safe-haskell>` Trustworthy mode.
2048 Declare the Safe Haskell state of the current module.
2050 .. extension:: Unsafe
2051 :shortdesc: Enable Safe Haskell Unsafe mode.
2056 Declare the Safe Haskell state of the current module.
2058 With the :extension:`Safe`, :extension:`Trustworthy` and :extension:`Unsafe`
2059 language flags, GHC extends the import declaration syntax to take an optional
2060 ``safe`` keyword after the ``import`` keyword. This feature is part of the Safe
2061 Haskell GHC extension. For example: ::
2063 import safe qualified Network.Socket as NS
2065 would import the module ``Network.Socket`` with compilation only
2066 succeeding if ``Network.Socket`` can be safely imported. For a description of
2067 when a import is considered safe see :ref:`safe-haskell`.
2069 .. _explicit-namespaces:
2071 Explicit namespaces in import/export
2072 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2074 .. extension:: ExplicitNamespaces
2075 :shortdesc: Enable using the keyword ``type`` to specify the namespace of
2076 entries in imports and exports (:ref:`explicit-namespaces`).
2077 Implied by :extension:`TypeOperators` and :extension:`TypeFamilies`.
2081 Enable use of explicit namespaces in module export lists.
2083 In an import or export list, such as ::
2085 module M( f, (++) ) where ...
2089 the entities ``f`` and ``(++)`` are *values*. However, with type
2090 operators (:ref:`type-operators`) it becomes possible to declare
2091 ``(++)`` as a *type constructor*. In that case, how would you export or
2094 The :extension:`ExplicitNamespaces` extension allows you to prefix the name of
2095 a type constructor in an import or export list with "``type``" to
2096 disambiguate this case, thus: ::
2098 module M( f, type (++) ) where ...
2099 import N( f, type (++) )
2101 module N( f, type (++) ) where
2102 data family a ++ b = L a | R b
2104 The extension :extension:`ExplicitNamespaces` is implied by
2105 :extension:`TypeOperators` and (for some reason) by :extension:`TypeFamilies`.
2107 In addition, with :extension:`PatternSynonyms` you can prefix the name of a
2108 data constructor in an import or export list with the keyword
2109 ``pattern``, to allow the import or export of a data constructor without
2110 its parent type constructor (see :ref:`patsyn-impexp`).
2112 .. _block-arguments:
2114 More liberal syntax for function arguments
2115 ------------------------------------------
2117 .. extension:: BlockArguments
2118 :shortdesc: Allow ``do`` blocks and other constructs as function arguments.
2122 Allow ``do`` expressions, lambda expressions, etc. to be directly used as
2123 a function argument.
2125 In Haskell 2010, certain kinds of expressions can be used without parentheses
2126 as an argument to an operator, but not as an argument to a function.
2127 They include ``do``, lambda, ``if``, ``case``, and ``let``
2128 expressions. Some GHC extensions also define language constructs of this type:
2129 ``mdo`` (:ref:`recursive-do-notation`), ``\case`` (:ref:`lambda-case`), and
2130 ``proc`` (:ref:`arrow-notation`).
2132 The :extension:`BlockArguments` extension allows these constructs to be directly
2133 used as a function argument. For example::
2149 withForeignPtr fptr \ptr -> c_memcpy buf ptr size
2153 withForeignPtr fptr (\ptr -> c_memcpy buf ptr size)
2155 Changes to the grammar
2156 ~~~~~~~~~~~~~~~~~~~~~~
2158 The Haskell report `defines
2159 <https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-220003>`_
2160 the ``lexp`` nonterminal thus (``*`` indicates a rule of interest)::
2162 lexp → \ apat1 … apatn -> exp (lambda abstraction, n ≥ 1) *
2163 | let decls in exp (let expression) *
2164 | if exp [;] then exp [;] else exp (conditional) *
2165 | case exp of { alts } (case expression) *
2166 | do { stmts } (do expression) *
2169 fexp → [fexp] aexp (function application)
2171 aexp → qvar (variable)
2172 | gcon (general constructor)
2174 | ( exp ) (parenthesized expression)
2175 | qcon { fbind1 … fbindn } (labeled construction)
2176 | aexp { fbind1 … fbindn } (labelled update)
2179 The :extension:`BlockArguments` extension moves these production rules under
2184 fexp → [fexp] aexp (function application)
2186 aexp → qvar (variable)
2187 | gcon (general constructor)
2189 | ( exp ) (parenthesized expression)
2190 | qcon { fbind1 … fbindn } (labeled construction)
2191 | aexp { fbind1 … fbindn } (labelled update)
2192 | \ apat1 … apatn -> exp (lambda abstraction, n ≥ 1) *
2193 | let decls in exp (let expression) *
2194 | if exp [;] then exp [;] else exp (conditional) *
2195 | case exp of { alts } (case expression) *
2196 | do { stmts } (do expression) *
2199 Now the ``lexp`` nonterminal is redundant and can be dropped from the grammar.
2201 Note that this change relies on an existing meta-rule to resolve ambiguities:
2203 The grammar is ambiguous regarding the extent of lambda abstractions, let
2204 expressions, and conditionals. The ambiguity is resolved by the meta-rule
2205 that each of these constructs extends as far to the right as possible.
2207 For example, ``f \a -> a b`` will be parsed as ``f (\a -> a b)``, not as ``f
2212 Summary of stolen syntax
2213 ------------------------
2215 Turning on an option that enables special syntax *might* cause working
2216 Haskell 98 code to fail to compile, perhaps because it uses a variable
2217 name which has become a reserved word. This section lists the syntax
2218 that is "stolen" by language extensions. We use notation and nonterminal
2219 names from the Haskell 98 lexical syntax (see the Haskell 98 Report). We
2220 only list syntax changes here that might affect existing working
2221 programs (i.e. "stolen" syntax). Many of these extensions will also
2222 enable new context-free syntax, but in all cases programs written to use
2223 the new syntax would not be compilable without the option enabled.
2225 There are two classes of special syntax:
2227 - New reserved words and symbols: character sequences which are no
2228 longer available for use as identifiers in the program.
2230 - Other special syntax: sequences of characters that have a different
2231 meaning when this particular option is turned on.
2233 The following syntax is stolen:
2239 Stolen (in types) by: :extension:`ExplicitForAll`, and hence by
2240 :extension:`ScopedTypeVariables`, :extension:`LiberalTypeSynonyms`,
2241 :extension:`RankNTypes`, :extension:`ExistentialQuantification`
2247 Stolen by: :extension:`RecursiveDo`
2253 Stolen by: :extension:`ForeignFunctionInterface`
2255 ``rec``, ``proc``, ``-<``, ``>-``, ``-<<``, ``>>-``, ``(|``, ``|)``
2259 Stolen by: :extension:`Arrows`
2263 single: implicit parameters
2265 Stolen by: :extension:`ImplicitParams`
2267 ``[|``, ``[e|``, ``[p|``, ``[d|``, ``[t|``, ``[||``, ``[e||``
2269 single: Quasi-quotes
2271 Stolen by: :extension:`QuasiQuotes`. Moreover, this introduces an ambiguity
2272 with list comprehension syntax. See the
2273 :ref:`discussion on quasi-quoting <quasi-quotes-list-comprehension-ambiguity>`
2276 ``$(``, ``$$(``, ``$varid``, ``$$varid``
2278 single: Template Haskell
2280 Stolen by: :extension:`TemplateHaskell`
2284 single: quasi-quotation
2286 Stolen by: :extension:`QuasiQuotes`
2288 ⟨varid⟩, ``#``\ ⟨char⟩, ``#``, ⟨string⟩, ``#``, ⟨integer⟩, ``#``, ⟨float⟩, ``#``, ⟨float⟩, ``##``
2289 Stolen by: :extension:`MagicHash`
2292 Stolen by: :extension:`UnboxedTuples`
2294 ⟨varid⟩, ``!``, ⟨varid⟩
2295 Stolen by: :extension:`BangPatterns`
2298 Stolen by: :extension:`PatternSynonyms`
2301 Stolen by: :extension:`StaticPointers`
2303 .. _data-type-extensions:
2305 Extensions to data types and type synonyms
2306 ==========================================
2310 Data types with no constructors
2311 -------------------------------
2313 .. extension:: EmptyDataDecls
2314 :shortdesc: Allow definition of empty ``data`` types.
2318 Allow definition of empty ``data`` types.
2320 With the :extension:`EmptyDataDecls` extension, GHC lets you declare a
2321 data type with no constructors.
2323 You only need to enable this extension if the language you're using
2324 is Haskell 98, in which a data type must have at least one constructor.
2325 Haskell 2010 relaxed this rule to allow data types with no constructors,
2326 and thus :extension:`EmptyDataDecls` is enabled by default when the
2327 language is Haskell 2010.
2332 data T a -- T :: Type -> Type
2334 Syntactically, the declaration lacks the "= constrs" part. The type can be
2335 parameterised over types of any kind, but if the kind is not ``Type`` then an
2336 explicit kind annotation must be used (see :ref:`kinding`).
2338 Such data types have only one value, namely bottom. Nevertheless, they
2339 can be useful when defining "phantom types".
2341 In conjunction with the :ghc-flag:`-XEmptyDataDeriving` extension, empty data
2342 declarations can also derive instances of standard type classes
2343 (see :ref:`empty-data-deriving`).
2345 .. _datatype-contexts:
2350 .. extension:: DatatypeContexts
2351 :shortdesc: Allow contexts on ``data`` types.
2355 Allow contexts on ``data`` types.
2357 Haskell allows datatypes to be given contexts, e.g. ::
2359 data Eq a => Set a = NilSet | ConsSet a (Set a)
2361 give constructors with types: ::
2364 ConsSet :: Eq a => a -> Set a -> Set a
2366 This is widely considered a misfeature, and is going to be removed from
2367 the language. In GHC, it is controlled by the deprecated extension
2368 ``DatatypeContexts``.
2372 Infix type constructors, classes, and type variables
2373 ----------------------------------------------------
2375 GHC allows type constructors, classes, and type variables to be
2376 operators, and to be written infix, very much like expressions. More
2379 - A type constructor or class can be any non-reserved operator.
2380 Symbols used in types are always like capitalized identifiers; they
2381 are never variables. Note that this is different from the lexical
2382 syntax of data constructors, which are required to begin with a
2385 - Data type and type-synonym declarations can be written infix,
2386 parenthesised if you want further arguments. E.g. ::
2388 data a :*: b = Foo a b
2389 type a :+: b = Either a b
2390 class a :=: b where ...
2392 data (a :**: b) x = Baz a b x
2393 type (a :++: b) y = Either (a,b) y
2395 - Types, and class constraints, can be written infix. For example ::
2398 f :: (a :=: b) => a -> b
2400 - Back-quotes work as for expressions, both for type constructors and
2401 type variables; e.g. ``Int `Either` Bool``, or ``Int `a` Bool``.
2402 Similarly, parentheses work the same; e.g. ``(:*:) Int Bool``.
2404 - Fixities may be declared for type constructors, or classes, just as
2405 for data constructors. However, one cannot distinguish between the
2406 two in a fixity declaration; a fixity declaration sets the fixity for
2407 a data constructor and the corresponding type constructor. For
2412 sets the fixity for both type constructor ``T`` and data constructor
2413 ``T``, and similarly for ``:*:``. ``Int `a` Bool``.
2415 - The function arrow ``->`` is ``infixr`` with fixity -1.
2422 .. extension:: TypeOperators
2423 :shortdesc: Enable type operators.
2424 Implies :extension:`ExplicitNamespaces`.
2426 :implies: :extension:`ExplicitNamespaces`
2429 Allow the use and definition of types with operator names.
2431 In types, an operator symbol like ``(+)`` is normally treated as a type
2432 *variable*, just like ``a``. Thus in Haskell 98 you can say
2436 type T (+) = ((+), (+))
2437 -- Just like: type T a = (a,a)
2442 As you can see, using operators in this way is not very useful, and
2443 Haskell 98 does not even allow you to write them infix.
2445 The language :extension:`TypeOperators` changes this behaviour:
2447 - Operator symbols become type *constructors* rather than type
2450 - Operator symbols in types can be written infix, both in definitions
2451 and uses. For example: ::
2453 data a + b = Plus a b
2454 type Foo = Int + Bool
2456 - There is now some potential ambiguity in import and export lists; for
2457 example if you write ``import M( (+) )`` do you mean the *function*
2458 ``(+)`` or the *type constructor* ``(+)``? The default is the former,
2459 but with :extension:`ExplicitNamespaces` (which is implied by
2460 :extension:`TypeOperators`) GHC allows you to specify the latter by
2461 preceding it with the keyword ``type``, thus: ::
2463 import M( type (+) )
2465 See :ref:`explicit-namespaces`.
2467 - The fixity of a type operator may be set using the usual fixity
2468 declarations but, as in :ref:`infix-tycons`, the function and type
2469 constructor share a single fixity.
2473 Liberalised type synonyms
2474 -------------------------
2476 .. extension:: LiberalTypeSynonyms
2477 :shortdesc: Enable liberalised type synonyms.
2479 :implies: :extension:`ExplicitForAll`
2482 Relax many of the Haskell 98 rules on type synonym definitions.
2484 Type synonyms are like macros at the type level, but Haskell 98 imposes
2485 many rules on individual synonym declarations. With the
2486 :extension:`LiberalTypeSynonyms` extension, GHC does validity checking on types
2487 *only after expanding type synonyms*. That means that GHC can be very
2488 much more liberal about type synonyms than Haskell 98.
2490 - You can write a ``forall`` (including overloading) in a type synonym,
2493 type Discard a = forall b. Show b => a -> b -> (a, String)
2498 g :: Discard Int -> (Int,String) -- A rank-2 type
2501 - If you also use :extension:`UnboxedTuples`, you can write an unboxed tuple
2502 in a type synonym: ::
2504 type Pr = (# Int, Int #)
2509 - You can apply a type synonym to a forall type: ::
2511 type Foo a = a -> a -> Bool
2513 f :: Foo (forall b. b->b)
2515 After expanding the synonym, ``f`` has the legal (in GHC) type: ::
2517 f :: (forall b. b->b) -> (forall b. b->b) -> Bool
2519 - You can apply a type synonym to a partially applied type synonym: ::
2521 type Generic i o = forall x. i x -> o x
2524 foo :: Generic Id []
2526 After expanding the synonym, ``foo`` has the legal (in GHC) type: ::
2528 foo :: forall x. x -> [x]
2530 GHC currently does kind checking before expanding synonyms (though even
2531 that could be changed).
2533 After expanding type synonyms, GHC does validity checking on types,
2534 looking for the following malformedness which isn't detected simply by
2537 - Type constructor applied to a type involving for-alls (if
2538 :extension:`ImpredicativeTypes` is off)
2540 - Partially-applied type synonym.
2542 So, for example, this will be rejected: ::
2544 type Pr = forall a. a
2549 because GHC does not allow type constructors applied to for-all types.
2551 .. _existential-quantification:
2553 Existentially quantified data constructors
2554 ------------------------------------------
2556 .. extension:: ExistentialQuantification
2557 :shortdesc: Enable liberalised type synonyms.
2559 :implies: :extension:`ExplicitForAll`
2562 Allow existentially quantified type variables in types.
2564 The idea of using existential quantification in data type declarations
2565 was suggested by Perry, and implemented in Hope+ (Nigel Perry, *The
2566 Implementation of Practical Functional Programming Languages*, PhD
2567 Thesis, University of London, 1991). It was later formalised by Laufer
2568 and Odersky (*Polymorphic type inference and abstract data types*,
2569 TOPLAS, 16(5), pp. 1411-1430, 1994). It's been in Lennart Augustsson's
2570 ``hbc`` Haskell compiler for several years, and proved very useful.
2571 Here's the idea. Consider the declaration: ::
2573 data Foo = forall a. MkFoo a (a -> Bool)
2576 The data type ``Foo`` has two constructors with types: ::
2578 MkFoo :: forall a. a -> (a -> Bool) -> Foo
2581 Notice that the type variable ``a`` in the type of ``MkFoo`` does not
2582 appear in the data type itself, which is plain ``Foo``. For example, the
2583 following expression is fine: ::
2585 [MkFoo 3 even, MkFoo 'c' isUpper] :: [Foo]
2587 Here, ``(MkFoo 3 even)`` packages an integer with a function ``even``
2588 that maps an integer to ``Bool``; and ``MkFoo 'c'
2589 isUpper`` packages a character with a compatible function. These two
2590 things are each of type ``Foo`` and can be put in a list.
2592 What can we do with a value of type ``Foo``? In particular, what
2593 happens when we pattern-match on ``MkFoo``? ::
2595 f (MkFoo val fn) = ???
2597 Since all we know about ``val`` and ``fn`` is that they are compatible,
2598 the only (useful) thing we can do with them is to apply ``fn`` to
2599 ``val`` to get a boolean. For example: ::
2602 f (MkFoo val fn) = fn val
2604 What this allows us to do is to package heterogeneous values together
2605 with a bunch of functions that manipulate them, and then treat that
2606 collection of packages in a uniform manner. You can express quite a bit
2607 of object-oriented-like programming this way.
2614 What has this to do with *existential* quantification? Simply that
2615 ``MkFoo`` has the (nearly) isomorphic type ::
2617 MkFoo :: (exists a . (a, a -> Bool)) -> Foo
2619 But Haskell programmers can safely think of the ordinary *universally*
2620 quantified type given above, thereby avoiding adding a new existential
2621 quantification construct.
2623 .. _existential-with-context:
2625 Existentials and type classes
2626 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2628 An easy extension is to allow arbitrary contexts before the constructor.
2631 data Baz = forall a. Eq a => Baz1 a a
2632 | forall b. Show b => Baz2 b (b -> b)
2634 The two constructors have the types you'd expect: ::
2636 Baz1 :: forall a. Eq a => a -> a -> Baz
2637 Baz2 :: forall b. Show b => b -> (b -> b) -> Baz
2639 But when pattern matching on ``Baz1`` the matched values can be compared
2640 for equality, and when pattern matching on ``Baz2`` the first matched
2641 value can be converted to a string (as well as applying the function to
2642 it). So this program is legal: ::
2645 f (Baz1 p q) | p == q = "Yes"
2647 f (Baz2 v fn) = show (fn v)
2649 Operationally, in a dictionary-passing implementation, the constructors
2650 ``Baz1`` and ``Baz2`` must store the dictionaries for ``Eq`` and
2651 ``Show`` respectively, and extract it on pattern matching.
2653 .. _existential-records:
2658 GHC allows existentials to be used with records syntax as well. For
2661 data Counter a = forall self. NewCounter
2663 , _inc :: self -> self
2664 , _display :: self -> IO ()
2668 Here ``tag`` is a public field, with a well-typed selector function
2669 ``tag :: Counter a -> a``. The ``self`` type is hidden from the outside;
2670 any attempt to apply ``_this``, ``_inc`` or ``_display`` as functions
2671 will raise a compile-time error. In other words, *GHC defines a record
2672 selector function only for fields whose type does not mention the
2673 existentially-quantified variables*. (This example used an underscore in
2674 the fields for which record selectors will not be defined, but that is
2675 only programming style; GHC ignores them.)
2677 To make use of these hidden fields, we need to create some helper
2680 inc :: Counter a -> Counter a
2681 inc (NewCounter x i d t) = NewCounter
2682 { _this = i x, _inc = i, _display = d, tag = t }
2684 display :: Counter a -> IO ()
2685 display NewCounter{ _this = x, _display = d } = d x
2687 Now we can define counters with different underlying implementations: ::
2689 counterA :: Counter String
2690 counterA = NewCounter
2691 { _this = 0, _inc = (1+), _display = print, tag = "A" }
2693 counterB :: Counter String
2694 counterB = NewCounter
2695 { _this = "", _inc = ('#':), _display = putStrLn, tag = "B" }
2698 display (inc counterA) -- prints "1"
2699 display (inc (inc counterB)) -- prints "##"
2701 Record update syntax is supported for existentials (and GADTs): ::
2703 setTag :: Counter a -> a -> Counter a
2704 setTag obj t = obj{ tag = t }
2706 The rule for record update is this:
2708 the types of the updated fields may mention only the universally-quantified
2709 type variables of the data constructor. For GADTs, the field may mention
2710 only types that appear as a simple type-variable argument in the
2711 constructor's result type.
2715 data T a b where { T1 { f1::a, f2::b, f3::(b,c) } :: T a b } -- c is existential
2716 upd1 t x = t { f1=x } -- OK: upd1 :: T a b -> a' -> T a' b
2717 upd2 t x = t { f3=x } -- BAD (f3's type mentions c, which is
2718 -- existentially quantified)
2720 data G a b where { G1 { g1::a, g2::c } :: G a [c] }
2721 upd3 g x = g { g1=x } -- OK: upd3 :: G a b -> c -> G c b
2722 upd4 g x = g { g2=x } -- BAD (f2's type mentions c, which is not a simple
2723 -- type-variable argument in G1's result type)
2728 There are several restrictions on the ways in which existentially-quantified
2729 constructors can be used.
2731 - When pattern matching, each pattern match introduces a new, distinct,
2732 type for each existential type variable. These types cannot be
2733 unified with any other type, nor can they escape from the scope of
2734 the pattern match. For example, these fragments are incorrect: ::
2738 Here, the type bound by ``MkFoo`` "escapes", because ``a`` is the
2739 result of ``f1``. One way to see why this is wrong is to ask what
2742 f1 :: Foo -> a -- Weird!
2744 What is this "``a``" in the result type? Clearly we don't mean this: ::
2746 f1 :: forall a. Foo -> a -- Wrong!
2748 The original program is just plain wrong. Here's another sort of
2751 f2 (Baz1 a b) (Baz1 p q) = a==q
2753 It's ok to say ``a==b`` or ``p==q``, but ``a==q`` is wrong because it
2754 equates the two distinct types arising from the two ``Baz1``
2757 - You can't pattern-match on an existentially quantified constructor in
2758 a ``let`` or ``where`` group of bindings. So this is illegal: ::
2760 f3 x = a==b where { Baz1 a b = x }
2762 Instead, use a ``case`` expression: ::
2764 f3 x = case x of Baz1 a b -> a==b
2766 In general, you can only pattern-match on an existentially-quantified
2767 constructor in a ``case`` expression or in the patterns of a function
2768 definition. The reason for this restriction is really an
2769 implementation one. Type-checking binding groups is already a
2770 nightmare without existentials complicating the picture. Also an
2771 existential pattern binding at the top level of a module doesn't make
2772 sense, because it's not clear how to prevent the
2773 existentially-quantified type "escaping". So for now, there's a
2774 simple-to-state restriction. We'll see how annoying it is.
2776 - You can't use existential quantification for ``newtype``
2777 declarations. So this is illegal: ::
2779 newtype T = forall a. Ord a => MkT a
2781 Reason: a value of type ``T`` must be represented as a pair of a
2782 dictionary for ``Ord t`` and a value of type ``t``. That contradicts
2783 the idea that ``newtype`` should have no concrete representation. You
2784 can get just the same efficiency and effect by using ``data`` instead
2785 of ``newtype``. If there is no overloading involved, then there is
2786 more of a case for allowing an existentially-quantified ``newtype``,
2787 because the ``data`` version does carry an implementation cost, but
2788 single-field existentially quantified constructors aren't much use.
2789 So the simple restriction (no existential stuff on ``newtype``)
2790 stands, unless there are convincing reasons to change it.
2792 - You can't use ``deriving`` to define instances of a data type with
2793 existentially quantified data constructors. Reason: in most cases it
2794 would not make sense. For example:; ::
2796 data T = forall a. MkT [a] deriving( Eq )
2798 To derive ``Eq`` in the standard way we would need to have equality
2799 between the single component of two ``MkT`` constructors: ::
2802 (MkT a) == (MkT b) = ???
2804 But ``a`` and ``b`` have distinct types, and so can't be compared.
2805 It's just about possible to imagine examples in which the derived
2806 instance would make sense, but it seems altogether simpler simply to
2807 prohibit such declarations. Define your own instances!
2811 Declaring data types with explicit constructor signatures
2812 ---------------------------------------------------------
2814 .. extension:: GADTSyntax
2815 :shortdesc: Enable generalised algebraic data type syntax.
2819 Allow the use of GADT syntax in data type definitions (but not GADTs
2820 themselves; for this see :extension:`GADTs`)
2822 When the ``GADTSyntax`` extension is enabled, GHC allows you to declare
2823 an algebraic data type by giving the type signatures of constructors
2824 explicitly. For example: ::
2828 Just :: a -> Maybe a
2830 The form is called a "GADT-style declaration" because Generalised
2831 Algebraic Data Types, described in :ref:`gadt`, can only be declared
2834 Notice that GADT-style syntax generalises existential types
2835 (:ref:`existential-quantification`). For example, these two declarations
2838 data Foo = forall a. MkFoo a (a -> Bool)
2839 data Foo' where { MKFoo :: a -> (a->Bool) -> Foo' }
2841 Any data type that can be declared in standard Haskell 98 syntax can
2842 also be declared using GADT-style syntax. The choice is largely
2843 stylistic, but GADT-style declarations differ in one important respect:
2844 they treat class constraints on the data constructors differently.
2845 Specifically, if the constructor is given a type-class context, that
2846 context is made available by pattern matching. For example: ::
2849 MkSet :: Eq a => [a] -> Set a
2851 makeSet :: Eq a => [a] -> Set a
2852 makeSet xs = MkSet (nub xs)
2854 insert :: a -> Set a -> Set a
2855 insert a (MkSet as) | a `elem` as = MkSet as
2856 | otherwise = MkSet (a:as)
2858 A use of ``MkSet`` as a constructor (e.g. in the definition of
2859 ``makeSet``) gives rise to a ``(Eq a)`` constraint, as you would expect.
2860 The new feature is that pattern-matching on ``MkSet`` (as in the
2861 definition of ``insert``) makes *available* an ``(Eq a)`` context. In
2862 implementation terms, the ``MkSet`` constructor has a hidden field that
2863 stores the ``(Eq a)`` dictionary that is passed to ``MkSet``; so when
2864 pattern-matching that dictionary becomes available for the right-hand
2865 side of the match. In the example, the equality dictionary is used to
2866 satisfy the equality constraint generated by the call to ``elem``, so
2867 that the type of ``insert`` itself has no ``Eq`` constraint.
2869 For example, one possible application is to reify dictionaries: ::
2871 data NumInst a where
2872 MkNumInst :: Num a => NumInst a
2874 intInst :: NumInst Int
2877 plus :: NumInst a -> a -> a -> a
2878 plus MkNumInst p q = p + q
2880 Here, a value of type ``NumInst a`` is equivalent to an explicit
2881 ``(Num a)`` dictionary.
2883 All this applies to constructors declared using the syntax of
2884 :ref:`existential-with-context`. For example, the ``NumInst`` data type
2885 above could equivalently be declared like this: ::
2888 = Num a => MkNumInst (NumInst a)
2890 Notice that, unlike the situation when declaring an existential, there
2891 is no ``forall``, because the ``Num`` constrains the data type's
2892 universally quantified type variable ``a``. A constructor may have both
2893 universal and existential type variables: for example, the following two
2894 declarations are equivalent: ::
2897 = forall b. (Num a, Eq b) => MkT1 a b
2899 MkT2 :: (Num a, Eq b) => a -> b -> T2 a
2901 All this behaviour contrasts with Haskell 98's peculiar treatment of
2902 contexts on a data type declaration (Section 4.2.1 of the Haskell 98
2903 Report). In Haskell 98 the definition ::
2905 data Eq a => Set' a = MkSet' [a]
2907 gives ``MkSet'`` the same type as ``MkSet`` above. But instead of
2908 *making available* an ``(Eq a)`` constraint, pattern-matching on
2909 ``MkSet'`` *requires* an ``(Eq a)`` constraint! GHC faithfully
2910 implements this behaviour, odd though it is. But for GADT-style
2911 declarations, GHC's behaviour is much more useful, as well as much more
2914 The rest of this section gives further details about GADT-style data
2917 - The result type of each data constructor must begin with the type
2918 constructor being defined. If the result type of all constructors has
2919 the form ``T a1 ... an``, where ``a1 ... an`` are distinct type
2920 variables, then the data type is *ordinary*; otherwise is a
2921 *generalised* data type (:ref:`gadt`).
2923 - As with other type signatures, you can give a single signature for
2924 several data constructors. In this example we give a single signature
2925 for ``T1`` and ``T2``: ::
2931 - The type signature of each constructor is independent, and is
2932 implicitly universally quantified as usual. In particular, the type
2933 variable(s) in the "``data T a where``" header have no scope, and
2934 different constructors may have different universally-quantified type
2937 data T a where -- The 'a' has no scope
2938 T1,T2 :: b -> T b -- Means forall b. b -> T b
2939 T3 :: T a -- Means forall a. T a
2941 - A constructor signature may mention type class constraints, which can
2942 differ for different constructors. For example, this is fine: ::
2945 T1 :: Eq b => b -> b -> T b
2946 T2 :: (Show c, Ix c) => c -> [c] -> T c
2948 When pattern matching, these constraints are made available to
2949 discharge constraints in the body of the match. For example: ::
2952 f (T1 x y) | x==y = "yes"
2956 Note that ``f`` is not overloaded; the ``Eq`` constraint arising from
2957 the use of ``==`` is discharged by the pattern match on ``T1`` and
2958 similarly the ``Show`` constraint arising from the use of ``show``.
2960 - Unlike a Haskell-98-style data type declaration, the type variable(s)
2961 in the "``data Set a where``" header have no scope. Indeed, one can
2962 write a kind signature instead: ::
2964 data Set :: Type -> Type where ...
2966 or even a mixture of the two: ::
2968 data Bar a :: (Type -> Type) -> Type where ...
2970 The type variables (if given) may be explicitly kinded, so we could
2971 also write the header for ``Foo`` like this: ::
2973 data Bar a (b :: Type -> Type) where ...
2975 - You can use strictness annotations, in the obvious places in the
2976 constructor type: ::
2979 Lit :: !Int -> Term Int
2980 If :: Term Bool -> !(Term a) -> !(Term a) -> Term a
2981 Pair :: Term a -> Term b -> Term (a,b)
2983 - You can use a ``deriving`` clause on a GADT-style data type
2984 declaration. For example, these two declarations are equivalent ::
2986 data Maybe1 a where {
2987 Nothing1 :: Maybe1 a ;
2988 Just1 :: a -> Maybe1 a
2989 } deriving( Eq, Ord )
2991 data Maybe2 a = Nothing2 | Just2 a
2994 - The type signature may have quantified type variables that do not
2995 appear in the result type: ::
2998 MkFoo :: a -> (a->Bool) -> Foo
3001 Here the type variable ``a`` does not appear in the result type of
3002 either constructor. Although it is universally quantified in the type
3003 of the constructor, such a type variable is often called
3004 "existential". Indeed, the above declaration declares precisely the
3005 same type as the ``data Foo`` in :ref:`existential-quantification`.
3007 The type may contain a class context too, of course: ::
3010 MkShowable :: Show a => a -> Showable
3012 - You can use record syntax on a GADT-style data type declaration: ::
3015 Adult :: { name :: String, children :: [Person] } -> Person
3016 Child :: Show a => { name :: !String, funny :: a } -> Person
3018 As usual, for every constructor that has a field ``f``, the type of
3019 field ``f`` must be the same (modulo alpha conversion). The ``Child``
3020 constructor above shows that the signature may have a context,
3021 existentially-quantified variables, and strictness annotations, just
3022 as in the non-record case. (NB: the "type" that follows the
3023 double-colon is not really a type, because of the record syntax and
3024 strictness annotations. A "type" of this form can appear only in a
3025 constructor signature.)
3027 - Record updates are allowed with GADT-style declarations, only fields
3028 that have the following property: the type of the field mentions no
3029 existential type variables.
3031 - As in the case of existentials declared using the Haskell-98-like
3032 record syntax (:ref:`existential-records`), record-selector functions
3033 are generated only for those fields that have well-typed selectors.
3034 Here is the example of that section, in GADT-style syntax: ::
3036 data Counter a where
3037 NewCounter :: { _this :: self
3038 , _inc :: self -> self
3039 , _display :: self -> IO ()
3043 As before, only one selector function is generated here, that for
3044 ``tag``. Nevertheless, you can still use all the field names in
3045 pattern matching and record construction.
3047 - In a GADT-style data type declaration there is no obvious way to
3048 specify that a data constructor should be infix, which makes a
3049 difference if you derive ``Show`` for the type. (Data constructors
3050 declared infix are displayed infix by the derived ``show``.) So GHC
3051 implements the following design: a data constructor declared in a
3052 GADT-style data type declaration is displayed infix by ``Show`` iff
3053 (a) it is an operator symbol, (b) it has two arguments, (c) it has a
3054 programmer-supplied fixity declaration. For example
3060 (:--:) :: Int -> Bool -> T Int
3064 Generalised Algebraic Data Types (GADTs)
3065 ----------------------------------------
3067 .. extension:: GADTs
3068 :shortdesc: Enable generalised algebraic data types.
3069 Implies :extension:`GADTSyntax` and :extension:`MonoLocalBinds`.
3071 :implies: :extension:`MonoLocalBinds`, :extension:`GADTSyntax`
3074 Allow use of Generalised Algebraic Data Types (GADTs).
3076 Generalised Algebraic Data Types generalise ordinary algebraic data
3077 types by allowing constructors to have richer return types. Here is an
3081 Lit :: Int -> Term Int
3082 Succ :: Term Int -> Term Int
3083 IsZero :: Term Int -> Term Bool
3084 If :: Term Bool -> Term a -> Term a -> Term a
3085 Pair :: Term a -> Term b -> Term (a,b)
3087 Notice that the return type of the constructors is not always
3088 ``Term a``, as is the case with ordinary data types. This generality
3089 allows us to write a well-typed ``eval`` function for these ``Terms``: ::
3093 eval (Succ t) = 1 + eval t
3094 eval (IsZero t) = eval t == 0
3095 eval (If b e1 e2) = if eval b then eval e1 else eval e2
3096 eval (Pair e1 e2) = (eval e1, eval e2)
3098 The key point about GADTs is that *pattern matching causes type
3099 refinement*. For example, in the right hand side of the equation ::
3104 the type ``a`` is refined to ``Int``. That's the whole point! A precise
3105 specification of the type rules is beyond what this user manual aspires
3106 to, but the design closely follows that described in the paper `Simple
3107 unification-based type inference for
3108 GADTs <http://research.microsoft.com/%7Esimonpj/papers/gadt/>`__, (ICFP
3109 2006). The general principle is this: *type refinement is only carried
3110 out based on user-supplied type annotations*. So if no type signature is
3111 supplied for ``eval``, no type refinement happens, and lots of obscure
3112 error messages will occur. However, the refinement is quite general. For
3113 example, if we had: ::
3115 eval :: Term a -> a -> a
3116 eval (Lit i) j = i+j
3118 the pattern match causes the type ``a`` to be refined to ``Int``
3119 (because of the type of the constructor ``Lit``), and that refinement
3120 also applies to the type of ``j``, and the result type of the ``case``
3121 expression. Hence the addition ``i+j`` is legal.
3123 These and many other examples are given in papers by Hongwei Xi, and Tim
3124 Sheard. There is a longer introduction `on the
3125 wiki <http://www.haskell.org/haskellwiki/GADT>`__, and Ralf Hinze's `Fun
3127 types <http://www.cs.ox.ac.uk/ralf.hinze/publications/With.pdf>`__ also
3128 has a number of examples. Note that papers may use different notation to
3129 that implemented in GHC.
3131 The rest of this section outlines the extensions to GHC that support
3132 GADTs. The extension is enabled with :extension:`GADTs`. The :extension:`GADTs` extension
3133 also sets :extension:`GADTSyntax` and :extension:`MonoLocalBinds`.
3135 - A GADT can only be declared using GADT-style syntax
3136 (:ref:`gadt-style`); the old Haskell 98 syntax for data declarations
3137 always declares an ordinary data type. The result type of each
3138 constructor must begin with the type constructor being defined, but
3139 for a GADT the arguments to the type constructor can be arbitrary
3140 monotypes. For example, in the ``Term`` data type above, the type of
3141 each constructor must end with ``Term ty``, but the ``ty`` need not
3142 be a type variable (e.g. the ``Lit`` constructor).
3144 - It is permitted to declare an ordinary algebraic data type using
3145 GADT-style syntax. What makes a GADT into a GADT is not the syntax,
3146 but rather the presence of data constructors whose result type is not
3149 - You cannot use a ``deriving`` clause for a GADT; only for an ordinary
3152 - As mentioned in :ref:`gadt-style`, record syntax is supported. For
3158 Lit :: { val :: Int } -> Term Int
3159 Succ :: { num :: Term Int } -> Term Int
3160 Pred :: { num :: Term Int } -> Term Int
3161 IsZero :: { arg :: Term Int } -> Term Bool
3162 Pair :: { arg1 :: Term a
3165 If :: { cnd :: Term Bool
3170 However, for GADTs there is the following additional constraint:
3171 every constructor that has a field ``f`` must have the same result
3172 type (modulo alpha conversion) Hence, in the above example, we cannot
3173 merge the ``num`` and ``arg`` fields above into a single name.
3174 Although their field types are both ``Term Int``, their selector
3175 functions actually have different types:
3179 num :: Term Int -> Term Int
3180 arg :: Term Bool -> Term Int
3182 - When pattern-matching against data constructors drawn from a GADT,
3183 for example in a ``case`` expression, the following rules apply:
3185 - The type of the scrutinee must be rigid.
3187 - The type of the entire ``case`` expression must be rigid.
3189 - The type of any free variable mentioned in any of the ``case``
3190 alternatives must be rigid.
3192 A type is "rigid" if it is completely known to the compiler at its
3193 binding site. The easiest way to ensure that a variable a rigid type
3194 is to give it a type signature. For more precise details see `Simple
3195 unification-based type inference for
3196 GADTs <http://research.microsoft.com/%7Esimonpj/papers/gadt/>`__. The
3197 criteria implemented by GHC are given in the Appendix.
3199 .. _record-system-extensions:
3201 Extensions to the record system
3202 ===============================
3204 .. _traditional-record-syntax:
3206 Traditional record syntax
3207 -------------------------
3209 .. extension:: NoTraditionalRecordSyntax
3210 :shortdesc: Disable support for traditional record syntax
3211 (as supported by Haskell 98) ``C {f = x}``
3215 Disallow use of record syntax.
3217 Traditional record syntax, such as ``C {f = x}``, is enabled by default.
3218 To disable it, you can use the :extension:`NoTraditionalRecordSyntax` extension.
3220 .. _disambiguate-fields:
3222 Record field disambiguation
3223 ---------------------------
3225 .. extension:: DisambiguateRecordFields
3226 :shortdesc: Enable record field disambiguation.
3227 Implied by :extension:`RecordWildCards`.
3231 Allow the compiler to automatically choose between identically-named
3232 record selectors based on type (if the choice is unambiguous).
3234 In record construction and record pattern matching it is entirely
3235 unambiguous which field is referred to, even if there are two different
3236 data types in scope with a common field name. For example:
3241 data S = MkS { x :: Int, y :: Bool }
3246 data T = MkT { x :: Int }
3248 ok1 (MkS { x = n }) = n+1 -- Unambiguous
3249 ok2 n = MkT { x = n+1 } -- Unambiguous
3251 bad1 k = k { x = 3 } -- Ambiguous
3252 bad2 k = x k -- Ambiguous
3254 Even though there are two ``x``'s in scope, it is clear that the ``x``
3255 in the pattern in the definition of ``ok1`` can only mean the field
3256 ``x`` from type ``S``. Similarly for the function ``ok2``. However, in
3257 the record update in ``bad1`` and the record selection in ``bad2`` it is
3258 not clear which of the two types is intended.
3260 Haskell 98 regards all four as ambiguous, but with the
3261 :extension:`DisambiguateRecordFields` extension, GHC will accept the former two. The
3262 rules are precisely the same as those for instance declarations in
3263 Haskell 98, where the method names on the left-hand side of the method
3264 bindings in an instance declaration refer unambiguously to the method of
3265 that class (provided they are in scope at all), even if there are other
3266 variables in scope with the same name. This reduces the clutter of
3267 qualified names when you import two records from different modules that
3268 use the same field name.
3272 - Field disambiguation can be combined with punning (see
3273 :ref:`record-puns`). For example: ::
3278 ok3 (MkS { x }) = x+1 -- Uses both disambiguation and punning
3280 - With :extension:`DisambiguateRecordFields` you can use *unqualified* field
3281 names even if the corresponding selector is only in scope *qualified*
3282 For example, assuming the same module ``M`` as in our earlier
3283 example, this is legal: ::
3286 import qualified M -- Note qualified
3288 ok4 (M.MkS { x = n }) = n+1 -- Unambiguous
3290 Since the constructor ``MkS`` is only in scope qualified, you must
3291 name it ``M.MkS``, but the field ``x`` does not need to be qualified
3292 even though ``M.x`` is in scope but ``x`` is not (In effect, it is
3293 qualified by the constructor).
3295 .. _duplicate-record-fields:
3297 Duplicate record fields
3298 -----------------------
3300 .. extension:: DuplicateRecordFields
3301 :shortdesc: Allow definition of record types with identically-named fields.
3303 :implies: :extension:`DisambiguateRecordFields`
3306 Allow definition of record types with identically-named fields.
3308 Going beyond :extension:`DisambiguateRecordFields` (see :ref:`disambiguate-fields`),
3309 the :extension:`DuplicateRecordFields` extension allows multiple datatypes to be
3310 declared using the same field names in a single module. For example, it allows
3314 data S = MkS { x :: Int }
3315 data T = MkT { x :: Bool }
3317 Uses of fields that are always unambiguous because they mention the constructor,
3318 including construction and pattern-matching, may freely use duplicated field
3319 names. For example, the following are permitted (just as with
3320 :extension:`DisambiguateRecordFields`): ::
3324 f (MkT { x = b }) = b
3326 Field names used as selector functions or in record updates must be unambiguous,
3327 either because there is only one such field in scope, or because a type
3328 signature is supplied, as described in the following sections.
3333 Fields may be used as selector functions only if they are unambiguous, so this
3334 is still not allowed if both ``S(x)`` and ``T(x)`` are in scope: ::
3338 An ambiguous selector may be disambiguated by the type being "pushed down" to
3339 the occurrence of the selector (see :ref:`higher-rank-type-inference` for more
3340 details on what "pushed down" means). For example, the following are permitted: ::
3347 ok3 = k x -- assuming we already have k :: (S -> Int) -> _
3349 In addition, the datatype that is meant may be given as a type signature on the
3350 argument to the selector: ::
3354 However, we do not infer the type of the argument to determine the datatype, or
3355 have any way of deferring the choice to the constraint solver. Thus the
3356 following is ambiguous: ::
3361 Even though a field label is duplicated in its defining module, it may be
3362 possible to use the selector unambiguously elsewhere. For example, another
3363 module could import ``S(x)`` but not ``T(x)``, and then use ``x`` unambiguously.
3368 In a record update such as ``e { x = 1 }``, if there are multiple ``x`` fields
3369 in scope, then the type of the context must fix which record datatype is
3370 intended, or a type annotation must be supplied. Consider the following
3373 data S = MkS { foo :: Int }
3374 data T = MkT { foo :: Int, bar :: Int }
3375 data U = MkU { bar :: Int, baz :: Int }
3377 Without :extension:`DuplicateRecordFields`, an update mentioning ``foo`` will always be
3378 ambiguous if all these definitions were in scope. When the extension is enabled,
3379 there are several options for disambiguating updates:
3381 - Check for types that have all the fields being updated. For example: ::
3383 f x = x { foo = 3, bar = 2 }
3385 Here ``f`` must be updating ``T`` because neither ``S`` nor ``U`` have both
3388 - Use the type being pushed in to the record update, as in the following: ::
3391 g1 x = x { foo = 3 }
3393 g2 x = x { foo = 3 } :: T
3395 g3 = k (x { foo = 3 }) -- assuming we already have k :: T -> _
3397 - Use an explicit type signature on the record expression, as in: ::
3399 h x = (x :: T) { foo = 3 }
3401 The type of the expression being updated will not be inferred, and no
3402 constraint-solving will be performed, so the following will be rejected as
3409 \x -> [x { foo = 3 }, blah :: T ]
3411 \ (x :: T) -> x { foo = 3 }
3413 Import and export of record fields
3414 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3416 When :extension:`DuplicateRecordFields` is enabled, an ambiguous field must be exported
3417 as part of its datatype, rather than at the top level. For example, the
3418 following is legal: ::
3420 module M (S(x), T(..)) where
3421 data S = MkS { x :: Int }
3422 data T = MkT { x :: Bool }
3424 However, this would not be permitted, because ``x`` is ambiguous: ::
3426 module M (x) where ...
3428 Similar restrictions apply on import.
3435 .. extension:: NamedFieldPuns
3436 :shortdesc: Enable record puns.
3440 Allow use of record puns.
3442 Record puns are enabled by the language extension :extension:`NamedFieldPuns`.
3444 When using records, it is common to write a pattern that binds a
3445 variable with the same name as a record field, such as: ::
3447 data C = C {a :: Int}
3450 Record punning permits the variable name to be elided, so one can simply
3455 to mean the same pattern as above. That is, in a record pattern, the
3456 pattern ``a`` expands into the pattern ``a = a`` for the same name
3461 - Record punning can also be used in an expression, writing, for
3468 let a = 1 in C {a = a}
3470 The expansion is purely syntactic, so the expanded right-hand side
3471 expression refers to the nearest enclosing variable that is spelled
3472 the same as the field name.
3474 - Puns and other patterns can be mixed in the same record: ::
3476 data C = C {a :: Int, b :: Int}
3477 f (C {a, b = 4}) = a
3479 - Puns can be used wherever record patterns occur (e.g. in ``let``
3480 bindings or at the top-level).
3482 - A pun on a qualified field name is expanded by stripping off the
3483 module qualifier. For example: ::
3489 f (M.C {M.a = a}) = a
3491 (This is useful if the field selector ``a`` for constructor ``M.C``
3492 is only in scope in qualified form.)
3494 .. _record-wildcards:
3499 .. extension:: RecordWildCards
3500 :shortdesc: Enable record wildcards.
3501 Implies :extension:`DisambiguateRecordFields`.
3503 :implies: :extension:`DisambiguateRecordFields`.
3506 Allow the use of wildcards in record construction and pattern matching.
3508 Record wildcards are enabled by the language extension :extension:`RecordWildCards`. This
3509 exension implies :extension:`DisambiguateRecordFields`.
3511 For records with many fields, it can be tiresome to write out each field
3512 individually in a record pattern, as in ::
3514 data C = C {a :: Int, b :: Int, c :: Int, d :: Int}
3515 f (C {a = 1, b = b, c = c, d = d}) = b + c + d
3517 Record wildcard syntax permits a "``..``" in a record pattern, where
3518 each elided field ``f`` is replaced by the pattern ``f = f``. For
3519 example, the above pattern can be written as ::
3521 f (C {a = 1, ..}) = b + c + d
3525 - Record wildcards in patterns can be mixed with other patterns,
3526 including puns (:ref:`record-puns`); for example, in a pattern
3527 ``(C {a = 1, b, ..})``. Additionally, record wildcards can be used
3528 wherever record patterns occur, including in ``let`` bindings and at
3529 the top-level. For example, the top-level binding ::
3533 defines ``b``, ``c``, and ``d``.
3535 - Record wildcards can also be used in an expression, when constructing
3536 a record. For example, ::
3538 let {a = 1; b = 2; c = 3; d = 4} in C {..}
3542 let {a = 1; b = 2; c = 3; d = 4} in C {a=a, b=b, c=c, d=d}
3544 The expansion is purely syntactic, so the record wildcard expression
3545 refers to the nearest enclosing variables that are spelled the same
3546 as the omitted field names.
3548 - For both pattern and expression wildcards, the "``..``" expands to
3549 the missing *in-scope* record fields. Specifically the expansion of
3550 "``C {..}``" includes ``f`` if and only if:
3552 - ``f`` is a record field of constructor ``C``.
3554 - The record field ``f`` is in scope somehow (either qualified or
3557 These rules restrict record wildcards to the situations in which the
3558 user could have written the expanded version. For example ::
3561 data R = R { a,b,c :: Int }
3563 import M( R(R,a,c) )
3566 The ``R{..}`` expands to ``R{a=a}``, omitting ``b`` since the
3567 record field is not in scope, and omitting ``c`` since the variable
3568 ``c`` is not in scope (apart from the binding of the record selector
3571 - When record wildcards are use in record construction, a field ``f``
3572 is initialised only if ``f`` is in scope,
3573 and is not imported or bound at top level.
3574 For example, ``f`` can be bound by an enclosing pattern match or
3575 let/where-binding. For example ::
3580 data R = R { a,b,c,d :: Int }
3584 f b = R { .. } -- Expands to R { b = b, d = d }
3588 Here, ``a`` is imported, and ``c`` is bound at top level, so neither
3589 contribute to the expansion of the "``..``".
3590 The motivation here is that it should be
3591 easy for the reader to figure out what the "``..``" expands to.
3593 - Record wildcards cannot be used (a) in a record update construct, and
3594 (b) for data constructors that are not declared with record fields.
3597 f x = x { v=True, .. } -- Illegal (a)
3599 data T = MkT Int Bool
3600 g = MkT { .. } -- Illegal (b)
3601 h (MkT { .. }) = True -- Illegal (b)
3604 .. _record-field-selector-polymorphism:
3606 Record field selector polymorphism
3607 ----------------------------------
3609 The module :base-ref:`GHC.Records.` defines the following: ::
3611 class HasField (x :: k) r a | x r -> a where
3614 A ``HasField x r a`` constraint represents the fact that ``x`` is a
3615 field of type ``a`` belonging to a record type ``r``. The
3616 ``getField`` method gives the record selector function.
3618 This allows definitions that are polymorphic over record types with a specified
3619 field. For example, the following works with any record type that has a field
3620 ``name :: String``: ::
3622 foo :: HasField "name" r String => r -> String
3623 foo r = reverse (getField @"name" r)
3625 ``HasField`` is a magic built-in typeclass (similar to ``Coercible``, for
3626 example). It is given special treatment by the constraint solver (see
3627 :ref:`solving-hasfield-constraints`). Users may define their own instances of
3628 ``HasField`` also (see :ref:`virtual-record-fields`).
3630 .. _solving-hasfield-constraints:
3632 Solving HasField constraints
3633 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3635 If the constraint solver encounters a constraint ``HasField x r a``
3636 where ``r`` is a concrete datatype with a field ``x`` in scope, it
3637 will automatically solve the constraint using the field selector as
3638 the dictionary, unifying ``a`` with the type of the field if
3639 necessary. This happens irrespective of which extensions are enabled.
3641 For example, if the following datatype is in scope ::
3643 data Person = Person { name :: String }
3645 the end result is rather like having an instance ::
3647 instance HasField "name" Person String where
3650 except that this instance is not actually generated anywhere, rather
3651 the constraint is solved directly by the constraint solver.
3653 A field must be in scope for the corresponding ``HasField`` constraint
3654 to be solved. This retains the existing representation hiding
3655 mechanism, whereby a module may choose not to export a field,
3656 preventing client modules from accessing or updating it directly.
3658 Solving ``HasField`` constraints depends on the field selector functions that
3659 are generated for each datatype definition:
3661 - If a record field does not have a selector function because its type would allow
3662 an existential variable to escape, the corresponding ``HasField`` constraint
3663 will not be solved. For example, ::
3665 {-# LANGUAGE ExistentialQuantification #-}
3666 data Exists t = forall x . MkExists { unExists :: t x }
3668 does not give rise to a selector ``unExists :: Exists t -> t x`` and we will not
3669 solve ``HasField "unExists" (Exists t) a`` automatically.
3671 - If a record field has a polymorphic type (and hence the selector function is
3672 higher-rank), the corresponding ``HasField`` constraint will not be solved,
3673 because doing so would violate the functional dependency on ``HasField`` and/or
3674 require impredicativity. For example, ::
3676 {-# LANGUAGE RankNTypes #-}
3677 data Higher = MkHigher { unHigher :: forall t . t -> t }
3679 gives rise to a selector ``unHigher :: Higher -> (forall t . t -> t)`` but does
3680 not lead to solution of the constraint ``HasField "unHigher" Higher a``.
3682 - A record GADT may have a restricted type for a selector function, which may lead
3683 to additional unification when solving ``HasField`` constraints. For example, ::
3685 {-# LANGUAGE GADTs #-}
3687 MkGadt :: { unGadt :: Maybe v } -> Gadt [v]
3689 gives rise to a selector ``unGadt :: Gadt [v] -> Maybe v``, so the solver will reduce
3690 the constraint ``HasField "unGadt" (Gadt t) b`` by unifying ``t ~ [v]`` and
3691 ``b ~ Maybe v`` for some fresh metavariable ``v``, rather as if we had an instance ::
3693 instance (t ~ [v], b ~ Maybe v) => HasField "unGadt" (Gadt t) b
3695 - If a record type has an old-fashioned datatype context, the ``HasField``
3696 constraint will be reduced to solving the constraints from the context.
3699 {-# LANGUAGE DatatypeContexts #-}
3700 data Eq a => Silly a = MkSilly { unSilly :: a }
3702 gives rise to a selector ``unSilly :: Eq a => Silly a -> a``, so
3703 the solver will reduce the constraint ``HasField "unSilly" (Silly a) b`` to
3704 ``Eq a`` (and unify ``a`` with ``b``), rather as if we had an instance ::
3706 instance (Eq a, a ~ b) => HasField "unSilly" (Silly a) b
3708 .. _virtual-record-fields:
3710 Virtual record fields
3711 ~~~~~~~~~~~~~~~~~~~~~
3713 Users may define their own instances of ``HasField``, provided they do
3714 not conflict with the built-in constraint solving behaviour. This
3715 allows "virtual" record fields to be defined for datatypes that do not
3716 otherwise have them.
3718 For example, this instance would make the ``name`` field of ``Person``
3719 accessible using ``#fullname`` as well: ::
3721 instance HasField "fullname" Person String where
3724 More substantially, an anonymous records library could provide
3725 ``HasField`` instances for its anonymous records, and thus be
3726 compatible with the polymorphic record selectors introduced by this
3727 proposal. For example, something like this makes it possible to use
3728 ``getField`` to access ``Record`` values with the appropriate
3729 string in the type-level list of fields: ::
3731 data Record (xs :: [(k, Type)]) where
3733 Cons :: Proxy x -> a -> Record xs -> Record ('(x, a) ': xs)
3735 instance HasField x (Record ('(x, a) ': xs)) a where
3736 getField (Cons _ v _) = v
3737 instance HasField x (Record xs) a => HasField x (Record ('(y, b) ': xs)) a where
3738 getField (Cons _ _ r) = getField @x r
3740 r :: Record '[ '("name", String) ]
3741 r = Cons Proxy "R" Nil)
3743 x = getField @"name" r
3745 Since representations such as this can support field labels with kinds other
3746 than ``Symbol``, the ``HasField`` class is poly-kinded (even though the built-in
3747 constraint solving works only at kind ``Symbol``). In particular, this allows
3748 users to declare scoped field labels such as in the following example: ::
3750 data PersonFields = Name
3752 s :: Record '[ '(Name, String) ]
3753 s = Cons Proxy "S" Nil
3755 y = getField @Name s
3757 In order to avoid conflicting with the built-in constraint solving,
3758 the following user-defined ``HasField`` instances are prohibited (in
3759 addition to the usual rules, such as the prohibition on type
3760 families appearing in instance heads):
3762 - ``HasField _ r _`` where ``r`` is a variable;
3764 - ``HasField _ (T ...) _`` if ``T`` is a data family (because it
3765 might have fields introduced later, using data instance declarations);
3767 - ``HasField x (T ...) _`` if ``x`` is a variable and ``T`` has any
3768 fields at all (but this instance is permitted if ``T`` has no fields);
3770 - ``HasField "foo" (T ...) _`` if ``T`` has a field ``foo`` (but this
3771 instance is permitted if it does not).
3773 If a field has a higher-rank or existential type, the corresponding ``HasField``
3774 constraint will not be solved automatically (as described above), but in the
3775 interests of simplicity we do not permit users to define their own instances
3776 either. If a field is not in scope, the corresponding instance is still
3777 prohibited, to avoid conflicts in downstream modules.
3782 Extensions to the "deriving" mechanism
3783 ======================================
3785 Haskell 98 allows the programmer to add a deriving clause to a data type
3786 declaration, to generate a standard instance declaration for specified class.
3787 GHC extends this mechanism along several axes:
3789 * The derivation mechanism can be used separtely from the data type
3790 declaration, using the `standalone deriving mechanism
3791 <#stand-alone-deriving>`__.
3793 * In Haskell 98, the only derivable classes are ``Eq``,
3794 ``Ord``, ``Enum``, ``Ix``, ``Bounded``, ``Read``, and ``Show``. `Various
3795 language extensions <#deriving-extra>`__ extend this list.
3797 * Besides the stock approach to deriving instances by generating all method
3798 definitions, GHC supports two additional deriving strategies, which can
3799 derive arbitrary classes:
3801 * `Generalised newtype deriving <#newtype-deriving>`__ for newtypes and
3802 * `deriving any class <#derive-any-class>`__ using an empty instance
3805 The user can optionally declare the desired `deriving strategy
3806 <#deriving-stragies>`__, especially if the compiler chooses the wrong
3807 one `by default <#default-deriving-strategy>`__.
3809 .. _empty-data-deriving:
3811 Deriving instances for empty data types
3812 ---------------------------------------
3814 .. ghc-flag:: -XEmptyDataDeriving
3815 :shortdesc: Allow deriving instances of standard type classes for
3818 :reverse: -XNoEmptyDataDeriving
3823 Allow deriving instances of standard type classes for empty data types.
3825 One can write data types with no constructors using the
3826 :ghc-flag:`-XEmptyDataDecls` flag (see :ref:`nullary-types`), which is on by
3827 default in Haskell 2010. What is not on by default is the ability to derive
3828 type class instances for these types. This ability is enabled through use of
3829 the :ghc-flag:`-XEmptyDataDeriving` flag. For instance, this lets one write: ::
3831 data Empty deriving (Eq, Ord, Read, Show)
3833 This would generate the following instances: ::
3835 instance Eq Empty where
3838 instance Ord Empty where
3841 instance Read Empty where
3844 instance Show Empty where
3845 showsPrec _ x = case x of {}
3847 The :ghc-flag:`-XEmptyDataDeriving` flag is only required to enable deriving
3848 of these four "standard" type classes (which are mentioned in the Haskell
3849 Report). Other extensions to the ``deriving`` mechanism, which are explained
3850 below in greater detail, do not require :ghc-flag:`-XEmptyDataDeriving` to be
3851 used in conjunction with empty data types. These include:
3853 * :ghc-flag:`-XStandaloneDeriving` (see :ref:`stand-alone-deriving`)
3854 * Type classes which require their own extensions to be enabled to be derived,
3855 such as :ghc-flag:`-XDeriveFunctor` (see :ref:`deriving-extra`)
3856 * :ghc-flag:`-XDeriveAnyClass` (see :ref:`derive-any-class`)
3858 .. _deriving-inferred:
3860 Inferred context for deriving clauses
3861 -------------------------------------
3863 The Haskell Report is vague about exactly when a ``deriving`` clause is
3864 legal. For example: ::
3866 data T0 f a = MkT0 a deriving( Eq )
3867 data T1 f a = MkT1 (f a) deriving( Eq )
3868 data T2 f a = MkT2 (f (f a)) deriving( Eq )
3870 The natural generated ``Eq`` code would result in these instance
3873 instance Eq a => Eq (T0 f a) where ...
3874 instance Eq (f a) => Eq (T1 f a) where ...
3875 instance Eq (f (f a)) => Eq (T2 f a) where ...
3877 The first of these is obviously fine. The second is still fine, although
3878 less obviously. The third is not Haskell 98, and risks losing
3879 termination of instances.
3881 GHC takes a conservative position: it accepts the first two, but not the
3882 third. The rule is this: each constraint in the inferred instance
3883 context must consist only of type variables, with no repetitions.
3885 This rule is applied regardless of flags. If you want a more exotic
3886 context, you can write it yourself, using the `standalone deriving
3887 mechanism <#stand-alone-deriving>`__.
3889 .. _stand-alone-deriving:
3891 Stand-alone deriving declarations
3892 ---------------------------------
3894 .. extension:: StandaloneDeriving
3895 :shortdesc: Enable standalone deriving.
3899 Allow the use of stand-alone ``deriving`` declarations.
3901 GHC allows stand-alone ``deriving`` declarations, enabled by
3902 :extension:`StandaloneDeriving`: ::
3904 data Foo a = Bar a | Baz String
3906 deriving instance Eq a => Eq (Foo a)
3908 The syntax is identical to that of an ordinary instance declaration
3909 apart from (a) the keyword ``deriving``, and (b) the absence of the
3912 However, standalone deriving differs from a ``deriving`` clause in a
3913 number of important ways:
3915 - The standalone deriving declaration does not need to be in the same
3916 module as the data type declaration. (But be aware of the dangers of
3917 orphan instances (:ref:`orphan-modules`).
3919 - In most cases, you must supply an explicit context (in the example the
3920 context is ``(Eq a)``), exactly as you would in an ordinary instance
3921 declaration. (In contrast, in a ``deriving`` clause attached to a
3922 data type declaration, the context is inferred.)
3924 The exception to this rule is that the context of a standalone deriving
3925 declaration can infer its context when a single, extra-wildcards constraint
3926 is used as the context, such as in: ::
3928 deriving instance _ => Eq (Foo a)
3930 This is essentially the same as if you had written ``deriving Foo`` after
3931 the declaration for ``data Foo a``. Using this feature requires the use of
3932 :extension:`PartialTypeSignatures` (:ref:`partial-type-signatures`).
3934 - Unlike a ``deriving`` declaration attached to a ``data`` declaration,
3935 the instance can be more specific than the data type (assuming you
3936 also use :extension:`FlexibleInstances`, :ref:`instance-rules`). Consider
3939 data Foo a = Bar a | Baz String
3941 deriving instance Eq a => Eq (Foo [a])
3942 deriving instance Eq a => Eq (Foo (Maybe a))
3944 This will generate a derived instance for ``(Foo [a])`` and
3945 ``(Foo (Maybe a))``, but other types such as ``(Foo (Int,Bool))``
3946 will not be an instance of ``Eq``.
3948 - Unlike a ``deriving`` declaration attached to a ``data`` declaration,
3949 GHC does not restrict the form of the data type. Instead, GHC simply
3950 generates the appropriate boilerplate code for the specified class,
3951 and typechecks it. If there is a type error, it is your problem. (GHC
3952 will show you the offending code if it has a type error.)
3954 The merit of this is that you can derive instances for GADTs and
3955 other exotic data types, providing only that the boilerplate code
3956 does indeed typecheck. For example: ::
3962 deriving instance Show (T a)
3964 In this example, you cannot say ``... deriving( Show )`` on the data
3965 type declaration for ``T``, because ``T`` is a GADT, but you *can*
3966 generate the instance declaration using stand-alone deriving.
3968 The down-side is that, if the boilerplate code fails to typecheck,
3969 you will get an error message about that code, which you did not
3970 write. Whereas, with a ``deriving`` clause the side-conditions are
3971 necessarily more conservative, but any error message may be more
3974 - Under most circumstances, you cannot use standalone deriving to create an
3975 instance for a data type whose constructors are not all in scope. This is
3976 because the derived instance would generate code that uses the constructors
3977 behind the scenes, which would break abstraction.
3979 The one exception to this rule is :extension:`DeriveAnyClass`, since
3980 deriving an instance via :extension:`DeriveAnyClass` simply generates
3981 an empty instance declaration, which does not require the use of any
3982 constructors. See the `deriving any class <#derive-any-class>`__ section
3985 In other ways, however, a standalone deriving obeys the same rules as
3988 - A ``deriving instance`` declaration must obey the same rules
3989 concerning form and termination as ordinary instance declarations,
3990 controlled by the same flags; see :ref:`instance-decls`.
3992 - The stand-alone syntax is generalised for newtypes in exactly the
3993 same way that ordinary ``deriving`` clauses are generalised
3994 (:ref:`newtype-deriving`). For example: ::
3996 newtype Foo a = MkFoo (State Int a)
3998 deriving instance MonadState Int Foo
4000 GHC always treats the *last* parameter of the instance (``Foo`` in
4001 this example) as the type whose instance is being derived.
4005 Deriving instances of extra classes (``Data``, etc.)
4006 ----------------------------------------------------
4008 Haskell 98 allows the programmer to add "``deriving( Eq, Ord )``" to a
4009 data type declaration, to generate a standard instance declaration for
4010 classes specified in the ``deriving`` clause. In Haskell 98, the only
4011 classes that may appear in the ``deriving`` clause are the standard
4012 classes ``Eq``, ``Ord``, ``Enum``, ``Ix``, ``Bounded``, ``Read``, and
4015 GHC extends this list with several more classes that may be
4016 automatically derived:
4018 - With :extension:`DeriveGeneric`, you can derive instances of the classes
4019 ``Generic`` and ``Generic1``, defined in ``GHC.Generics``. You can
4020 use these to define generic functions, as described in
4021 :ref:`generic-programming`.
4023 - With :extension:`DeriveFunctor`, you can derive instances of the class
4024 ``Functor``, defined in ``GHC.Base``.
4026 - With :extension:`DeriveDataTypeable`, you can derive instances of the class
4027 ``Data``, defined in ``Data.Data``.
4029 - With :extension:`DeriveFoldable`, you can derive instances of the class
4030 ``Foldable``, defined in ``Data.Foldable``.
4032 - With :extension:`DeriveTraversable`, you can derive instances of the class
4033 ``Traversable``, defined in ``Data.Traversable``. Since the
4034 ``Traversable`` instance dictates the instances of ``Functor`` and
4035 ``Foldable``, you'll probably want to derive them too, so
4036 :extension:`DeriveTraversable` implies :extension:`DeriveFunctor` and
4037 :extension:`DeriveFoldable`.
4039 - With :extension:`DeriveLift`, you can derive instances of the class ``Lift``,
4040 defined in the ``Language.Haskell.TH.Syntax`` module of the
4041 ``template-haskell`` package.
4043 You can also use a standalone deriving declaration instead (see
4044 :ref:`stand-alone-deriving`).
4046 In each case the appropriate class must be in scope before it can be
4047 mentioned in the ``deriving`` clause.
4049 .. _deriving-functor:
4051 Deriving ``Functor`` instances
4052 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
4054 .. extension:: DeriveFunctor
4055 :shortdesc: Enable deriving for the Functor class.
4056 Implied by :extension:`DeriveTraversable`.
4060 Allow automatic deriving of instances for the ``Functor`` typeclass.
4063 With :extension:`DeriveFunctor`, one can derive ``Functor`` instances for data types
4064 of kind ``Type -> Type``. For example, this declaration::
4066 data Example a = Ex a Char (Example a) (Example Char)
4069 would generate the following instance: ::
4071 instance Functor Example where
4072 fmap f (Ex a1 a2 a3 a4) = Ex (f a1) a2 (fmap f a3) a4
4074 The basic algorithm for :extension:`DeriveFunctor` walks the arguments of each
4075 constructor of a data type, applying a mapping function depending on the type
4076 of each argument. If a plain type variable is found that is syntactically
4077 equivalent to the last type parameter of the data type (``a`` in the above
4078 example), then we apply the function ``f`` directly to it. If a type is
4079 encountered that is not syntactically equivalent to the last type parameter
4080 *but does mention* the last type parameter somewhere in it, then a recursive
4081 call to ``fmap`` is made. If a type is found which doesn't mention the last
4082 type parameter at all, then it is left alone.
4084 The second of those cases, in which a type is unequal to the type parameter but
4085 does contain the type parameter, can be surprisingly tricky. For example, the
4086 following example compiles::
4088 newtype Right a = Right (Either Int a) deriving Functor
4090 Modifying the code slightly, however, produces code which will not compile::
4092 newtype Wrong a = Wrong (Either a Int) deriving Functor
4094 The difference involves the placement of the last type parameter, ``a``. In the
4095 ``Right`` case, ``a`` occurs within the type ``Either Int a``, and moreover, it
4096 appears as the last type argument of ``Either``. In the ``Wrong`` case,
4097 however, ``a`` is not the last type argument to ``Either``; rather, ``Int`` is.
4099 This distinction is important because of the way :extension:`DeriveFunctor` works. The
4100 derived ``Functor Right`` instance would be::
4102 instance Functor Right where
4103 fmap f (Right a) = Right (fmap f a)
4105 Given a value of type ``Right a``, GHC must produce a value of type
4106 ``Right b``. Since the argument to the ``Right`` constructor has type
4107 ``Either Int a``, the code recursively calls ``fmap`` on it to produce a value
4108 of type ``Either Int b``, which is used in turn to construct a final value of
4111 The generated code for the ``Functor Wrong`` instance would look exactly the
4112 same, except with ``Wrong`` replacing every occurrence of ``Right``. The
4113 problem is now that ``fmap`` is being applied recursively to a value of type
4114 ``Either a Int``. This cannot possibly produce a value of type
4115 ``Either b Int``, as ``fmap`` can only change the last type parameter! This
4116 causes the generated code to be ill-typed.
4118 As a general rule, if a data type has a derived ``Functor`` instance and its
4119 last type parameter occurs on the right-hand side of the data declaration, then
4120 either it must (1) occur bare (e.g., ``newtype Id a = Id a``), or (2) occur as the
4121 last argument of a type constructor (as in ``Right`` above).
4123 There are two exceptions to this rule:
4125 #. Tuple types. When a non-unit tuple is used on the right-hand side of a data
4126 declaration, :extension:`DeriveFunctor` treats it as a product of distinct types.
4127 In other words, the following code::