X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=docs%2Fusers_guide%2Fglasgow_exts.xml;h=f6879febecf3a1c4e660caf00235c09af0871bc1;hb=b7078f351d72f77b0a2b5d1fdf6e050ea0bfef61;hp=c0feb5bff0f803e9588f011dd7a60ae4615b46eb;hpb=aecccd3eae278f4bcc9fc89c9250f889a66d5ded;p=ghc-hetmet.git diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index c0feb5b..f6879fe 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -78,10 +78,11 @@ documentation describes all the libraries that come with GHC. , , , + , , , , - , + , , , , @@ -840,39 +841,77 @@ y) will not be coalesced. + + + +n+k patterns + + + +n+k pattern support is enabled by default. To disable +it, you can use the flag. + + + + The recursive do-notation - The recursive do-notation (also known as mdo-notation) is implemented as described in -A recursive do for Haskell, -by Levent Erkok, John Launchbury, -Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania. -This paper is essential reading for anyone making non-trivial use of mdo-notation, -and we do not repeat it here. - -The do-notation of Haskell does not allow recursive bindings, +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 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, and this extension provides the necessary syntactic support. +the do-notation. The flag provides the necessary syntactic support. -Here is a simple (yet contrived) example: - +Here is a simple (albeit contrived) example: +{-# LANGUAGE DoRec #-} import Control.Monad.Fix -justOnes = mdo xs <- Just (1:xs) - return xs +justOnes = do { rec { xs <- Just (1:xs) } + ; return (map negate xs) } +As you can guess justOnes will evaluate to Just [-1,-1,-1,.... + -As you can guess justOnes will evaluate to Just [1,1,1,.... +The background and motivation for recusrive do-notation is described in +A recursive do for Haskell, +by Levent Erkok, John Launchbury, +Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania. +This paper is essential reading for anyone making non-trivial use of mdo-notation, +and we do not repeat it here. However, note that GHC uses a different syntax than the one +in the paper. + +Details of recursive do-notation + +The recursive do-notation is enabled with the flag or, equivalently, +the LANGUAGE pragma . It introduces the single new keyword "rec", +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 +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 } + ; return (r1 ++ r2) } ; return (r1 ++ r2) } + +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 +really letrec, of course.) + The Control.Monad.Fix library introduces the MonadFix class. Its definition is: @@ -885,30 +924,37 @@ The function mfix dictates how the required recursion operation should be performed. For example, justOnes desugars as follows: -justOnes = mfix (\xs' -> do { xs <- Just (1:xs'); return xs } +justOnes = do { xs <- mfix (\xs' -> do { xs <- Just (1:xs'); return xs }) + ; return (map negate xs) } -For full details of the way in which mdo is typechecked and desugared, see -the paper A recursive do for Haskell. -In particular, GHC implements the segmentation technique described in Section 3.2 of the paper. - - -If recursive bindings are required for a monad, -then that monad must be declared an instance 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). +In general, the statment rec ss +is desugared to the statement + + vs <- mfix (\~vs -> do { ss; return vs }) + +where vs is a tuple of the variables bound by ss. +Moreover, 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.) -Here are some important points in using the recursive-do notation: +Here are some other important points in using the recursive-do notation: -The recursive version of the do-notation uses the keyword mdo (rather -than do). +It is enabled with the flag -XDoRec, which is in turn implied by +-fglasgow-exts. -It is enabled with the flag -XRecursiveDo, which is in turn implied by --fglasgow-exts. +If recursive bindings are required for a monad, +then that monad must be declared an instance 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). @@ -918,20 +964,32 @@ be distinct (Section 3.3 of the paper). -Variables bound by a let statement in an mdo -are monomorphic in the mdo (Section 3.1 of the paper). However -GHC breaks the mdo into segments to enhance polymorphism, -and improve termination (Section 3.2 of the paper). +Similar to let-bindings, GHC implements the segmentation technique described in Section 3.2 of +A recursive do for Haskell, +to break up a single rec statement into a sequence of statements with +rec groups of minimal size. This +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). + + Mdo-notation (deprecated) + + GHC used to support the flag , +which enabled the keyword mdo, precisely as described in +A recursive do for Haskell, +but this is now deprecated. Instead of mdo { Q; e }, write +do { rec Q; e }. + Historical note: The old implementation of the mdo-notation (and most of the existing documents) used the name MonadRec for the class and the corresponding library. This name is not supported by GHC. + @@ -1323,7 +1381,6 @@ module Foo where data T = MkT { x :: Int } ok1 (MkS { x = n }) = n+1 -- Unambiguous - ok2 n = MkT { x = n+1 } -- Unambiguous bad1 k = k { x = 3 } -- Ambiguous @@ -1348,6 +1405,37 @@ if there are other variables in scope with the same name. This reduces the clutter of qualified names when you import two records from different modules that use the same field name. + +Some details: + + +Field disambiguation can be combined with punning (see ). For exampe: + +module Foo where + import M + x=True + ok3 (MkS { x }) = x+1 -- Uses both disambiguation and punning + + + + +With you can use unqualifed +field names even if the correponding selector is only in scope qualified +For example, assuming the same module M as in our earlier example, this is legal: + +module Foo where + import qualified M -- Note qualified + + ok4 (M.MkS { x = n }) = n+1 -- Unambiguous + +Since the constructore 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.) + + + + @@ -1384,16 +1472,9 @@ a for the same name a. -Note that puns and other patterns can be mixed in the same record: - -data C = C {a :: Int, b :: Int} -f (C {a, b = 4}) = a - -and that puns can be used wherever record patterns occur (e.g. in -let bindings or at the top-level). - - - +Note that: + + Record punning can also be used in an expression, writing, for example, let a = 1 in C {a} @@ -1402,12 +1483,41 @@ instead of let a = 1 in C {a = a} - -Note that this expansion is purely syntactic, so the record pun +The expansion is purely syntactic, so the expanded right-hand side expression refers to the nearest enclosing variable that is spelled the same as the field name. + + + +Puns and other patterns can be mixed in the same record: + +data C = C {a :: Int, b :: Int} +f (C {a, b = 4}) = a + + + + +Puns can be used wherever record patterns occur (e.g. in +let bindings or at the top-level). + + + +A pun on a qualified field name is expanded by stripping off the module qualifier. +For example: + +f (C {M.a}) = a + +means + +f (M.C {M.a = a}) = a + +(This is useful if the field selector a for constructor M.C +is only in scope in qualified form.) + + + @@ -1418,6 +1528,7 @@ same as the field name. Record wildcards are enabled by the flag -XRecordWildCards. +This flag implies -XDisambiguateRecordFields. @@ -1430,7 +1541,7 @@ f (C {a = 1, b = b, c = c, d = d}) = b + c + d -Record wildcard syntax permits a (..) in a record +Record wildcard syntax permits a ".." in a record pattern, where each elided field f is replaced by the pattern f = f. For example, the above pattern can be written as @@ -1440,7 +1551,10 @@ f (C {a = 1, ..}) = b + c + d -Note that wildcards can be mixed with other patterns, including puns +More details: + + +Wildcards can be mixed with other patterns, including puns (); for example, in a pattern C {a = 1, b, ..}). Additionally, record wildcards can be used wherever record patterns occur, including in let @@ -1450,24 +1564,38 @@ C {a = 1, ..} = e defines b, c, and d. - + - + Record wildcards can also be used in expressions, writing, for example, - let {a = 1; b = 2; c = 3; d = 4} in C {..} - in place of - let {a = 1; b = 2; c = 3; d = 4} in C {a=a, b=b, c=c, d=d} - -Note that this expansion is purely syntactic, so the record wildcard +The expansion is purely syntactic, so the record wildcard expression refers to the nearest enclosing variables that are spelled the same as the omitted field names. + + + +The ".." expands to the missing +in-scope record fields, where "in scope" +includes both unqualified and qualified-only. +Any fields that are not in scope are not filled in. For example + +module M where + data R = R { a,b,c :: Int } +module X where + import qualified M( R(a,b) ) + f a b = R { .. } + +The {..} expands to {M.a=a,M.b=b}, +omitting c since it is not in scope at all. + + @@ -1581,7 +1709,8 @@ The following syntax is stolen: forall - Stolen (in types) by: , + Stolen (in types) by: , and hence by + , , , , @@ -3074,7 +3203,8 @@ All the extensions are enabled by the flag. Multi-parameter type classes -Multi-parameter type classes are permitted. For example: +Multi-parameter type classes are permitted, with flag . +For example: @@ -3086,13 +3216,17 @@ Multi-parameter type classes are permitted. For example: - + The superclasses of a class declaration -There are no restrictions on the context in a class declaration -(which introduces superclasses), except that the class hierarchy must -be acyclic. So these class declarations are OK: +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 +() +lifts this restriction, +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: @@ -3174,7 +3308,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 -mentioned in ) +mentioned in ) from the free variables of each method type. For example: @@ -4625,10 +4759,30 @@ might be in another module, or even in a module that is not yet written. Other type system extensions - -Type signatures +Explicit universal quantification (forall) + +Haskell type signatures are implicitly quantified. When the language option +is used, the keyword forall +allows us to say exactly what this means. For example: + + + + g :: b -> b + +means this: + + g :: forall b. (b -> b) + +The two are treated identically. + + +Of course forall becomes a keyword; you can't use forall as +a type variable any more! + + + -The context of a type signature +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 @@ -4640,7 +4794,11 @@ these type signatures are perfectly OK g :: Eq [a] => ... g :: Ord (T a ()) => ... +The flag also lifts the corresponding +restriction on class declarations () and instance declarations +(). + GHC imposes the following restrictions on the constraints in a type signature. Consider the type: @@ -4653,7 +4811,7 @@ Consider the type: language omits them; in Haskell 98, all the free type variables of an explicit source-language type signature are universally quantified, except for the class type variables in a class declaration. However, -in GHC, you can give the foralls if you want. See ). +in GHC, you can give the foralls if you want. See ). @@ -4741,9 +4899,6 @@ territory free in case we need it later. - - - @@ -5221,22 +5376,7 @@ The parentheses are required. -Haskell type signatures are implicitly quantified. The new keyword forall -allows us to say exactly what this means. For example: - - - - g :: b -> b - -means this: - - g :: forall b. (b -> b) - -The two are treated identically. - - - -However, GHC's type system supports arbitrary-rank +GHC's type system supports arbitrary-rank explicit universal quantification in types. For example, all the following types are legal: @@ -5291,8 +5431,6 @@ field type signatures. -Of course forall becomes a keyword; you can't use forall as -a type variable any more! @@ -5907,6 +6045,21 @@ pattern binding must have the same context. For example, this is fine: + +Monomorphic local bindings + +We are actively thinking of simplifying GHC's type system, by not generalising local bindings. +The rationale is described in the paper +Let should not be generalised. + + +The experimental new behaviour is enabled by the flag . The effect is +that local (that is, non-top-level) bindings without a type signature are not generalised at all. You can +think of it as an extreme (but much more predictable) version of the Monomorphism Restriction. +If you supply a type signature, then the flag has no effect. + + + @@ -5973,12 +6126,11 @@ Wiki page. have type Q Exp an type; the spliced expression must have type Q Typ - a list of top-level declarations; the spliced expression must have type Q [Dec] + a list of top-level declarations; the spliced expression + must have type Q [Dec] - Inside a splice you can can only call functions defined in imported modules, - not functions defined elsewhere in the same module. - + not functions defined elsewhere in the same module. A expression quotation is written in Oxford brackets, thus: @@ -5995,7 +6147,7 @@ Wiki page. A quasi-quotation can appear in either a pattern context or an expression context and is also written in Oxford brackets: - [:varid| ... |], + [$varid| ... |], where the "..." is an arbitrary string; a full description of the quasi-quotation facility is given in . @@ -6016,6 +6168,25 @@ Wiki page. + 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 +import Bar + +f x = x + +$(deriveStuff 'f) -- Uses the $(...) notation + +g y = y+1 + +deriveStuff 'g -- Omits the $(...) + +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. @@ -7180,24 +7351,11 @@ Assertion failures can be caught, see the documentation for the INCLUDE pragma - The INCLUDE pragma is for specifying the names - of C header files that should be #include'd into - the C source code generated by the compiler for the current module (if - compiling via C). For example: - - -{-# INCLUDE "foo.h" #-} -{-# INCLUDE <stdio.h> #-} - - INCLUDE is a file-header pragma (see ). - - An INCLUDE pragma is the preferred alternative - to the option (), because the - INCLUDE pragma is understood by other - compilers. Yet another alternative is to add the include file to each - foreign import declaration in your code, but we - don't recommend using this approach with GHC. + The INCLUDE used to be necessary for + specifying header files to be included when using the FFI and + compiling via C. It is no longer required for GHC, but is + accepted (and ignored) for compatibility with other + compilers.