X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=docs%2Fusers_guide%2Fglasgow_exts.xml;h=54a483323026bf95756a06292b5f921de2779e30;hp=5bcaa1b5d73012efbe927a3d3f5a6ef3dddd862f;hb=478e69b303eb2e653a2ebf5c888b5efdfef1fb9d;hpb=03bf7b49daf1778346ecde84eca30945a079e8ae diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 5bcaa1b..54a4833 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -3,8 +3,9 @@ language, GHC extensions, GHC As with all known Haskell systems, GHC implements some extensions to -the language. They are all enabled by options; by default GHC -understands only plain Haskell 98. +the language. They can all be enabled or disabled by commandline flags +or language pragmas. By default GHC understands the most recent Haskell +version it supports, plus a handful of extensions. @@ -39,8 +40,7 @@ documentation describes all the libraries that come with GHC. The language option flags control what variation of the language are - permitted. Leaving out all of them gives you standard Haskell - 98. + permitted. Language options can be controlled in two ways: @@ -56,38 +56,7 @@ documentation describes all the libraries that come with GHC. The flag is equivalent to enabling the following extensions: - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - , - . + &what_glasgow_exts_does; Enabling these options is the only effect of . We are trying to move away from this portmanteau flag, @@ -110,7 +79,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 +320,15 @@ Indeed, the bindings can even be recursive. Name + + + :: @@ -391,14 +369,52 @@ Indeed, the bindings can even be recursive. LEFTWARDS ARROW + + + + -< + + 0x2919 + LEFTWARDS ARROW-TAIL + + + + + + >- + + 0x291A + RIGHTWARDS ARROW-TAIL + + + + + + -<< + + 0x291B + LEFTWARDS DOUBLE ARROW-TAIL + + + + + + >>- + + 0x291C + RIGHTWARDS DOUBLE ARROW-TAIL + + + - .. - - 0x22EF - MIDLINE HORIZONTAL ELLIPSIS + * + + 0x2605 + BLACK STAR + @@ -423,10 +439,10 @@ Indeed, the bindings can even be recursive. 'x'# has type Char# "foo"# has type Addr# 3# has type Int#. In general, - any Haskell 98 integer lexeme followed by a # is an Int# literal, e.g. + any Haskell integer lexeme followed by a # is an Int# literal, e.g. -0x3A# as well as 32#. 3## has type Word#. In general, - any non-negative Haskell 98 integer lexeme followed by ## + any non-negative Haskell integer lexeme followed by ## is a Word#. 3.2# has type Float#. 3.2## has type Double# @@ -434,43 +450,6 @@ Indeed, the bindings can even be recursive. - - New qualified operator syntax - - A new syntax for referencing qualified operators is - planned to be introduced by Haskell', and is enabled in GHC - with - the - option. In the new syntax, the prefix form of a qualified - operator is - written module.(symbol) - (in Haskell 98 this would - be (module.symbol)), - and the infix form is - written `module.(symbol)` - (in Haskell 98 this would - be `module.symbol`. - For example: - - add x y = Prelude.(+) x y - subtract y = (`Prelude.(-)` y) - - The new form of qualified operators is intended to regularise - the syntax by eliminating odd cases - like Prelude... For example, - when NewQualifiedOperators is on, it is possible to - write the enumerated sequence [Monday..] - without spaces, whereas in Haskell 98 this would be a - reference to the operator ‘.‘ - from module Monday. - - When is on, the old Haskell - 98 syntax for qualified operators is not accepted, so this - option may cause existing Haskell 98 code to break. - - - - @@ -771,10 +750,8 @@ let {(x -> y) = e1 ; (y -> x) = e2 } in x -(We may lift this -restriction in the future; the only cost is that type checking patterns -would get a little more complicated.) - +(For some amplification on this design choice see +Trac #4061.) @@ -856,7 +833,7 @@ it, you can use the flag. - + The recursive do-notation @@ -877,7 +854,7 @@ justOnes = do { rec { xs <- Just (1: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. @@ -992,9 +969,9 @@ 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, but this is now deprecated. Instead of mdo { Q; e }, write @@ -1190,7 +1167,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. @@ -1224,6 +1201,168 @@ output = [ x + + + + Monad comprehensions + monad comprehensions + + + Monad comprehesions generalise the list comprehension notation to work + for any monad. + + + Monad comprehensions support: + + + + + Bindings: + + + +[ x + y | x <- Just 1, y <- Just 2 ] + + + + Bindings are translated with the (>>=) and + return functions to the usual do-notation: + + + +do x <- Just 1 + y <- Just 2 + return (x+y) + + + + + + Guards: + + + +[ x | x <- [1..10], x <= 5 ] + + + + Guards are translated with the guard function, + which requires a MonadPlus instance: + + + +do x <- [1..10] + guard (x <= 5) + return x + + + + + + Transform statements (as with -XTransformListComp): + + + +[ x+y | x <- [1..10], y <- [1..x], then take 2 ] + + + + This translates to: + + + +do (x,y) <- take 2 (do x <- [1..10] + y <- [1..x] + return (x,y)) + return (x+y) + + + + + + Group statements (as with -XTransformListComp): + + + +[ x | x <- [1,1,2,2,3], then group by x ] +[ x | x <- [1,1,2,2,3], then group by x using GHC.Exts.groupWith ] +[ x | x <- [1,1,2,2,3], then group using myGroup ] + + + + The basic then group by e statement is + translated using the mgroupWith function, which + requires a MonadGroup instance, defined in + Control.Monad.Group: + + + +do x <- mgroupWith (do x <- [1,1,2,2,3] + return x) + return x + + + + Note that the type of x is changed by the + grouping statement. + + + + The grouping function can also be defined with the + using keyword. + + + + + + Parallel statements (as with -XParallelListComp): + + + +[ (x+y) | x <- [1..10] + | y <- [11..20] + ] + + + + Parallel statements are translated using the + mzip function, which requires a + MonadZip instance defined in + Control.Monad.Zip: + + + +do (x,y) <- mzip (do x <- [1..10] + return x) + (do y <- [11..20] + return y) + return (x+y) + + + + + + + All these features are enabled by default if the + MonadComprehensions extension is enabled. The types + and more detailed examples on how to use comprehensions are explained + in the previous chapters and . In general you just have + to replace the type [a] with the type + Monad m => m a for monad comprehensions. + + + + Note: Even though most of these examples are using the list monad, + monad comprehensions work for any monad. + The base package offers all necessary instances for + lists, which make MonadComprehensions backward + compatible to built-in, transform and parallel list comprehensions. + + + + @@ -1244,8 +1383,8 @@ output = [ x hierarchy. It completely defeats that purpose if the literal "1" means "Prelude.fromInteger 1", which is what the Haskell Report specifies. - So the - flag also causes + So the + flag causes the following pieces of built-in syntax to refer to whatever is in scope, not the Prelude versions: @@ -1277,6 +1416,11 @@ output = [ x + Conditionals (e.g. "if e1 then e2 else e3") + means "ifThenElse e1 e2 e3". However case expressions are unaffected. + + + "Do" notation is translated using whatever functions (>>=), (>>), and fail, @@ -1296,6 +1440,9 @@ output = [ x to use this, ask! + implies . + + 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 static semantics of the literal 368 @@ -1642,7 +1789,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. @@ -1849,6 +1996,26 @@ not * then an explicit kind annotation must be used Nevertheless, they can be useful when defining "phantom types". + +Data type contexts + +Haskell allows datatypes to be given contexts, e.g. + + +data Eq a => Set a = NilSet | ConsSet a (Set a) + + +give constructors with types: + + +NilSet :: Set a +ConsSet :: Eq a => a -> Set a -> Set a + + +In GHC this feature is an extension called +DatatypeContexts, and on by default. + + Infix type constructors, classes, and type variables @@ -2429,7 +2596,8 @@ declarations. Define your own instances! Declaring data types with explicit constructor signatures -GHC allows you to declare an algebraic data type by +When the GADTSyntax extension is enabled, +GHC allows you to declare an algebraic data type by giving the type signatures of constructors explicitly. For example: data Maybe a where @@ -3950,22 +4118,70 @@ 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 and flags when that module is -being defined. Neither flag is required in a module that imports and uses the -instance declaration. Specifically, during the lookup process: +being defined. Specifically, during the lookup process: -An instance declaration is ignored during the lookup process if (a) a more specific -match is found, and (b) the instance declaration was compiled with -. The flag setting for the -more-specific instance does not matter. +If the constraint being looked up matches two instance declarations IA and IB, +and + +IB is a substitution instance of IA (but not vice versa); +that is, IB is strictly more specific than IA +either IA or IB was compiled with + +then the less-specific instance IA is ignored. Suppose an instance declaration does not match the constraint being looked up, but -does unify with it, so that it might match when the constraint is further +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?" @@ -3975,18 +4191,6 @@ 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. - -If an instance declaration is compiled without -, -then that instance can never be overlapped. This could perhaps be -inconvenient. Perhaps the rule should instead say that the -overlapping instance declaration should be compiled in -this way, rather than the overlapped one. Perhaps overlap -at a usage site should be permitted regardless of how the instance declarations -are compiled, if the flag is -used at the usage site. (Mind you, the exact usage site can occasionally be -hard to pin down.) We are interested to receive feedback on these points. - The flag implies the flag, but not vice versa. @@ -5684,9 +5888,6 @@ 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 @@ -5809,7 +6010,7 @@ signature is explicit. For example: g (x:xs) = xs ++ [ x :: a ] This program will be rejected, because "a" does not scope -over the definition of "f", so "x::a" +over the definition of "g", so "x::a" means "x::forall a. a" by Haskell's usual implicit quantification rules. @@ -5845,7 +6046,7 @@ 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 a. ST s Bool brings the +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). @@ -6149,25 +6350,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 . @@ -6373,19 +6578,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 @@ -6397,12 +6650,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 @@ -6410,22 +6657,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 @@ -6452,7 +6698,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 @@ -6468,19 +6714,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 - + @@ -6553,7 +6798,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. @@ -6668,7 +6913,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 @@ -6685,7 +6930,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)) >>> @@ -6981,7 +7226,7 @@ additional restrictions: The module must import -Control.Arrow. +Control.Arrow. @@ -7069,16 +7314,23 @@ forces evaluation anyway does nothing. There is one (apparent) exception to this general rule that a bang only makes a difference when it precedes a variable or wild-card: a bang at the top level of a let or where -binding makes the binding strict, regardless of the pattern. For example: +binding makes the binding strict, regardless of the pattern. +(We say "apparent" exception because the Right Way to think of it is that the bang +at the top of a binding is not part of the pattern; rather it +is part of the syntax of the binding, +creating a "bang-pattern binding".) +For example: let ![x,y] = e in b -is a strict binding: operationally, it evaluates e, matches -it against the pattern [x,y], and then evaluates b. -(We say "apparent" exception because the Right Way to think of it is that the bang -at the top of a binding is not part of the pattern; rather it -is part of the syntax of the binding.) -Nested bangs in a pattern binding behave uniformly with all other forms of +is a bang-pattern binding. Operationally, it behaves just like a case expression: + +case e of [x,y] -> b + +Like a case expression, a bang-pattern binding must be non-recursive, and +is monomorphic. + +However, nested bangs in a pattern binding behave uniformly with all other forms of pattern matching. For example let (!x,[y]) = e in b @@ -7341,11 +7593,11 @@ Assertion failures can be caught, see the documentation for the A list of all supported language extensions can be obtained by invoking - ghc --supported-languages (see ). + ghc --supported-extensions (see ). 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. @@ -7471,21 +7723,68 @@ key_function :: Int -> String -> (Bool, Double) function "f" has a number of other effects: -No functions are inlined into f. Otherwise -GHC might inline a big function into f's right hand side, -making f big; and then inline f blindly. +While GHC is keen to inline the function, it does not do so +blindly. For example, if you write + +map key_function xs + +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. + -The float-in, float-out, and common-sub-expression transformations are not -applied to the body of f. +Moreover, GHC will only inline the function if it is fully applied, +where "fully applied" +means applied to as many arguments as appear (syntactically) +on the LHS of the function +definition. For example: + +comp1 :: (b -> c) -> (a -> b) -> a -> c +{-# INLINE comp1 #-} +comp1 f g = \x -> f (g x) + +comp2 :: (b -> c) -> (a -> b) -> a -> c +{-# INLINE comp2 #-} +comp2 f g x = f (g x) + +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 + +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, +in case the non-inlined version of f is +ultimately called. But we don't want to inline +the optimised version +of f; +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. + + +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 +the inline-RHS (not the optimised RHS) is recorded in the interface file. An INLINE function is not worker/wrappered by strictness analysis. It's going to be inlined wholesale instead. -All of these effects are aimed at ensuring that what gets inlined is -exactly what you asked for, no more and no less. GHC ensures that inlining cannot go on forever: every mutually-recursive group is cut by one or more loop breakers that is never inlined @@ -7513,8 +7812,9 @@ itself, so an INLINE pragma is always ignored. {-# INLINE returnUs #-} - See also the NOINLINE pragma (). + 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 @@ -7523,6 +7823,57 @@ itself, so an INLINE pragma is always ignored. + + INLINABLE pragma + +An {-# INLINABLE f #-} pragma on a +function f has the following behaviour: + + +While INLINE says "please inline me", the INLINABLE +says "feel free to inline me; use your +discretion". In other words the choice is left to GHC, which uses the same +rules as for pragma-free functions. Unlike INLINE, that decision is made at +the call site, and +will therefore be affected by the inlining threshold, optimisation level etc. + + +Like INLINE, the INLINABLE pragma retains a +copy of the original RHS for +inlining purposes, and persists it in the interface file, regardless of +the size of the RHS. + + + +One way to use INLINABLE is in conjunction with +the special function inline (). +The call inline f tries very hard to inline f. +To make sure that f can be inlined, +it is a good idea to mark the definition +of f as INLINABLE, +so that GHC guarantees to expose an unfolding regardless of how big it is. +Moreover, by annotating f as INLINABLE, +you ensure that f's original RHS is inlined, rather than +whatever random optimised version of f GHC's optimiser +has produced. + + + +The INLINABLE pragma also works with SPECIALISE: +if you mark function f as INLINABLE, then +you can subsequently SPECIALISE in another module +(see ). + + +Unlike INLINE, it is OK to use +an INLINABLE pragma on a recursive function. +The principal reason do to so to allow later use of SPECIALISE + + + + + + NOINLINE pragma @@ -7779,6 +8130,9 @@ RULE with a somewhat-complex left-hand side (try it yourself), so it might not f 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 followed by a phase, as described in . @@ -7807,6 +8161,66 @@ specialisation, whose body is also inlined. The result is a type-based unrolling of the indexing function. Warning: you can make GHC diverge by using SPECIALISE INLINE on an ordinarily-recursive function. + + +SPECIALIZE for imported functions + + +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 +importing modules (see ). +For example + +module Map( lookup, blah blah ) where + lookup :: Ord key => [(key,a)] -> key -> Maybe a + lookup = ... + {-# INLINABLE lookup #-} + +module Client where + import Map( lookup ) + + data T = T1 | T2 deriving( Eq, Ord ) + {-# SPECIALISE lookup :: [(T,a)] -> T -> Maybe a + +Here, lookup is declared INLINABLE, but +it cannot be specialised for type T at its definition site, +because that type does not exist yet. Instead a client module can define T +and then specialise lookup at that type. + + +Moreover, every module that imports Client (or imports a module +that imports Client, transitively) will "see", and make use of, +the specialised version of lookup. You don't need to put +a SPECIALIZE pragma in every module. + + +Moreover you often don't even need the SPECIALIZE pragma in the +first place. When compiling a module M, +GHC's optimiser (with -O) automatically considers each top-level +overloaded function declared in M, and specialises it +for the different types at which it is called in M. The optimiser +also considers each imported +INLINABLE overloaded function, and specialises it +for the different types at which it is called in M. +So in our example, it would be enough for lookup to +be called at type T: + +module Client where + import Map( lookup ) + + data T = T1 | T2 deriving( Eq, Ord ) + + findT1 :: [(T,a)] -> Maybe a + findT1 m = lookup m T1 -- A call of lookup at type T + +However, sometimes there are no such calls, in which case the +pragma can be useful. + + + +Obselete SPECIALIZE syntax Note: In earlier versions of GHC, it was possible to provide your own specialised function for a given type: @@ -7817,6 +8231,7 @@ on an ordinarily-recursive function. This feature has been removed, as it is now subsumed by the RULES pragma (see ). + @@ -7901,10 +8316,6 @@ data S = S {-# UNPACK #-} !Int {-# UNPACK #-} !Int directly in the T constructor. The unpacker can see through newtypes, too. - If a field cannot be unpacked, you will not get a warning, - so it might be an idea to check the generated code with - . - See also the flag, which essentially has the effect of adding {-# UNPACK #-} to every strict @@ -7945,7 +8356,7 @@ Here is an example: Use the debug flag to see what rules fired. If you need more information, then shows you -each individual rule firing in detail. +each individual rule firing and also shows what the code looks like before and after the rewrite. @@ -8505,8 +8916,8 @@ comparison. - -Controlling what's going on + +Controlling what's going on in rewrite rules @@ -8514,7 +8925,10 @@ 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. @@ -8527,7 +8941,8 @@ If you add you get a more detailed listing. - Use to see in great detail what rules are being fired. + Use or +to see in great detail what rules are being fired. If you add you get a still more detailed listing. @@ -8633,8 +9048,24 @@ r) -> Special built-in functions GHC has a few built-in functions with special behaviour. These are now described in the module GHC.Prim -in the library documentation. +url="&libraryGhcPrimLocation;/GHC-Prim.html">GHC.Prim +in the library documentation. +In particular: + + +inline +allows control over inlining on a per-call-site basis. + + +lazy +restrains the strictness analyser. + + +lazy +allows you to fool the type checker. + + + @@ -8648,7 +9079,7 @@ An example will give the idea: - import Generics + import Data.Generics class Bin a where toBin :: a -> [Int] @@ -8668,7 +9099,7 @@ An example will give the idea: This class declaration explains how toBin and fromBin work for arbitrary data types. They do so by giving cases for unit, product, and sum, -which are defined thus in the library module Generics: +which are defined thus in the library module Data.Generics: data Unit = Unit @@ -8690,14 +9121,16 @@ where clause and over-ride whichever methods you please. To use generics you need to - Use the flags (to enable the extra syntax), - (to generate extra per-data-type code), - and (to make the Generics library - available. + + Use the flags (to enable the + extra syntax and generate extra per-data-type code), + and (to make the + Data.Generics module available. + - Import the module Generics from the - lang package. This import brings into + Import the module Data.Generics from the + syb package. This import brings into scope the data types Unit, :*:, and :+:. (You don't need this import if you don't mention these types @@ -8940,7 +9373,6 @@ standard behaviour.