X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=docs%2Fusers_guide%2Fglasgow_exts.xml;h=b7d43c9f3fd80a77247c11acec0527835e47182b;hp=f6879febecf3a1c4e660caf00235c09af0871bc1;hb=661c97c65e5fa47177502e592bb763f752b487ac;hpb=b7078f351d72f77b0a2b5d1fdf6e050ea0bfef61 diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index f6879fe..b7d43c9 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -110,7 +110,7 @@ While you really can use this stuff to write fast code, All these primitive data types and operations are exported by the library GHC.Prim, for which there is -detailed online documentation. +detailed online documentation. (This documentation is generated from the file compiler/prelude/primops.txt.pp.) @@ -351,6 +351,15 @@ Indeed, the bindings can even be recursive. Name + + + :: @@ -391,14 +400,52 @@ Indeed, the bindings can even be recursive. LEFTWARDS ARROW + + + + -< + + 0x2919 + LEFTWARDS ARROW-TAIL + + + + + + >- + + 0x291A + RIGHTWARDS ARROW-TAIL + + + + + + -<< + + 0x291B + LEFTWARDS DOUBLE ARROW-TAIL + + + - .. - - 0x22EF - MIDLINE HORIZONTAL ELLIPSIS + >>- + + 0x291C + RIGHTWARDS DOUBLE ARROW-TAIL + + + + * + + 0x2605 + BLACK STAR + + + @@ -856,7 +903,7 @@ it, you can use the flag. - + The recursive do-notation @@ -871,21 +918,19 @@ the do-notation. The flag provides the necessary synta Here is a simple (albeit contrived) example: {-# LANGUAGE DoRec #-} -import Control.Monad.Fix - justOnes = do { rec { xs <- Just (1:xs) } ; return (map negate xs) } As you can guess justOnes will evaluate to Just [-1,-1,-1,.... -The background and motivation for recusrive do-notation is described in +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. -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. +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. @@ -913,30 +958,54 @@ while rec is monadic. (In Haskell let is really letrec, of course.) -The Control.Monad.Fix library introduces the MonadFix class. Its definition is: - +The static and dynamic semantics of rec can be described as follows: + + +First, +similar to let-bindings, the rec is broken into +minimal recursive groups, a process known as segmentation. +For example: -class Monad m => MonadFix m where - mfix :: (a -> m a) -> m a +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 - -The function mfix -dictates how the required recursion operation should be performed. For example, -justOnes desugars as follows: +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 +describes, also has a semantic effect (unless the monad satisfies the right-shrinking law). + + +Then each resulting rec is desugared, using a call to Control.Monad.Fix.mfix. +For example, the rec group in the preceding example is desugared like this: -justOnes = do { xs <- mfix (\xs' -> do { xs <- Just (1:xs'); return xs }) - ; return (map negate xs) } +rec { b <- f a c ===> (b,c) <- mfix (\~(b,c) -> do { b <- f a c + ; c <- f b a } ; c <- f b a + ; return (b,c) }) In general, the statment rec ss is desugared to the statement - vs <- mfix (\~vs -> do { ss; return vs }) +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 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.) +following the rec, because they are bound by a lambda. + + +The mfix function is defined in the MonadFix +class, in Control.Monad.Fix, thus: + +class Monad m => MonadFix m where + mfix :: (a -> m a) -> m a + + + + Here are some other important points in using the recursive-do notation: @@ -958,28 +1027,23 @@ for Haskell's internal state monad (strict and lazy, respectively). -Unlike ordinary do-notation, but like let and where bindings, -name shadowing is not allowed; that is, all the names bound in a single mdo must +Like let and where bindings, +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). - -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). +It supports rebindable syntax (see ). - Mdo-notation (deprecated) + Mdo-notation (deprecated) - GHC used to support the flag , + GHC used to support the flag , which enabled the keyword mdo, precisely as described in -A recursive do for Haskell, +A recursive do for Haskell, but this is now deprecated. Instead of mdo { Q; e }, write do { rec Q; e }. @@ -1173,7 +1237,7 @@ 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 - GHC.Exts. This + GHC.Exts. This is the form of the group statement that we made use of in the opening example. @@ -1625,7 +1689,7 @@ and the fixity declaration applies wherever the binding is in scope. For example, in a let, it applies in the right-hand sides of other let-bindings and the body of the letC. Or, in recursive do -expressions (), the local fixity +expressions (), the local fixity declarations of a let statement scope over other statements in the group, just as the bound name does. @@ -3933,6 +3997,51 @@ of the instance declaration, thus: (You need to do this.) +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: + +{-# LANGUAGE OverlappingInstances #-} +module Help where + + class MyShow a where + myshow :: a -> String + + instance MyShow a => MyShow [a] where + myshow xs = concatMap myshow xs + + showHelp :: MyShow a => [a] -> String + showHelp xs = myshow xs + +{-# LANGUAGE FlexibleInstances, OverlappingInstances #-} +module Main where + import Help + + data T = MkT + + instance MyShow T where + myshow x = "Used generic instance" + + instance MyShow [T] where + myshow xs = "Used more specific instance" + + main = do { print (myshow [MkT]); print (showHelp [MkT]) } + +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, +the program prints + + "Used more specific instance" + "Used generic instance" + +(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 instance declaration itself, controlled by the presence or otherwise of the @@ -5667,6 +5776,9 @@ for rank-2 types. Impredicative polymorphism +NOTE: the impredicative-polymorphism feature is deprecated in GHC 6.12, and +will be removed or replaced in GHC 6.14. + GHC supports impredicative polymorphism, enabled with . This means @@ -6129,25 +6241,29 @@ Wiki page. a list of top-level declarations; the spliced expression must have type Q [Dec] + Note that pattern splices are not supported. 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: - [| ... |], 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]. [t| ... |], where the "..." is a type; - the quotation has type Q Typ. + the quotation has type Q Type. + [p| ... |], where the "..." is a pattern; + the quotation has type Q Pat. 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 . @@ -6353,19 +6469,67 @@ several examples are documented in Nice to be Quoted: Quasiquoting for Haskell" (Proc Haskell Workshop 2007). The example below shows how to write a quasiquoter for a simple expression language. - -In the example, the quasiquoter expr is bound to a value of -type Language.Haskell.TH.Quote.QuasiQuoter which contains two -functions for quoting expressions and patterns, respectively. The first argument -to each quoter is the (arbitrary) string enclosed in the Oxford brackets. The -context of the quasi-quotation statement determines which of the two parsers is -called: if the quasi-quotation occurs in an expression context, the expression -parser is called, and if it occurs in a pattern context, the pattern parser is -called. +Here are the salient features + + +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 cannot be "e", +"t", "d", or "p", since +those overlap with Template Haskell quotations. + + +There must be no spaces in the token +[quoter|. + + +The quoted string +can be arbitrary, and may contain newlines. + + + + + +A quasiquote may appear in place of + +An expression +A pattern +A type +A top-level declaration + +(Only the first two are described in the paper.) + + +A quoter is a value of type Language.Haskell.TH.Quote.QuasiQuoter, +which is defined thus: + +data QuasiQuoter = QuasiQuoter { quoteExp :: String -> Q Exp, + quotePat :: String -> Q Pat, + quoteType :: String -> Q Type, + quoteDec :: String -> Q [Dec] } + +That is, a quoter is a tuple of four parsers, one for each of the contexts +in which a quasi-quote can occur. + + +A quasi-quote is expanded by applying the appropriate parser to the string +enclosed by the Oxford brackets. The context of the quasi-quote (expression, pattern, +type, declaration) determines which of the parsers is called. + + + -Note that in the example we make use of an antiquoted +The example below shows quasi-quotation in action. The quoter expr +is bound to a value of type QuasiQuoter defined in module Expr. +The example makes use of an antiquoted variable n, indicated by the syntax 'int:n (this syntax for anti-quotation was defined by the parser's author, not by GHC). This binds n to the @@ -6377,12 +6541,6 @@ an expression parser that returns a value of type Q Exp and a pattern parser that returns a value of type Q Pat. -In general, a quasi-quote has the form -[$quoter| string |]. -The quoter must be the name of an imported quoter; it -cannot be an arbitrary expression. The quoted string -can be arbitrary, and may contain newlines. - Quasiquoters must obey the same stage restrictions as Template Haskell, e.g., in the example, expr cannot be defined @@ -6390,22 +6548,21 @@ in Main.hs where it is used, but must be imported. - -{- Main.hs -} +{- ------------- file Main.hs --------------- -} module Main where import Expr main :: IO () -main = do { print $ eval [$expr|1 + 2|] +main = do { print $ eval [expr|1 + 2|] ; case IntExpr 1 of - { [$expr|'int:n|] -> print n + { [expr|'int:n|] -> print n ; _ -> return () } } -{- Expr.hs -} +{- ------------- file Expr.hs --------------- -} module Expr where import qualified Language.Haskell.TH as TH @@ -6432,7 +6589,7 @@ eval (BinopExpr op x y) = (opToFun op) (eval x) (eval y) opToFun MulOp = (*) opToFun DivOp = div -expr = QuasiQuoter parseExprExp parseExprPat +expr = QuasiQuoter { quoteExp = parseExprExp, quotePat = parseExprPat } -- Parse an Expr, returning its representation as -- either a Q Exp or a Q Pat. See the referenced paper @@ -6448,19 +6605,18 @@ parseExprPat ... Now run the compiler: - $ ghc --make -XQuasiQuotes Main.hs -o main + -Run "main" and here is your output: - +Run "main" and here is your output: $ ./main 3 1 - + @@ -6533,7 +6689,7 @@ The arrows web page at With the flag, GHC supports the arrow notation described in the second of these papers, translating it using combinators from the -Control.Arrow +Control.Arrow module. What follows is a brief introduction to the notation; it won't make much sense unless you've read Hughes's paper. @@ -6648,7 +6804,7 @@ the arrow f, and matches its output against y. In the next line, the output is discarded. The arrow returnA is defined in the -Control.Arrow +Control.Arrow module as arr id. The above example is treated as an abbreviation for @@ -6665,7 +6821,7 @@ arr (\ x -> (x, x)) >>> Note that variables not used later in the composition are projected out. After simplification using rewrite rules (see ) defined in the -Control.Arrow +Control.Arrow module, this reduces to arr (\ x -> (x+1, x)) >>> @@ -6961,7 +7117,7 @@ additional restrictions: The module must import -Control.Arrow. +Control.Arrow. @@ -7325,7 +7481,7 @@ Assertion failures can be caught, see the documentation for the Any extension from the Extension type defined in Language.Haskell.Extension + url="&libraryCabalLocation;/Language-Haskell-Extension.html">Language.Haskell.Extension may be used. GHC will report an error if any of the requested extensions are not supported. @@ -7521,6 +7677,14 @@ itself, so an INLINE pragma is always ignored. portable). + + CONLIKE modifier + CONLIKE + An INLINE or NOINLINE pragma may have a CONLIKE modifier, + which affects matching in RULEs (only). See . + + + Phase control @@ -8156,18 +8320,24 @@ not be substituted, and the rule would not fire. - + + + + + + + +How rules interact with INLINE/NOINLINE and CONLIKE pragmas Ordinary inlining happens at the same time as rule rewriting, which may lead to unexpected results. Consider this (artificial) example f x = x -{-# RULES "f" f True = False #-} - g y = f y - h z = g True + +{-# RULES "f" f True = False #-} Since f's right-hand side is small, it is inlined into g, to give @@ -8181,14 +8351,37 @@ would have been a better chance that f's RULE might fire. The way to get predictable behaviour is to use a NOINLINE -pragma on f, to ensure +pragma, or an INLINE[phase] pragma, on f, to ensure that it is not inlined until its RULEs have had a chance to fire. - - - + +GHC is very cautious about duplicating work. For example, consider + +f k z xs = let xs = build g + in ...(foldr k z xs)...sum xs... +{-# RULES "foldr/build" forall k z g. foldr k z (build g) = g k z #-} + +Since xs is used twice, GHC does not fire the foldr/build rule. Rightly +so, because it might take a lot of work to compute xs, which would be +duplicated if the rule fired. + + +Sometimes, however, this approach is over-cautious, and we do want the +rule to fire, even though doing so would duplicate redex. There is no way that GHC can work out +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 +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 +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. - @@ -8448,8 +8641,8 @@ comparison. - -Controlling what's going on + +Controlling what's going on in rewrite rules @@ -8457,18 +8650,28 @@ comparison. - Use to see what transformation rules GHC is using. +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. - + Use to see what rules are being fired. If you add you get a more detailed listing. + + + Use to see in great detail what rules are being fired. +If you add you get a still more detailed listing. + + + The definition of (say) build in GHC/Base.lhs looks like this: @@ -8569,7 +8772,7 @@ r) -> Special built-in functions GHC has a few built-in functions with special behaviour. These are now described in the module GHC.Prim +url="&libraryGhcPrimLocation;/GHC-Prim.html">GHC.Prim in the library documentation.