X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=docs%2Fusers_guide%2Fglasgow_exts.xml;h=b7d43c9f3fd80a77247c11acec0527835e47182b;hp=dee62f469352e2cc6995d9fcf8e0f7eb6c9127a7;hb=661c97c65e5fa47177502e592bb763f752b487ac;hpb=177b31ca6ebe01f8011926e30c4ac7ee32791753 diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index dee62f4..b7d43c9 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -38,19 +38,20 @@ documentation describes all the libraries that come with GHC. extensionsoptions controlling - The language option flag control what variation of the language are + The language option flags control what variation of the language are permitted. Leaving out all of them gives you standard Haskell 98. - 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 >). + Language options can be controlled in two ways: + + Every language option can switched on by a command-line flag "" + (e.g. ), and switched off by the flag ""; + (e.g. ). + + Language options recognised by Cabal can also be enabled using the LANGUAGE pragma, + thus {-# LANGUAGE TemplateHaskell #-} (see ). + + The flag @@ -77,10 +78,11 @@ documentation describes all the libraries that come with GHC. , , , + , , , , - , + , , , , @@ -108,7 +110,7 @@ While you really can use this stuff to write fast code, All these primitive data types and operations are exported by the library GHC.Prim, for which there is -detailed online documentation. +detailed online documentation. (This documentation is generated from the file compiler/prelude/primops.txt.pp.) @@ -209,22 +211,20 @@ in a top-level binding. in a recursive binding. You may bind unboxed variables in a (non-recursive, -non-top-level) pattern binding, but any such variable causes the entire -pattern-match -to become strict. For example: +non-top-level) pattern binding, but you must make any such pattern-match +strict. For example, rather than: data Foo = Foo Int Int# f x = let (Foo a b, w) = ..rhs.. in ..body.. -Since b has type Int#, the entire pattern -match -is strict, and the program behaves as if you had written +you must write: data Foo = Foo Int Int# - f x = case ..rhs.. of { (Foo a b, w) -> ..body.. } + f x = let !(Foo a b, w) = ..rhs.. in ..body.. +since b has type Int#. @@ -334,6 +334,122 @@ Indeed, the bindings can even be recursive. Syntactic extensions + + Unicode syntax + The language + extension + enables Unicode characters to be used to stand for certain ASCII + character sequences. The following alternatives are provided: + + + + + + ASCII + Unicode alternative + Code point + Name + + + + + + + + :: + :: + 0x2237 + PROPORTION + + + + + => + + 0x21D2 + RIGHTWARDS DOUBLE ARROW + + + + + forall + + 0x2200 + FOR ALL + + + + + -> + + 0x2192 + RIGHTWARDS ARROW + + + + + <- + + 0x2190 + LEFTWARDS ARROW + + + + + + -< + + 0x2919 + LEFTWARDS ARROW-TAIL + + + + + + >- + + 0x291A + RIGHTWARDS ARROW-TAIL + + + + + + -<< + + 0x291B + LEFTWARDS DOUBLE ARROW-TAIL + + + + + + >>- + + 0x291C + RIGHTWARDS DOUBLE ARROW-TAIL + + + + + + * + + 0x2605 + BLACK STAR + + + + + + + The magic hash The language extension allows "#" as a @@ -390,7 +506,7 @@ Indeed, the bindings can even be recursive. the syntax by eliminating odd cases like Prelude... For example, when NewQualifiedOperators is on, it is possible to - write the enerated sequence [Monday..] + write the enumerated sequence [Monday..] without spaces, whereas in Haskell 98 this would be a reference to the operator ‘.‘ from module Monday. @@ -772,98 +888,172 @@ y) will not be coalesced. + + + +n+k patterns + + + +n+k pattern support is enabled by default. To disable +it, you can use the flag. + + + + - + The recursive do-notation - The recursive do-notation (also known as mdo-notation) is implemented as described in -A recursive do for Haskell, -by Levent Erkok, John Launchbury, -Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania. -This paper is essential reading for anyone making non-trivial use of mdo-notation, -and we do not repeat it here. - -The do-notation of Haskell does not allow recursive bindings, +The do-notation of Haskell 98 does not allow recursive bindings, that is, the variables bound in a do-expression are visible only in the textually following code block. Compare this to a let-expression, where bound variables are visible in the entire binding group. It turns out that several applications can benefit from recursive bindings in -the do-notation, and this extension provides the necessary syntactic support. +the do-notation. The flag provides the necessary syntactic support. -Here is a simple (yet contrived) example: - +Here is a simple (albeit contrived) example: -import Control.Monad.Fix - -justOnes = mdo xs <- Just (1:xs) - return xs +{-# LANGUAGE DoRec #-} +justOnes = do { rec { xs <- Just (1:xs) } + ; return (map negate xs) } +As you can guess justOnes will evaluate to Just [-1,-1,-1,.... + -As you can guess justOnes will evaluate to Just [1,1,1,.... +The background and motivation for recursive do-notation is described in +A recursive do for Haskell, +by Levent Erkok, John Launchbury, +Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania. +The theory behind monadic value recursion is explained further in Erkok's thesis +Value Recursion in Monadic Computations. +However, note that GHC uses a different syntax than the one described in these documents. + +Details of recursive do-notation -The Control.Monad.Fix library introduces the MonadFix class. It's definition is: +The recursive do-notation is enabled with the flag or, equivalently, +the LANGUAGE pragma . It introduces the single new keyword "rec", +which wraps a mutually-recursive group of monadic statements, +producing a single statement. +Similar to a let +statement, the variables bound in the rec are +visible throughout the rec group, and below it. +For example, compare -class Monad m => MonadFix m where - mfix :: (a -> m a) -> m a +do { a <- getChar do { a <- getChar + ; let { r1 = f a r2 ; rec { r1 <- f a r2 + ; r2 = g r1 } ; r2 <- g r1 } + ; return (r1 ++ r2) } ; return (r1 ++ r2) } +In both cases, r1 and r2 are +available both throughout the let or rec block, and +in the statements that follow it. The difference is that let is non-monadic, +while rec is monadic. (In Haskell let is +really letrec, of course.) + -The function mfix -dictates how the required recursion operation should be performed. For example, -justOnes desugars as follows: +The static and dynamic semantics of rec can be described as follows: + + +First, +similar to let-bindings, the rec is broken into +minimal recursive groups, a process known as segmentation. +For example: + +rec { a <- getChar ===> a <- getChar + ; b <- f a c rec { b <- f a c + ; c <- f b a ; c <- f b a } + ; putChar c } putChar c + +The details of segmentation are described in Section 3.2 of +A recursive do for Haskell. +Segmentation improves polymorphism, reduces the size of the recursive "knot", and, as the paper +describes, also has a semantic effect (unless the monad satisfies the right-shrinking law). + + +Then each resulting rec is desugared, using a call to Control.Monad.Fix.mfix. +For example, the rec group in the preceding example is desugared like this: + +rec { b <- f a c ===> (b,c) <- mfix (\~(b,c) -> do { b <- f a c + ; c <- f b a } ; c <- f b a + ; return (b,c) }) + +In general, the statment rec ss +is desugared to the statement -justOnes = mfix (\xs' -> do { xs <- Just (1:xs'); return xs } +vs <- mfix (\~vs -> do { ss; return vs }) -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. +where vs is a tuple of the variables bound by ss. + +The original rec typechecks exactly +when the above desugared version would do so. For example, this means that +the variables vs are all monomorphic in the statements +following the rec, because they are bound by a lambda. -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). +The mfix function is defined in the MonadFix +class, in Control.Monad.Fix, thus: + +class Monad m => MonadFix m where + mfix :: (a -> m a) -> m a + + + + -Here are some important points in using the recursive-do notation: +Here are some other important points in using the recursive-do notation: -The recursive version of the do-notation uses the keyword mdo (rather -than do). +It is enabled with the flag -XDoRec, which is in turn implied by +-fglasgow-exts. -It is enabled with the flag -XRecursiveDo, which is in turn implied by --fglasgow-exts. +If recursive bindings are required for a monad, +then that monad must be declared an instance of the MonadFix class. -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). +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). -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). +Like let and where bindings, +name shadowing is not allowed within a rec; +that is, all the names bound in a single rec must +be distinct (Section 3.3 of the paper). + + +It supports rebindable syntax (see ). + + + Mdo-notation (deprecated) + GHC used to support the flag , +which enabled the keyword mdo, precisely as described in +A recursive do for Haskell, +but this is now deprecated. Instead of mdo { Q; e }, write +do { rec Q; e }. + Historical note: The old implementation of the mdo-notation (and most of the existing documents) used the name MonadRec for the class and the corresponding library. This name is not supported by GHC. + @@ -933,11 +1123,12 @@ This name is not supported by GHC. Generalised list comprehensions are a further enhancement to the - list comprehension syntatic sugar to allow operations such as sorting + list comprehension syntactic 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. +The extension is enabled with the flag . Here is an example: employees = [ ("Simon", "MS", 80) @@ -973,7 +1164,7 @@ 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 + forall a. [a] -> [a]. You can see an example of its use in the motivating example, as this form is used to apply take 5. @@ -1046,7 +1237,7 @@ then group by e This form of grouping is essentially the same as the one described above. However, since no function to use for the grouping has been supplied it will fall back on the groupWith function defined in - GHC.Exts. This + GHC.Exts. This is the form of the group statement that we made use of in the opening example. @@ -1200,6 +1391,44 @@ definitions; you must define such a function in prefix form. + +Tuple sections + + + The flag enables Python-style partially applied + tuple constructors. For example, the following program + + (, True) + + is considered to be an alternative notation for the more unwieldy alternative + + \x -> (x, True) + +You can omit any combination of arguments to the tuple, as in the following + + (, "I", , , "Love", , 1337) + +which translates to + + \a b c d -> (a, "I", b, c, "Love", d, 1337) + + + + + If you have unboxed tuples enabled, tuple sections + will also be available for them, like so + + (# , True #) + +Because there is no unboxed unit tuple, the following expression + + (# #) + +continues to stand for the unboxed singleton tuple data constructor. + + + + Record field disambiguation @@ -1216,7 +1445,6 @@ module Foo where 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 @@ -1232,7 +1460,7 @@ 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 + 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 @@ -1241,6 +1469,37 @@ 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. + +Some details: + + +Field disambiguation can be combined with punning (see ). For exampe: + +module Foo where + import M + x=True + ok3 (MkS { x }) = x+1 -- Uses both disambiguation and punning + + + + +With you can use unqualifed +field names even if the correponding selector is only in scope qualified +For example, assuming the same module M as in our earlier example, this is legal: + +module Foo where + import qualified M -- Note qualified + + ok4 (M.MkS { x = n }) = n+1 -- Unambiguous + +Since the constructore MkS is only in scope qualified, you must +name it M.MkS, but the field x does not need +to be qualified even though M.x is in scope but x +is not. (In effect, it is qualified by the constructor.) + + + + @@ -1277,16 +1536,9 @@ 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). - - - +Note that: + + Record punning can also be used in an expression, writing, for example, let a = 1 in C {a} @@ -1295,12 +1547,41 @@ instead of let a = 1 in C {a = a} - -Note that this expansion is purely syntactic, so the record pun +The expansion is purely syntactic, so the expanded right-hand side expression refers to the nearest enclosing variable that is spelled the same as the field name. + + + +Puns and other patterns can be mixed in the same record: + +data C = C {a :: Int, b :: Int} +f (C {a, b = 4}) = a + + + + +Puns can be used wherever record patterns occur (e.g. in +let bindings or at the top-level). + + + +A pun on a qualified field name is expanded by stripping off the module qualifier. +For example: + +f (C {M.a}) = a + +means + +f (M.C {M.a = a}) = a + +(This is useful if the field selector a for constructor M.C +is only in scope in qualified form.) + + + @@ -1311,6 +1592,7 @@ same as the field name. Record wildcards are enabled by the flag -XRecordWildCards. +This flag implies -XDisambiguateRecordFields. @@ -1323,7 +1605,7 @@ f (C {a = 1, b = b, c = c, d = d}) = b + c + d -Record wildcard syntax permits a (..) in a record +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 @@ -1333,7 +1615,10 @@ f (C {a = 1, ..}) = b + c + d -Note that wildcards can be mixed with other patterns, including puns +More details: + + +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 @@ -1343,24 +1628,38 @@ 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 +The 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. + + + +The ".." expands to the missing +in-scope record fields, where "in scope" +includes both unqualified and qualified-only. +Any fields that are not in scope are not filled in. For example + +module M where + data R = R { a,b,c :: Int } +module X where + import qualified M( R(a,b) ) + f a b = R { .. } + +The {..} expands to {M.a=a,M.b=b}, +omitting c since it is not in scope at all. + + @@ -1390,7 +1689,7 @@ and the fixity declaration applies wherever the binding is in scope. For example, in a let, it applies in the right-hand sides of other let-bindings and the body of the letC. Or, in recursive do -expressions (), the local fixity +expressions (), the local fixity declarations of a let statement scope over other statements in the group, just as the bound name does. @@ -1474,7 +1773,8 @@ The following syntax is stolen: forall - Stolen (in types) by: , + Stolen (in types) by: , and hence by + , , , , @@ -1990,15 +2290,28 @@ main = do display (inc (inc counterB)) -- prints "##" -At the moment, record update syntax is only supported for Haskell 98 data types, -so the following function does not work: - +Record update syntax is supported for existentials (and GADTs): --- This is invalid; use explicit NewCounter instead for now setTag :: Counter a -> a -> Counter a setTag obj t = obj{ tag = t } +The rule for record update is this: +the types of the updated fields may +mention only the universally-quantified type variables +of the data constructor. For GADTs, the field may mention only types +that appear as a simple type-variable argument in the constructor's result +type. For example: + +data T a b where { T1 { f1::a, f2::b, f3::(b,c) } :: T a b } -- c is existential +upd1 t x = t { f1=x } -- OK: upd1 :: T a b -> a' -> T a' b +upd2 t x = t { f3=x } -- BAD (f3's type mentions c, which is + -- existentially quantified) +data G a b where { G1 { g1::a, g2::c } :: G a [c] } +upd3 g x = g { g1=x } -- OK: upd3 :: G a b -> c -> G c b +upd4 g x = g { g2=x } -- BAD (f2's type mentions c, which is not a simple + -- type-variable argument in G1's result type) + @@ -2270,16 +2583,46 @@ otherwise is a generalised data type ( +As with other type signatures, you can give a single signature for several data constructors. +In this example we give a single signature for T1 and T2: + + data T a where + T1,T2 :: a -> T a + T3 :: T a + + + + The type signature of each constructor is independent, and is implicitly universally quantified as usual. -Different constructors may have different universally-quantified type variables -and different type-class constraints. -For example, this is fine: +In particular, the type variable(s) in the "data T a where" header +have no scope, and different constructors may have different universally-quantified type variables: + + data T a where -- The 'a' has no scope + T1,T2 :: b -> T b -- Means forall b. b -> T b + T3 :: T a -- Means forall a. T a + + + + +A constructor signature may mention type class constraints, which can differ for +different constructors. For example, this is fine: data T a where - T1 :: Eq b => b -> T b + T1 :: Eq b => b -> b -> T b T2 :: (Show c, Ix c) => c -> [c] -> T c +When patten matching, these constraints are made available to discharge constraints +in the body of the match. For example: + + f :: T a -> String + f (T1 x y) | x==y = "yes" + | otherwise = "no" + f (T2 a b) = show a + +Note that f is not overloaded; the Eq constraint arising +from the use of == is discharged by the pattern match on T1 +and similarly the Show constraint arising from the use of show. @@ -2291,12 +2634,12 @@ have no scope. Indeed, one can write a kind signature instead: or even a mixture of the two: - data Foo a :: (* -> *) -> * where ... + data Bar a :: (* -> *) -> * where ... The type variables (if given) may be explicitly kinded, so we could also write the header for Foo like this: - data Foo a (b :: * -> *) where ... + data Bar a (b :: * -> *) where ... @@ -2327,27 +2670,48 @@ declaration. For example, these two declarations are equivalent +The type signature may have quantified type variables that do not appear +in the result type: + + data Foo where + MkFoo :: a -> (a->Bool) -> Foo + Nil :: Foo + +Here the type variable a does not appear in the result type +of either constructor. +Although it is universally quantified in the type of the constructor, such +a type variable is often called "existential". +Indeed, the above declaration declares precisely the same type as +the data Foo in . + +The type may contain a class context too, of course: + + data Showable where + MkShowable :: Show a => a -> Showable + + + + You can use record syntax on a GADT-style data type declaration: data Person where - Adult { name :: String, children :: [Person] } :: Person - Child { name :: String } :: Person + Adult :: { name :: String, children :: [Person] } -> Person + Child :: Show a => { name :: !String, funny :: a } -> Person As usual, for every constructor that has a field f, the type of 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 example - - aPerson = Adult { name = "Fred", children = [] } +The Child constructor above shows that the signature +may have a context, existentially-quantified variables, and strictness annotations, +just as in the non-record case. (NB: the "type" that follows the double-colon +is not really a type, because of the record syntax and strictness annotations. +A "type" of this form can appear only in a constructor signature.) + - shortName :: Person -> Bool - hasChildren (Adult { children = kids }) = not (null kids) - hasChildren (Child {}) = False - + +Record updates are allowed with GADT-style declarations, +only fields that have the following property: the type of the field +mentions no existential type variables. @@ -2446,7 +2810,7 @@ constructor). -It's is permitted to declare an ordinary algebraic data type using GADT-style syntax. +It 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. @@ -2558,16 +2922,22 @@ GHC now allows stand-alone deriving declarations, enabled by 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)), +Note the following points: + + +You must supply an explicit 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.) +(In contrast, in a deriving clause +attached to a data type declaration, the context is inferred.) + + 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 @@ -2581,8 +2951,31 @@ for example 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. + + + +Unlike a deriving +declaration attached to a data declaration, +GHC does not restrict the form of the data type. Instead, GHC simply generates the appropriate +boilerplate code for the specified class, and typechecks it. If there is a type error, it is +your problem. (GHC will show you the offending code if it has a type error.) +The merit of this is that you can derive instances for GADTs and other exotic +data types, providing only that the boilerplate code does indeed typecheck. For example: + + data T a where + T1 :: T Int + T2 :: T Bool + + deriving instance Show (T a) + +In this example, you cannot say ... deriving( Show ) on the +data type declaration for T, +because T is a GADT, but you can generate +the instance declaration using stand-alone deriving. + + The stand-alone syntax is generalised for newtypes in exactly the same way that ordinary deriving clauses are generalised (). For example: @@ -2593,13 +2986,14 @@ For example: GHC always treats the last parameter of the instance (Foo in this example) as the type whose instance is being derived. - + + -Deriving clause for classes <literal>Typeable</literal> and <literal>Data</literal> +Deriving clause for extra classes (<literal>Typeable</literal>, <literal>Data</literal>, etc) Haskell 98 allows the programmer to add "deriving( Eq, Ord )" to a data type @@ -2609,11 +3003,11 @@ classes Eq, Ord, Enum, Ix, Bounded, Read, and Show. -GHC extends this list with two more classes that may be automatically derived -(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. +GHC extends this list with several more classes that may be automatically derived: + + With , you can derive instances of the classes +Typeable, and Data, defined in the library +modules Data.Typeable and Data.Generics respectively. An instance of Typeable can only be derived if the data type has seven or fewer type parameters, all of kind *. @@ -2629,6 +3023,26 @@ In other cases, there is nothing to stop the programmer writing a Typab class, whose kind suits that of the data type constructor, and then writing the data type instance by hand. + + + With , you can derive instances of +the class Functor, +defined in GHC.Base. + + + With , you can derive instances of +the class Foldable, +defined in Data.Foldable. + + + With , you can derive instances of +the class Traversable, +defined in Data.Traversable. + + +In each case the appropriate class must be in scope before it +can be mentioned in the deriving clause. + @@ -2853,7 +3267,8 @@ All the extensions are enabled by the flag. Multi-parameter type classes -Multi-parameter type classes are permitted. For example: +Multi-parameter type classes are permitted, with flag . +For example: @@ -2865,13 +3280,17 @@ Multi-parameter type classes are permitted. For example: - + The superclasses of a class declaration -There are no restrictions on the context in a class declaration -(which introduces superclasses), except that the class hierarchy must -be acyclic. So these class declarations are OK: +In Haskell 98 the context of a class declaration (which introduces superclasses) +must be simple; that is, each predicate must consist of a class applied to +type variables. The flag +() +lifts this restriction, +so that the only restriction on the context in a class declaration is +that the class hierarchy must be acyclic. So these class declarations are OK: @@ -2953,7 +3372,7 @@ There should be more documentation, but there isn't (yet). Yell if you need it. Rules for functional dependencies In a class declaration, all of the class type variables must be reachable (in the sense -mentioned in ) +mentioned in ) from the free variables of each method type. For example: @@ -3578,6 +3997,51 @@ of the instance declaration, thus: (You need to do this.) +Warning: overlapping instances must be used with care. They +can give rise to incoherence (ie different instance choices are made +in different parts of the program) even without . Consider: + +{-# LANGUAGE OverlappingInstances #-} +module Help where + + class MyShow a where + myshow :: a -> String + + instance MyShow a => MyShow [a] where + myshow xs = concatMap myshow xs + + showHelp :: MyShow a => [a] -> String + showHelp xs = myshow xs + +{-# LANGUAGE FlexibleInstances, OverlappingInstances #-} +module Main where + import Help + + data T = MkT + + instance MyShow T where + myshow x = "Used generic instance" + + instance MyShow [T] where + myshow xs = "Used more specific instance" + + main = do { print (myshow [MkT]); print (showHelp [MkT]) } + +In function showHelp GHC sees no overlapping +instances, and so uses the MyShow [a] instance +without complaint. In the call to myshow in main, +GHC resolves the MyShow [T] constraint using the overlapping +instance declaration in module Main. As a result, +the program prints + + "Used more specific instance" + "Used generic instance" + +(An alternative possible behaviour, not currently implemented, +would be to reject module Help +on the grounds that a later instance declaration might overlap the local one.) + + The willingness to be overlapped or incoherent is a property of the instance declaration itself, controlled by the presence or otherwise of the @@ -3847,37 +4311,71 @@ data instance GMap (Either a b) v = GMapEither (GMap a v) (GMap b v) can be any number. - Data and newtype instance declarations are only legit when an - appropriate family declaration is in scope - just like class instances - require the class declaration to be visible. Moreover, each instance + Data and newtype instance declarations are only permitted when an + appropriate family declaration is in scope - just as a class instance declaratoin + requires the class declaration to be visible. Moreover, each instance declaration has to conform to the kind determined by its family declaration. This implies that the number of parameters of an instance declaration matches the arity determined by the kind of the family. - Although, all data families are declared with - the data keyword, instances can be - either data or newtypes, or a mix - of both. + A data family instance declaration can use the full exprssiveness of + ordinary data or newtype declarations: + + Although, a data family is introduced with + the keyword "data", a data family instance can + use either data or newtype. For example: + +data family T a +data instance T Int = T1 Int | T2 Bool +newtype instance T Char = TC Bool + + + A data instance can use GADT syntax for the data constructors, + and indeed can define a GADT. For example: + +data family G a b +data instance G [a] b where + G1 :: c -> G [Int] b + G2 :: G [a] Bool + + + You can use a deriving clause on a + data instance or newtype instance + declaration. + + + + + Even if type families are defined as toplevel declarations, functions - that perform different computations for different family instances still + that perform different computations for different family instances may still need to be defined as methods of type classes. In particular, the following is not possible: data family T a data instance T Int = A data instance T Char = B -nonsence :: T a -> Int -nonsence A = 1 -- WRONG: These two equations together... -nonsence B = 2 -- ...will produce a type error. +foo :: T a -> Int +foo A = 1 -- WRONG: These two equations together... +foo B = 2 -- ...will produce a type error. + +Instead, you would have to write foo as a class operation, thus: + +class C a where + foo :: T a -> Int +instance Foo Int where + foo A = 1 +instance Foo Char where + foo B = 2 - Given the functionality provided by GADTs (Generalised Algebraic Data + (Given the functionality provided by GADTs (Generalised Algebraic Data Types), it might seem as if a definition, such as the above, should be feasible. However, type families are - in contrast to GADTs - are open; i.e., new instances can always be added, possibly in other modules. Supporting pattern matching across different data instances - would require a form of extensible case construct. + would require a form of extensible case construct.) @@ -4111,7 +4609,7 @@ type family Elem c example, consider the following declaration: type family F a b :: * -> * -- F's arity is 2, - -- although it's overall kind is * -> * -> * -> * + -- although its overall kind is * -> * -> * -> * Given this declaration the following are examples of well-formed and malformed types: @@ -4370,10 +4868,30 @@ might be in another module, or even in a module that is not yet written. Other type system extensions - -Type signatures +Explicit universal quantification (forall) + +Haskell type signatures are implicitly quantified. When the language option +is used, the keyword forall +allows us to say exactly what this means. For example: + + + + g :: b -> b + +means this: + + g :: forall b. (b -> b) + +The two are treated identically. + + +Of course forall becomes a keyword; you can't use forall as +a type variable any more! + + + -The context of a type signature +The context of a type signature The flag lifts the Haskell 98 restriction that the type-class constraints in a type signature must have the @@ -4385,7 +4903,11 @@ these type signatures are perfectly OK g :: Eq [a] => ... g :: Ord (T a ()) => ... +The flag also lifts the corresponding +restriction on class declarations () and instance declarations +(). + GHC imposes the following restrictions on the constraints in a type signature. Consider the type: @@ -4398,7 +4920,7 @@ Consider the type: language omits them; in Haskell 98, all the free type variables of an explicit source-language type signature are universally quantified, except for the class type variables in a class declaration. However, -in GHC, you can give the foralls if you want. See ). +in GHC, you can give the foralls if you want. See ). @@ -4486,9 +5008,6 @@ territory free in case we need it later. - - - @@ -4966,22 +5485,7 @@ The parentheses are required. -Haskell type signatures are implicitly quantified. The new keyword forall -allows us to say exactly what this means. For example: - - - - g :: b -> b - -means this: - - g :: forall b. (b -> b) - -The two are treated identically. - - - -However, GHC's type system supports arbitrary-rank +GHC's type system supports arbitrary-rank explicit universal quantification in types. For example, all the following types are legal: @@ -5036,8 +5540,6 @@ field type signatures. -Of course forall becomes a keyword; you can't use forall as -a type variable any more! @@ -5274,6 +5776,9 @@ for rank-2 types. Impredicative polymorphism +NOTE: the impredicative-polymorphism feature is deprecated in GHC 6.12, and +will be removed or replaced in GHC 6.14. + GHC supports impredicative polymorphism, enabled with . This means @@ -5309,9 +5814,13 @@ f xs = ys ++ ys ys :: [a] ys = reverse xs -The type signature for f brings the type variable a into scope; it scopes over -the entire definition of f. -In particular, it is in scope at the type signature for ys. +The type signature for f brings the type variable a into scope, +because of the explicit forall (). +The type variables bound by a forall scope over +the entire definition of the accompanying value declaration. +In this example, the type variable a scopes over the whole +definition of f, including over +the type signature for ys. In Haskell 98 it is not possible to declare a type for ys; a major benefit of scoped type variables is that it becomes possible to do so. @@ -5648,6 +6157,21 @@ pattern binding must have the same context. For example, this is fine: + +Monomorphic local bindings + +We are actively thinking of simplifying GHC's type system, by not generalising local bindings. +The rationale is described in the paper +Let should not be generalised. + + +The experimental new behaviour is enabled by the flag . The effect is +that local (that is, non-top-level) bindings without a type signature are not generalised at all. You can +think of it as an extreme (but much more predictable) version of the Monomorphism Restriction. +If you supply a type signature, then the flag has no effect. + + + @@ -5712,29 +6236,34 @@ Wiki page. an expression; the spliced expression must have type Q Exp - a list of top-level declarations; the spliced expression must have type Q [Dec] + an type; the spliced expression must + have type Q Typ + a list of top-level declarations; the spliced expression + must have type Q [Dec] - + Note that pattern splices are not supported. Inside a splice you can can only call functions defined in imported modules, - not functions defined elsewhere in the same module. - + not functions defined elsewhere in the same module. A expression quotation is written in Oxford brackets, thus: - [| ... |], where the "..." is an expression; + [| ... |], or [e| ... |], + where the "..." is an expression; the quotation has type Q Exp. [d| ... |], where the "..." is a list of top-level declarations; the quotation has type Q [Dec]. [t| ... |], where the "..." is a type; - the quotation has type Q Typ. + the quotation has type Q Type. + [p| ... |], where the "..." is a pattern; + the quotation has type Q Pat. A quasi-quotation can appear in either a pattern context or an expression context and is also written in Oxford brackets: - [:varid| ... |], + [varid| ... |], where the "..." is an arbitrary string; a full description of the quasi-quotation facility is given in . @@ -5755,12 +6284,31 @@ Wiki page. + You may omit the $(...) in a top-level declaration splice. + Simply writing an expression (rather than a declaration) implies a splice. For example, you can write + +module Foo where +import Bar + +f x = x + +$(deriveStuff 'f) -- Uses the $(...) notation + +g y = y+1 + +deriveStuff 'g -- Omits the $(...) + +h z = z-1 + + This abbreviation makes top-level declaration slices quieter and less intimidating. + + (Compared to the original paper, there are many differences of detail. The syntax for a declaration splice uses "$" not "splice". The type of the enclosed expression must be Q [Dec], not [Q Dec]. -Type splices are not implemented, and neither are pattern splices or quotations. +Pattern splices and quotations are not implemented.) @@ -5921,19 +6469,67 @@ several examples are documented in Nice to be Quoted: Quasiquoting for Haskell" (Proc Haskell Workshop 2007). The example below shows how to write a quasiquoter for a simple expression language. - -In the example, the quasiquoter expr is bound to a value of -type Language.Haskell.TH.Quote.QuasiQuoter which contains two -functions for quoting expressions and patterns, respectively. The first argument -to each quoter is the (arbitrary) string enclosed in the Oxford brackets. The -context of the quasi-quotation statement determines which of the two parsers is -called: if the quasi-quotation occurs in an expression context, the expression -parser is called, and if it occurs in a pattern context, the pattern parser is -called. +Here are the salient features + + +A quasi-quote has the form +[quoter| string |]. + + +The quoter must be the (unqualified) name of an imported +quoter; it cannot be an arbitrary expression. + + +The quoter cannot be "e", +"t", "d", or "p", since +those overlap with Template Haskell quotations. + + +There must be no spaces in the token +[quoter|. + + +The quoted string +can be arbitrary, and may contain newlines. + + + + +A quasiquote may appear in place of + +An expression +A pattern +A type +A top-level declaration + +(Only the first two are described in the paper.) + + + +A quoter is a value of type Language.Haskell.TH.Quote.QuasiQuoter, +which is defined thus: + +data QuasiQuoter = QuasiQuoter { quoteExp :: String -> Q Exp, + quotePat :: String -> Q Pat, + quoteType :: String -> Q Type, + quoteDec :: String -> Q [Dec] } + +That is, a quoter is a tuple of four parsers, one for each of the contexts +in which a quasi-quote can occur. + + +A quasi-quote is expanded by applying the appropriate parser to the string +enclosed by the Oxford brackets. The context of the quasi-quote (expression, pattern, +type, declaration) determines which of the parsers is called. + + + -Note that in the example we make use of an antiquoted +The example below shows quasi-quotation in action. The quoter expr +is bound to a value of type QuasiQuoter defined in module Expr. +The example makes use of an antiquoted variable n, indicated by the syntax 'int:n (this syntax for anti-quotation was defined by the parser's author, not by GHC). This binds n to the @@ -5945,12 +6541,6 @@ an expression parser that returns a value of type Q Exp and a pattern parser that returns a value of type Q Pat. -In general, a quasi-quote has the form -[$quoter| string |]. -The quoter must be the name of an imported quoter; it -cannot be an arbitrary expression. The quoted string -can be arbitrary, and may contain newlines. - Quasiquoters must obey the same stage restrictions as Template Haskell, e.g., in the example, expr cannot be defined @@ -5958,26 +6548,25 @@ in Main.hs where it is used, but must be imported. - -{- Main.hs -} +{- ------------- file Main.hs --------------- -} module Main where import Expr main :: IO () -main = do { print $ eval [$expr|1 + 2|] +main = do { print $ eval [expr|1 + 2|] ; case IntExpr 1 of - { [$expr|'int:n|] -> print n + { [expr|'int:n|] -> print n ; _ -> return () } } -{- Expr.hs -} +{- ------------- file Expr.hs --------------- -} module Expr where import qualified Language.Haskell.TH as TH -import Language.Haskell.TH.Quasi +import Language.Haskell.TH.Quote data Expr = IntExpr Integer | AntiIntExpr String @@ -6000,7 +6589,7 @@ eval (BinopExpr op x y) = (opToFun op) (eval x) (eval y) opToFun MulOp = (*) opToFun DivOp = div -expr = QuasiQuoter parseExprExp parseExprPat +expr = QuasiQuoter { quoteExp = parseExprExp, quotePat = parseExprPat } -- Parse an Expr, returning its representation as -- either a Q Exp or a Q Pat. See the referenced paper @@ -6016,19 +6605,18 @@ parseExprPat ... Now run the compiler: - $ ghc --make -XQuasiQuotes Main.hs -o main + -Run "main" and here is your output: - +Run "main" and here is your output: $ ./main 3 1 - + @@ -6101,7 +6689,7 @@ The arrows web page at With the flag, GHC supports the arrow notation described in the second of these papers, translating it using combinators from the -Control.Arrow +Control.Arrow module. What follows is a brief introduction to the notation; it won't make much sense unless you've read Hughes's paper. @@ -6216,7 +6804,7 @@ the arrow f, and matches its output against y. In the next line, the output is discarded. The arrow returnA is defined in the -Control.Arrow +Control.Arrow module as arr id. The above example is treated as an abbreviation for @@ -6233,7 +6821,7 @@ arr (\ x -> (x, x)) >>> Note that variables not used later in the composition are projected out. After simplification using rewrite rules (see ) defined in the -Control.Arrow +Control.Arrow module, this reduces to arr (\ x -> (x+1, x)) >>> @@ -6529,7 +7117,7 @@ additional restrictions: The module must import -Control.Arrow. +Control.Arrow. @@ -6561,13 +7149,24 @@ Because the preprocessor targets Haskell (rather than Core), Bang patterns GHC supports an extension of pattern matching called bang -patterns. Bang patterns are under consideration for Haskell Prime. +patterns, written !pat. +Bang patterns are under consideration for Haskell Prime. The Haskell prime feature description contains more discussion and examples than the material below. +The key change is the addition of a new rule to the +semantics of pattern matching in the Haskell 98 report. +Add new bullet 10, saying: Matching the pattern !pat +against a value v behaves as follows: + +if v is bottom, the match diverges +otherwise, pat is matched against v + + + Bang patterns are enabled by the flag . @@ -6598,9 +7197,40 @@ A bang only really has an effect if it precedes a variable or wild-card pattern: f3 !(x,y) = [x,y] f4 (x,y) = [x,y] -Here, f3 and f4 are identical; putting a bang before a pattern that +Here, f3 and f4 are identical; +putting a bang before a pattern that forces evaluation anyway does nothing. - + + +There is one (apparent) exception to this general rule that a bang only +makes a difference when it precedes a variable or wild-card: a bang at the +top level of a let or where +binding makes the binding strict, regardless of the pattern. For example: + +let ![x,y] = e in b + +is a strict binding: operationally, it evaluates e, matches +it against the pattern [x,y], and then evaluates b. +(We say "apparent" exception because the Right Way to think of it is that the bang +at the top of a binding is not part of the pattern; rather it +is part of the syntax of the binding.) +Nested bangs in a pattern binding behave uniformly with all other forms of +pattern matching. For example + +let (!x,[y]) = e in b + +is equivalent to this: + +let { t = case e of (x,[y]) -> x `seq` (x,y) + x = fst t + y = snd t } +in b + +The binding is lazy, but when either x or y is +evaluated by b the entire pattern is matched, including forcing the +evaluation of x. + + Bang patterns work in case expressions too, of course: g5 x = let y = f x in body @@ -6610,18 +7240,6 @@ g7 x = case f x of { !y -> body } The functions g5 and g6 mean exactly the same thing. But g7 evaluates (f x), binds y to the result, and then evaluates body. - -Bang patterns work in let and where -definitions too. For example: - -let ![x,y] = e in b - -is a strict pattern: operationally, it evaluates e, matches -it against the pattern [x,y], and then evaluates b -The "!" should not be regarded as part of the pattern; after all, -in a function argument ![x,y] means the -same as [x,y]. Rather, the "!" -is part of the syntax of let bindings. @@ -6807,14 +7425,31 @@ Assertion failures can be caught, see the documentation for the word. The various values for word that GHC understands are described in the following sections; any pragma encountered with an - unrecognised word is (silently) + unrecognised word is 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. + 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. + preceded or followed by comments. + + + File-header pragmas are read once only, before + pre-processing the file (e.g. with cpp). + + + The file-header pragmas are: {-# LANGUAGE #-}, + {-# OPTIONS_GHC #-}, and + {-# INCLUDE #-}. + + + LANGUAGE pragma @@ -6846,7 +7481,7 @@ Assertion failures can be caught, see the documentation for the Any extension from the Extension type defined in Language.Haskell.Extension + url="&libraryCabalLocation;/Language-Haskell-Extension.html">Language.Haskell.Extension may be used. GHC will report an error if any of the requested extensions are not supported. @@ -6872,24 +7507,11 @@ 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> #-} - - 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. + The INCLUDE used to be necessary for + specifying header files to be included when using the FFI and + compiling via C. It is no longer required for GHC, but is + accepted (and ignored) for compatibility with other + compilers. @@ -7055,6 +7677,14 @@ itself, so an INLINE pragma is always ignored. portable). + + CONLIKE modifier + CONLIKE + An INLINE or NOINLINE pragma may have a CONLIKE modifier, + which affects matching in RULEs (only). See . + + + Phase control @@ -7122,6 +7752,83 @@ happen. + + ANN pragmas + + GHC offers the ability to annotate various code constructs with additional + data by using three pragmas. This data can then be inspected at a later date by + using GHC-as-a-library. + + + Annotating values + + ANN + + Any expression that has both Typeable and Data instances may be attached to a top-level value + binding using an ANN pragma. In particular, this means you can use ANN + to annotate data constructors (e.g. Just) as well as normal values (e.g. take). + By way of example, to annotate the function foo with the annotation Just "Hello" + you would do this: + + +{-# ANN foo (Just "Hello") #-} +foo = ... + + + + A number of restrictions apply to use of annotations: + + The binder being annotated must be at the top level (i.e. no nested binders) + The binder being annotated must be declared in the current module + The expression you are annotating with must have a type with Typeable and Data instances + The Template Haskell staging restrictions apply to the + expression being annotated with, so for example you cannot run a function from the module being compiled. + + To be precise, the annotation {-# ANN x e #-} is well staged if and only if $(e) would be + (disregarding the usual type restrictions of the splice syntax, and the usual restriction on splicing inside a splice - $([|1|]) is fine as an annotation, albeit redundant). + + + If you feel strongly that any of these restrictions are too onerous, + please give the GHC team a shout. + + + However, apart from these restrictions, many things are allowed, including expressions which are not fully evaluated! + Annotation expressions will be evaluated by the compiler just like Template Haskell splices are. So, this annotation is fine: + + +{-# ANN f SillyAnnotation { foo = (id 10) + $([| 20 |]), bar = 'f } #-} +f = ... + + + + + Annotating types + + ANN type + ANN + + You can annotate types with the ANN pragma by using the type keyword. For example: + + +{-# ANN type Foo (Just "A `Maybe String' annotation") #-} +data Foo = ... + + + + + Annotating modules + + ANN module + ANN + + You can annotate modules with the ANN pragma by using the module keyword. For example: + + +{-# ANN module (Just "A `Maybe String' annotation") #-} + + + + LINE pragma @@ -7613,18 +8320,24 @@ not be substituted, and the rule would not fire. - + + + + + + + +How rules interact with INLINE/NOINLINE and CONLIKE pragmas Ordinary inlining happens at the same time as rule rewriting, which may lead to unexpected results. Consider this (artificial) example f x = x -{-# RULES "f" f True = False #-} - g y = f y - h z = g True + +{-# RULES "f" f True = False #-} Since f's right-hand side is small, it is inlined into g, to give @@ -7638,14 +8351,37 @@ would have been a better chance that f's RULE might fire. The way to get predictable behaviour is to use a NOINLINE -pragma on f, to ensure +pragma, or an INLINE[phase] pragma, on f, to ensure that it is not inlined until its RULEs have had a chance to fire. - - - + +GHC is very cautious about duplicating work. For example, consider + +f k z xs = let xs = build g + in ...(foldr k z xs)...sum xs... +{-# RULES "foldr/build" forall k z g. foldr k z (build g) = g k z #-} + +Since xs is used twice, GHC does not fire the foldr/build rule. Rightly +so, because it might take a lot of work to compute xs, which would be +duplicated if the rule fired. + + +Sometimes, however, this approach is over-cautious, and we do want the +rule to fire, even though doing so would duplicate redex. There is no way that GHC can work out +when this is a good idea, so we provide the CONLIKE pragma to declare it, thus: + +{-# INLINE[1] CONLIKE f #-} +f x = blah + +CONLIKE is a modifier to an INLINE or NOINLINE pragam. It specifies that an application +of f to one argument (in general, the number of arguments to the left of the '=' sign) +should be considered cheap enough to duplicate, if such a duplication would make rule +fire. (The name "CONLIKE" is short for "constructor-like", because constructors certainly +have such a property.) +The CONLIKE pragam is a modifier to INLINE/NOINLINE because it really only makes sense to match +f on the LHS of a rule if you are sure that f is +not going to be inlined before the rule has a chance to fire. - @@ -7905,8 +8641,8 @@ comparison. - -Controlling what's going on + +Controlling what's going on in rewrite rules @@ -7914,18 +8650,28 @@ comparison. - Use to see what transformation rules GHC is using. +Use to see the rules that are defined +in this module. +This includes rules generated by the specialisation pass, but excludes +rules imported from other modules. - + Use to see what rules are being fired. If you add you get a more detailed listing. + + + Use to see in great detail what rules are being fired. +If you add you get a still more detailed listing. + + + The definition of (say) build in GHC/Base.lhs looks like this: @@ -8026,7 +8772,7 @@ r) -> Special built-in functions GHC has a few built-in functions with special behaviour. These are now described in the module GHC.Prim +url="&libraryGhcPrimLocation;/GHC-Prim.html">GHC.Prim in the library documentation.