X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=docs%2Fusers_guide%2Fglasgow_exts.xml;h=372ebab6fcfee28552cd754a08da78cd612c5928;hp=6dfda6b84fbeee125d1af01fff7ed64496cfb7b4;hb=25f84fa7e4b84c3db5ba745a7881c009b778e0b1;hpb=63006863be568d5cbb21d3198d43859c743152ce diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 6dfda6b..372ebab 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -38,11 +38,21 @@ documentation describes all the libraries that come with GHC. extensionsoptions controlling - These flags control what variation of the language are + The language option flag control what variation of the language are permitted. Leaving out all of them gives you standard Haskell 98. - NB. turning on an option that enables special syntax + Generally speaking, all the language options are introduced by "", + e.g. . + + + All the language options can be turned off by using the prefix ""; + e.g. "". + + 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 @@ -81,7 +91,8 @@ documentation describes all the libraries that come with GHC. This simultaneously enables all of the extensions to Haskell 98 described in , except where otherwise - noted. + noted. We are trying to move away from this portmanteau flag, + and towards enabling features individaully. New reserved words: forall (only in types), mdo. @@ -95,14 +106,20 @@ documentation describes all the libraries that come with GHC. float##, (#, #), |), {|. + + Implies these specific language options: + , + , + , + , + . - and : - - + : + This option enables the language extension defined in the @@ -114,7 +131,7 @@ documentation describes all the libraries that come with GHC. - ,: + ,: These two flags control how generalisation is done. @@ -125,8 +142,8 @@ documentation describes all the libraries that come with GHC. - : - + : + Use GHCi's extended default rules in a regular module (). @@ -137,16 +154,16 @@ documentation describes all the libraries that come with GHC. - - + + - - + + - - + + @@ -171,8 +188,8 @@ documentation describes all the libraries that come with GHC. - - + + See . Independent of @@ -190,8 +207,8 @@ documentation describes all the libraries that come with GHC. - - + + See . Independent of @@ -200,13 +217,13 @@ documentation describes all the libraries that come with GHC. - + - -fno-implicit-prelude + -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 + 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 @@ -221,14 +238,14 @@ documentation describes all the libraries that come with GHC. translation for list comprehensions continues to use Prelude.map etc. - However, does + However, does change the handling of certain built-in syntax: see . - + Enables implicit parameters (see ). Currently also implied by @@ -241,7 +258,15 @@ documentation describes all the libraries that come with GHC. - + + + Enables overloaded string literals (see ). + + + + + Enables lexically-scoped type variables (see ). Implied by @@ -250,7 +275,7 @@ documentation describes all the libraries that come with GHC. - + Enables Template Haskell (see ). This flag must @@ -269,8 +294,6 @@ documentation describes all the libraries that come with GHC. - - Unboxed types and primitive operations @@ -375,6 +398,13 @@ worse, the unboxed value might be larger than a pointer (Double# for instance). + You cannot define a newtype whose representation type +(the argument type of the data constructor) is an unboxed type. Thus, +this is illegal: + + newtype A = MkA Int# + + You cannot bind a variable with an unboxed type in a top-level binding. @@ -544,14 +574,11 @@ import qualified Control.Monad.ST.Strict as ST linkend="search-path"/>. GHC comes with a large collection of libraries arranged - hierarchically; see the accompanying library documentation. - There is an ongoing project to create and maintain a stable set - of core libraries used by several Haskell - compilers, and the libraries that GHC comes with represent the - current status of that project. For more details, see Haskell - Libraries. - + hierarchically; see the accompanying library + documentation. More libraries to install are available + from HackageDB. @@ -690,9 +717,11 @@ qualifier list has just one element, a boolean expression. The recursive do-notation (also known as mdo-notation) is implemented as described in -"A recursive do for Haskell", -Levent Erkok, John Launchbury", +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, @@ -723,17 +752,24 @@ class Monad m => MonadFix m where The function mfix -dictates how the required recursion operation should be performed. If recursive bindings are required for a monad, -then that monad must be declared an instance of the MonadFix class. -For details, see the above mentioned reference. +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 } + +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). -There are three important points in using the recursive-do notation: +Here are some important points in using the recursive-do notation: The recursive version of the do-notation uses the keyword mdo (rather @@ -741,14 +777,21 @@ than do). -You should import Control.Monad.Fix. -(Note: Strictly speaking, this import is required only when you need to refer to the name -MonadFix in your program, but the import is always safe, and the programmers -are encouraged to always import this module when using the mdo-notation.) +It is enabled with the flag -XRecursiveDo, which is in turn implied by +-fglasgow-exts. -As with other extensions, ghc should be given the flag -fglasgow-exts +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 +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). @@ -832,7 +875,7 @@ This name is not supported by GHC. 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 causes the following pieces of built-in syntax to refer to whatever is in scope, not the Prelude versions: @@ -935,6 +978,48 @@ definitions; you must define such a function in prefix form. + +Record field disambiguation + +In record construction and record pattern matching +it is entirely unambiguous which field is referred to, even if there are two different +data types in scope with a common field name. For example: + +module M where + data S = MkS { x :: Int, y :: Bool } + +module Foo where + import M + + 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 + bad2 k = x k -- Ambiguous + +Even though there are two x's in scope, +it is clear that the x in the pattern in the +definition of ok1 can only mean the field +x from type S. Similarly for +the function ok2. However, in the record update +in bad1 and the record selection in bad2 +it is not clear which of the two types is intended. + + +Haskell 98 regards all four as ambiguous, but with the + flag, GHC will accept +the former two. The rules are precisely the same as those for instance +declarations in Haskell 98, where the method names on the left-hand side +of the method bindings in an instance declaration refer unambiguously +to the method of that class (provided they are in scope at all), even +if there are other variables in scope with the same name. +This reduces the clutter of qualified names when you import two +records from different modules that use the same field name. + + @@ -956,7 +1041,7 @@ a data type with no constructors. For example: Syntactically, the declaration lacks the "= constrs" part. The type can be parameterised over types of any kind, but if the kind is not * then an explicit kind annotation must be used -(see ). +(see ). Such data types have only one value, namely bottom. Nevertheless, they can be useful when defining "phantom types". @@ -1218,7 +1303,7 @@ that collection of packages in a uniform manner. You can express quite a bit of object-oriented-like programming this way. - + Why existential? @@ -1241,9 +1326,9 @@ But Haskell programmers can safely think of the ordinary adding a new existential quantification construct. - + - + Type classes @@ -1303,9 +1388,9 @@ Notice the way that the syntax fits smoothly with that used for universal quantification earlier. - + - + Record Constructors @@ -1322,7 +1407,7 @@ data Counter a = forall self. NewCounter Here tag is a public field, with a well-typed selector function tag :: Counter a -> a. The self type is hidden from the outside; any attempt to apply _this, -_inc or _output as functions will raise a +_inc or _display as functions will raise a compile-time error. In other words, GHC defines a record selector function only for fields whose type does not mention the existentially-quantified variables. (This example used an underscore in the fields for which record selectors @@ -1368,10 +1453,10 @@ setTag obj t = obj{ tag = t } - + - + Restrictions @@ -1522,7 +1607,7 @@ declarations. Define your own instances! - + @@ -1777,7 +1862,8 @@ and Ralf Hinze's may use different notation to that implemented in GHC. -The rest of this section outlines the extensions to GHC that support GADTs. +The rest of this section outlines the extensions to GHC that support GADTs. The extension is enabled with +. A GADT can only be declared using GADT-style syntax (); @@ -1830,9 +1916,77 @@ their selector functions actually have different types: + + +Extensions to the "deriving" mechanism + + +Inferred context for deriving clauses + + +The Haskell Report is vague about exactly when a deriving clause is +legal. For example: + + data T0 f a = MkT0 a deriving( Eq ) + data T1 f a = MkT1 (f a) deriving( Eq ) + data T2 f a = MkT2 (f (f a)) deriving( Eq ) + +The natural generated Eq code would result in these instance declarations: + + instance Eq a => Eq (T0 f a) where ... + instance Eq (f a) => Eq (T1 f a) where ... + instance Eq (f (f a)) => Eq (T2 f a) where ... + +The first of these is obviously fine. The second is still fine, although less obviously. +The third is not Haskell 98, and risks losing termination of instances. + + +GHC takes a conservative position: it accepts the first two, but not the third. The rule is this: +each constraint in the inferred instance context must consist only of type variables, +with no repititions. + + +This rule is applied regardless of flags. If you want a more exotic context, you can write +it yourself, using the standalone deriving mechanism. + + + + +Stand-alone deriving declarations + + +GHC now allows stand-alone deriving declarations, enabled by -XStandaloneDeriving: + + data Foo a = Bar a | Baz String + + deriving instance Eq a => Eq (Foo a) + +The syntax is identical to that of an ordinary instance declaration apart from (a) the keyword +deriving, and (b) the absence of the where part. +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 . + +The stand-alone syntax is generalised for newtypes in exactly the same +way that ordinary deriving clauses are generalised (). +For example: + + newtype Foo a = MkFoo (State Int a) + + deriving instance MonadState Int Foo + +GHC always treats the last parameter of the instance +(Foo in this exmample) as the type whose instance is being derived. + + + + Deriving clause for classes <literal>Typeable</literal> and <literal>Data</literal> @@ -1846,7 +2000,7 @@ classes Eq, Ord, GHC extends this list with two more classes that may be automatically derived -(provided the flag is specified): +(provided the flag is specified): Typeable, and Data. These classes are defined in the library modules Data.Typeable and Data.Generics respectively, and the appropriate class must be in scope before it can be mentioned in the deriving clause. @@ -1900,7 +2054,9 @@ dictionary, only slower! Generalising the deriving clause -GHC now permits such instances to be derived instead, so one can write +GHC now permits such instances to be derived instead, +using the flag , +so one can write newtype Dollars = Dollars Int deriving (Eq,Show,Num) @@ -1946,7 +2102,7 @@ In this case the derived instance declaration is of the form Notice that, since Monad is a constructor class, the instance is a partial application of the new type, not the entire left hand side. We can imagine that the type declaration is -``eta-converted'' to generate the context of the instance +"eta-converted" to generate the context of the instance declaration. @@ -2062,41 +2218,13 @@ and Data, for which the built-in derivation applies (section the standard method is used or the one described here.) - - - - -Stand-alone deriving declarations - - -GHC now allows stand-alone deriving declarations, enabled by -fglasgow-exts: - - data Foo a = Bar a | Baz String - - derive instance Eq (Foo a) - -The token "derive" is a keyword only when followed by "instance"; -you can use it as a variable name elsewhere. -The stand-alone syntax is generalised for newtypes in exactly the same -way that ordinary deriving clauses are generalised (). -For example: - - newtype Foo a = MkFoo (State Int a) - - derive instance MonadState Int Foo - -GHC always treats the last parameter of the instance -(Foo in this exmample) as the type whose instance is being derived. - - - - -Other type system extensions + +Class and instances declarations Class declarations @@ -2538,7 +2666,7 @@ the context and head of the instance declaration can each consist of arbitrary following rules: -For each assertion in the context: +The Paterson Conditions: for each assertion in the context No type variable has more occurrences in the assertion than in the head The assertion has fewer constructors and variables (taken together @@ -2546,7 +2674,7 @@ For each assertion in the context: -The coverage condition. For each functional dependency, +The Coverage Condition. For each functional dependency, tvsleft -> tvsright, of the class, every type variable in @@ -2558,11 +2686,15 @@ 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. For example, the following would make the type checker -loop if it wasn't excluded: - - instance C a => C a where ... - +constructor. Both the Paterson Conditions and the Coverage Condition are lifted +if you give the +flag (). +You can find lots of background material about the reason for these +restrictions in the paper +Understanding functional dependencies via Constraint Handling Rules. + + For example, these are OK: instance C Int [a] -- Multiple parameters @@ -2614,11 +2746,6 @@ something more specific does not: op = ... -- Default -You can find lots of background material about the reason for these -restrictions in the paper -Understanding functional dependencies via Constraint Handling Rules. - @@ -2681,10 +2808,10 @@ makes instance inference go into a loop, because it requires the constraint Nevertheless, GHC allows you to experiment with more liberal rules. If you use -the experimental flag --fallow-undecidable-instances -option, you can use arbitrary -types in both an instance context and instance head. Termination is ensured by having a +the experimental flag +-XUndecidableInstances, +both the Paterson Conditions and the Coverage Condition +(described in ) are lifted. Termination is ensured by having a fixed-depth recursion stack. If you exceed the stack depth you get a sort of backtrace, and the opportunity to increase the stack depth with N. @@ -2699,11 +2826,11 @@ with N. In general, GHC requires that that it be unambiguous which instance declaration should be used to resolve a type-class constraint. This behaviour -can be modified by two flags: --fallow-overlapping-instances +can be modified by two flags: +-XOverlappingInstances -and --fallow-incoherent-instances +and +-XIncoherentInstances , as this section discusses. Both these flags are dynamic flags, and can be set on a per-module basis, using an OPTIONS_GHC pragma if desired (). @@ -2731,7 +2858,7 @@ particular constraint matches more than one. -The flag instructs GHC to allow +The flag instructs GHC to allow more than one instance to match, provided there is a most specific one. For example, the constraint C Int [Int] matches instances (A), (C) and (D), but the last is more specific, and hence is chosen. If there is no @@ -2748,30 +2875,45 @@ Suppose that from the RHS of f we get the constraint GHC does not commit to instance (C), because in a particular call of f, b might be instantiate to Int, in which case instance (D) would be more specific still. -So GHC rejects the program. If you add the flag , +So GHC rejects the program. +(If you add the flag , GHC will instead pick (C), without complaining about -the problem of subsequent instantiations. +the problem of subsequent instantiations.) + + +Notice that we gave a type signature to f, so GHC had to +check that f has the specified type. +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 +as before) but, rather than rejecting the program, it will infer the type + + f :: C Int b => [b] -> [b] + +That postpones the question of which instance to pick to the +call site for f +by which time more is known about the type b. 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 mdodule is +presence or otherwise of the +and flags when that mdodule is being defined. Neither flag is required in a module that imports and uses the instance declaration. 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 +. The flag setting for the more-specific instance does not matter. -Suppose an instance declaration does not matche the constraint being looked up, but +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 instantiated. Usually GHC will regard this as a reason for not committing to some other constraint. But if the instance declaration was compiled with -, GHC will skip the "does-it-unify?" +, GHC will skip the "does-it-unify?" check for that declaration. @@ -2780,18 +2922,18 @@ 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 +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. +The flag implies the + flag, but not vice versa. @@ -2840,6 +2982,86 @@ reversed, but it makes sense to me. + +Overloaded string literals + + + +GHC supports overloaded string literals. Normally a +string literal has type String, but with overloaded string +literals enabled (with -XOverloadedStrings) + a string literal has type (IsString a) => a. + + +This means that the usual string syntax can be used, e.g., for packed strings +and other variations of string like types. String literals behave very much +like integer literals, i.e., they can be used in both expressions and patterns. +If used in a pattern the literal with be replaced by an equality test, in the same +way as an integer literal is. + + +The class IsString is defined as: + +class IsString a where + fromString :: String -> a + +The only predefined instance is the obvious one to make strings work as usual: + +instance IsString [Char] where + fromString cs = cs + +The class IsString is not in scope by default. If you want to mention +it explicitly (for exmaple, to give an instance declaration for it), you can import it +from module GHC.Exts. + + +Haskell's defaulting mechanism is extended to cover string literals, when is specified. +Specifically: + + +Each type in a default declaration must be an +instance of Num or of IsString. + + + +The standard defaulting rule (Haskell Report, Section 4.3.4) +is extended thus: defaulting applies when all the unresolved constraints involve standard classes +or IsString; and at least one is a numeric class +or IsString. + + + + +A small example: + +module Main where + +import GHC.Exts( IsString(..) ) + +newtype MyString = MyString String deriving (Eq, Show) +instance IsString MyString where + fromString = MyString + +greet :: MyString -> MyString +greet "hello" = "world" +greet other = other + +main = do + print $ greet "hello" + print $ greet "fool" + + + +Note that deriving Eq is necessary for the pattern matching +to work since it gets translated into an equality comparison. + + + + + + +Other type system extensions + Type signatures @@ -2974,7 +3196,7 @@ Boston, Jan 2000. due to Jeff Lewis.) Implicit parameter support is enabled with the option -. +. A variable is called dynamically bound when it is bound by the calling @@ -3364,7 +3586,7 @@ and you'd be right. That is why they are an experimental feature. ================ END OF Linear Implicit Parameters commented out --> - + Explicitly-kinded quantification @@ -3484,7 +3706,6 @@ including an operational type class context, is legal: On the left or right (see f4, for example) of a function arrow - On the right of a function arrow (see ) As the argument of a constructor, or type of a field, in a data type declaration. For example, any of the f1,f2,f3,g1,g2 above would be valid field type signatures. @@ -4013,7 +4234,7 @@ and all others are monomorphic until the group is generalised Following a suggestion of Mark Jones, in his paper Typing Haskell in Haskell, -GHC implements a more general scheme. If is +GHC implements a more general scheme. If is specified: the dependency analysis ignores references to variables that have an explicit type signature. @@ -4042,7 +4263,7 @@ Now, the defintion for f is typechecked, with this type for The same refined dependency analysis also allows the type signatures of mutually-recursive functions to have different contexts, something that is illegal in Haskell 98 (Section 4.5.2, last sentence). With - + GHC only insists that the type signatures of a refined group have identical type signatures; in practice this means that only variables bound by the same pattern binding must have the same context. For example, this is fine: @@ -4056,6 +4277,33 @@ pattern binding must have the same context. For example, this is fine: + +Type families + + + +GHC supports the definition of type families indexed by types. They may be +seen as an extension of Haskell 98's class-based overloading of values to +types. When type families are declared in classes, they are also known as +associated types. + + +There are two forms of type families: data families and type synonym families. +Currently, only the former are fully implemented, while we are still working +on the latter. As a result, the specification of the language extension is +also still to some degree in flux. Hence, a more detailed description of +the language extension and its use is currently available +from the Haskell +wiki page on type families. The material will be moved to this user's +guide when it has stabilised. + + +Type families are enabled by the flag . + + + + + @@ -4099,9 +4347,10 @@ Tim Sheard is going to expand it.) Template Haskell has the following new syntactic constructions. You need to use the flag - + + to switch these syntactic extensions on - ( is no longer implied by + ( is no longer implied by ). @@ -4133,7 +4382,7 @@ Tim Sheard is going to expand it.) the quotation has type Expr. [d| ... |], where the "..." is a list of top-level declarations; the quotation has type Q [Dec]. - [Planned, but not implemented yet.] [t| ... |], where the "..." is a type; + [t| ... |], where the "..." is a type; the quotation has type Type. @@ -4167,6 +4416,14 @@ Tim Sheard is going to expand it.) (It would make sense to do so, but it's hard to implement.) + + Furthermore, you can only run a function at compile time if it is imported + from another module that is not part of a mutually-recursive group of modules + that includes the module currently being compiled. For example, when compiling module A, + you can only run Template Haskell functions imported from B if B does not import A (directly or indirectly). + The reason should be clear: to run B we must compile and run A, but we are currently type-checking A. + + The flag -ddump-splices shows the expansion of all top-level splices as they happen. @@ -4239,7 +4496,7 @@ pr s = gen (parse s) Now run the compiler (here we are a Cygwin prompt on Windows): -$ ghc --make -fth main.hs -o main.exe +$ ghc --make -XTemplateHaskell main.hs -o main.exe Run "main.exe" and here is your output: @@ -4328,7 +4585,7 @@ Palgrave, 2003. and the arrows web page at http://www.haskell.org/arrows/. -With the flag, GHC supports the arrow +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. @@ -4786,7 +5043,7 @@ Because the preprocessor targets Haskell (rather than Core), - + Bang patterns <indexterm><primary>Bang patterns</primary></indexterm> @@ -4798,10 +5055,10 @@ prime feature description contains more discussion and examples than the material below. -Bang patterns are enabled by the flag . +Bang patterns are enabled by the flag . - + Informal description of bang patterns @@ -4856,7 +5113,7 @@ is part of the syntax of let bindings. - + Syntax and semantics @@ -4930,7 +5187,7 @@ a module. - + Assertions <indexterm><primary>Assertions</primary></indexterm> @@ -5899,12 +6156,6 @@ The following are good consumers: - length - - - - - ++ (on its first argument) @@ -6190,112 +6441,10 @@ r) -> Special built-in functions -GHC has a few built-in funcions with special behaviour, -described in this section. All are exported by -GHC.Exts. - - The <literal>seq</literal> function - -The function seq is as described in the Haskell98 Report. - - seq :: a -> b -> b - -It evaluates its first argument to head normal form, and then returns its -second argument as the result. The reason that it is documented here is -that, despite seq's polymorphism, its -second argument can have an unboxed type, or -can be an unboxed tuple; for example (seq x 4#) -or (seq x (# p,q #)). This requires b -to be instantiated to an unboxed type, which is not usually allowed. - - - - The <literal>inline</literal> function - -The inline function is somewhat experimental. - - inline :: a -> a - -The call (inline f) arranges that f -is inlined, regardless of its size. More precisely, the call -(inline f) rewrites to the right-hand side of f's -definition. -This allows the programmer to control inlining from -a particular call site -rather than the definition site of the function -(c.f. INLINE pragmas ). - - -This inlining occurs regardless of the argument to the call -or the size of f's definition; it is unconditional. -The main caveat is that f's definition must be -visible to the compiler. That is, f must be -let-bound in the current scope. -If no inlining takes place, the inline function -expands to the identity function in Phase zero; so its use imposes -no overhead. - - If the function is defined in another -module, GHC only exposes its inlining in the interface file if the -function is sufficiently small that it might be -inlined by the automatic mechanism. There is currently no way to tell -GHC to expose arbitrarily-large functions in the interface file. (This -shortcoming is something that could be fixed, with some kind of pragma.) - - - - The <literal>lazy</literal> function - -The lazy function restrains strictness analysis a little: - - lazy :: a -> a - -The call (lazy e) means the same as e, -but lazy has a magical property so far as strictness -analysis is concerned: it is lazy in its first argument, -even though its semantics is strict. After strictness analysis has run, -calls to lazy are inlined to be the identity function. - - -This behaviour is occasionally useful when controlling evaluation order. -Notably, lazy is used in the library definition of -Control.Parallel.par: - - par :: a -> b -> b - par x y = case (par# x) of { _ -> lazy y } - -If lazy were not lazy, par would -look strict in y which would defeat the whole -purpose of par. - - -Like seq, the argument of lazy can have -an unboxed type. - - - - - The <literal>unsafeCoerce#</literal> function - -The function unsafeCoerce# allows you to side-step the -typechecker entirely. It has type - - unsafeCoerce# :: a -> b - -That is, it allows you to coerce any type into any other type. If you use this -function, you had better get it right, otherwise segmentation faults await. -It is generally used when you want to write a program that you know is -well-typed, but where Haskell's type system is not expressive enough to prove -that it is well typed. - - -The argument to unsafeCoerce# can have unboxed types, -although extremely bad things will happen if you coerce a boxed type -to an unboxed type. - - - - +GHC has a few built-in funcions with special behaviour. These +are now described in the module GHC.Prim +in the library documentation. @@ -6352,7 +6501,7 @@ where clause and over-ride whichever methods you please. Use the flags (to enable the extra syntax), - (to generate extra per-data-type code), + (to generate extra per-data-type code), and (to make the Generics library available. @@ -6561,21 +6710,21 @@ carried out at let and where bindings. Switching off the dreaded Monomorphism Restriction - + Haskell's monomorphism restriction (see Section 4.5.5 of the Haskell Report) can be completely switched off by -. +. Monomorphic pattern bindings - - + + As an experimental change, we are exploring the possibility of making pattern bindings monomorphic; that is, not generalised at all. @@ -6591,7 +6740,7 @@ can be completely switched off by [x] = e -- A pattern binding Experimentally, GHC now makes pattern bindings monomorphic by -default. Use to recover the +default. Use to recover the standard behaviour.