From 9c2dfd97d008c04c2f86a4a58fa7c3c956f7bedc Mon Sep 17 00:00:00 2001 From: Daniel Fischer Date: Mon, 30 May 2011 10:49:21 +0200 Subject: [PATCH] glasgow_exts.xml typos and whitespace --- docs/users_guide/glasgow_exts.xml | 1004 ++++++++++++++++++------------------- 1 file changed, 502 insertions(+), 502 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 0f37953..2490855 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -44,8 +44,8 @@ documentation describes all the libraries that come with GHC. Language options can be controlled in two ways: - Every language option can switched on by a command-line flag "" - (e.g. ), and switched off by the flag ""; + Every language option can switched on by a command-line flag "" + (e.g. ), and switched off by the flag ""; (e.g. ). Language options recognised by Cabal can also be enabled using the LANGUAGE pragma, @@ -55,11 +55,11 @@ documentation describes all the libraries that come with GHC. The flag - is equivalent to enabling the following extensions: + is equivalent to enabling the following extensions: &what_glasgow_exts_does; - Enabling these options is the only + Enabling these options is the only effect of . - We are trying to move away from this portmanteau flag, + We are trying to move away from this portmanteau flag, and towards enabling features individually. @@ -77,8 +77,8 @@ While you really can use this stuff to write fast code, unboxed version in any case. And if it isn't, we'd like to know about it. -All these primitive data types and operations are exported by the -library GHC.Prim, for which there is +All these primitive data types and operations are exported by the +library GHC.Prim, for which there is detailed online documentation. (This documentation is generated from the file compiler/prelude/primops.txt.pp.) @@ -89,10 +89,10 @@ into scope. Many of them have names ending in "#", and to mention such names you need the extension (). -The primops make extensive use of unboxed types +The primops make extensive use of unboxed types and unboxed tuples, which we briefly summarise here. - + Unboxed types @@ -124,7 +124,7 @@ know and love—usually one instruction. Primitive (unboxed) types cannot be defined in Haskell, and are therefore built into the language and compiler. Primitive types are always unlifted; that is, a value of a primitive type cannot be -bottom. We use the convention (but it is only a convention) +bottom. We use the convention (but it is only a convention) that primitive types, values, and operations have a # suffix (see ). For some primitive types we have special syntax for literals, also @@ -283,7 +283,7 @@ You can have an unboxed tuple in a pattern binding, thus f x = let (# p,q #) = h x in ..body.. If the types of p and q are not unboxed, -the resulting binding is lazy like any other Haskell pattern binding. The +the resulting binding is lazy like any other Haskell pattern binding. The above example desugars like this: f x = let t = case h x o f{ (# p,q #) -> (p,q) @@ -302,7 +302,7 @@ Indeed, the bindings can even be recursive. Syntactic extensions - + Unicode syntax The language @@ -425,17 +425,17 @@ Indeed, the bindings can even be recursive. postfix modifier to identifiers. Thus, "x#" is a valid variable, and "T#" is a valid type constructor or data constructor. - The hash sign does not change sematics at all. We tend to use variable - names ending in "#" for unboxed values or types (e.g. Int#), + The hash sign does not change semantics at all. We tend to use variable + names ending in "#" for unboxed values or types (e.g. Int#), but there is no requirement to do so; they are just plain ordinary variables. Nor does the extension bring anything into scope. - For example, to bring Int# into scope you must - import GHC.Prim (see ); + For example, to bring Int# into scope you must + import GHC.Prim (see ); the extension then allows you to refer to the Int# that is now in scope. The also enables some new forms of literals (see ): - + 'x'# has type Char# "foo"# has type Addr# 3# has type Int#. In general, @@ -530,7 +530,7 @@ where -The auxiliary functions are +The auxiliary functions are @@ -575,10 +575,10 @@ This is a bit shorter, but hardly better. Of course, we can rewrite any set of pattern-matching, guarded equations as case expressions; that is precisely what the compiler does when compiling equations! The reason that Haskell provides guarded equations is because they allow us to write down -the cases we want to consider, one at a time, independently of each other. +the cases we want to consider, one at a time, independently of each other. This structure is hidden in the case version. Two of the right-hand sides are really the same (fail), and the whole expression -tends to become more and more indented. +tends to become more and more indented. @@ -594,9 +594,9 @@ clunky env var1 var2 -The semantics should be clear enough. The qualifiers are matched in order. +The semantics should be clear enough. The qualifiers are matched in order. For a <- qualifier, which I call a pattern guard, the -right hand side is evaluated and matched against the pattern on the left. +right hand side is evaluated and matched against the pattern on the left. If the match fails then the whole guard fails and the next equation is tried. If it succeeds, then the appropriate binding takes place, and the next qualifier is matched, in the augmented environment. Unlike list @@ -646,7 +646,7 @@ language as follows: type Typ - + data TypView = Unit | Arrow Typ Typ @@ -658,7 +658,7 @@ view :: Type -> TypeView The representation of Typ is held abstract, permitting implementations to use a fancy representation (e.g., hash-consing to manage sharing). -Without view patterns, using this signature a little inconvenient: +Without view patterns, using this signature a little inconvenient: size :: Typ -> Integer size t = case view t of @@ -673,7 +673,7 @@ against t is buried deep inside another pattern. View patterns permit calling the view function inside the pattern and -matching against the result: +matching against the result: size (view -> Unit) = 1 size (view -> Arrow t1 t2) = size t1 + size t2 @@ -716,7 +716,7 @@ clunky env (lookup env -> Just val1) (lookup env -> Just val2) = val1 + val2 -More precisely, the scoping rules are: +More precisely, the scoping rules are: @@ -734,7 +734,7 @@ example :: (String -> Integer) -> String -> Bool example f (f -> 4) = True That is, the scoping is the same as it would be if the curried arguments -were collected into a tuple. +were collected into a tuple. @@ -750,7 +750,7 @@ let {(x -> y) = e1 ; (y -> x) = e2 } in x -(For some amplification on this design choice see +(For some amplification on this design choice see Trac #4061.) @@ -771,8 +771,8 @@ a T2, then the whole view pattern matches a Haskell 98 Report, add the following: -case v of { (e -> p) -> e1 ; _ -> e2 } - = +case v of { (e -> p) -> e1 ; _ -> e2 } + = case (e v) of { p -> e1 ; _ -> e2 } That is, to match a variable v against a pattern @@ -781,7 +781,7 @@ That is, to match a variable v against a pattern ), evaluate ( exp v ) and match the result against -pat. +pat. Efficiency: When the same view function is applied in @@ -839,7 +839,7 @@ it, you can use the flag. The do-notation of Haskell 98 does not allow recursive bindings, -that is, the variables bound in a do-expression are visible only in the textually following +that is, the variables bound in a do-expression are visible only in the textually following code block. Compare this to a let-expression, where bound variables are visible in the entire binding group. It turns out that several applications can benefit from recursive bindings in the do-notation. The flag provides the necessary syntactic support. @@ -857,7 +857,7 @@ As you can guess justOnes will evaluate to Just [-1, The background and motivation for recursive do-notation is described in A recursive do for Haskell, by Levent Erkok, John Launchbury, -Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania. +Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania. The theory behind monadic value recursion is explained further in Erkok's thesis Value Recursion in Monadic Computations. However, note that GHC uses a different syntax than the one described in these documents. @@ -872,38 +872,38 @@ which wraps a mutually-recursive group of monadic statements, producing a single statement. Similar to a let -statement, the variables bound in the rec are +statement, the variables bound in the rec are visible throughout the rec group, and below it. For example, compare -do { a <- getChar do { a <- getChar - ; let { r1 = f a r2 ; rec { r1 <- f a r2 - ; r2 = g r1 } ; r2 <- g r1 } +do { a <- getChar do { a <- getChar + ; let { r1 = f a r2 ; rec { r1 <- f a r2 + ; r2 = g r1 } ; r2 <- g r1 } ; return (r1 ++ r2) } ; return (r1 ++ r2) } -In both cases, r1 and r2 are +In both cases, r1 and r2 are available both throughout the let or rec block, and in the statements that follow it. The difference is that let is non-monadic, -while rec is monadic. (In Haskell let is +while rec is monadic. (In Haskell let is really letrec, of course.) -The static and dynamic semantics of rec can be described as follows: +The static and dynamic semantics of rec can be described as follows: First, -similar to let-bindings, the rec is broken into +similar to let-bindings, the rec is broken into minimal recursive groups, a process known as segmentation. For example: rec { a <- getChar ===> a <- getChar ; b <- f a c rec { b <- f a c ; c <- f b a ; c <- f b a } - ; putChar c } putChar c + ; putChar c } putChar c The details of segmentation are described in Section 3.2 of A recursive do for Haskell. -Segmentation improves polymorphism, reduces the size of the recursive "knot", and, as the paper +Segmentation improves polymorphism, reduces the size of the recursive "knot", and, as the paper describes, also has a semantic effect (unless the monad satisfies the right-shrinking law). @@ -921,13 +921,13 @@ is desugared to the statement where vs is a tuple of the variables bound by ss. -The original rec typechecks exactly -when the above desugared version would do so. For example, this means that +The original rec typechecks exactly +when the above desugared version would do so. For example, this means that the variables vs are all monomorphic in the statements following the rec, because they are bound by a lambda. -The mfix function is defined in the MonadFix +The mfix function is defined in the MonadFix class, in Control.Monad.Fix, thus: class Monad m => MonadFix m where @@ -951,14 +951,14 @@ then that monad must be declared an instance of the MonadFix -The following instances of MonadFix are automatically provided: List, Maybe, IO. -Furthermore, the Control.Monad.ST and Control.Monad.ST.Lazy modules provide the instances of the MonadFix class +The following instances of MonadFix are automatically provided: List, Maybe, IO. +Furthermore, the Control.Monad.ST and Control.Monad.ST.Lazy modules provide the instances of the MonadFix class for Haskell's internal state monad (strict and lazy, respectively). Like let and where bindings, -name shadowing is not allowed within a rec; +name shadowing is not allowed within a rec; that is, all the names bound in a single rec must be distinct (Section 3.3 of the paper). @@ -1007,7 +1007,7 @@ This name is not supported by GHC. example, the following zips together two lists: - [ (x, y) | x <- xs | y <- ys ] + [ (x, y) | x <- xs | y <- ys ] The behavior of parallel list comprehensions follows that of @@ -1020,26 +1020,26 @@ This name is not supported by GHC. Given a parallel comprehension of the form: - [ e | p1 <- e11, p2 <- e12, ... - | q1 <- e21, q2 <- e22, ... - ... - ] + [ e | p1 <- e11, p2 <- e12, ... + | q1 <- e21, q2 <- e22, ... + ... + ] This will be translated to: - [ e | ((p1,p2), (q1,q2), ...) <- zipN [(p1,p2) | p1 <- e11, p2 <- e12, ...] - [(q1,q2) | q1 <- e21, q2 <- e22, ...] - ... - ] + [ e | ((p1,p2), (q1,q2), ...) <- zipN [(p1,p2) | p1 <- e11, p2 <- e12, ...] + [(q1,q2) | q1 <- e21, q2 <- e22, ...] + ... + ] where `zipN' is the appropriate zip for the given number of branches. - + @@ -1059,7 +1059,7 @@ This name is not supported by GHC. Comprehensive comprehensions: comprehensions with "order by" and "group by", except that the syntax we use differs slightly from the paper. The extension is enabled with the flag . -Here is an example: +Here is an example: employees = [ ("Simon", "MS", 80) , ("Erik", "MS", 100) @@ -1073,9 +1073,9 @@ output = [ (the dept, sum salary) , then sortWith by (sum salary) , then take 5 ] -In this example, the list output would take on +In this example, the list output would take on the value: - + [("Yale", 60), ("Ed", 85), ("MS", 180)] @@ -1088,7 +1088,7 @@ function that is exported by GHC.Exts.) all introduced by the (existing) keyword then: - + then f @@ -1096,10 +1096,10 @@ then f This statement requires that f have the type forall a. [a] -> [a]. You can see an example of its use in the motivating example, as this form is used to apply take 5. - + - - + + @@ -1107,13 +1107,13 @@ then f by e This form is similar to the previous one, but allows you to create a function - which will be passed as the first argument to f. As a consequence f must have + which will be passed as the first argument to f. As a consequence f must have the type forall a. (a -> t) -> [a] -> [a]. As you can see - from the type, this function lets f "project out" some information + from the type, this function lets f "project out" some information from the elements of the list it is transforming. - An example is shown in the opening example, where sortWith - is supplied with a function that lets it find out the sum salary + An example is shown in the opening example, where sortWith + is supplied with a function that lets it find out the sum salary for any item in the list comprehension it transforms. @@ -1134,7 +1134,7 @@ then group by e using f at every point after this statement, binders occurring before it in the comprehension refer to lists of possible values, not single values. To help understand this, let's look at an example: - + -- This works similarly to groupWith in GHC.Exts, but doesn't sort its input first groupRuns :: Eq b => (a -> b) -> [a] -> [[a]] @@ -1152,8 +1152,8 @@ output = [ (the x, y) [(1, [4, 5, 6]), (2, [4, 5, 6]), (3, [4, 5, 6]), (1, [4, 5, 6]), (2, [4, 5, 6])] - Note that we have used the the function to change the type - of x from a list to its original numeric type. The variable y, in contrast, is left + Note that we have used the the function to change the type + of x from a list to its original numeric type. The variable y, in contrast, is left unchanged from the list form introduced by the grouping. @@ -1166,13 +1166,13 @@ then group by e This form of grouping is essentially the same as the one described above. However, since no function to use for the grouping has been supplied it will fall back on the - groupWith function defined in + groupWith function defined in GHC.Exts. This is the form of the group statement that we made use of in the opening example. - - + + @@ -1182,7 +1182,7 @@ then group using f With this form of the group statement, f is required to simply have the type forall a. [a] -> [[a]], which will be used to group up the comprehension so far directly. An example of this form is as follows: - + output = [ x | y <- [1..5] @@ -1208,10 +1208,10 @@ output = [ x monad comprehensions - Monad comprehesions generalise the list comprehension notation, - including parallel comprehensions - () and - transform comprenensions () + Monad comprehensions generalise the list comprehension notation, + including parallel comprehensions + () and + transform comprehensions () to work for any monad. @@ -1364,11 +1364,11 @@ do (x,y) <- mzip (do x <- [1..10] compatible to built-in, transform and parallel list comprehensions. More formally, the desugaring is as follows. We write D[ e | Q] -to mean the desugaring of the monad comprehension [ e | Q]: +to mean the desugaring of the monad comprehension [ e | Q]: Expressions: e Declarations: d -Lists of qualifiers: Q,R,S +Lists of qualifiers: Q,R,S -- Basic forms D[ e | ] = return e @@ -1384,11 +1384,11 @@ D[ e | Q then f, R ] = f D[ Qv | Q ] >>= \Qv -> D[ e | D[ e | Q then f by b, R ] = f b D[ Qv | Q ] >>= \Qv -> D[ e | R ] -D[ e | Q then group using f, R ] = f D[ Qv | Q ] >>= \ys -> +D[ e | Q then group using f, R ] = f D[ Qv | Q ] >>= \ys -> case (fmap selQv1 ys, ..., fmap selQvn ys) of Qv -> D[ e | R ] -D[ e | Q then group by b using f, R ] = f b D[ Qv | Q ] >>= \ys -> +D[ e | Q then group by b using f, R ] = f b D[ Qv | Q ] >>= \ys -> case (fmap selQv1 ys, ..., fmap selQvn ys) of Qv -> D[ e | R ] @@ -1404,11 +1404,11 @@ guard Control.Monad t1 -> m t2 fmap GHC.Base forall a b. (a->b) -> n a -> n b mgroupWith Control.Monad.Group forall a. (a -> t) -> m1 a -> m2 (n a) mzip Control.Monad.Zip forall a b. m a -> m b -> m (a,b) - -The comprehension should typecheck when its desugaring would typecheck. + +The comprehension should typecheck when its desugaring would typecheck. -Monad comprehensions support rebindable syntax (). +Monad comprehensions support rebindable syntax (). Without rebindable syntax, the operators from the "standard binding" module are used; with rebindable syntax, the operators are looked up in the current lexical scope. @@ -1416,7 +1416,7 @@ For example, parallel comprehensions will be typechecked and desugared using whatever "mzip" is in scope. -The rebindable operators must have the "Expected type" given in the +The rebindable operators must have the "Expected type" given in the table above. These types are surprisingly general. For example, you can use a bind operator with the type @@ -1449,7 +1449,7 @@ the comprehension being over an arbitrary monad. hierarchy. It completely defeats that purpose if the literal "1" means "Prelude.fromInteger 1", which is what the Haskell Report specifies. - So the + So the flag causes the following pieces of built-in syntax to refer to whatever is in scope, not the Prelude @@ -1459,16 +1459,16 @@ the comprehension being over an arbitrary monad. An integer literal 368 means "fromInteger (368::Integer)", rather than "Prelude.fromInteger (368::Integer)". - + Fractional literals are handed in just the same way, - except that the translation is + except that the translation is fromRational (3.68::Rational). - + The equality test in an overloaded numeric pattern uses whatever (==) is in scope. - + The subtraction operation, and the greater-than-or-equal test, in n+k patterns @@ -1510,7 +1510,7 @@ the comprehension being over an arbitrary monad. In all cases (apart from arrow notation), the static semantics should be that of the desugared form, -even if that is a little unexpected. For example, the +even if that is a little unexpected. For example, the static semantics of the literal 368 is exactly that of fromInteger (368::Integer); it's fine for fromInteger to have any of the types: @@ -1521,7 +1521,7 @@ fromInteger :: Num a => a -> Integer fromInteger :: Integer -> Bool -> Bool - + Be warned: this is an experimental facility, with fewer checks than usual. Use -dcore-lint to typecheck the desugared program. If Core Lint is happy @@ -1609,7 +1609,7 @@ module Foo where import M data T = MkT { x :: Int } - + ok1 (MkS { x = n }) = n+1 -- Unambiguous ok2 n = MkT { x = n+1 } -- Unambiguous @@ -1628,7 +1628,7 @@ it is not clear which of the two types is intended. Haskell 98 regards all four as ambiguous, but with the flag, GHC will accept the former two. The rules are precisely the same as those for instance -declarations in Haskell 98, where the method names on the left-hand side +declarations in Haskell 98, where the method names on the left-hand side of the method bindings in an instance declaration refer unambiguously to the method of that class (provided they are in scope at all), even if there are other variables in scope with the same name. @@ -1639,7 +1639,7 @@ records from different modules that use the same field name. Some details: -Field disambiguation can be combined with punning (see ). For exampe: +Field disambiguation can be combined with punning (see ). For example: module Foo where import M @@ -1649,8 +1649,8 @@ module Foo where -With you can use unqualifed -field names even if the correponding selector is only in scope qualified +With you can use unqualified +field names even if the corresponding selector is only in scope qualified For example, assuming the same module M as in our earlier example, this is legal: module Foo where @@ -1658,7 +1658,7 @@ module Foo where ok4 (M.MkS { x = n }) = n+1 -- Unambiguous -Since the constructore MkS is only in scope qualified, you must +Since the constructor MkS is only in scope qualified, you must name it M.MkS, but the field x does not need to be qualified even though M.x is in scope but x is not. (In effect, it is qualified by the constructor.) @@ -1698,7 +1698,7 @@ f (C {a}) = a to mean the same pattern as above. That is, in a record pattern, the pattern a expands into the pattern a = -a for the same name a. +a for the same name a. @@ -1709,7 +1709,7 @@ Record punning can also be used in an expression, writing, for example, let a = 1 in C {a} -instead of +instead of let a = 1 in C {a = a} @@ -1728,7 +1728,7 @@ f (C {a, b = 4}) = a Puns can be used wherever record patterns occur (e.g. in -let bindings or at the top-level). +let bindings or at the top-level). @@ -1811,9 +1811,9 @@ the same as the omitted field names. -The ".." expands to the missing +The ".." expands to the missing in-scope record fields, where "in scope" -includes both unqualified and qualified-only. +includes both unqualified and qualified-only. Any fields that are not in scope are not filled in. For example module M where @@ -1848,7 +1848,7 @@ the semantics of such bindings very precisely. let f = ... infixr 3 `f` -in +in ... and the fixity declaration applies wherever the binding is in scope. @@ -1883,7 +1883,7 @@ necessary to enable them. import "network" Network.Socket - + would import the module Network.Socket from the package network (any version). This may be used to disambiguate an import when the same module is @@ -1907,7 +1907,7 @@ import "network" Network.Socket "stolen" by language extensions. We use notation and nonterminal names from the Haskell 98 lexical syntax - (see the Haskell 98 Report). + (see the Haskell 98 Report). We only list syntax changes here that might affect existing working programs (i.e. "stolen" syntax). Many of these extensions will also enable new context-free syntax, but in all @@ -1929,7 +1929,7 @@ import "network" Network.Socket on. - + The following syntax is stolen: @@ -2021,12 +2021,12 @@ The following syntax is stolen: varid{#}, - char#, - string#, - integer#, - float#, - float##, - (#, #), + char#, + string#, + integer#, + float#, + float##, + (#, #), Stolen by: , @@ -2053,7 +2053,7 @@ a data type with no constructors. For example: data T a -- T :: * -> * -Syntactically, the declaration lacks the "= constrs" part. The +Syntactically, the declaration lacks the "= constrs" part. The type can be parameterised over types of any kind, but if the kind is not * then an explicit kind annotation must be used (see ). @@ -2121,7 +2121,7 @@ to be written infix, very much like expressions. More specifically: type T (+) = Int + Int f :: T Either f = Left 3 - + liftA2 :: Arrow (~>) => (a -> b -> c) -> (e ~> a) -> (e ~> b) -> (e ~> c) liftA2 = ... @@ -2159,7 +2159,7 @@ Type synonyms are like macros at the type level, but Haskell 98 imposes many rul on individual synonym declarations. With the extension, GHC does validity checking on types only after expanding type synonyms. -That means that GHC can be very much more liberal about type synonyms than Haskell 98. +That means that GHC can be very much more liberal about type synonyms than Haskell 98. You can write a forall (including overloading) @@ -2177,7 +2177,7 @@ in a type synonym, thus: -If you also use , +If you also use , you can write an unboxed tuple in a type synonym: type Pr = (# Int, Int #) @@ -2191,7 +2191,7 @@ you can write an unboxed tuple in a type synonym: You can apply a type synonym to a forall type: type Foo a = a -> a -> Bool - + f :: Foo (forall b. b->b) After expanding the synonym, f has the legal (in GHC) type: @@ -2205,7 +2205,7 @@ You can apply a type synonym to a partially applied type synonym: type Generic i o = forall x. i x -> o x type Id x = x - + foo :: Generic Id [] After expanding the synonym, foo has the legal (in GHC) type: @@ -2454,7 +2454,7 @@ To make use of these hidden fields, we need to create some helper functions: inc :: Counter a -> Counter a inc (NewCounter x i d t) = NewCounter - { _this = i x, _inc = i, _display = d, tag = t } + { _this = i x, _inc = i, _display = d, tag = t } display :: Counter a -> IO () display NewCounter{ _this = x, _display = d } = d x @@ -2463,11 +2463,11 @@ display NewCounter{ _this = x, _display = d } = d x Now we can define counters with different underlying implementations: -counterA :: Counter String +counterA :: Counter String counterA = NewCounter { _this = 0, _inc = (1+), _display = print, tag = "A" } -counterB :: Counter String +counterB :: Counter String counterB = NewCounter { _this = "", _inc = ('#':), _display = putStrLn, tag = "B" } @@ -2671,16 +2671,16 @@ giving the type signatures of constructors explicitly. For example: Just :: a -> Maybe a The form is called a "GADT-style declaration" -because Generalised Algebraic Data Types, described in , +because Generalised Algebraic Data Types, described in , can only be declared using this form. -Notice that GADT-style syntax generalises existential types (). +Notice that GADT-style syntax generalises existential types (). For example, these two declarations are equivalent: data Foo = forall a. MkFoo a (a -> Bool) data Foo' where { MKFoo :: a -> (a->Bool) -> Foo' } -Any data type that can be declared in standard Haskell-98 syntax +Any data type that can be declared in standard Haskell-98 syntax can also be declared using GADT-style syntax. The choice is largely stylistic, but GADT-style declarations differ in one important respect: they treat class constraints on the data constructors differently. @@ -2697,14 +2697,14 @@ context is made available by pattern matching. For example: insert a (MkSet as) | a `elem` as = MkSet as | otherwise = MkSet (a:as) -A use of MkSet as a constructor (e.g. in the definition of makeSet) +A use of MkSet as a constructor (e.g. in the definition of makeSet) gives rise to a (Eq a) constraint, as you would expect. The new feature is that pattern-matching on MkSet (as in the definition of insert) makes available an (Eq a) context. In implementation terms, the MkSet constructor has a hidden field that stores the (Eq a) dictionary that is passed to MkSet; so when pattern-matching that dictionary becomes available for the right-hand side of the match. -In the example, the equality dictionary is used to satisfy the equality constraint +In the example, the equality dictionary is used to satisfy the equality constraint generated by the call to elem, so that the type of insert itself has no Eq constraint. @@ -2720,36 +2720,36 @@ For example, one possible application is to reify dictionaries: plus :: NumInst a -> a -> a -> a plus MkNumInst p q = p + q -Here, a value of type NumInst a is equivalent +Here, a value of type NumInst a is equivalent to an explicit (Num a) dictionary. All this applies to constructors declared using the syntax of . -For example, the NumInst data type above could equivalently be declared +For example, the NumInst data type above could equivalently be declared like this: - data NumInst a + data NumInst a = Num a => MkNumInst (NumInst a) -Notice that, unlike the situation when declaring an existential, there is +Notice that, unlike the situation when declaring an existential, there is no forall, because the Num constrains the -data type's universally quantified type variable a. +data type's universally quantified type variable a. A constructor may have both universal and existential type variables: for example, the following two declarations are equivalent: - data T1 a + data T1 a = forall b. (Num a, Eq b) => MkT1 a b data T2 a where MkT2 :: (Num a, Eq b) => a -> b -> T2 a -All this behaviour contrasts with Haskell 98's peculiar treatment of +All this behaviour contrasts with Haskell 98's peculiar treatment of contexts on a data type declaration (Section 4.2.1 of the Haskell 98 Report). In Haskell 98 the definition data Eq a => Set' a = MkSet' [a] -gives MkSet' the same type as MkSet above. But instead of +gives MkSet' the same type as MkSet above. But instead of making available an (Eq a) constraint, pattern-matching on MkSet' requires an (Eq a) constraint! GHC faithfully implements this behaviour, odd though it is. But for GADT-style declarations, @@ -2763,7 +2763,7 @@ type declarations. The result type of each data constructor must begin with the type constructor being defined. -If the result type of all constructors +If the result type of all constructors has the form T a1 ... an, where a1 ... an are distinct type variables, then the data type is ordinary; otherwise is a generalised data type (). @@ -2781,8 +2781,8 @@ In this example we give a single signature for T1 and The type signature of -each constructor is independent, and is implicitly universally quantified as usual. -In particular, the type variable(s) in the "data T a where" header +each constructor is independent, and is implicitly universally quantified as usual. +In particular, the type variable(s) in the "data T a where" header have no scope, and different constructors may have different universally-quantified type variables: data T a where -- The 'a' has no scope @@ -2813,8 +2813,8 @@ and similarly the Show constraint arising from the use of
  • -Unlike a Haskell-98-style -data type declaration, the type variable(s) in the "data Set a where" header +Unlike a Haskell-98-style +data type declaration, the type variable(s) in the "data Set a where" header have no scope. Indeed, one can write a kind signature instead: data Set :: * -> * where ... @@ -2851,7 +2851,7 @@ declaration. For example, these two declarations are equivalent Just1 :: a -> Maybe1 a } deriving( Eq, Ord ) - data Maybe2 a = Nothing2 | Just2 a + data Maybe2 a = Nothing2 | Just2 a deriving( Eq, Ord ) @@ -2865,10 +2865,10 @@ in the result type: Nil :: Foo Here the type variable a does not appear in the result type -of either constructor. +of either constructor. Although it is universally quantified in the type of the constructor, such -a type variable is often called "existential". -Indeed, the above declaration declares precisely the same type as +a type variable is often called "existential". +Indeed, the above declaration declares precisely the same type as the data Foo in . The type may contain a class context too, of course: @@ -2889,23 +2889,23 @@ You can use record syntax on a GADT-style data type declaration: As usual, for every constructor that has a field f, the type of field f must be the same (modulo alpha conversion). The Child constructor above shows that the signature -may have a context, existentially-quantified variables, and strictness annotations, +may have a context, existentially-quantified variables, and strictness annotations, just as in the non-record case. (NB: the "type" that follows the double-colon is not really a type, because of the record syntax and strictness annotations. A "type" of this form can appear only in a constructor signature.) - -Record updates are allowed with GADT-style declarations, + +Record updates are allowed with GADT-style declarations, only fields that have the following property: the type of the field mentions no existential type variables. - -As in the case of existentials declared using the Haskell-98-like record syntax + +As in the case of existentials declared using the Haskell-98-like record syntax (), record-selector functions are generated only for those fields that have well-typed -selectors. +selectors. Here is the example of that section, in GADT-style syntax: data Counter a where @@ -2925,18 +2925,18 @@ Nevertheless, you can still use all the field names in pattern matching and reco Generalised Algebraic Data Types (GADTs) -Generalised Algebraic Data Types generalise ordinary algebraic data types +Generalised Algebraic Data Types generalise ordinary algebraic data types by allowing constructors to have richer return types. Here is an example: data Term a where Lit :: Int -> Term Int Succ :: Term Int -> Term Int - IsZero :: Term Int -> Term Bool + IsZero :: Term Int -> Term Bool If :: Term Bool -> Term a -> Term a -> Term a Pair :: Term a -> Term b -> Term (a,b) Notice that the return type of the constructors is not always Term a, as is the -case with ordinary data types. This generality allows us to +case with ordinary data types. This generality allows us to write a well-typed eval function for these Terms: @@ -2947,22 +2947,22 @@ for these Terms: eval (If b e1 e2) = if eval b then eval e1 else eval e2 eval (Pair e1 e2) = (eval e1, eval e2) -The key point about GADTs is that pattern matching causes type refinement. +The key point about GADTs is that pattern matching causes type refinement. For example, in the right hand side of the equation eval :: Term a -> a eval (Lit i) = ... the type a is refined to Int. That's the whole point! -A precise specification of the type rules is beyond what this user manual aspires to, +A precise specification of the type rules is beyond what this user manual aspires to, but the design closely follows that described in the paper Simple unification-based type inference for GADTs, (ICFP 2006). -The general principle is this: type refinement is only carried out +The general principle is this: type refinement is only carried out based on user-supplied type annotations. -So if no type signature is supplied for eval, no type refinement happens, +So if no type signature is supplied for eval, no type refinement happens, and lots of obscure error messages will occur. However, the refinement is quite general. For example, if we had: @@ -2982,14 +2982,14 @@ and Ralf Hinze's may use different notation to that implemented in GHC. -The rest of this section outlines the extensions to GHC that support GADTs. The extension is enabled with +The rest of this section outlines the extensions to GHC that support GADTs. The extension is enabled with . The flag also sets . -A GADT can only be declared using GADT-style syntax (); +A GADT can only be declared using GADT-style syntax (); the old Haskell-98 syntax for data declarations always declares an ordinary data type. The result type of each constructor must begin with the type constructor being defined, -but for a GADT the arguments to the type constructor can be arbitrary monotypes. +but for a GADT the arguments to the type constructor can be arbitrary monotypes. For example, in the Term data type above, the type of each constructor must end with Term ty, but the ty need not be a type variable (e.g. the Lit @@ -3015,7 +3015,7 @@ For example: Lit { val :: Int } :: Term Int Succ { num :: Term Int } :: Term Int Pred { num :: Term Int } :: Term Int - IsZero { arg :: Term Int } :: Term Bool + IsZero { arg :: Term Int } :: Term Bool Pair { arg1 :: Term a , arg2 :: Term b } :: Term (a,b) @@ -3024,11 +3024,11 @@ For example: , fls :: Term a } :: Term a -However, for GADTs there is the following additional constraint: +However, for GADTs there is the following additional constraint: every constructor that has a field f must have the same result type (modulo alpha conversion) -Hence, in the above example, we cannot merge the num -and arg fields above into a +Hence, in the above example, we cannot merge the num +and arg fields above into a single name. Although their field types are both Term Int, their selector functions actually have different types: @@ -3039,7 +3039,7 @@ their selector functions actually have different types: -When pattern-matching against data constructors drawn from a GADT, +When pattern-matching against data constructors drawn from a GADT, for example in a case expression, the following rules apply: The type of the scrutinee must be rigid. @@ -3083,12 +3083,12 @@ The natural generated Eq code would result in these instance instance Eq (f a) => Eq (T1 f a) where ... instance Eq (f (f a)) => Eq (T2 f a) where ... -The first of these is obviously fine. The second is still fine, although less obviously. +The first of these is obviously fine. The second is still fine, although less obviously. The third is not Haskell 98, and risks losing termination of instances. GHC takes a conservative position: it accepts the first two, but not the third. The rule is this: -each constraint in the inferred instance context must consist only of type variables, +each constraint in the inferred instance context must consist only of type variables, with no repetitions. @@ -3112,10 +3112,10 @@ The syntax is identical to that of an ordinary instance declaration apart from ( Note the following points: -You must supply an explicit context (in the example the context is (Eq a)), +You must supply an explicit context (in the example the context is (Eq a)), exactly as you would in an ordinary instance declaration. -(In contrast, in a deriving clause -attached to a data type declaration, the context is inferred.) +(In contrast, in a deriving clause +attached to a data type declaration, the context is inferred.) @@ -3127,7 +3127,7 @@ controlled by the same flags; see . Unlike a deriving declaration attached to a data declaration, the instance can be more specific -than the data type (assuming you also use +than the data type (assuming you also use -XFlexibleInstances, ). Consider for example @@ -3142,10 +3142,10 @@ but other types such as (Foo (Int,Bool)) will not be an insta Unlike a deriving -declaration attached to a data declaration, +declaration attached to a data declaration, GHC does not restrict the form of the data type. Instead, GHC simply generates the appropriate boilerplate code for the specified class, and typechecks it. If there is a type error, it is -your problem. (GHC will show you the offending code if it has a type error.) +your problem. (GHC will show you the offending code if it has a type error.) The merit of this is that you can derive instances for GADTs and other exotic data types, providing only that the boilerplate code does indeed typecheck. For example: @@ -3155,8 +3155,8 @@ data types, providing only that the boilerplate code does indeed typecheck. For deriving instance Show (T a) -In this example, you cannot say ... deriving( Show ) on the -data type declaration for T, +In this example, you cannot say ... deriving( Show ) on the +data type declaration for T, because T is a GADT, but you can generate the instance declaration using stand-alone deriving. @@ -3183,10 +3183,10 @@ GHC always treats the last parameter of the instance Deriving clause for extra classes (<literal>Typeable</literal>, <literal>Data</literal>, etc) -Haskell 98 allows the programmer to add "deriving( Eq, Ord )" to a data type -declaration, to generate a standard instance declaration for classes specified in the deriving clause. +Haskell 98 allows the programmer to add "deriving( Eq, Ord )" to a data type +declaration, to generate a standard instance declaration for classes specified in the deriving clause. In Haskell 98, the only classes that may appear in the deriving clause are the standard -classes Eq, Ord, +classes Eq, Ord, Enum, Ix, Bounded, Read, and Show. @@ -3206,7 +3206,7 @@ Scrap More Boilerplate: Reflection, Zips, and Generalised Casts (Section 7.4 of the paper describes the multiple Typeable classes that are used, and only Typeable1 up to Typeable7 are provided in the library.) -In other cases, there is nothing to stop the programmer writing a TypableX +In other cases, there is nothing to stop the programmer writing a TypeableX class, whose kind suits that of the data type constructor, and then writing the data type instance by hand. @@ -3218,22 +3218,22 @@ instances of the class Generic, defined in as described in . - With , you can derive instances of + With , you can derive instances of the class Functor, defined in GHC.Base. - With , you can derive instances of + With , you can derive instances of the class Foldable, defined in Data.Foldable. - With , you can derive instances of + With , you can derive instances of the class Traversable, defined in Data.Traversable. -In each case the appropriate class must be in scope before it +In each case the appropriate class must be in scope before it can be mentioned in the deriving clause. @@ -3250,7 +3250,7 @@ other classes you have to write an explicit instance declaration. For example, if you define - newtype Dollars = Dollars Int + newtype Dollars = Dollars Int and you want to use arithmetic on Dollars, you have to @@ -3271,9 +3271,9 @@ dictionary, only slower! Generalising the deriving clause -GHC now permits such instances to be derived instead, +GHC now permits such instances to be derived instead, using the flag , -so one can write +so one can write newtype Dollars = Dollars Int deriving (Eq,Show,Num) @@ -3295,10 +3295,10 @@ way. For example, suppose we have implemented state and failure monad transformers, such that - instance Monad m => Monad (State s m) + instance Monad m => Monad (State s m) instance Monad m => Monad (Failure m) -In Haskell 98, we can define a parsing monad by +In Haskell 98, we can define a parsing monad by type Parser tok m a = State [tok] (Failure m) a @@ -3311,9 +3311,9 @@ without needing to write an instance of class Monad, via newtype Parser tok m a = Parser (State [tok] (Failure m) a) deriving Monad -In this case the derived instance declaration is of the form +In this case the derived instance declaration is of the form - instance Monad (State [tok] (Failure m)) => Monad (Parser tok m) + instance Monad (State [tok] (Failure m)) => Monad (Parser tok m) Notice that, since Monad is a constructor class, the @@ -3330,10 +3330,10 @@ application'' of the class appears in the deriving clause. For example, given the class - class StateMonad s m | m -> s where ... - instance Monad m => StateMonad s (State s m) where ... + class StateMonad s m | m -> s where ... + instance Monad m => StateMonad s (State s m) where ... -then we can derive an instance of StateMonad for Parsers by +then we can derive an instance of StateMonad for Parsers by newtype Parser tok m a = Parser (State [tok] (Failure m) a) deriving (Monad, StateMonad [tok]) @@ -3363,10 +3363,10 @@ Derived instance declarations are constructed as follows. Consider the declaration (after expansion of any type synonyms) - newtype T v1...vn = T' (t vk+1...vn) deriving (c1...cm) + newtype T v1...vn = T' (t vk+1...vn) deriving (c1...cm) -where +where The ci are partial applications of @@ -3380,15 +3380,15 @@ where The type t is an arbitrary type. - The type variables vk+1...vn do not occur in t, + The type variables vk+1...vn do not occur in t, nor in the ci, and - None of the ci is Read, Show, + None of the ci is Read, Show, Typeable, or Data. These classes should not "look through" the type or its constructor. You can still - derive these classes for a newtype, but it happens in the usual way, not - via this new mechanism. + derive these classes for a newtype, but it happens in the usual way, not + via this new mechanism. Then, for each ci, the derived instance @@ -3396,13 +3396,13 @@ declaration is: instance ci t => ci (T v1...vk) -As an example which does not work, consider +As an example which does not work, consider - newtype NonMonad m s = NonMonad (State s m s) deriving Monad + newtype NonMonad m s = NonMonad (State s m s) deriving Monad -Here we cannot derive the instance +Here we cannot derive the instance - instance Monad (State s m) => Monad (NonMonad m) + instance Monad (State s m) => Monad (NonMonad m) because the type variable s occurs in State s m, @@ -3418,7 +3418,7 @@ important, since we can only derive instances for the last one. If the StateMonad class above were instead defined as - class StateMonad m s | m -> s where ... + class StateMonad m s | m -> s where ... then we would not have been able to derive an instance for the @@ -3427,7 +3427,7 @@ classes usually have one "main" parameter for which deriving new instances is most interesting. Lastly, all of this applies only for classes other than -Read, Show, Typeable, +Read, Show, Typeable, and Data, for which the built-in derivation applies (section 4.3.3. of the Haskell Report). (For the standard classes Eq, Ord, @@ -3460,7 +3460,7 @@ All the extensions are enabled by the flag. Multi-parameter type classes -Multi-parameter type classes are permitted, with flag . +Multi-parameter type classes are permitted, with flag . For example: @@ -3478,11 +3478,11 @@ For example: In Haskell 98 the context of a class declaration (which introduces superclasses) -must be simple; that is, each predicate must consist of a class applied to -type variables. The flag +must be simple; that is, each predicate must consist of a class applied to +type variables. The flag () lifts this restriction, -so that the only restriction on the context in a class declaration is +so that the only restriction on the context in a class declaration is that the class hierarchy must be acyclic. So these class declarations are OK: @@ -3532,7 +3532,7 @@ class type variable, thus: elem :: Eq a => a -> s a -> Bool The type of elem is illegal in Haskell 98, because it -contains the constraint Eq a, constrains only the +contains the constraint Eq a, constrains only the class type variable (in this case a). GHC lifts this restriction (flag ). @@ -3555,7 +3555,7 @@ The type of the enum method is [a], and this is also the type of the default method. You can lift this restriction and give another type to the default method using the flag . For instance, if you have written a -generic implementation of enumeration in a class GEnum +generic implementation of enumeration in a class GEnum with method genum in terms of GHC.Generics, you can specify a default method that uses that generic implementation: @@ -3574,7 +3574,7 @@ and type-checked with the type -We use default signatures to simplify generic programming in GHC +We use default signatures to simplify generic programming in GHC (). @@ -3587,14 +3587,14 @@ We use default signatures to simplify generic programming in GHC Functional dependencies are implemented as described by Mark Jones -in “Type Classes with Functional Dependencies”, Mark P. Jones, -In Proceedings of the 9th European Symposium on Programming, +in “Type Classes with Functional Dependencies”, Mark P. Jones, +In Proceedings of the 9th European Symposium on Programming, ESOP 2000, Berlin, Germany, March 2000, Springer-Verlag LNCS 1782, . -Functional dependencies are introduced by a vertical bar in the syntax of a -class declaration; e.g. +Functional dependencies are introduced by a vertical bar in the syntax of a +class declaration; e.g. class (Monad m) => MonadState s m | m -> s where ... @@ -3605,7 +3605,7 @@ There should be more documentation, but there isn't (yet). Yell if you need it. Rules for functional dependencies -In a class declaration, all of the class type variables must be reachable (in the sense +In a class declaration, all of the class type variables must be reachable (in the sense mentioned in ) from the free variables of each method type. For example: @@ -3658,7 +3658,7 @@ class like this: from the Hugs user manual, reproduced here (with minor changes) by kind permission of Mark Jones. - + Consider the following class, intended as part of a library for collection types: @@ -3673,7 +3673,7 @@ instances of this class for lists or characteristic functions (both of which can be used to represent collections of any equality type), bit sets (which can be used to represent collections of characters), or hash tables (which can be used to represent any collection whose elements have a hash function). Omitting -standard implementation details, this would lead to the following declarations: +standard implementation details, this would lead to the following declarations: instance Eq e => Collects e [e] where ... instance Eq e => Collects e (e -> Bool) where ... @@ -3683,7 +3683,7 @@ standard implementation details, this would lead to the following declarations: All this looks quite promising; we have a class and a range of interesting implementations. Unfortunately, there are some serious problems with the class -declaration. First, the empty function has an ambiguous type: +declaration. First, the empty function has an ambiguous type: empty :: Collects e ce => ce @@ -3697,12 +3697,12 @@ type. We can sidestep this specific problem by removing the empty member from the class declaration. However, although the remaining members, insert and member, do not have ambiguous types, we still run into problems when we try to use -them. For example, consider the following two functions: +them. For example, consider the following two functions: f x y = insert x . insert y g = f True 'a' -for which GHC infers the following types: +for which GHC infers the following types: f :: (Collects a c, Collects b c) => a -> b -> c -> c g :: (Collects Bool c, Collects Char c) => c -> c @@ -3721,7 +3721,7 @@ might even be in a different module. Faced with the problems described above, some Haskell programmers might be -tempted to use something like the following version of the class declaration: +tempted to use something like the following version of the class declaration: class Collects e c where empty :: c e @@ -3732,16 +3732,16 @@ The key difference here is that we abstract over the type constructor c that is used to form the collection type c e, and not over that collection type itself, represented by ce in the original class declaration. This avoids the immediate problems that we mentioned above: empty has type Collects e c => c -e, which is not ambiguous. +e, which is not ambiguous. -The function f from the previous section has a more accurate type: +The function f from the previous section has a more accurate type: f :: (Collects e c) => e -> e -> c e -> c e The function g from the previous section is now rejected with a type error as we would hope because the type of f does not allow the two arguments to have -different types. +different types. This, then, is an example of a multiple parameter class that does actually work quite well in practice, without ambiguity problems. There is, however, a catch. This version of the Collects class is nowhere near @@ -3767,14 +3767,14 @@ underlying ideas are also discussed in a more theoretical and abstract setting in a manuscript [implparam], where they are identified as one point in a general design space for systems of implicit parameterization.). -To start with an abstract example, consider a declaration such as: +To start with an abstract example, consider a declaration such as: class C a b where ... which tells us simply that C can be thought of as a binary relation on types (or type constructors, depending on the kinds of a and b). Extra clauses can be included in the definition of classes to add information about dependencies -between parameters, as in the following examples: +between parameters, as in the following examples: class D a b | a -> b where ... class E a b | a -> b, b -> a where ... @@ -3797,11 +3797,11 @@ annotated with multiple dependencies using commas as separators, as in the definition of E above. Some dependencies that we can write in this notation are redundant, and will be rejected because they don't serve any useful purpose, and may instead indicate an error in the program. Examples of -dependencies like this include a -> a , -a -> a a , +dependencies like this include a -> a , +a -> a a , a -> , etc. There can also be -some redundancy if multiple dependencies are given, as in -a->b, +some redundancy if multiple dependencies are given, as in +a->b, b->c , a->c , and in which some subset implies the remaining dependencies. Examples like this are not treated as errors. Note that dependencies appear only in class @@ -3816,19 +3816,19 @@ compiler, on the other hand, is responsible for ensuring that the set of instances that are in scope at any given point in the program is consistent with any declared dependencies. For example, the following pair of instance declarations cannot appear together in the same scope because they violate the -dependency for D, even though either one on its own would be acceptable: +dependency for D, even though either one on its own would be acceptable: instance D Bool Int where ... instance D Bool Char where ... -Note also that the following declaration is not allowed, even by itself: +Note also that the following declaration is not allowed, even by itself: instance D [a] b where ... The problem here is that this instance would allow one particular choice of [a] to be associated with more than one choice for b, which contradicts the dependency specified in the definition of D. More generally, this means that, -in any instance of the form: +in any instance of the form: instance D t s where ... @@ -3841,7 +3841,7 @@ The benefit of including dependency information is that it allows us to define more general multiple parameter classes, without ambiguity problems, and with the benefit of more accurate types. To illustrate this, we return to the collection class example, and annotate the original definition of Collects -with a simple dependency: +with a simple dependency: class Collects e ce | ce -> e where empty :: ce @@ -3870,18 +3870,18 @@ contains a variable on the left of the => that is not uniquely determined Dependencies also help to produce more accurate types for user defined functions, and hence to provide earlier detection of errors, and less cluttered types for programmers to work with. Recall the previous definition for a -function f: +function f: f x y = insert x y = insert x . insert y -for which we originally obtained a type: +for which we originally obtained a type: f :: (Collects a c, Collects b c) => a -> b -> c -> c Given the dependency information that we have for Collects, however, we can deduce that a and b must be equal because they both appear as the second parameter in a Collects constraint with the same first parameter c. Hence we -can infer a shorter and more accurate type for f: +can infer a shorter and more accurate type for f: f :: (Collects a c) => a -> a -> c -> c @@ -3992,7 +3992,7 @@ The Paterson Conditions: for each assertion in the context tvsleft -> tvsright, of the class, every type variable in -S(tvsright) must appear in +S(tvsright) must appear in S(tvsleft), where S is the substitution mapping each type variable in the class declaration to the corresponding type in the instance declaration. @@ -4000,8 +4000,8 @@ corresponding type in the instance declaration. These restrictions ensure that context reduction terminates: each reduction step makes the problem smaller by at least one -constructor. Both the Paterson Conditions and the Coverage Condition are lifted -if you give the +constructor. Both the Paterson Conditions and the Coverage Condition are lifted +if you give the flag (). You can find lots of background material about the reason for these restrictions in the paper C4 [a] [a] + instance C4 a a => C4 [a] [a] instance Stateful (ST s) (MutVar s) -- Head can consist of type variables only @@ -4089,7 +4089,7 @@ the head, something that is excluded by the normal rules. For example: class HasConverter a b | a -> b where convert :: a -> b - + data Foo a = MkFoo a instance (HasConverter a b,Show b) => Show (Foo a) where @@ -4123,7 +4123,7 @@ makes instance inference go into a loop, because it requires the constraint Nevertheless, GHC allows you to experiment with more liberal rules. If you use the experimental flag --XUndecidableInstances, +-XUndecidableInstances, both the Paterson Conditions and the Coverage Condition (described in ) are lifted. Termination is ensured by having a fixed-depth recursion stack. If you exceed the stack depth you get a @@ -4142,11 +4142,11 @@ declaration should be used to resolve a type-class constraint. This behaviour can be modified by two flags: -XOverlappingInstances - + and -XIncoherentInstances , as this section discusses. Both these -flags are dynamic flags, and can be set on a per-module basis, using +flags are dynamic flags, and can be set on a per-module basis, using an OPTIONS_GHC pragma if desired (). When GHC tries to resolve, say, the constraint C Int Bool, @@ -4160,14 +4160,14 @@ these declarations: instance context3 => C Int [a] where ... -- (C) instance context4 => C Int [Int] where ... -- (D) -The instances (A) and (B) match the constraint C Int Bool, +The instances (A) and (B) match the constraint C Int Bool, but (C) and (D) do not. When matching, GHC takes no account of the context of the instance declaration (context1 etc). GHC's default behaviour is that exactly one instance must match the -constraint it is trying to resolve. +constraint it is trying to resolve. It is fine for there to be a potential of overlap (by -including both declarations (A) and (B), say); an error is only reported if a +including both declarations (A) and (B), say); an error is only reported if a particular constraint matches more than one. @@ -4187,16 +4187,16 @@ However, GHC is conservative about committing to an overlapping instance. For e Suppose that from the RHS of f we get the constraint C Int [b]. But GHC does not commit to instance (C), because in a particular -call of f, b might be instantiate +call of f, b might be instantiate to Int, in which case instance (D) would be more specific still. -So GHC rejects the program. +So GHC rejects the program. (If you add the flag , -GHC will instead pick (C), without complaining about +GHC will instead pick (C), without complaining about the problem of subsequent instantiations.) Notice that we gave a type signature to f, so GHC had to -check that f has the specified type. +check that f has the specified type. Suppose instead we do not give a type signature, asking GHC to infer it instead. In this case, GHC will refrain from simplifying the constraint C Int [b] (for the same reason @@ -4204,10 +4204,10 @@ as before) but, rather than rejecting the program, it will infer the type f :: C Int [b] => [b] -> [b] -That postpones the question of which instance to pick to the +That postpones the question of which instance to pick to the call site for f by which time more is known about the type b. -You can write this type signature yourself if you use the +You can write this type signature yourself if you use the flag. @@ -4231,7 +4231,7 @@ of the instance declaration, thus: (You need to do this.) -Warning: overlapping instances must be used with care. They +Warning: overlapping instances must be used with care. They can give rise to incoherence (ie different instance choices are made in different parts of the program) even without . Consider: @@ -4265,20 +4265,20 @@ In function showHelp GHC sees no overlapping instances, and so uses the MyShow [a] instance without complaint. In the call to myshow in main, GHC resolves the MyShow [T] constraint using the overlapping -instance declaration in module Main. As a result, +instance declaration in module Main. As a result, the program prints "Used more specific instance" "Used generic instance" -(An alternative possible behaviour, not currently implemented, +(An alternative possible behaviour, not currently implemented, would be to reject module Help on the grounds that a later instance declaration might overlap the local one.) -The willingness to be overlapped or incoherent is a property of +The willingness to be overlapped or incoherent is a property of the instance declaration itself, controlled by the -presence or otherwise of the +presence or otherwise of the and flags when that module is being defined. Specifically, during the lookup process: @@ -4297,12 +4297,12 @@ Suppose an instance declaration does not match the constraint being looked up, b does unify with it, so that it might match when the constraint is further instantiated. Usually GHC will regard this as a reason for not committing to some other constraint. But if the instance declaration was compiled with -, GHC will skip the "does-it-unify?" +, GHC will skip the "does-it-unify?" check for that declaration. -These rules make it possible for a library author to design a library that relies on -overlapping instances without the library client having to know. +These rules make it possible for a library author to design a library that relies on +overlapping instances without the library client having to know. The flag implies the flag, but not vice versa. @@ -4350,7 +4350,7 @@ Haskell's defaulting mechanism is extended to cover string literals, when -Each type in a default declaration must be an +Each type in a default declaration must be an instance of Num or of IsString. @@ -4395,23 +4395,23 @@ to work since it gets translated into an equality comparison. Indexed type families are a new GHC extension to - facilitate type-level + facilitate type-level programming. Type families are a generalisation of associated - data types - (“Associated + data types + (“Associated Types with Class”, M. Chakravarty, G. Keller, S. Peyton Jones, and S. Marlow. In Proceedings of “The 32nd Annual ACM SIGPLAN-SIGACT Symposium on Principles of Programming Languages (POPL'05)”, pages 1-13, ACM Press, 2005) and associated type synonyms - (“Type + (“Type Associated Type Synonyms”. M. Chakravarty, G. Keller, and - S. Peyton Jones. + S. Peyton Jones. In Proceedings of “The Tenth ACM SIGPLAN International Conference on Functional Programming”, ACM Press, pages 241-253, 2005). Type families - themselves are described in the paper “Type Checking with Open Type Functions”, T. Schrijvers, - S. Peyton-Jones, + S. Peyton-Jones, M. Chakravarty, and M. Sulzmann, in Proceedings of “ICFP 2008: The 13th ACM SIGPLAN International Conference on Functional Programming”, ACM Press, pages 51-62, 2008. Type families @@ -4420,13 +4420,13 @@ to work since it gets translated into an equality comparison. interfaces as well as interfaces with enhanced static information, much like dependent types. They might also be regarded as an alternative to functional dependencies, but provide a more functional style of type-level programming - than the relational style of functional dependencies. + than the relational style of functional dependencies. Indexed type families, or type families for short, are type constructors that represent sets of types. Set members are denoted by supplying the type family constructor with type parameters, which are called type - indices. The + indices. The difference between vanilla parametrised type constructors and family constructors is much like between parametrically polymorphic functions and (ad-hoc polymorphic) methods of type classes. Parametric polymorphic functions @@ -4434,14 +4434,14 @@ to work since it gets translated into an equality comparison. behaviour in dependence on the class type parameters. Similarly, vanilla type constructors imply the same data representation for all type instances, but family constructors can have varying representation types for varying type - indices. + indices. Indexed type families come in two flavours: data - families and type synonym + families and type synonym families. They are the indexed family variants of algebraic data types and type synonyms, respectively. The instances of data families - can be data types and newtypes. + can be data types and newtypes. Type families are enabled by the flag . @@ -4455,7 +4455,7 @@ to work since it gets translated into an equality comparison. Data families appear in two flavours: (1) they can be defined on the - toplevel + toplevel or (2) they can appear inside type classes (in which case they are known as associated types). The former is the more general variant, as it lacks the requirement for the type-indexes to coincide with the class @@ -4465,11 +4465,11 @@ to work since it gets translated into an equality comparison. and then cover the additional constraints placed on associated types. - + Data family declarations - Indexed data families are introduced by a signature, such as + Indexed data families are introduced by a signature, such as data family GMap k :: * -> * @@ -4483,7 +4483,7 @@ data family Array e Just as with [http://www.haskell.org/ghc/docs/latest/html/users_guide/gadt.html GADT declarations] named arguments are entirely optional, so that we can - declare Array alternatively with + declare Array alternatively with data family Array :: * -> * @@ -4494,7 +4494,7 @@ data family Array :: * -> * When a data family is declared as part of a type class, we drop the family special. The GMap - declaration takes the following form + declaration takes the following form class GMapKey k where data GMap k :: * -> * @@ -4505,7 +4505,7 @@ class GMapKey k where the argument names must be class parameters. Each class parameter may only be used at most once per associated type, but some may be omitted and they may be in an order other than in the class head. Hence, the - following contrived example is admissible: + following contrived example is admissible: class C a b c where data T c a :: * @@ -4514,7 +4514,7 @@ class GMapKey k where - + Data instance declarations @@ -4528,7 +4528,7 @@ class GMapKey k where they are fully applied and expand to a type that is itself admissible - exactly as this is required for occurrences of type synonyms in class instance parameters. For example, the Either - instance for GMap is + instance for GMap is data instance GMap (Either a b) v = GMapEither (GMap a v) (GMap b v) @@ -4537,18 +4537,18 @@ data instance GMap (Either a b) v = GMapEither (GMap a v) (GMap b v) Data and newtype instance declarations are only permitted when an - appropriate family declaration is in scope - just as a class instance declaratoin + appropriate family declaration is in scope - just as a class instance declaration requires the class declaration to be visible. Moreover, each instance declaration has to conform to the kind determined by its family declaration. This implies that the number of parameters of an instance declaration matches the arity determined by the kind of the family. - A data family instance declaration can use the full exprssiveness of + A data family instance declaration can use the full expressiveness of ordinary data or newtype declarations: Although, a data family is introduced with - the keyword "data", a data family instance can + the keyword "data", a data family instance can use either data or newtype. For example: data family T a @@ -4576,7 +4576,7 @@ data instance G [a] b where Even if type families are defined as toplevel declarations, functions that perform different computations for different family instances may still need to be defined as methods of type classes. In particular, the - following is not possible: + following is not possible: data family T a data instance T Int = A @@ -4587,7 +4587,7 @@ foo B = 2 -- ...will produce a type error. Instead, you would have to write foo as a class operation, thus: -class C a where +class C a where foo :: T a -> Int instance Foo Int where foo A = 1 @@ -4598,7 +4598,7 @@ instance Foo Char where Types), it might seem as if a definition, such as the above, should be feasible. However, type families are - in contrast to GADTs - are open; i.e., new instances can always be added, - possibly in other + possibly in other modules. Supporting pattern matching across different data instances would require a form of extensible case construct.) @@ -4609,7 +4609,7 @@ instance Foo Char where When an associated data family instance is declared within a type class instance, we drop the instance keyword in the family instance. So, the Either instance - for GMap becomes: + for GMap becomes: instance (GMapKey a, GMapKey b) => GMapKey (Either a b) where data GMap (Either a b) v = GMapEither (GMap a v) (GMap b v) @@ -4622,7 +4622,7 @@ instance (GMapKey a, GMapKey b) => GMapKey (Either a b) where which coincides with the only class parameter. Any parameters to the family constructor that do not correspond to class parameters, need to be variables in every instance; here this is the - variable v. + variable v. Instances for an associated family can only appear as part of @@ -4632,7 +4632,7 @@ instance (GMapKey a, GMapKey b) => GMapKey (Either a b) where types can be omitted in class instances. If an associated family instance is omitted, the corresponding instance type is not inhabited; i.e., only diverging expressions, such - as undefined, can assume the type. + as undefined, can assume the type. @@ -4642,13 +4642,13 @@ instance (GMapKey a, GMapKey b) => GMapKey (Either a b) where In the case of multi-parameter type classes, the visibility of class parameters in the right-hand side of associated family instances depends solely on the parameters of the data - family. As an example, consider the simple class declaration + family. As an example, consider the simple class declaration class C a b where data T a Only one of the two class parameters is a parameter to the data - family. Hence, the following instance declaration is invalid: + family. Hence, the following instance declaration is invalid: instance C [c] d where data T [c] = MkT (c, d) -- WRONG!! 'd' is not in scope @@ -4656,7 +4656,7 @@ instance C [c] d where Here, the right-hand side of the data instance mentions the type variable d that does not occur in its left-hand side. We cannot admit such data instances as they would compromise - type safety. + type safety. @@ -4665,7 +4665,7 @@ instance C [c] d where Type class instances of instances of data families can be defined as usual, and in particular data instance declarations can - have deriving clauses. For example, we can write + have deriving clauses. For example, we can write data GMap () v = GMapUnit (Maybe v) deriving Show @@ -4682,7 +4682,7 @@ instance Show v => Show (GMap () v) where ... reasons that we cannot define a toplevel function that performs pattern matching on the data constructors of different instances of a single type family. - It would require a form of extensible case construct. + It would require a form of extensible case construct. @@ -4692,7 +4692,7 @@ instance Show v => Show (GMap () v) where ... The instance declarations of a data family used in a single program may not overlap at all, independent of whether they are associated or not. In contrast to type class instances, this is not only a matter - of consistency, but one of type safety. + of consistency, but one of type safety. @@ -4716,7 +4716,7 @@ instance Show v => Show (GMap () v) where ... an export item, these may be either imported or defined in the current module. The treatment of import and export items that explicitly list data constructors, such as GMap(GMapEither), is - analogous. + analogous. @@ -4731,7 +4731,7 @@ instance Show v => Show (GMap () v) where ... type name needs to be prefixed by the keyword type. So for example, when explicitly listing the components of the GMapKey class, we write GMapKey(type - GMap, empty, lookup, insert). + GMap, empty, lookup, insert). @@ -4739,7 +4739,7 @@ instance Show v => Show (GMap () v) where ... Examples Assuming our running GMapKey class example, let us - look at some export lists and their meaning: + look at some export lists and their meaning: module GMap (GMapKey) where...: Exports @@ -4750,14 +4750,14 @@ instance Show v => Show (GMap () v) where ... Exports the class, the associated type GMap and the member functions empty, lookup, - and insert. None of the data constructors is + and insert. None of the data constructors is exported. - + module GMap (GMapKey(..), GMap(..)) where...: As before, but also exports all the data - constructors GMapInt, - GMapChar, + constructors GMapInt, + GMapChar, GMapUnit, GMapPair, and GMapUnit. @@ -4778,7 +4778,7 @@ instance Show v => Show (GMap () v) where ... write GMapKey(type GMap(..)) — i.e., sub-component specifications cannot be nested. To specify GMap's data constructors, you have to list - it separately. + it separately. @@ -4787,7 +4787,7 @@ instance Show v => Show (GMap () v) where ... Family instances are implicitly exported, just like class instances. However, this applies only to the heads of instances, not to the data - constructors an instance defines. + constructors an instance defines. @@ -4814,13 +4814,13 @@ instance Show v => Show (GMap () v) where ... Type family declarations - Indexed type families are introduced by a signature, such as + Indexed type families are introduced by a signature, such as type family Elem c :: * The special family distinguishes family from standard type declarations. The result kind annotation is optional and, as - usual, defaults to * if omitted. An example is + usual, defaults to * if omitted. An example is type family Elem c @@ -4831,13 +4831,13 @@ type family Elem c and it implies that the kind of a type family is not sufficient to determine a family's arity, and hence in general, also insufficient to determine whether a type family application is well formed. As an - example, consider the following declaration: + example, consider the following declaration: -type family F a b :: * -> * -- F's arity is 2, +type family F a b :: * -> * -- F's arity is 2, -- although its overall kind is * -> * -> * -> * Given this declaration the following are examples of well-formed and - malformed types: + malformed types: F Char [Int] -- OK! Kind: * -> * F Char [Int] Bool -- OK! Kind: * @@ -4851,7 +4851,7 @@ F Bool -- WRONG: unsaturated application When a type family is declared as part of a type class, we drop the family special. The Elem - declaration takes the following form + declaration takes the following form class Collects ce where type Elem ce :: * @@ -4860,7 +4860,7 @@ class Collects ce where The argument names of the type family must be class parameters. Each class parameter may only be used at most once per associated type, but some may be omitted and they may be in an order other than in the - class head. Hence, the following contrived example is admissible: + class head. Hence, the following contrived example is admissible: class C a b c where type T c a :: * @@ -4882,7 +4882,7 @@ class C a b c where type synonyms are allowed as long as they are fully applied and expand to a type that is admissible - these are the exact same requirements as for data instances. For example, the [e] instance - for Elem is + for Elem is type instance Elem [e] = e @@ -4898,7 +4898,7 @@ type instance Elem [e] = e monotype (i.e., it may not include foralls) and after the expansion of all saturated vanilla type synonyms, no synonyms, except family synonyms may remain. Here are some examples of admissible and illegal type - instances: + instances: type family F a :: * type instance F [Int] = Int -- OK! @@ -4919,7 +4919,7 @@ type instance G Int Char Float = Double -- WRONG: must be two type parameters When an associated family instance is declared within a type class instance, we drop the instance keyword in the family instance. So, the [e] instance - for Elem becomes: + for Elem becomes: instance (Eq (Elem [e])) => Collects ([e]) where type Elem [e] = e @@ -4928,7 +4928,7 @@ instance (Eq (Elem [e])) => Collects ([e]) where The most important point about associated family instances is that the type indexes corresponding to class parameters must be identical to the type given in the instance head; here this is [e], - which coincides with the only class parameter. + which coincides with the only class parameter. Instances for an associated family can only appear as part of instances @@ -4937,7 +4937,7 @@ instance (Eq (Elem [e])) => Collects ([e]) where how methods are handled, declarations of associated types can be omitted in class instances. If an associated family instance is omitted, the corresponding instance type is not inhabited; i.e., only diverging - expressions, such as undefined, can assume the type. + expressions, such as undefined, can assume the type. @@ -4952,11 +4952,11 @@ instance (Eq (Elem [e])) => Collects ([e]) where that is the case, the right-hand sides of the instances must also be syntactically equal under the same substitution. This condition is independent of whether the type family is associated or not, and it is - not only a matter of consistency, but one of type safety. + not only a matter of consistency, but one of type safety. Here are two example to illustrate the condition under which overlap - is permitted. + is permitted. type instance F (a, Int) = [a] type instance F (Int, b) = [b] -- overlap permitted @@ -4973,15 +4973,15 @@ type instance G (Char, a) = [a] -- ILLEGAL overlap, as [Char] /= [Int] In order to guarantee that type inference in the presence of type families decidable, we need to place a number of additional restrictions on the formation of type instance declarations (c.f., - Definition 5 (Relaxed Conditions) of “Type Checking with Open Type Functions”). Instance - declarations have the general form + declarations have the general form type instance F t1 .. tn = t where we require that for every type family application (G s1 - .. sm) in t, + .. sm) in t, s1 .. sm do not contain any type family @@ -4990,7 +4990,7 @@ type instance F t1 .. tn = t the total number of symbols (data type constructors and type variables) in s1 .. sm is strictly smaller than - in t1 .. tn, and + in t1 .. tn, and for every type @@ -5004,13 +5004,13 @@ type instance F t1 .. tn = t of type inference in the presence of, so called, ''loopy equalities'', such as a ~ [F a], where a recursive occurrence of a type variable is underneath a family application and data - constructor application - see the above mentioned paper for details. + constructor application - see the above mentioned paper for details. If the option is passed to the compiler, the above restrictions are not enforced and it is on the programmer to ensure termination of the normalisation of type families - during type inference. + during type inference. @@ -5023,7 +5023,7 @@ type instance F t1 .. tn = t and t2 need to be the same. In the presence of type families, whether two types are equal cannot generally be decided locally. Hence, the contexts of function signatures may include - equality constraints, as in the following example: + equality constraints, as in the following example: sumCollects :: (Collects c1, Collects c2, Elem c1 ~ Elem c2) => c1 -> c2 -> c2 @@ -5032,13 +5032,13 @@ sumCollects :: (Collects c1, Collects c2, Elem c1 ~ Elem c2) => c1 -> c2 -> c2 types t1 and t2 of an equality constraint may be arbitrary monotypes; i.e., they may not contain any quantifiers, independent of whether higher-rank types are otherwise - enabled. + enabled. Equality constraints can also appear in class and instance contexts. The former enable a simple translation of programs using functional dependencies into programs using family synonyms instead. The general - idea is to rewrite a class declaration of the form + idea is to rewrite a class declaration of the form class C a b | a -> b @@ -5053,18 +5053,18 @@ class (F a ~ b) => C a b where essentially giving a name to the functional dependency. In class instances, we define the type instances of FD families in accordance with the class head. Method signatures are not affected by that - process. + process. NB: Equalities in superclass contexts are not fully implemented in - GHC 6.10. + GHC 6.10. Type families and instance declarations - Type families require us to extend the rules for - the form of instance heads, which are given + Type families require us to extend the rules for + the form of instance heads, which are given in . Specifically: @@ -5119,9 +5119,9 @@ a type variable any more! The context of a type signature The flag lifts the Haskell 98 restriction -that the type-class constraints in a type signature must have the +that the type-class constraints in a type signature must have the form (class type-variable) or -(class (type-variable type-variable ...)). +(class (type-variable type-variable ...)). With these type signatures are perfectly OK @@ -5159,8 +5159,8 @@ in GHC, you can give the foralls if you want. See type, or another reachable type variable. -A value with a type that does not obey +type, or another reachable type variable. +A value with a type that does not obey this reachability restriction cannot be used without introducing ambiguity; that is why the type is rejected. Here, for example, is an illegal type: @@ -5239,8 +5239,8 @@ territory free in case we need it later. Implicit parameters - Implicit parameters are implemented as described in -"Implicit parameters: dynamic scoping with static types", + Implicit parameters are implemented as described in +"Implicit parameters: dynamic scoping with static types", J Lewis, MB Shields, E Meijer, J Launchbury, 27th ACM Symposium on Principles of Programming Languages (POPL'00), Boston, Jan 2000. @@ -5267,7 +5267,7 @@ However, by a simple extension to the type class system of Haskell, we can support dynamic binding. Basically, we express the use of a dynamically bound variable as a constraint on the type. These constraints lead to types of the form (?x::t') => t, which says "this -function uses a dynamically-bound variable ?x +function uses a dynamically-bound variable ?x of type t'". For example, the following expresses the type of a sort function, implicitly parameterized by a comparison function named cmp. @@ -5277,11 +5277,11 @@ implicitly parameterized by a comparison function named cmp. The dynamic binding constraints are just a new form of predicate in the type class system. -An implicit parameter occurs in an expression using the special form ?x, +An implicit parameter occurs in an expression using the special form ?x, where x is -any valid identifier (e.g. ord ?x is a valid expression). +any valid identifier (e.g. ord ?x is a valid expression). Use of this construct also introduces a new -dynamic-binding constraint in the type of the expression. +dynamic-binding constraint in the type of the expression. For example, the following definition shows how we can define an implicitly parameterized sort function in terms of an explicitly parameterized sortBy function: @@ -5314,8 +5314,8 @@ propagate them. An implicit-parameter type constraint differs from other type class constraints in the following way: All uses of a particular implicit parameter must have -the same type. This means that the type of (?x, ?x) -is (?x::a) => (a,a), and not +the same type. This means that the type of (?x, ?x) +is (?x::a) => (a,a), and not (?x::a, ?x::b) => (a, b), as would be the case for type class constraints. @@ -5340,7 +5340,7 @@ Implicit-parameter constraints do not cause ambiguity. For example, consider: g s = show (read s) Here, g has an ambiguous type, and is rejected, but f -is fine. The binding for ?x at f's call site is +is fine. The binding for ?x at f's call site is quite unambiguous, and fixes the type a. @@ -5360,8 +5360,8 @@ For example, we define the min function by binding A group of implicit-parameter bindings may occur anywhere a normal group of Haskell -bindings can occur, except at top level. That is, they can occur in a let -(including in a list comprehension, or do-notation, or pattern guards), +bindings can occur, except at top level. That is, they can occur in a let +(including in a list comprehension, or do-notation, or pattern guards), or a where clause. Note the following points: @@ -5369,10 +5369,10 @@ Note the following points: An implicit-parameter binding group must be a collection of simple bindings to implicit-style variables (no function-style bindings, and no type signatures); these bindings are -neither polymorphic or recursive. +neither polymorphic or recursive. -You may not mix implicit-parameter bindings with ordinary bindings in a +You may not mix implicit-parameter bindings with ordinary bindings in a single let expression; use two nested lets instead. (In the case of where you are stuck, since you can't nest where clauses.) @@ -5485,7 +5485,7 @@ problem that monads seem over-kill for certain sorts of problem, notably: Linear implicit parameters are just like ordinary implicit parameters, except that they are "linear"; that is, they cannot be copied, and must be explicitly "split" instead. Linear implicit parameters are -written '%x' instead of '?x'. +written '%x' instead of '?x'. (The '/' in the '%' suggests the split!) @@ -5494,7 +5494,7 @@ For example: import GHC.Exts( Splittable ) data NameSupply = ... - + splitNS :: NameSupply -> (NameSupply, NameSupply) newName :: NameSupply -> Name @@ -5509,7 +5509,7 @@ For example: env' = extend env x x' ...more equations for f... -Notice that the implicit parameter %ns is consumed +Notice that the implicit parameter %ns is consumed once by the call to newName once by the recursive call to f @@ -5543,14 +5543,14 @@ and GHC will infer g :: (Splittable a, %ns :: a) => b -> (b,a,a) -The Splittable class is built into GHC. It's exported by module +The Splittable class is built into GHC. It's exported by module GHC.Exts. Other points: - '?x' and '%x' -are entirely distinct implicit parameters: you + '?x' and '%x' +are entirely distinct implicit parameters: you can use them together and they won't interfere with each other. @@ -5583,7 +5583,7 @@ usually a harmless thing to do, we get: But now the name supply is consumed in three places (the two calls to newName,and the recursive call to f), so -the result is utterly different. Urk! We don't even have +the result is utterly different. Urk! We don't even have the beta rule. @@ -5632,7 +5632,7 @@ semantics of the program depends on whether or not foo has a type signature. Yikes! You may say that this is a good reason to dislike linear implicit parameters -and you'd be right. That is why they are an experimental feature. +and you'd be right. That is why they are an experimental feature. @@ -5645,7 +5645,7 @@ and you'd be right. That is why they are an experimental feature. Haskell infers the kind of each type variable. Sometimes it is nice to be able -to give the kind explicitly as (machine-checked) documentation, +to give the kind explicitly as (machine-checked) documentation, just as it is nice to give a type signature for a function. On some occasions, it is essential to do so. For example, in his paper "Restricted Data Types in Haskell" (Haskell Workshop 1999) John Hughes had to define the data type: @@ -5710,9 +5710,9 @@ The parentheses are required. -GHC's type system supports arbitrary-rank +GHC's type system supports arbitrary-rank explicit universal quantification in -types. +types. For example, all the following types are legal: f1 :: forall a b. a -> b -> a @@ -5846,11 +5846,11 @@ the constructor to suitable values, just as usual. For example, a1 :: T Int a1 = T1 (\xy->x) 3 - + a2, a3 :: Swizzle a2 = MkSwizzle sort a3 = MkSwizzle reverse - + a4 :: MonadT Maybe a4 = let r x = Just x b m k = case m of @@ -5917,7 +5917,7 @@ provides an explicit polymorphic type for x, or GHC's type inference will assume that x's type has no foralls in it. -What does it mean to "provide" an explicit type for x? You can do that by +What does it mean to "provide" an explicit type for x? You can do that by giving a type signature for x directly, using a pattern type signature (), thus: @@ -5953,10 +5953,10 @@ it needs to know. Implicit quantification -GHC performs implicit quantification as follows. At the top level (only) of +GHC performs implicit quantification as follows. At the top level (only) of user-written types, if and only if there is no explicit forall, GHC finds all the type variables mentioned in the type that are not already -in scope, and universally quantifies them. For example, the following pairs are +in scope, and universally quantifies them. For example, the following pairs are equivalent: f :: a -> a @@ -6001,8 +6001,8 @@ for rank-2 types. Impredicative polymorphism -GHC supports impredicative polymorphism, -enabled with . +GHC supports impredicative polymorphism, +enabled with . This means that you can call a polymorphic function at a polymorphic type, and parameterise data structures over polymorphic types. For example: @@ -6018,7 +6018,7 @@ Notice here that the Maybe type is parameterised by the The technical details of this extension are described in the paper Boxy types: type inference for higher-rank types and impredicativity, -which appeared at ICFP 2006. +which appeared at ICFP 2006. @@ -6040,9 +6040,9 @@ The type signature for f brings the type variable a< because of the explicit forall (). The type variables bound by a forall scope over the entire definition of the accompanying value declaration. -In this example, the type variable a scopes over the whole +In this example, the type variable a scopes over the whole definition of f, including over -the type signature for ys. +the type signature for ys. In Haskell 98 it is not possible to declare a type for ys; a major benefit of scoped type variables is that it becomes possible to do so. @@ -6084,7 +6084,7 @@ A lexically scoped type variable can be bound by: In Haskell, a programmer-written type signature is implicitly quantified over its free type variables (Section -4.1.2 +4.1.2 of the Haskell Report). Lexically scoped type variables affect this implicit quantification rules as follows: any type variable that is in scope is not universally @@ -6127,7 +6127,7 @@ over the definition of "g", so "x::a" means "x::forall a. a" by Haskell's usual implicit quantification rules. - The signature gives a type for a function binding or a bare variable binding, + The signature gives a type for a function binding or a bare variable binding, not a pattern binding. For example: @@ -6137,7 +6137,7 @@ For example: f2 :: forall a. [a] -> [a] f2 = \(x:xs) -> xs ++ [ x :: a ] -- OK - f3 :: forall a. [a] -> [a] + f3 :: forall a. [a] -> [a] Just f3 = Just (\(x:xs) -> xs ++ [ x :: a ]) -- Not OK! The binding for f3 is a pattern binding, and so its type signature @@ -6159,8 +6159,8 @@ type variables, in the annotated expression. For example: f = runST ( (op >>= \(x :: STRef s Int) -> g x) :: forall s. ST s Bool ) -Here, the type signature forall s. ST s Bool brings the -type variable s into scope, in the annotated expression +Here, the type signature forall s. ST s Bool brings the +type variable s into scope, in the annotated expression (op >>= \(x :: STRef s Int) -> g x). @@ -6170,7 +6170,7 @@ type variable s into scope, in the annotated expression Pattern type signatures A type signature may occur in any pattern; this is a pattern type -signature. +signature. For example: -- f and g assume that 'a' is already in scope @@ -6197,7 +6197,7 @@ that are already in scope. For example: Here, the pattern signatures for ys and zs are fine, but the one for v is not because b is -not in scope. +not in scope. However, in all patterns other than pattern bindings, a pattern @@ -6220,7 +6220,7 @@ not already in scope; the effect is to bring it into scope, standing for the existentially-bound type variable. -When a pattern type signature binds a type variable in this way, GHC insists that the +When a pattern type signature binds a type variable in this way, GHC insists that the type variable is bound to a rigid, or fully-known, type variable. This means that any user-written type signature always stands for a completely known type. @@ -6230,7 +6230,7 @@ If all this seems a little odd, we think so too. But we must have could not name existentially-bound type variables in subsequent type signatures. -This is (now) the only situation in which a pattern type +This is (now) the only situation in which a pattern type signature is allowed to mention a lexical variable that is not already in scope. For example, both f and g would be @@ -6240,7 +6240,7 @@ illegal if a was not already in scope. - - + Template Haskell Template Haskell allows you to do compile-time meta-programming in -Haskell. +Haskell. The background to the main technical innovations is discussed in " @@ -6414,23 +6414,23 @@ There is a Wiki page about Template Haskell at http://www.haskell.org/haskellwiki/Template_Haskell, and that is the best place to look for further details. -You may also +You may also consult the online -Haskell library reference material +Haskell library reference material (look for module Language.Haskell.TH). -Many changes to the original design are described in +Many changes to the original design are described in Notes on Template Haskell version 2. Not all of these changes are in GHC, however. - The first example from that paper is set out below () -as a worked example to help get you started. + The first example from that paper is set out below () +as a worked example to help get you started. -The documentation here describes the realisation of Template Haskell in GHC. It is not detailed enough to +The documentation here describes the realisation of Template Haskell in GHC. It is not detailed enough to understand Template Haskell; see the Wiki page. @@ -6454,13 +6454,13 @@ Wiki page. of "$" overrides its meaning as an infix operator, just as "M.x" overrides the meaning of "." as an infix operator. If you want the infix operator, put spaces around it. - A splice can occur in place of + A splice can occur in place of an expression; the spliced expression must have type Q Exp an type; the spliced expression must have type Q Typ - a list of top-level declarations; the spliced expression + a list of top-level declarations; the spliced expression must have type Q [Dec] Note that pattern splices are not supported. @@ -6470,8 +6470,8 @@ Wiki page. A expression quotation is written in Oxford brackets, thus: - [| ... |], or [e| ... |], - where the "..." is an expression; + [| ... |], or [e| ... |], + where the "..." is an expression; the quotation has type Q Exp. [d| ... |], where the "..." is a list of top-level declarations; the quotation has type Q [Dec]. @@ -6496,17 +6496,17 @@ Wiki page. 'f has type Name, and names the function f. Similarly 'C has type Name and names the data constructor C. In general 'thing interprets thing in an expression context. - + ''T has type Name, and names the type constructor T. That is, ''thing interprets thing in a type context. - + These Names can be used to construct Template Haskell expressions, patterns, declarations etc. They may also be given as an argument to the reify function. - You may omit the $(...) in a top-level declaration splice. + You may omit the $(...) in a top-level declaration splice. Simply writing an expression (rather than a declaration) implies a splice. For example, you can write module Foo where @@ -6525,7 +6525,7 @@ h z = z-1 This abbreviation makes top-level declaration slices quieter and less intimidating. - + (Compared to the original paper, there are many differences of detail. The syntax for a declaration splice uses "$" not "splice". @@ -6551,7 +6551,7 @@ Pattern splices and quotations are not implemented.) You can only run a function at compile time if it is imported from another module that is not part of a mutually-recursive group of modules - that includes the module currently being compiled. Furthermore, all of the modules of + that includes the module currently being compiled. Furthermore, all of the modules of the mutually-recursive group must be reachable by non-SOURCE imports from the module where the splice is to be run. @@ -6573,11 +6573,11 @@ Pattern splices and quotations are not implemented.) Template Haskell works in any mode (--make, --interactive, - or file-at-a-time). There used to be a restriction to the former two, but that restriction + or file-at-a-time). There used to be a restriction to the former two, but that restriction has been lifted. - + A Template Haskell Worked Example To help you get over the confidence barrier, try out this skeletal worked example. First cut and paste the two modules below into "Main.hs" and "Printf.hs": @@ -6647,7 +6647,7 @@ Hello Using Template Haskell with Profiling profilingwith Template Haskell - + Template Haskell relies on GHC's built-in bytecode compiler and interpreter to run the splice expressions. The bytecode interpreter runs the compiled expression on top of the same runtime on which GHC @@ -6699,11 +6699,11 @@ A quasi-quote has the form [quoter| string |]. -The quoter must be the (unqualified) name of an imported -quoter; it cannot be an arbitrary expression. +The quoter must be the (unqualified) name of an imported +quoter; it cannot be an arbitrary expression. -The quoter cannot be "e", +The quoter cannot be "e", "t", "d", or "p", since those overlap with Template Haskell quotations. @@ -6712,7 +6712,7 @@ There must be no spaces in the token [quoter|. -The quoted string +The quoted string can be arbitrary, and may contain newlines. @@ -6730,7 +6730,7 @@ A quasiquote may appear in place of -A quoter is a value of type Language.Haskell.TH.Quote.QuasiQuoter, +A quoter is a value of type Language.Haskell.TH.Quote.QuasiQuoter, which is defined thus: data QuasiQuoter = QuasiQuoter { quoteExp :: String -> Q Exp, @@ -6923,7 +6923,7 @@ it won't make much sense unless you've read Hughes's paper. | proc apat -> cmd where proc is a new keyword. -The variables of the pattern are bound in the body of the +The variables of the pattern are bound in the body of the proc-expression, which is a new sort of thing called a command. The syntax of commands is as follows: @@ -7326,7 +7326,7 @@ a new form keyword. Although only GHC implements arrow notation directly, there is also a preprocessor -(available from the +(available from the arrows web page) that translates arrow notation into Haskell 98 for use with other Haskell systems. @@ -7371,7 +7371,7 @@ Because the preprocessor targets Haskell (rather than Core), Bang patterns GHC supports an extension of pattern matching called bang -patterns, written !pat. +patterns, written !pat. Bang patterns are under consideration for Haskell Prime. The Haskell @@ -7379,9 +7379,9 @@ prime feature description contains more discussion and examples than the material below. -The key change is the addition of a new rule to the +The key change is the addition of a new rule to the semantics of pattern matching in the Haskell 98 report. -Add new bullet 10, saying: Matching the pattern !pat +Add new bullet 10, saying: Matching the pattern !pat against a value v behaves as follows: if v is bottom, the match diverges @@ -7413,13 +7413,13 @@ Bang patterns can be nested of course: f2 (!x, y) = [x,y] Here, f2 is strict in x but not in -y. +y. A bang only really has an effect if it precedes a variable or wild-card pattern: f3 !(x,y) = [x,y] f4 (x,y) = [x,y] -Here, f3 and f4 are identical; +Here, f3 and f4 are identical; putting a bang before a pattern that forces evaluation anyway does nothing. @@ -7466,7 +7466,7 @@ g5 x = let y = f x in body g6 x = case f x of { y -> body } g7 x = case f x of { !y -> body } -The functions g5 and g6 mean exactly the same thing. +The functions g5 and g6 mean exactly the same thing. But g7 evaluates (f x), binds y to the result, and then evaluates body. @@ -7496,7 +7496,7 @@ prefix notation: The semantics of Haskell pattern matching is described in -Section 3.17.2 of the Haskell Report. To this description add +Section 3.17.2 of the Haskell Report. To this description add one extra item 10, saying: Matching the pattern !pat against a value v behaves as follows: @@ -7512,13 +7512,13 @@ case v of { !pat -> e; _ -> e' } = v `seq` case v of { pat -> e; _ -> e' } -That leaves let expressions, whose translation is given in +That leaves let expressions, whose translation is given in Section 3.12 of the Haskell Report. -In the translation box, first apply -the following transformation: for each pattern pi that is of -form !qi = ei, transform it to (xi,!qi) = ((),ei), and and replace e0 +In the translation box, first apply +the following transformation: for each pattern pi that is of +form !qi = ei, transform it to (xi,!qi) = ((),ei), and and replace e0 by (xi `seq` e0). Then, when none of the left-hand-side patterns have a bang at the top, apply the rules in the existing box. @@ -7646,7 +7646,7 @@ Assertion failures can be caught, see the documentation for the Pragmas all take the form -{-# word ... #-} +{-# word ... #-} where word indicates the type of pragma, and is followed optionally by information specific to that @@ -7656,7 +7656,7 @@ Assertion failures can be caught, see the documentation for the in the following sections; any pragma encountered with an unrecognised word is ignored. The layout rule applies in pragmas, so the closing #-} - should start in a column to the right of the opening {-#. + should start in a column to the right of the opening {-#. Certain pragmas are file-header pragmas: @@ -7666,7 +7666,7 @@ Assertion failures can be caught, see the documentation for the There can be as many file-header pragmas as you please, and they can be - preceded or followed by comments. + preceded or followed by comments. File-header pragmas are read once only, before @@ -7686,7 +7686,7 @@ Assertion failures can be caught, see the documentation for the LANGUAGEpragma pragmaLANGUAGE - The LANGUAGE pragma allows language extensions to be enabled + The LANGUAGE pragma allows language extensions to be enabled in a portable way. It is the intention that all Haskell compilers support the LANGUAGE pragma with the same syntax, although not @@ -7795,7 +7795,7 @@ Assertion failures can be caught, see the documentation for the (a) uses within the defining module, and (b) uses in an export list. The latter reduces spurious complaints within a library - in which one module gathers together and re-exports + in which one module gathers together and re-exports the exports of several others. You can suppress the warnings with the flag @@ -7832,7 +7832,7 @@ key_function :: Int -> String -> (Bool, Double) The major effect of an INLINE pragma is to declare a function's “cost” to be very low. The normal unfolding machinery will then be very keen to - inline it. However, an INLINE pragma for a + inline it. However, an INLINE pragma for a function "f" has a number of other effects: @@ -7846,13 +7846,13 @@ there really isn't any point in inlining key_function to get map (\x -> body) xs In general, GHC only inlines the function if there is some reason (no matter -how slight) to supose that it is useful to do so. +how slight) to suppose that it is useful to do so. -Moreover, GHC will only inline the function if it is fully applied, +Moreover, GHC will only inline the function if it is fully applied, where "fully applied" -means applied to as many arguments as appear (syntactically) +means applied to as many arguments as appear (syntactically) on the LHS of the function definition. For example: @@ -7864,7 +7864,7 @@ comp2 :: (b -> c) -> (a -> b) -> a -> c {-# INLINE comp2 #-} comp2 f g x = f (g x) -The two functions comp1 and comp2 have the +The two functions comp1 and comp2 have the same semantics, but comp1 will be inlined when applied to two arguments, while comp2 requires three. This might make a big difference if you say @@ -7874,14 +7874,14 @@ map (not `comp1` not) xs which will optimise better than the corresponding use of `comp2`. - + It is useful for GHC to optimise the definition of an -INLINE function f just like any other non-INLINE function, +INLINE function f just like any other non-INLINE function, in case the non-inlined version of f is -ultimately called. But we don't want to inline +ultimately called. But we don't want to inline the optimised version of f; -a major reason for INLINE pragmas is to expose functions +a major reason for INLINE pragmas is to expose functions in f's RHS that have rewrite rules, and it's no good if those functions have been optimised away. @@ -7890,7 +7890,7 @@ away. So GHC guarantees to inline precisely the code that you wrote, no more and no less. It does this by capturing a copy of the definition of the function to use for inlining (we call this the "inline-RHS"), which it leaves untouched, -while optimising the ordinarly RHS as usual. For externally-visible functions +while optimising the ordinarily RHS as usual. For externally-visible functions the inline-RHS (not the optimised RHS) is recorded in the interface file. @@ -7925,13 +7925,13 @@ itself, so an INLINE pragma is always ignored. {-# INLINE returnUs #-} - See also the NOINLINE () - and INLINABLE () + See also the NOINLINE () + and INLINABLE () pragmas. Note: the HBC compiler doesn't like INLINE pragmas, so if you want your code to be HBC-compatible you'll have to surround - the pragma with C pre-processor directives + the pragma with C pre-processor directives #ifdef __GLASGOW_HASKELL__...#endif. @@ -7989,7 +7989,7 @@ The principal reason do to so to allow later use of SPECIALISE NOINLINE pragma - + NOINLINE NOTINLINE @@ -8008,7 +8008,7 @@ The principal reason do to so to allow later use of SPECIALISE CONLIKE modifier CONLIKE - An INLINE or NOINLINE pragma may have a CONLIKE modifier, + An INLINE or NOINLINE pragma may have a CONLIKE modifier, which affects matching in RULEs (only). See . @@ -8082,27 +8082,27 @@ happen. ANN pragmas - + GHC offers the ability to annotate various code constructs with additional data by using three pragmas. This data can then be inspected at a later date by using GHC-as-a-library. - + Annotating values - + ANN - + Any expression that has both Typeable and Data instances may be attached to a top-level value binding using an ANN pragma. In particular, this means you can use ANN to annotate data constructors (e.g. Just) as well as normal values (e.g. take). By way of example, to annotate the function foo with the annotation Just "Hello" you would do this: - + {-# ANN foo (Just "Hello") #-} foo = ... - + A number of restrictions apply to use of annotations: @@ -8111,46 +8111,46 @@ foo = ... The expression you are annotating with must have a type with Typeable and Data instances The Template Haskell staging restrictions apply to the expression being annotated with, so for example you cannot run a function from the module being compiled. - - To be precise, the annotation {-# ANN x e #-} is well staged if and only if $(e) would be + + To be precise, the annotation {-# ANN x e #-} is well staged if and only if $(e) would be (disregarding the usual type restrictions of the splice syntax, and the usual restriction on splicing inside a splice - $([|1|]) is fine as an annotation, albeit redundant). - + If you feel strongly that any of these restrictions are too onerous, please give the GHC team a shout. - + However, apart from these restrictions, many things are allowed, including expressions which are not fully evaluated! Annotation expressions will be evaluated by the compiler just like Template Haskell splices are. So, this annotation is fine: - + {-# ANN f SillyAnnotation { foo = (id 10) + $([| 20 |]), bar = 'f } #-} f = ... - + Annotating types - + ANN type ANN - + You can annotate types with the ANN pragma by using the type keyword. For example: - + {-# ANN type Foo (Just "A `Maybe String' annotation") #-} data Foo = ... - + Annotating modules - + ANN module ANN - + You can annotate modules with the ANN pragma by using the module keyword. For example: - + {-# ANN module (Just "A `Maybe String' annotation") #-} @@ -8238,7 +8238,7 @@ data Foo = ... h :: Eq a => a -> a -> a {-# SPECIALISE h :: (Eq a) => [a] -> [a] -> [a] #-} -The last of these examples will generate a +The last of these examples will generate a RULE with a somewhat-complex left-hand side (try it yourself), so it might not fire very well. If you use this kind of specialisation, let us know how well it works. @@ -8247,7 +8247,7 @@ well. If you use this kind of specialisation, let us know how well it works. SPECIALIZE INLINE A SPECIALIZE pragma can optionally be followed with a -INLINE or NOINLINE pragma, optionally +INLINE or NOINLINE pragma, optionally followed by a phase, as described in . The INLINE pragma affects the specialised version of the function (only), and applies even if the function is recursive. The motivating @@ -8282,7 +8282,7 @@ on an ordinarily-recursive function. Generally, you can only give a SPECIALIZE pragma for a function defined in the same module. However if a function f is given an INLINABLE -pragma at its definition site, then it can subequently be specialised by +pragma at its definition site, then it can subsequently be specialised by importing modules (see ). For example @@ -8333,7 +8333,7 @@ pragma can be useful. -Obselete SPECIALIZE syntax +Obsolete SPECIALIZE syntax Note: In earlier versions of GHC, it was possible to provide your own specialised function for a given type: @@ -8358,7 +8358,7 @@ pragma can be useful. Same idea, except for instance declarations. For example: -instance (Eq a) => Eq (Foo a) where { +instance (Eq a) => Eq (Foo a) where { {-# SPECIALIZE instance Eq (Foo [(Int, Bar)]) #-} ... usual stuff ... } @@ -8377,7 +8377,7 @@ of the pragma. UNPACK pragma UNPACK - + The UNPACK indicates to the compiler that it should unpack the contents of a constructor field into the constructor itself, removing a level of indirection. For @@ -8457,7 +8457,7 @@ data S = S {-# UNPACK #-} !Int {-# UNPACK #-} !Int The programmer can specify rewrite rules as part of the source program -(in a pragma). +(in a pragma). Here is an example: @@ -8590,7 +8590,7 @@ declarations. Inside a RULE "forall" is treated as a keyword, regardless of any other flag settings. Furthermore, inside a RULE, the language extension - is automatically enabled; see + is automatically enabled; see . @@ -8598,9 +8598,9 @@ any other flag settings. Furthermore, inside a RULE, the language extension Like other pragmas, RULE pragmas are always checked for scope errors, and -are typechecked. Typechecking means that the LHS and RHS of a rule are typechecked, +are typechecked. Typechecking means that the LHS and RHS of a rule are typechecked, and must have the same type. However, rules are only enabled -if the flag is +if the flag is on (see ). @@ -8623,8 +8623,8 @@ Rules are enabled (that is, used during optimisation) by the flag. This flag is implied by , and may be switched off (as usual) by . -(NB: enabling without -may not do what you expect, though, because without GHC +(NB: enabling without +may not do what you expect, though, because without GHC ignores all optimisation information in interface files; see , .) Note that is an optimisation flag, and @@ -8733,12 +8733,12 @@ to give g y = y Now g is inlined into h, but f's RULE has -no chance to fire. +no chance to fire. If instead GHC had first inlined g into h then there -would have been a better chance that f's RULE might fire. +would have been a better chance that f's RULE might fire. -The way to get predictable behaviour is to use a NOINLINE +The way to get predictable behaviour is to use a NOINLINE pragma, or an INLINE[phase] pragma, on f, to ensure that it is not inlined until its RULEs have had a chance to fire. @@ -8761,12 +8761,12 @@ when this is a good idea, so we provide the CONLIKE pragma to declare it, thus: {-# INLINE[1] CONLIKE f #-} f x = blah -CONLIKE is a modifier to an INLINE or NOINLINE pragam. It specifies that an application +CONLIKE is a modifier to an INLINE or NOINLINE pragma. It specifies that an application of f to one argument (in general, the number of arguments to the left of the '=' sign) should be considered cheap enough to duplicate, if such a duplication would make rule fire. (The name "CONLIKE" is short for "constructor-like", because constructors certainly have such a property.) -The CONLIKE pragam is a modifier to INLINE/NOINLINE because it really only makes sense to match +The CONLIKE pragma is a modifier to INLINE/NOINLINE because it really only makes sense to match f on the LHS of a rule if you are sure that f is not going to be inlined before the rule has a chance to fire. @@ -9041,7 +9041,7 @@ comparison. Use to see the rules that are defined in this module. This includes rules generated by the specialisation pass, but excludes -rules imported from other modules. +rules imported from other modules. @@ -9174,7 +9174,7 @@ allows control over inlining on a per-call-site basis. restrains the strictness analyser. -unsafeCoerce# +unsafeCoerce# allows you to fool the type checker. @@ -9212,7 +9212,7 @@ or the original paper: -José Pedro Magalhães, Atze Dijkstra, Johan Jeuring, and Andres Löh. +Jos� Pedro Magalh�es, Atze Dijkstra, Johan Jeuring, and Andres L�h. A generic deriving mechanism for Haskell. Proceedings of the third ACM Haskell symposium on Haskell @@ -9240,17 +9240,17 @@ that can be used to represent most Haskell datatypes: -- | Unit: used for constructors without arguments data U1 p = U1 - + -- | Constants, additional parameters and recursion of kind * newtype K1 i c p = K1 { unK1 :: c } - + -- | Meta-information (constructor names, etc.) newtype M1 i c f p = M1 { unM1 :: f p } - + -- | Sums: encode choice between constructors infixr 5 :+: data (:+:) f g p = L1 (f p) | R1 (g p) - + -- | Products: encode multiple arguments to constructors infixr 6 :*: data (:*:) f g p = f p :*: g p @@ -9262,7 +9262,7 @@ For example, a user-defined datatype of trees data UserTree a = Node a instance Generic (UserTree a) where -- Representation type - type Rep (UserTree a) = + type Rep (UserTree a) = M1 D D1UserTree ( M1 C C1_0UserTree ( M1 S NoSelector (K1 P a) @@ -9284,10 +9284,10 @@ data C1_1UserTree instance Datatype D1UserTree where datatypeName _ = "UserTree" moduleName _ = "Main" - + instance Constructor C1_0UserTree where conName _ = "Node" - + instance Constructor C1_1UserTree where conName _ = "Leaf" @@ -9343,7 +9343,7 @@ exposed to the user: class Serialize a where put :: a -> [Bin] - + default put :: (Generic a, GSerialize (Rep a)) => a -> [Bit] put = gput . from @@ -9376,7 +9376,7 @@ carried out at let and where bindings. Switching off the dreaded Monomorphism Restriction -Haskell's monomorphism restriction (see +Haskell's monomorphism restriction (see Section 4.5.5 of the Haskell Report) @@ -9391,7 +9391,7 @@ can be completely switched off by As an experimental change, we are exploring the possibility of - making pattern bindings monomorphic; that is, not generalised at all. + making pattern bindings monomorphic; that is, not generalised at all. A pattern binding is a binding whose LHS has no function arguments, and is not a simple variable. For example: -- 1.7.10.4