X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=docs%2Fusers_guide%2Fglasgow_exts.xml;h=de69b6006300bca4e780cccf406da4a5a64d67bd;hp=da6a125eb4a6cf30872ec2ee74d608eb19e8b203;hb=67cb409159fa9136dff942b8baaec25909416022;hpb=4d60ffc3e9a167c64e395046e1d2ef51eeb165ec diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index da6a125..de69b60 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -319,7 +319,7 @@ 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 + url="http://www.haskell.org/ghc/docs/papers/core.ps.gz">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 SGML @@ -710,6 +710,202 @@ qualifier list has just one element, a boolean expression. + + + +View patterns + + + +View patterns are enabled by the flag -XViewPatterns. +More information and examples of view patterns can be found on the +Wiki +page. + + + +View patterns are somewhat like pattern guards that can be nested inside +of other patterns. They are a convenient way of pattern-matching +against values of abstract types. For example, in a programming language +implementation, we might represent the syntax of the types of the +language as follows: + + +type Typ + +data TypView = Unit + | Arrow Typ Typ + +view :: Type -> TypeView + +-- additional operations for constructing Typ's ... + + +The representation of Typ is held abstract, permitting implementations +to use a fancy representation (e.g., hash-consing to managage sharing). + +Without view patterns, using this signature a little inconvenient: + +size :: Typ -> Integer +size t = case view t of + Unit -> 1 + Arrow t1 t2 -> size t1 + size t2 + + +It is necessary to iterate the case, rather than using an equational +function definition. And the situation is even worse when the matching +against t is buried deep inside another pattern. + + + +View patterns permit calling the view function inside the pattern and +matching against the result: + +size (view -> Unit) = 1 +size (view -> Arrow t1 t2) = size t1 + size t2 + + +That is, we add a new form of pattern, written +expression -> +pattern that means "apply the expression to +whatever we're trying to match against, and then match the result of +that application against the pattern". The expression can be any Haskell +expression of function type, and view patterns can be used wherever +patterns are used. + + + +The semantics of a pattern ( +exp -> +pat ) are as follows: + + + + Scoping: + +The variables bound by the view pattern are the variables bound by +pat. + + + +Any variables in exp are bound occurrences, +but variables bound "to the left" in a pattern are in scope. This +feature permits, for example, one argument to a function to be used in +the view of another argument. For example, the function +clunky from can be +written using view patterns as follows: + + +clunky env (lookup env -> Just val1) (lookup env -> Just val2) = val1 + val2 +...other equations for clunky... + + + + +More precisely, the scoping rules are: + + + +In a single pattern, variables bound by patterns to the left of a view +pattern expression are in scope. For example: + +example :: Maybe ((String -> Integer,Integer), String) -> Bool +example Just ((f,_), f -> 4) = True + + +Additionally, in function definitions, variables bound by matching earlier curried +arguments may be used in view pattern expressions in later arguments: + +example :: (String -> Integer) -> String -> Bool +example f (f -> 4) = True + +That is, the scoping is the same as it would be if the curried arguments +were collected into a tuple. + + + + + +In mutually recursive bindings, such as let, +where, or the top level, view patterns in one +declaration may not mention variables bound by other declarations. That +is, each declaration must be self-contained. For example, the following +program is not allowed: + +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.) + + + + + + + + + + Typing: If exp has type +T1 -> +T2 and pat matches +a T2, then the whole view pattern matches a +T1. + + + Matching: To the equations in Section 3.17.3 of the +Haskell 98 +Report, add the following: + +case v of { (e -> p) -> e1 ; _ -> e2 } + = +case (e v) of { p -> e1 ; _ -> e2 } + +That is, to match a variable v against a pattern +( exp +-> pat +), evaluate ( +exp v +) and match the result against +pat. + + + Efficiency: When the same view function is applied in +multiple branches of a function definition or a case expression (e.g., +in size above), GHC makes an attempt to collect these +applications into a single nested case expression, so that the view +function is only applied once. Pattern compilation in GHC follows the +matrix algorithm described in Chapter 4 of The +Implementation of Functional Programming Languages. When the +top rows of the first column of a matrix are all view patterns with the +"same" expression, these patterns are transformed into a single nested +case. This includes, for example, adjacent view patterns that line up +in a tuple, as in + +f ((view -> A, p1), p2) = e1 +f ((view -> B, p3), p4) = e2 + + + + The current notion of when two view pattern expressions are "the +same" is very restricted: it is not even full syntactic equality. +However, it does include variables, literals, applications, and tuples; +e.g., two instances of view ("hi", "there") will be +collected. However, the current implementation does not compare up to +alpha-equivalence, so two instances of (x, view x -> +y) will not be coalesced. + + + + + + + + + @@ -797,7 +993,7 @@ and improve termination (Section 3.2 of the paper). -The web page: http://www.cse.ogi.edu/PacSoft/projects/rmb +The web page: http://www.cse.ogi.edu/PacSoft/projects/rmb/ contains up to date information on recursive monadic bindings. @@ -862,11 +1058,172 @@ This name is not supported by GHC. branches. + + + + + Generalised (SQL-Like) List Comprehensions + list comprehensionsgeneralised + + extended list comprehensions + + group + sql + + + Generalised list comprehensions are a further enhancement to the + list comprehension syntatic sugar to allow operations such as sorting + and grouping which are familiar from SQL. They are fully described in the + paper + Comprehensive comprehensions: comprehensions with "order by" and "group by", + except that the syntax we use differs slightly from the paper. +Here is an example: + +employees = [ ("Simon", "MS", 80) +, ("Erik", "MS", 100) +, ("Phil", "Ed", 40) +, ("Gordon", "Ed", 45) +, ("Paul", "Yale", 60)] + +output = [ (the dept, sum salary) +| (name, dept, salary) <- employees +, then group by dept +, then sortWith by (sum salary) +, then take 5 ] + +In this example, the list output would take on + the value: + + +[("Yale", 60), ("Ed", 85), ("MS", 180)] + + +There are three new keywords: group, by, and using. +(The function sortWith is not a keyword; it is an ordinary +function that is exported by GHC.Exts.) + +There are five new forms of compehension qualifier, +all introduced by the (existing) keyword then: + + + + +then f + + + This statement requires that f have the type + forall a. [a] -> [a]. You can see an example of it's use in the + motivating example, as this form is used to apply take 5. + + + + + + + +then f by e + + + This form is similar to the previous one, but allows you to create a function + which will be passed as the first argument to f. As a consequence f must have + the type forall a. (a -> t) -> [a] -> [a]. As you can see + from the type, this function lets f "project out" some information + from the elements of the list it is transforming. + + An example is shown in the opening example, where sortWith + is supplied with a function that lets it find out the sum salary + for any item in the list comprehension it transforms. + + + + + + + +then group by e using f + + + This is the most general of the grouping-type statements. In this form, + f is required to have type forall a. (a -> t) -> [a] -> [[a]]. + As with the then f by e case above, the first argument + is a function supplied to f by the compiler which lets it compute e on every + element of the list being transformed. However, unlike the non-grouping case, + f additionally partitions the list into a number of sublists: this means that + at every point after this statement, binders occuring before it in the comprehension + refer to lists of possible values, not single values. To help understand + this, let's look at an example: + + +-- This works similarly to groupWith in GHC.Exts, but doesn't sort its input first +groupRuns :: Eq b => (a -> b) -> [a] -> [[a]] +groupRuns f = groupBy (\x y -> f x == f y) + +output = [ (the x, y) +| x <- ([1..3] ++ [1..2]) +, y <- [4..6] +, then group by x using groupRuns ] + + + This results in the variable output taking on the value below: + + +[(1, [4, 5, 6]), (2, [4, 5, 6]), (3, [4, 5, 6]), (1, [4, 5, 6]), (2, [4, 5, 6])] + + + Note that we have used the the function to change the type + of x from a list to its original numeric type. The variable y, in contrast, is left + unchanged from the list form introduced by the grouping. + + + + + + +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 + is the form of the group statement that we made use of in the opening example. + + + + + + + +then group using f + + + With this form of the group statement, f is required to simply have the type + forall a. [a] -> [[a]], which will be used to group up the + comprehension so far directly. An example of this form is as follows: + + +output = [ x +| y <- [1..5] +, x <- "hello" +, then group using inits] + + + This will yield a list containing every prefix of the word "hello" written out 5 times: + + +["","h","he","hel","hell","hello","helloh","hellohe","hellohel","hellohell","hellohello","hellohelloh",...] + + + + + + + + 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. @@ -955,16 +1312,16 @@ GHC allows a small extension to the syntax of left operator sections, which allows you to define postfix operators. The extension is this: the left section (e !) - + is equivalent (from the point of view of both type checking and execution) to the expression ((!) e) - + (for any expression e and operator (!). The strict Haskell 98 interpretation is that the section is equivalent to (\y -> (!) e y) - + That is, the operator must be a function of two arguments. GHC allows it to take only one argument, and that in turn allows you to write the function postfix. @@ -1020,6 +1377,170 @@ This reduces the clutter of qualified names when you import two records from different modules that use the same field name. + + + + +Record puns + + + +Record puns are enabled by the flag -XRecordPuns. + + + +When using records, it is common to write a pattern that binds a +variable with the same name as a record field, such as: + + +data C = C {a :: Int} +f (C {a = a}) = a + + + + +Record punning permits the variable name to be elided, so one can simply +write + + +f (C {a}) = a + + +to mean the same pattern as above. That is, in a record pattern, the +pattern a expands into the pattern a = +a for the same name a. + + + +Note that puns and other patterns can be mixed in the same record: + +data C = C {a :: Int, b :: Int} +f (C {a, b = 4}) = a + +and that puns can be used wherever record patterns occur (e.g. in +let bindings or at the top-level). + + + +Record punning can also be used in an expression, writing, for example, + +let a = 1 in C {a} + +instead of + +let a = 1 in C {a = a} + + +Note that this expansion is purely syntactic, so the record pun +expression refers to the nearest enclosing variable that is spelled the +same as the field name. + + + + + + + +Record wildcards + + + +Record wildcards are enabled by the flag -XRecordWildCards. + + + +For records with many fields, it can be tiresome to write out each field +individually in a record pattern, as in + +data C = C {a :: Int, b :: Int, c :: Int, d :: Int} +f (C {a = 1, b = b, c = c, d = d}) = b + c + d + + + + +Record wildcard syntax permits a (..) in a record +pattern, where each elided field f is replaced by the +pattern f = f. For example, the above pattern can be +written as + +f (C {a = 1, ..}) = b + c + d + + + + +Note that wildcards can be mixed with other patterns, including puns +(); for example, in a pattern C {a += 1, b, ..}). Additionally, record wildcards can be used +wherever record patterns occur, including in let +bindings and at the top-level. For example, the top-level binding + +C {a = 1, ..} = e + +defines b, c, and +d. + + + +Record wildcards can also be used in expressions, writing, for example, + + +let {a = 1; b = 2; c = 3; d = 4} in C {..} + + +in place of + + +let {a = 1; b = 2; c = 3; d = 4} in C {a=a, b=b, c=c, d=d} + + +Note that this expansion is purely syntactic, so the record wildcard +expression refers to the nearest enclosing variables that are spelled +the same as the omitted field names. + + + + + + + +Local Fixity Declarations + + +A careful reading of the Haskell 98 Report reveals that fixity +declarations (infix, infixl, and +infixr) are permitted to appear inside local bindings +such those introduced by let and +where. However, the Haskell Report does not specify +the semantics of such bindings very precisely. + + +In GHC, a fixity declaration may accompany a local binding: + +let f = ... + infixr 3 `f` +in + ... + +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 +declarations of aA let statement scope over other +statements in the group, just as the bound name does. + + +Moreover, a local fixity declatation *must* accompany a local binding of +that name: it is not possible to revise the fixity of name bound +elsewhere, as in + +let infixr 9 $ in ... + + +Because local fixity declarations are technically Haskell 98, no flag is +necessary to enable them. + + @@ -1328,8 +1849,8 @@ adding a new existential quantification construct. - -Type classes + +Existentials and type classes An easy extension is to allow @@ -1383,11 +1904,6 @@ dictionaries for Eq and Show respectively, extract it on pattern matching. - -Notice the way that the syntax fits smoothly with that used for -universal quantification earlier. - - @@ -1660,19 +2176,8 @@ In the example, the equality dictionary is used to satisfy the equality constrai generated by the call to elem, so that the type of insert itself has no Eq constraint. -This behaviour contrasts with Haskell 98's peculiar treament of -contexts on a data type declaration (Section 4.2.1 of the Haskell 98 Report). -In Haskell 98 the defintion - - data Eq a => Set' a = MkSet' [a] - -gives MkSet' the same type as MkSet above. But instead of -making available an (Eq a) constraint, pattern-matching -on MkSet' requires an (Eq a) constraint! -GHC faithfully implements this behaviour, odd though it is. But for GADT-style declarations, -GHC's behaviour is much more useful, as well as much more intuitive. -For example, a possible application of GHC's behaviour is to reify dictionaries: +For example, one possible application is to reify dictionaries: data NumInst a where MkNumInst :: Num a => NumInst a @@ -1686,6 +2191,38 @@ For example, a possible application of GHC's behaviour is to reify dictionaries: Here, a value of type NumInst a is equivalent to an explicit (Num a) dictionary. + +All this applies to constructors declared using the syntax of . +For example, the NumInst data type above could equivalently be declared +like this: + + data NumInst a + = Num a => MkNumInst (NumInst a) + +Notice that, unlike the situation when declaring an existental, there is +no forall, because the Num constrains the +data type's univerally quantified type variable a. +A constructor may have both universal and existential type variables: for example, +the following two declarations are equivalent: + + data T1 a + = forall b. (Num a, Eq b) => MkT1 a b + data T2 a where + MkT2 :: (Num a, Eq b) => a -> b -> T2 a + + +All this behaviour contrasts with Haskell 98's peculiar treatment of +contexts on a data type declaration (Section 4.2.1 of the Haskell 98 Report). +In Haskell 98 the definition + + data Eq a => Set' a = MkSet' [a] + +gives MkSet' the same type as MkSet above. But instead of +making available an (Eq a) constraint, pattern-matching +on MkSet' requires an (Eq a) constraint! +GHC faithfully implements this behaviour, odd though it is. But for GADT-style declarations, +GHC's behaviour is much more useful, as well as much more intuitive. + The rest of this section gives further details about GADT-style data @@ -1771,7 +2308,7 @@ field f must be the same (modulo alpha conversion). At the moment, record updates are not yet possible with GADT-style declarations, so support is limited to record construction, selection and pattern matching. -For exmaple +For example aPerson = Adult { name = "Fred", children = [] } @@ -1837,7 +2374,7 @@ the type a is refined to Int. That's the A precise specification of the type rules is beyond what this user manual aspires to, but the design closely follows that described in the paper Simple +url="http://research.microsoft.com/%7Esimonpj/papers/gadt/">Simple unification-based type inference for GADTs, (ICFP 2006). The general principle is this: type refinement is only carried out @@ -1856,7 +2393,7 @@ the result type of the case expression. Hence the addition < These and many other examples are given in papers by Hongwei Xi, and Tim Sheard. There is a longer introduction -on the wiki, +on the wiki, and Ralf Hinze's Fun with phantom types also has a number of examples. Note that papers may use different notation to that implemented in GHC. @@ -1878,7 +2415,7 @@ constructor). You cannot use a deriving clause for a GADT; only for -an ordianary data type. +an ordinary data type. @@ -1946,7 +2483,7 @@ 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. +with no repetitions. This rule is applied regardless of flags. If you want a more exotic context, you can write @@ -1982,7 +2519,7 @@ For example: 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. +(Foo in this example) as the type whose instance is being derived. @@ -2032,14 +2569,14 @@ Haskell 98, you can inherit instances of Eq, Ord + newtype Dollars = Dollars Int - + and you want to use arithmetic on Dollars, you have to explicitly define an instance of Num: - + instance Num Dollars where Dollars a + Dollars b = Dollars (a+b) ... @@ -2057,17 +2594,17 @@ dictionary, only slower! GHC now permits such instances to be derived instead, using the flag , so one can write - + newtype Dollars = Dollars Int deriving (Eq,Show,Num) - + and the implementation uses the same Num dictionary for Dollars as for Int. Notionally, the compiler derives an instance declaration of the form - + instance Num Int => Num Dollars - + which just adds or removes the newtype constructor according to the type. @@ -2077,27 +2614,27 @@ We can also derive instances of constructor classes in a similar way. For example, suppose we have implemented state and failure monad transformers, such that - + instance Monad m => Monad (State s m) instance Monad m => Monad (Failure m) - + In Haskell 98, we can define a parsing monad by - + type Parser tok m a = State [tok] (Failure m) a - + which is automatically a monad thanks to the instance declarations above. With the extension, we can make the parser type abstract, without needing to write an instance of class Monad, via - + newtype Parser tok m a = Parser (State [tok] (Failure m) a) deriving Monad In this case the derived instance declaration is of the form - + instance Monad (State [tok] (Failure m)) => Monad (Parser tok m) - + Notice that, since Monad is a constructor class, the instance is a partial application of the new type, not the @@ -2112,12 +2649,12 @@ newtype is the last class parameter. In this case, a ``partial application'' of the class appears in the deriving clause. For example, given the class - + class StateMonad s m | m -> s where ... instance Monad m => StateMonad s (State s m) where ... - + then we can derive an instance of StateMonad for Parsers by - + newtype Parser tok m a = Parser (State [tok] (Failure m) a) deriving (Monad, StateMonad [tok]) @@ -2125,7 +2662,7 @@ then we can derive an instance of StateMonad for Par The derived instance is obtained by completing the application of the class to the new type: - + instance StateMonad [tok] (State [tok] (Failure m)) => StateMonad [tok] (Parser tok m) @@ -2145,9 +2682,9 @@ the newtype and its representation. Derived instance declarations are constructed as follows. Consider the declaration (after expansion of any type synonyms) - + newtype T v1...vn = T' (t vk+1...vn) deriving (c1...cm) - + where @@ -2176,17 +2713,17 @@ where Then, for each ci, the derived instance declaration is: - + instance ci t => ci (T v1...vk) As an example which does not work, consider - + newtype NonMonad m s = NonMonad (State s m s) deriving Monad - + Here we cannot derive the instance - + instance Monad (State s m) => Monad (NonMonad m) - + because the type variable s occurs in State s m, and so cannot be "eta-converted" away. It is a good thing that this @@ -2200,7 +2737,7 @@ Notice also that the order of class parameters becomes important, since we can only derive instances for the last one. If the StateMonad class above were instead defined as - + class StateMonad m s | m -> s where ... @@ -2232,8 +2769,8 @@ the standard method is used or the one described here.) This section, and the next one, documents GHC's type-class extensions. There's lots of background in the paper Type -classes: exploring the design space (Simon Peyton Jones, Mark +url="http://research.microsoft.com/~simonpj/Papers/type-class-design-space/">Type +classes: exploring the design space (Simon Peyton Jones, Mark Jones, Erik Meijer). @@ -2312,7 +2849,7 @@ class type variable, thus: The type of elem is illegal in Haskell 98, because it contains the constraint Eq a, constrains only the class type variable (in this case a). -GHC lifts this restriction. +GHC lifts this restriction (flag ). @@ -2324,7 +2861,7 @@ GHC lifts this restriction. Functional dependencies are implemented as described by Mark Jones -in “Type Classes with Functional Dependencies”, Mark P. Jones, +in “Type Classes with Functional Dependencies”, Mark P. Jones, In Proceedings of the 9th European Symposium on Programming, ESOP 2000, Berlin, Germany, March 2000, Springer-Verlag LNCS 1782, . @@ -2659,7 +3196,7 @@ must be of the form C a where a is a type variable that occurs in the head. -The flag loosens these restrictions +The flag loosens these restrictions considerably. Firstly, multi-parameter type classes are permitted. Secondly, the context and head of the instance declaration can each consist of arbitrary (well-kinded) assertions (C t1 ... tn) subject only to the @@ -2788,7 +3325,7 @@ typechecker loop: class F a b | a->b instance F [a] [[a]] instance (D c, F a c) => D [a] -- 'c' is not mentioned in the head - + Similarly, it can be tempting to lift the coverage condition: class Mul a b c | a b -> c where @@ -2898,7 +3435,7 @@ 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 +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: @@ -3011,7 +3548,7 @@ 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 +it explicitly (for example, to give an instance declaration for it), you can import it from module GHC.Exts. @@ -3024,7 +3561,7 @@ instance of Num or of IsString< -The standard defaulting rule (Haskell Report, Section 4.3.4) +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. @@ -3065,7 +3602,7 @@ to work since it gets translated into an equality comparison. Type signatures -The context of a type signature +The context of a type signature Unlike Haskell 98, constraints in types do not have to be of the form (class type-variable) or @@ -3192,7 +3729,7 @@ J Lewis, MB Shields, E Meijer, J Launchbury, Boston, Jan 2000. -(Most of the following, stil rather incomplete, documentation is +(Most of the following, still rather incomplete, documentation is due to Jeff Lewis.) Implicit parameter support is enabled with the option @@ -3372,7 +3909,7 @@ In the former case, len_acc1 is monomorphic in its own right-hand side, so the implicit parameter ?acc is not passed to the recursive call. In the latter case, because len_acc2 has a type signature, the recursive call is made to the -polymoprhic version, which takes ?acc +polymorphic version, which takes ?acc as an implicit parameter. So we get the following results in GHCi: Prog> len1 "hello" @@ -3497,7 +4034,7 @@ Other points: '?x' and '%x' are entirely distinct implicit parameters: you - can use them together and they won't intefere with each other. + can use them together and they won't interfere with each other. You can bind linear implicit parameters in 'with' clauses. @@ -3604,7 +4141,10 @@ kind for the type variable cxt. GHC now instead allows you to specify the kind of a type variable directly, wherever -a type variable is explicitly bound. Namely: +a type variable is explicitly bound, with the flag . + + +This flag enables kind signatures in the following places: data declarations: @@ -3698,9 +4238,18 @@ The function f3 has a rank-3 type; it has rank-2 types on the left of a function arrow. -GHC allows types of arbitrary rank; you can nest foralls -arbitrarily deep in function arrows. (GHC used to be restricted to rank 2, but -that restriction has now been lifted.) +GHC has three flags to control higher-rank types: + + + : data constructors (only) can have polymorphic argment types. + + + : any function (including data constructors) can have a rank-2 type. + + + : any function (including data constructors) can have an arbitrary-rank type. +That is, you can nest foralls +arbitrarily deep in function arrows. In particular, a forall-type (also called a "type scheme"), including an operational type class context, is legal: @@ -3712,6 +4261,8 @@ field type signatures. As the type of an implicit parameter In a pattern type signature (see ) + + Of course forall becomes a keyword; you can't use forall as a type variable any more! @@ -3963,7 +4514,7 @@ Notice here that the Maybe type is parameterised by the [a]). The technical details of this extension are described in the paper -Boxy types: +Boxy types: type inference for higher-rank types and impredicativity, which appeared at ICFP 2006. @@ -4007,7 +4558,7 @@ a type. (This is a change from GHC's earlier design.) Furthermore, distinct lexical type variables stand for distinct type variables. This means that every programmer-written type signature -(includin one that contains free scoped type variables) denotes a +(including one that contains free scoped type variables) denotes a rigid type; that is, the type is fully known to the type checker, and no inference is involved. Lexical type variables may be alpha-renamed freely, without @@ -4024,9 +4575,9 @@ A lexically scoped type variable can be bound by: -In Haskell, a programmer-written type signature is implicitly quantifed over +In Haskell, a programmer-written type signature is implicitly quantified over its free type variables (Section +url="http://www.haskell.org/onlinereport/decls.html#sect4.1.2">Section 4.1.2 of the Haskel Report). Lexically scoped type variables affect this implicit quantification rules @@ -4091,7 +4642,7 @@ type variable s into scope, in the annotated expression Pattern type signatures A type signature may occur in any pattern; this is a pattern type -signature. +signature. For example: -- f and g assume that 'a' is already in scope @@ -4099,14 +4650,32 @@ For example: g (x::a) = x h ((x,y) :: (Int,Bool)) = (y,x) -In the case where all the type variables in the pattern type sigature are +In the case where all the type variables in the pattern type signature are already in scope (i.e. bound by the enclosing context), matters are simple: the signature simply constrains the type of the pattern in the obvious way. -There is only one situation in which you can write a pattern type signature that -mentions a type variable that is not already in scope, namely in pattern match -of an existential data constructor. For example: +Unlike expression and declaration type signatures, pattern type signatures are not implictly generalised. +The pattern in a patterm binding may only mention type variables +that are already in scope. For example: + + f :: forall a. [a] -> (Int, [a]) + f xs = (n, zs) + where + (ys::[a], n) = (reverse xs, length xs) -- OK + zs::[a] = xs ++ ys -- OK + + Just (v::b) = ... -- Not OK; b is not in scope + +Here, the pattern signatures for ys and zs +are fine, but the one for v is not because b is +not in scope. + + +However, in all patterns other than pattern bindings, a pattern +type signature may mention a type variable that is not in scope; in this case, +the signature brings that type variable into scope. +This is particularly important for existential data constructors. For example: data T = forall a. MkT [a] @@ -4116,16 +4685,21 @@ of an existential data constructor. For example: t3::[a] = [t,t,t] Here, the pattern type signature (t::a) mentions a lexical type -variable that is not already in scope. Indeed, it cannot already be in scope, +variable that is not already in scope. Indeed, it cannot already be in scope, because it is bound by the pattern match. GHC's rule is that in this situation (and only then), a pattern type signature can mention a type variable that is not already in scope; the effect is to bring it into scope, standing for the existentially-bound type variable. -If this seems a little odd, we think so too. But we must have +When a pattern type signature binds a type variable in this way, GHC insists that the +type variable is bound to a rigid, or fully-known, type variable. +This means that any user-written type signature always stands for a completely known type. + + +If all this seems a little odd, we think so too. But we must have some way to bring such type variables into scope, else we -could not name existentially-bound type variables in subequent type signatures. +could not name existentially-bound type variables in subsequent type signatures. This is (now) the only situation in which a pattern type @@ -4221,18 +4795,18 @@ scope over the methods defined in the where part. For exampl The Haskell Report specifies that a group of bindings (at top level, or in a let or where) should be sorted into strongly-connected components, and then type-checked in dependency order -(Haskell +(Haskell Report, Section 4.5.1). As each group is type-checked, any binders of the group that have an explicit type signature are put in the type environment with the specified polymorphic type, and all others are monomorphic until the group is generalised -(Haskell Report, Section 4.5.2). +(Haskell Report, Section 4.5.2). Following a suggestion of Mark Jones, in his paper -Typing Haskell in +Typing Haskell in Haskell, GHC implements a more general scheme. If is specified: @@ -4250,12 +4824,12 @@ This is rejected by Haskell 98, but under Jones's scheme the definition for g is typechecked first, separately from that for f, because the reference to f in g's right -hand side is ingored by the dependency analysis. Then g's +hand side is ignored by the dependency analysis. Then g's type is generalised, to get g :: Ord a => a -> Bool -Now, the defintion for f is typechecked, with this type for +Now, the definition for f is typechecked, with this type for g in the type environment. @@ -4293,7 +4867,7 @@ 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 +from the Haskell wiki page on type families. The material will be moved to this user's guide when it has stabilised. @@ -4316,12 +4890,12 @@ Type families are enabled by the flag . Haskell. The background to the main technical innovations is discussed in " +url="http://research.microsoft.com/~simonpj/papers/meta-haskell/"> Template Meta-programming for Haskell" (Proc Haskell Workshop 2002). There is a Wiki page about -Template Haskell at +Template Haskell at http://www.haskell.org/haskellwiki/Template_Haskell, and that is the best place to look for further details. You may also @@ -4546,7 +5120,7 @@ The basic idea is to compile the program twice: Then compile it again with , and additionally use - to name the object files differentliy (you can choose any suffix + to name the object files differently (you can choose any suffix that isn't the normal object suffix here). GHC will automatically load the object files built in the first step when executing splice expressions. If you omit the flag when @@ -5104,7 +5678,7 @@ g6 x = case f x of { y -> body } g7 x = case f x of { !y -> body } The functions g5 and g6 mean exactly the same thing. -But g7 evalutes (f x), binds y to the +But g7 evaluates (f x), binds y to the result, and then evaluates body. Bang patterns work in let and where @@ -5144,7 +5718,7 @@ prefix notation: (!) f x = 3 The semantics of Haskell pattern matching is described in +url="http://www.haskell.org/onlinereport/exps.html#sect3.17.2"> Section 3.17.2 of the Haskell Report. To this description add one extra item 10, saying: Matching @@ -5154,7 +5728,7 @@ the pattern !pat against a value v behaves v -Similarly, in Figure 4 of +Similarly, in Figure 4 of Section 3.17.3, add a new case (t): case v of { !pat -> e; _ -> e' } @@ -5162,7 +5736,7 @@ case v of { !pat -> e; _ -> e' } That leaves let expressions, whose translation is given in -Section +Section 3.12 of the Haskell Report. In the translation box, first apply @@ -5306,6 +5880,87 @@ Assertion failures can be caught, see the documentation for the unrecognised word is (silently) ignored. + Certain pragmas are file-header pragmas. A file-header + pragma must precede the module keyword in the file. + There can be as many file-header pragmas as you please, and they can be + preceded or followed by comments. + + + LANGUAGE pragma + + LANGUAGEpragma + pragmaLANGUAGE + + The LANGUAGE pragma allows language extensions to be enabled + in a portable way. + It is the intention that all Haskell compilers support the + LANGUAGE pragma with the same syntax, although not + all extensions are supported by all compilers, of + course. The LANGUAGE pragma should be used instead + of OPTIONS_GHC, if possible. + + For example, to enable the FFI and preprocessing with CPP: + +{-# LANGUAGE ForeignFunctionInterface, CPP #-} + + LANGUAGE is a file-header pragma (see ). + + Every language extension can also be turned into a command-line flag + by prefixing it with "-X"; for example . + (Similarly, all "-X" flags can be written as LANGUAGE pragmas. + + + A list of all supported language extensions can be obtained by invoking + ghc --supported-languages (see ). + + Any extension from the Extension type defined in + Language.Haskell.Extension + may be used. GHC will report an error if any of the requested extensions are not supported. + + + + + OPTIONS_GHC pragma + OPTIONS_GHC + + pragmaOPTIONS_GHC + + + The OPTIONS_GHC pragma is used to specify + additional options that are given to the compiler when compiling + this source file. See for + details. + + Previous versions of GHC accepted OPTIONS rather + than OPTIONS_GHC, but that is now deprecated. + + + OPTIONS_GHC is a file-header pragma (see ). + + + INCLUDE pragma + + The INCLUDE pragma is for specifying the names + of C header files that should be #include'd into + the C source code generated by the compiler for the current module (if + compiling via C). For example: + + +{-# INCLUDE "foo.h" #-} +{-# INCLUDE <stdio.h> #-} + + INCLUDE is a file-header pragma (see ). + + An INCLUDE pragma is the preferred alternative + to the option (), because the + INCLUDE pragma is understood by other + compilers. Yet another alternative is to add the include file to each + foreign import declaration in your code, but we + don't recommend using this approach with GHC. + + DEPRECATED pragma DEPRECATED @@ -5336,7 +5991,7 @@ Assertion failures can be caught, see the documentation for the When you compile any module that imports and uses any of the specified entities, GHC will print the specified message. - You can only depecate entities declared at top level in the module + You can only deprecate 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 refers to either the type constructor T @@ -5358,31 +6013,6 @@ Assertion failures can be caught, see the documentation for the . - - INCLUDE pragma - - The INCLUDE pragma is for specifying the names - of C header files that should be #include'd into - the C source code generated by the compiler for the current module (if - compiling via C). For example: - - -{-# INCLUDE "foo.h" #-} -{-# INCLUDE <stdio.h> #-} - - The INCLUDE pragma(s) must appear at the top of - your source file with any OPTIONS_GHC - pragma(s). - - An INCLUDE pragma is the preferred alternative - to the option (), because the - INCLUDE pragma is understood by other - compilers. Yet another alternative is to add the include file to each - foreign import declaration in your code, but we - don't recommend using this approach with GHC. - - INLINE and NOINLINE pragmas @@ -5420,8 +6050,26 @@ key_function :: Int -> String -> (Bool, Double) 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 - inline it. - + inline it. However, an INLINE pragma for a + function "f" has a number of other effects: + + +No funtions 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. + + +The float-in, float-out, and common-sub-expression transformations are not +applied to the body of f. + + +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. + Syntactically, an INLINE pragma for a function can be put anywhere its type signature could be put. @@ -5529,29 +6177,6 @@ happen. - - LANGUAGE pragma - - LANGUAGEpragma - pragmaLANGUAGE - - This allows language extensions to be enabled in a portable way. - It is the intention that all Haskell compilers support the - LANGUAGE pragma with the same syntax, although not - all extensions are supported by all compilers, of - course. The LANGUAGE pragma should be used instead - of OPTIONS_GHC, if possible. - - For example, to enable the FFI and preprocessing with CPP: - -{-# LANGUAGE ForeignFunctionInterface, CPP #-} - - Any extension from the Extension type defined in - Language.Haskell.Extension may be used. GHC will report an error if any of the requested extensions are not supported. - - - LINE pragma @@ -5571,22 +6196,6 @@ happen. pragma. - - OPTIONS_GHC pragma - OPTIONS_GHC - - pragmaOPTIONS_GHC - - - The OPTIONS_GHC pragma is used to specify - additional options that are given to the compiler when compiling - this source file. See for - details. - - Previous versions of GHC accepted OPTIONS rather - than OPTIONS_GHC, but that is now deprecated. - - RULES pragma @@ -5632,7 +6241,7 @@ happen. {-# SPECIALIZE f :: <type> #-} - is valid if and only if the defintion + is valid if and only if the definition f_spec :: <type> f_spec = f @@ -5648,7 +6257,7 @@ happen. h :: Eq a => a -> a -> a {-# SPECIALISE h :: (Eq a) => [a] -> [a] -> [a] #-} - + The last of these examples will generate a RULE with a somewhat-complex left-hand side (try it yourself), so it might not fire very well. If you use this kind of specialisation, let us know how well it works. @@ -5657,7 +6266,7 @@ well. If you use this kind of specialisation, let us know how well it works. A SPECIALIZE pragma can optionally be followed with a INLINE or NOINLINE pragma, optionally followed by a phase, as described in . -The INLINE pragma affects the specialised verison of the +The INLINE pragma affects the specialised version of the function (only), and applies even if the function is recursive. The motivating example is this: @@ -6353,7 +6962,7 @@ If you add you get a more detailed listing. - The definition of (say) build in GHC/Base.lhs looks llike this: + The definition of (say) build in GHC/Base.lhs looks like this: build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] @@ -6450,7 +7059,7 @@ r) -> Special built-in functions -GHC has a few built-in funcions with special behaviour. These +GHC has a few built-in functions with special behaviour. These are now described in the module GHC.Prim in the library documentation. @@ -6620,7 +7229,7 @@ So this too is illegal: op2 :: a -> Bool op2 {| p :*: q |} (x :*: y) = False -(The reason for this restriction is that we gather all the equations for a particular type consructor +(The reason for this restriction is that we gather all the equations for a particular type constructor into a single generic instance declaration.) @@ -6651,7 +7260,7 @@ Here, op1, op2, op3 are OK, but op4 is rejected, because it has a type variable inside a list. -This restriction is an implementation restriction: we just havn't got around to +This restriction is an implementation restriction: we just haven't got around to implementing the necessary bidirectional maps over arbitrary type constructors. It would be relatively easy to add specific type constructors, such as Maybe and list, to the ones that are allowed. @@ -6722,7 +7331,7 @@ carried out at let and where bindings. Haskell's monomorphism restriction (see -Section +Section 4.5.5 of the Haskell Report) can be completely switched off by @@ -6749,7 +7358,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.