X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=docs%2Fusers_guide%2Fglasgow_exts.xml;h=782bc5797404fb42f5625deb45c5e1b84b416767;hp=e42bf79f92c05e92f107443407b2ea941fca2fde;hb=abc32aba7135136c89e089296e296fbb380bda39;hpb=0edaca4834b511ac2c58fea3734a75cc52ac5c50 diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index e42bf79..782bc57 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -52,263 +52,53 @@ documentation describes all the libraries that come with GHC. Language options recognised by Cabal can also be enabled using the LANGUAGE pragma, thus {-# LANGUAGE TemplateHaskell #-} (see >). - Turning on an option that enables special syntax - might cause working Haskell 98 code to fail - to compile, perhaps because it uses a variable name which has - become a reserved word. So, together with each option below, we - list the special syntax which is enabled by this option. We use - notation and nonterminal names from the Haskell 98 lexical syntax - (see the Haskell 98 Report). There are two classes of special - syntax: - - - - New reserved words and symbols: character sequences - which are no longer available for use as identifiers in the - program. - - - Other special syntax: sequences of characters that have - a different meaning when this particular option is turned - on. - - - - We are only listing 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 - cases programs written to use the new syntax would not be - compilable without the option enabled. - - - - - - : + The flag - - - This simultaneously enables all of the extensions to - Haskell 98 described in , except where otherwise - noted. We are trying to move away from this portmanteau flag, + is equivalent to enabling the following extensions: + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + , + . + Enabling these options is the only + effect of -fglasgow-exts. + We are trying to move away from this portmanteau flag, and towards enabling features individually. - New reserved words: forall (only in - types), mdo. - - Other syntax stolen: - varid{#}, - char#, - string#, - integer#, - float#, - float##, - (#, #), - |), {|. - - Implies these specific language options: - , - , - , - , - . - - - - - - : - - - - This option enables the language extension defined in the - Haskell 98 Foreign Function Interface Addendum. - - New reserved words: foreign. - - - - - - ,: - - - These two flags control how generalisation is done. - See . - - - - - - - : - - - - Use GHCi's extended default rules in a regular module (). - Independent of the - flag. - - - - - - - - - - - - - - - - - - - - - - See . Only relevant - if you also use . - - - - - - - - - - See . Only relevant if - you also use . - - - - - - - - - - See . Independent of - . - - New reserved words/symbols: rec, - proc, -<, - >-, -<<, - >>-. - - Other syntax stolen: (|, - |). - - - - - - - - - - See . Independent of - . - - - - - - - -XNoImplicitPrelude - option GHC normally imports - Prelude.hi files for you. If you'd - rather it didn't, then give it a - option. The idea is - that you can then import a Prelude of your own. (But don't - call it Prelude; the Haskell module - namespace is flat, and you must not conflict with any - Prelude module.) - - Even though you have not imported the Prelude, most of - the built-in syntax still refers to the built-in Haskell - Prelude types and values, as specified by the Haskell - Report. For example, the type [Int] - still means Prelude.[] Int; tuples - continue to refer to the standard Prelude tuples; the - translation for list comprehensions continues to use - Prelude.map etc. - - However, does - change the handling of certain built-in syntax: see . - - - - - - - Enables implicit parameters (see ). Currently also implied by - . - - Syntax stolen: - ?varid, - %varid. - - - - - - - Enables overloaded string literals (see ). - - - - - - - Enables lexically-scoped type variables (see ). Implied by - . - - - - - - - Enables Template Haskell (see ). This flag must - be given explicitly; it is no longer implied by - . - - Syntax stolen: [|, - [e|, [p|, - [d|, [t|, - $(, - $varid. - - - - - - - Enables quasiquotation (see ). - - Syntax stolen: - [:varid|. - - - - Unboxed types and primitive operations -GHC is built on a raft of primitive data types and operations. +GHC is built on a raft of primitive data types and operations; +"primitive" in the sense that they cannot be defined in Haskell itself. While you really can use this stuff to write fast code, we generally find it a lot less painful, and more satisfying in the long run, to use higher-level language features and libraries. With @@ -316,28 +106,21 @@ 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. -We do not currently have good, up-to-date documentation about the -primitives, perhaps because they are mainly intended for internal use. -There used to be a long section about them here in the User Guide, but it -became out of date, and wrong information is worse than none. - -The Real Truth about what primitive types there are, and what operations -work over those types, is held in the file -fptools/ghc/compiler/prelude/primops.txt.pp. -This file is used directly to generate GHC's primitive-operation definitions, so -it is always correct! It is also intended for processing into text. - - Indeed, -the result of such processing is part of the description of the - External - Core language. -So that document is a good place to look for a type-set version. -We would be very happy if someone wanted to volunteer to produce an XML -back end to the program that processes primops.txt so that -we could include the results here in the User Guide. - -What follows here is a brief summary of some main points. +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.) + + +If you want to mention any of the primitive data types or operations in your +program, you must first import GHC.Prim to bring them +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 +and unboxed tuples, which +we briefly summarise here. Unboxed types @@ -370,8 +153,11 @@ 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 that primitive types, values, and -operations have a <literal>#</literal> suffix. +bottom. We use the convention (but it is only a convention) +that primitive types, values, and +operations have a <literal>#</literal> suffix (see <xref linkend="magic-hash"/>). +For some primitive types we have special syntax for literals, also +described in the <link linkend="magic-hash">same section</link>. </para> <para> @@ -548,8 +334,77 @@ Indeed, the bindings can even be recursive. <sect1 id="syntax-extns"> <title>Syntactic extensions + + The magic hash + The language extension allows "#" as a + 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#), + 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 ); + 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, + any Haskell 98 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 ## + is a Word#. + 3.2# has type Float#. + 3.2## has type Double# + + + + + + 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 enerated 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. + + + + + Hierarchical Modules @@ -1233,21 +1088,28 @@ output = [ x -Rebindable syntax - - GHC allows most kinds of built-in syntax to be rebound by - the user, to facilitate replacing the Prelude - with a home-grown version, for example. - - You may want to define your own numeric class +Rebindable syntax and the implicit Prelude import + + -XNoImplicitPrelude + option GHC normally imports + Prelude.hi files for you. If you'd + rather it didn't, then give it a + option. The idea is + that you can then import a Prelude of your own. (But don't + call it Prelude; the Haskell module + namespace is flat, and you must not conflict with any + Prelude module.) + + Suppose you are importing a Prelude of your own + in order to define your own numeric class hierarchy. It completely defeats that purpose if the literal "1" means "Prelude.fromInteger 1", which is what the Haskell Report specifies. - So the flag causes + So the + flag also causes the following pieces of built-in syntax to refer to whatever is in scope, not the Prelude versions: - An integer literal 368 means @@ -1396,7 +1258,7 @@ records from different modules that use the same field name. -Record puns are enabled by the flag -XRecordPuns. +Record puns are enabled by the flag -XNamedFieldPuns. @@ -1554,6 +1416,167 @@ necessary to enable them. + + Package-qualified imports + + With the flag, GHC allows + import declarations to be qualified by the package name that the + module is intended to be imported from. For example: + + +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 + available from multiple packages, or is present in both the + current package being built and an external package. + + Note: you probably don't need to use this feature, it was + added mainly so that we can build backwards-compatible versions of + packages when APIs change. It can lead to fragile dependencies in + the common case: modules occasionally move from one package to + another, rendering any package-qualified imports broken. + + + +Summary of stolen syntax + + Turning on an option that enables special syntax + might cause working Haskell 98 code to fail + to compile, perhaps because it uses a variable name which has + become a reserved word. This section lists the syntax that is + "stolen" by language extensions. + We use + notation and nonterminal names from the Haskell 98 lexical syntax + (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 + cases programs written to use the new syntax would not be + compilable without the option enabled. + +There are two classes of special + syntax: + + + + New reserved words and symbols: character sequences + which are no longer available for use as identifiers in the + program. + + + Other special syntax: sequences of characters that have + a different meaning when this particular option is turned + on. + + + +The following syntax is stolen: + + + + + forall + forall + + + Stolen (in types) by: , + , + , + , + , + + + + + + + mdo + mdo + + + Stolen by: , + + + + + + foreign + foreign + + + Stolen by: , + + + + + + rec, + proc, -<, + >-, -<<, + >>-, and (|, + |) brackets + proc + + + Stolen by: , + + + + + + ?varid, + %varid + implicit parameters + + + Stolen by: , + + + + + + [|, + [e|, [p|, + [d|, [t|, + $(, + $varid + Template Haskell + + + Stolen by: , + + + + + + [:varid| + quasi-quotation + + + Stolen by: , + + + + + + varid{#}, + char#, + string#, + integer#, + float#, + float##, + (#, #), + + + Stolen by: , + + + + + @@ -1654,9 +1677,12 @@ to be written infix, very much like expressions. More specifically: Liberalised type synonyms -Type synonyms are like macros at the type level, and +Type synonyms are like macros at the type level, but Haskell 98 imposes many rules +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) in a type synonym, thus: @@ -1673,7 +1699,8 @@ in a type synonym, thus: -You can write an unboxed tuple in a type synonym: +If you also use , +you can write an unboxed tuple in a type synonym: type Pr = (# Int, Int #) @@ -2422,11 +2449,17 @@ The result type of each constructor must begin with the type constructor being d 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 may not be a type variable (e.g. the Lit +the ty need not be a type variable (e.g. the Lit constructor). +It's is permitted to declare an ordinary algebraic data type using GADT-style syntax. +What makes a GADT into a GADT is not the syntax, but rather the presence of data constructors +whose result type is not just T a b. + + + You cannot use a deriving clause for a GADT; only for an ordinary data type. @@ -2462,6 +2495,23 @@ their selector functions actually have different types: + +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. +The type of the entire case expression must be rigid. +The type of any free variable mentioned in any of +the case alternatives must be rigid. + +A type is "rigid" if it is completely known to the compiler at its binding site. The easiest +way to ensure that a variable a rigid type is to give it a type signature. +For more precise details see +Simple unification-based type inference for GADTs +. The criteria implemented by GHC are given in the Appendix. + + + @@ -2519,9 +2569,27 @@ The syntax is identical to that of an ordinary instance declaration apart from ( You must supply a context (in the example the context is (Eq a)), exactly as you would in an ordinary instance declaration. (In contrast the context is inferred in a deriving clause -attached to a data type declaration.) These deriving instance -rules obey the same rules concerning form and termination as ordinary instance declarations, -controlled by the same flags; see . +attached to a data type declaration.) + +A deriving instance declaration +must obey the same rules concerning form and termination as ordinary instance declarations, +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 +-XFlexibleInstances, ). Consider +for example + + data Foo a = Bar a | Baz String + + deriving instance Eq a => Eq (Foo [a]) + deriving instance Eq a => Eq (Foo (Maybe a)) + +This will generate a derived instance for (Foo [a]) and (Foo (Maybe a)), +but other types such as (Foo (Int,Bool)) will not be an instance of Eq. + The stand-alone syntax is generalised for newtypes in exactly the same way that ordinary deriving clauses are generalised (). @@ -3237,7 +3305,7 @@ 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 +if you give the flag (). You can find lots of background material about the reason for these restrictions in the paper f, so GHC had to 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 [Int] (for the same reason +simplifying the constraint C Int [b] (for the same reason as before) but, rather than rejecting the program, it will infer the type - f :: C Int b => [b] -> [b] + f :: C Int [b] => [b] -> [b] 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 + +flag. + + +Exactly the same situation can arise in instance declarations themselves. Suppose we have + + class Foo a where + f :: a -> a + instance Foo [b] where + f x = ... + +and, as before, the constraint C Int [b] arises from f's +right hand side. GHC will reject the instance, complaining as before that it does not know how to resolve +the constraint C Int [b], because it matches more than one instance +declaration. The solution is to postpone the choice by adding the constraint to the context +of the instance declaration, thus: + + instance C Int [b] => Foo [b] where + f x = ... + +(You need to do this.) The willingness to be overlapped or incoherent is a property of @@ -3617,9 +3707,11 @@ to work since it gets translated into an equality comparison. The context of a type signature -Unlike Haskell 98, constraints in types do not have to be of -the form (class type-variable) or -(class (type-variable type-variable ...)). Thus, +The flag lifts the Haskell 98 restriction +that the type-class constraints in a type signature must have the +form (class type-variable) or +(class (type-variable type-variable ...)). +With these type signatures are perfectly OK g :: Eq [a] => ... @@ -5315,6 +5407,8 @@ For more details, see “Generalising Monads to Arrows”, John Hughes, in Science of Computer Programming 37, pp67–111, May 2000. +The paper that introduced arrows: a friendly introduction, motivated with +programming examples. @@ -5322,6 +5416,7 @@ pp67–111, May 2000. A New Notation for Arrows”, Ross Paterson, in ICFP, Sep 2001. +Introduced the notation described here. @@ -5333,17 +5428,42 @@ Palgrave, 2003. - -and the arrows web page at + + +“Programming with Arrows”, +John Hughes, in 5th International Summer School on +Advanced Functional Programming, +Lecture Notes in Computer Science vol. 3622, +Springer, 2004. +This paper includes another introduction to the notation, +with practical examples. + + + + + +“Type and Translation Rules for Arrow Notation in GHC”, +Ross Paterson and Simon Peyton Jones, September 16, 2004. +A terse enumeration of the formal rules used +(extracted from comments in the source code). + + + + + +The arrows web page at http://www.haskell.org/arrows/. + + + + With the flag, GHC supports the arrow -notation described in the second of these papers. -What follows is a brief introduction to the notation; -it won't make much sense unless you've read Hughes's paper. -This notation is translated to ordinary Haskell, -using combinators from the +notation described in the second of these papers, +translating it using combinators from the 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. The extension adds a new kind of expression for defining arrows: @@ -5617,7 +5737,8 @@ We could define our own operator untilA :: ArrowChoice a => a e () -> a e Bool -> a e () untilA body cond = proc x -> - if cond x then returnA -< () + b <- cond -< x + if b then returnA -< () else do body -< x untilA body cond -< x @@ -6046,7 +6167,8 @@ Assertion failures can be caught, see the documentation for the word that GHC understands are described in the following sections; any pragma encountered with an unrecognised word is (silently) - ignored. + ignored. The layout rule applies in pragmas, so the closing #-} + should start in a column to the right of the opening {-#. Certain pragmas are file-header pragmas. A file-header pragma must precede the module keyword in the file. @@ -6129,56 +6251,63 @@ Assertion failures can be caught, see the documentation for the don't recommend using this approach with GHC. - - DEPRECATED pragma - DEPRECATED - + + WARNING and DEPRECATED pragmas + WARNING + DEPRECATED - The DEPRECATED pragma lets you specify that a particular - function, class, or type, is deprecated. There are two - forms. + The WARNING pragma allows you to attach an arbitrary warning + to a particular function, class, or type. + A DEPRECATED pragma lets you specify that + a particular function, class, or type is deprecated. + There are two ways of using these pragmas. - You can deprecate an entire module thus: + You can work on an entire module thus: module Wibble {-# DEPRECATED "Use Wobble instead" #-} where ... + Or: + + module Wibble {-# WARNING "This is an unstable interface." #-} where + ... + When you compile any module that import Wibble, GHC will print the specified message. - You can deprecate a function, class, type, or data constructor, with the - following top-level declaration: + You can attach a warning to a function, class, type, or data constructor, with the + following top-level declarations: {-# DEPRECATED f, C, T "Don't use these" #-} + {-# WARNING unsafePerformIO "This is unsafe; I hope you know what you're doing" #-} When you compile any module that imports and uses any of the specified entities, GHC will print the specified message. - You can only deprecate entities declared at top level in the module + You can only attach to entities declared at top level in the module being compiled, and you can only use unqualified names in the list of - entities being deprecated. A capitalised name, such as T + entities. A capitalised name, such as T refers to either the type constructor T or the data constructor T, or both if - both are in scope. If both are in scope, there is currently no way to deprecate - one without the other (c.f. fixities ). + both are in scope. If both are in scope, there is currently no way to + specify one without the other (c.f. fixities + ). - Any use of the deprecated item, or of anything from a deprecated - module, will be flagged with an appropriate message. However, - deprecations are not reported for - (a) uses of a deprecated function within its defining module, and - (b) uses of a deprecated function in an export list. + Warnings and deprecations are not reported for + (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 the exports of several others. You can suppress the warnings with the flag - . + . @@ -6205,16 +6334,9 @@ Assertion failures can be caught, see the documentation for the key_function :: Int -> String -> (Bool, Double) - -#ifdef __GLASGOW_HASKELL__ {-# INLINE key_function #-} -#endif - (You don't need to do the C pre-processor carry-on - unless you're going to stick the code through HBC—it - doesn't like INLINE pragmas.) - 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 @@ -6238,6 +6360,16 @@ 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 +(see +Secrets of the GHC inliner, JFP 12(4) July 2002). +GHC tries not to select a function with an INLINE pragma as a loop breaker, but +when there is no choice even an INLINE function can be selected, in which case +the INLINE pragma is ignored. +For example, for a self-recursive function, the loop breaker can only be the function +itself, so an INLINE pragma is always ignored. + Syntactically, an INLINE pragma for a function can be put anywhere its type signature could be put. @@ -6250,14 +6382,18 @@ exactly what you asked for, no more and no less. UniqueSupply monad code, we have: -#ifdef __GLASGOW_HASKELL__ {-# INLINE thenUs #-} {-# INLINE returnUs #-} -#endif See also the NOINLINE pragma (). + + 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 + #ifdef __GLASGOW_HASKELL__...#endif. + @@ -6585,23 +6721,19 @@ data S = S {-# UNPACK #-} !Int {-# UNPACK #-} !Int The programmer can specify rewrite rules as part of the source program -(in a pragma). GHC applies these rewrite rules wherever it can, provided (a) -the flag () is on, -and (b) the flag -() is not specified, and (c) the - () -flag is active. - - - +(in a pragma). Here is an example: {-# RULES - "map/map" forall f g xs. map f (map g xs) = map (f.g) xs - #-} + "map/map" forall f g xs. map f (map g xs) = map (f.g) xs + #-} - + + +Use the debug flag to see what rules fired. +If you need more information, then shows you +each individual rule firing in detail. @@ -6611,15 +6743,32 @@ Here is an example: From a syntactic point of view: - + - There may be zero or more rules in a RULES pragma. + There may be zero or more rules in a RULES pragma, separated by semicolons (which + may be generated by the layout rule). + +The layout rule applies in a pragma. +Currently no new indentation level +is set, so if you put several rules in single RULES pragma and wish to use layout to separate them, +you must lay out the starting in the same column as the enclosing definitions. + + {-# RULES + "map/map" forall f g xs. map f (map g xs) = map (f.g) xs + "map/append" forall f xs ys. map f (xs ++ ys) = map f xs ++ map f ys + #-} + +Furthermore, the closing #-} +should start in a column to the right of the opening {-#. + + + Each rule has a name, enclosed in double quotes. The name itself has no significance at all. It is only used when reporting how many times the rule fired. @@ -6633,7 +6782,7 @@ immediately after the name of the rule. Thus: {-# RULES "map/map" [2] forall f g xs. map f (map g xs) = map (f.g) xs - #-} + #-} The "[2]" means that the rule is active in Phase 2 and subsequent phases. The inverse notation "[~2]" is also accepted, meaning that the rule is active up to, but not including, @@ -6642,17 +6791,8 @@ Phase 2. - - - - Layout applies in a RULES pragma. Currently no new indentation level -is set, so you must lay out your rules starting in the same column as the -enclosing definitions. - - - Each variable mentioned in a rule must either be in scope (e.g. map), or bound by the forall (e.g. f, g, xs). The variables bound by @@ -6701,17 +6841,40 @@ variables it mentions, though of course they need to be in scope. - Rules are automatically exported from a module, just as instance declarations are. + All rules are implicitly exported from the module, and are therefore +in force in any module that imports the module that defined the rule, directly +or indirectly. (That is, if A imports B, which imports C, then C's rules are +in force when compiling A.) The situation is very similar to that for instance +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 +. + + + + + +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, +and must have the same type. However, rules are only enabled +if the flag is +on (see ). + + - + Semantics @@ -6719,9 +6882,17 @@ From a semantic point of view: - -Rules are only applied if you use the flag. +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 +ignores all optimisation information in interface files; +see , .) +Note that is an optimisation flag, and +has no effect on parsing or typechecking. @@ -6738,14 +6909,6 @@ expression by substituting for the pattern variables. - The LHS and RHS of a rule are typechecked, and must have the -same type. - - - - - - GHC makes absolutely no attempt to verify that the LHS and RHS of a rule have the same meaning. That is undecidable in general, and infeasible in most interesting cases. The responsibility is entirely the programmer's! @@ -6759,7 +6922,7 @@ infeasible in most interesting cases. The responsibility is entirely the progra terminating. For example: - "loop" forall x,y. f x y = f y x + "loop" forall x y. f x y = f y x This rule will cause the compiler to go into an infinite loop. @@ -6812,48 +6975,32 @@ not be substituted, and the rule would not fire. - In the earlier phases of compilation, GHC inlines nothing -that appears on the LHS of a rule, because once you have substituted -for something you can't match against it (given the simple minded -matching). So if you write the rule - +Ordinary inlining happens at the same time as rule rewriting, which may lead to unexpected +results. Consider this (artificial) example - "map/map" forall f,g. map f . map g = map (f.g) - +f x = x +{-# RULES "f" f True = False #-} -this won't match the expression map f (map g xs). -It will only match something written with explicit use of ".". -Well, not quite. It will match the expression +g y = f y - -wibble f g xs +h z = g True - -where wibble is defined: - +Since f's right-hand side is small, it is inlined into g, +to give -wibble f g = map f . map g +g y = y - -because wibble will be inlined (it's small). - -Later on in compilation, GHC starts inlining even things on the -LHS of rules, but still leaves the rules enabled. This inlining -policy is controlled by the per-simplification-pass flag n. - +Now g is inlined into h, but f's RULE has +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. - - - - All rules are implicitly exported from the module, and are therefore -in force in any module that imports the module that defined the rule, directly -or indirectly. (That is, if A imports B, which imports C, then C's rules are -in force when compiling A.) The situation is very similar to that for instance -declarations. +The way to get predictable behaviour is to use a NOINLINE +pragma on f, to ensure +that it is not inlined until its RULEs have had a chance to fire. -