X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fdocs%2Fusers_guide%2Fglasgow_exts.sgml;h=a3ff83c2507625172ed20eeb6402025d57ff20e7;hb=a8cf15f207bb5b3d7173cf8e2f9314ad9a80d40b;hp=e5202b8cee81aa0d69ac57d729e927fb43adf891;hpb=7fc19edc1a604c30159113404d02489142c84d42;p=ghc-hetmet.git diff --git a/ghc/docs/users_guide/glasgow_exts.sgml b/ghc/docs/users_guide/glasgow_exts.sgml index e5202b8..a3ff83c 100644 --- a/ghc/docs/users_guide/glasgow_exts.sgml +++ b/ghc/docs/users_guide/glasgow_exts.sgml @@ -16,167 +16,15 @@ performance because of the implementation costs of Haskell's -Executive summary of our extensions: - - - - - - Unboxed types and primitive operations: - - You can get right down to the raw machine types and - operations; included in this are “primitive - arrays” (direct access to Big Wads of Bytes). Please - see and following. - - - - - Type system extensions: - - GHC supports a large number of extensions to Haskell's - type system. Specifically: - - - - Class method types: - - - - - - - Multi-parameter type classes: - - - - - - - Functional dependencies: - - - - - - - Implicit parameters: - - - - - - - Linear implicit parameters: - - - - - - - Local universal quantification: - - - - - - - Extistentially quantification in data types: - - - - - - - Scoped type variables: - - Scoped type variables enable the programmer to - supply type signatures for some nested declarations, - where this would not be legal in Haskell 98. Details in - . - - - - - - - - Pattern guards - - Instead of being a boolean expression, a guard is a list - of qualifiers, exactly as in a list comprehension. See . - - - - - Data types with no constructors - - See . - - - - - Parallel list comprehensions - - An extension to the list comprehension syntax to support - zipWith-like functionality. See . - - - - - Foreign calling: - - Just what it sounds like. We provide - lots of rope that you can dangle around - your neck. Please see . - - - - - Pragmas - - Pragmas are special instructions to the compiler placed - in the source file. The pragmas GHC supports are described in - . - - - - - Rewrite rules: - - The programmer can specify rewrite rules as part of the - source program (in a pragma). GHC applies these rewrite rules - wherever it can. Details in . - - - - - Generic classes: - - (Note: support for generic classes is currently broken - in GHC 5.02). - - Generic class declarations allow you to define a class - whose methods say how to work over an arbitrary data type. - Then it's really easy to make any new type into an instance of - the class. This generalises the rather ad-hoc "deriving" - feature of Haskell 98. Details in . - - - - - Before you get too carried away working at the lowest level (e.g., sloshing MutableByteArray#s around your program), you may wish to check if there are libraries that provide a -“Haskellised veneer” over the features you want. See -. +“Haskellised veneer” over the features you want. The +separate libraries documentation describes all the libraries that come +with GHC. + Language options @@ -205,6 +53,30 @@ program), you may wish to check if there are libraries that provide a + and : + + + + This option enables the language extension defined in the + Haskell 98 Foreign Function Interface Addendum plus deprecated + syntax of previous versions of the FFI for backwards + compatibility. + + + + + : + + + This option enables the deprecated with + keyword for implicit parameters; it is merely provided for backwards + compatibility. + It is independent of the + flag. + + + + : @@ -259,7 +131,7 @@ program), you may wish to check if there are libraries that provide a module namespace is flat, and you must not conflict with any Prelude module.) - Even though you have not imported the Prelude, all + Even though you have not imported the Prelude, most of the built-in syntax still refers to the built-in Haskell Prelude types and values, as specified by the Haskell Report. For example, the type [Int] @@ -268,51 +140,9 @@ program), you may wish to check if there are libraries that provide a translation for list comprehensions continues to use Prelude.map etc. - With one group of exceptions! You may want to - define your own numeric class hierarchy. It completely - defeats that purpose if the literal "1" means - "Prelude.fromInteger 1", which is what - the Haskell Report specifies. So the - flag causes the - following pieces of built-in syntax to refer to whatever - is in scope, not the Prelude versions: - - - - Integer and fractional literals mean - "fromInteger 1" and - "fromRational 3.2", not the - Prelude-qualified versions; both in expressions and in - patterns. - - - - Negation (e.g. "- (f x)") - means "negate (f x)" (not - Prelude.negate). - - - - In an n+k pattern, the standard Prelude - Ord class is still used for comparison, - but the necessary subtraction uses whatever - "(-)" is in scope (not - "Prelude.(-)"). - - - - Note: Negative literals, such as -3, are - specified by (a careful reading of) the Haskell Report as - meaning Prelude.negate (Prelude.fromInteger 3). - However, GHC deviates from this slightly, and treats them as meaning - fromInteger (-3). One particular effect of this - slightly-non-standard reading is that there is no difficulty with - the literal -2147483648 at type Int; - it means fromInteger (-2147483648). The strict interpretation - would be negate (fromInteger 2147483648), - and the call to fromInteger would overflow - (at type Int, remember). - + However, does + change the handling of certain built-in syntax: see + . @@ -321,321 +151,150 @@ program), you may wish to check if there are libraries that provide a + &primitives; - -Primitive state-transformer monad - - -state transformers (Glasgow extensions) -ST monad (Glasgow extension) - - - -This monad underlies our implementation of arrays, mutable and -immutable, and our implementation of I/O, including “C calls”. - - - -The ST library, which provides access to the -ST monad, is described in . - - - - - -Primitive arrays, mutable and otherwise - - - -primitive arrays (Glasgow extension) -arrays, primitive (Glasgow extension) - - - -GHC knows about quite a few flavours of Large Swathes of Bytes. - - - -First, GHC distinguishes between primitive arrays of (boxed) Haskell -objects (type Array# obj) and primitive arrays of bytes (type -ByteArray#). - - - -Second, it distinguishes between… - - - -Immutable: - - -Arrays that do not change (as with “standard” Haskell arrays); you -can only read from them. Obviously, they do not need the care and -attention of the state-transformer monad. - - - - -Mutable: - - -Arrays that may be changed or “mutated.” All the operations on them -live within the state-transformer monad and the updates happen -in-place. - - - - -“Static” (in C land): - - -A C routine may pass an Addr# pointer back into Haskell land. There -are then primitive operations with which you may merrily grab values -over in C land, by indexing off the “static” pointer. - - - - -“Stable” pointers: - - -If, for some reason, you wish to hand a Haskell pointer (i.e., -not an unboxed value) to a C routine, you first make the -pointer “stable,” so that the garbage collector won't forget that it -exists. That is, GHC provides a safe way to pass Haskell pointers to -C. - - - -Please see for more details. - - - - -“Foreign objects”: - - -A “foreign object” is a safe way to pass an external object (a -C-allocated pointer, say) to Haskell and have Haskell do the Right -Thing when it no longer references the object. So, for example, C -could pass a large bitmap over to Haskell and say “please free this -memory when you're done with it.” - - -Please see for more details. - - - - - + + +Type system extensions - -The libraries documentatation gives more details on all these -“primitive array” types and the operations on them. - - - - - - + Data types with no constructors With the flag, GHC lets you declare a data type with no constructors. For example: + data S -- S :: * data T a -- T :: * -> * + Syntactically, the declaration lacks the "= constrs" part. The -type can be parameterised, but only over ordinary types, of kind *; since -Haskell does not have kind signatures, you cannot parameterise over higher-kinded -types. +type can be parameterised over types of any kind, but if the kind is +not * then an explicit kind annotation must be used +(see ). Such data types have only one value, namely bottom. Nevertheless, they can be useful when defining "phantom types". - - - -Pattern guards - - -Pattern guards (Glasgow extension) -The discussion that follows is an abbreviated version of Simon Peyton Jones's original proposal. (Note that the proposal was written before pattern guards were implemented, so refers to them as unimplemented.) - - - -Suppose we have an abstract data type of finite maps, with a -lookup operation: - - -lookup :: FiniteMap -> Int -> Maybe Int - - -The lookup returns Nothing if the supplied key is not in the domain of the mapping, and (Just v) otherwise, -where v is the value that the key maps to. Now consider the following definition: - - - -clunky env var1 var2 | ok1 && ok2 = val1 + val2 -| otherwise = var1 + var2 -where - m1 = lookup env var1 - m2 = lookup env var2 - ok1 = maybeToBool m1 - ok2 = maybeToBool m2 - val1 = expectJust m1 - val2 = expectJust m2 - - - -The auxiliary functions are - + - -maybeToBool :: Maybe a -> Bool -maybeToBool (Just x) = True -maybeToBool Nothing = False - -expectJust :: Maybe a -> a -expectJust (Just x) = x -expectJust Nothing = error "Unexpected Nothing" - + +Infix type constructors -What is clunky doing? The guard ok1 && -ok2 checks that both lookups succeed, using -maybeToBool to convert the Maybe -types to booleans. The (lazily evaluated) expectJust -calls extract the values from the results of the lookups, and binds the -returned values to val1 and val2 -respectively. If either lookup fails, then clunky takes the -otherwise case and returns the sum of its arguments. - +GHC allows type constructors to be operators, and to be written infix, very much +like expressions. More specifically: + + + A type constructor can be an operator, beginning with a colon; e.g. :*:. + The lexical syntax is the same as that for data constructors. + + + Types can be written infix. For example Int :*: Bool. + + + Back-quotes work + as for expressions, both for type constructors and type variables; e.g. Int `Either` Bool, or + Int `a` Bool. Similarly, parentheses work the same; e.g. (:*:) Int Bool. + + + Fixities may be declared for type constructors just as for data constructors. However, + one cannot distinguish between the two in a fixity declaration; a fixity declaration + sets the fixity for a data constructor and the corresponding type constructor. For example: + + infixl 7 T, :*: + + sets the fixity for both type constructor T and data constructor T, + and similarly for :*:. + Int `a` Bool. + + + Function arrow is infixr with fixity 0. (This might change; I'm not sure what it should be.) + + + Data type and type-synonym declarations can be written infix. E.g. + + data a :*: b = Foo a b + type a :+: b = Either a b + + + + The only thing that differs between operators in types and operators in expressions is that + ordinary non-constructor operators, such as + and * + are not allowed in types. Reason: the uniform thing to do would be to make them type + variables, but that's not very useful. A less uniform but more useful thing would be to + allow them to be type constructors. But that gives trouble in export + lists. So for now we just exclude them. + - -This is certainly legal Haskell, but it is a tremendously verbose and -un-obvious way to achieve the desired effect. Arguably, a more direct way -to write clunky would be to use case expressions: + + - -clunky env var1 var1 = case lookup env var1 of - Nothing -> fail - Just val1 -> case lookup env var2 of - Nothing -> fail - Just val2 -> val1 + val2 -where - fail = val1 + val2 - - - -This is a bit shorter, but hardly better. Of course, we can rewrite any set -of pattern-matching, guarded equations as case expressions; that is -precisely what the compiler does when compiling equations! The reason that -Haskell provides guarded equations is because they allow us to write down -the cases we want to consider, one at a time, independently of each other. -This structure is hidden in the case version. Two of the right-hand sides -are really the same (fail), and the whole expression -tends to become more and more indented. - + +Explicitly-kinded quantification -Here is how I would write clunky: +Haskell infers the kind of each type variable. Sometimes it is nice to be able +to give the kind explicitly as (machine-checked) documentation, +just as it is nice to give a type signature for a function. On some occasions, +it is essential to do so. For example, in his paper "Restricted Data Types in Haskell" (Haskell Workshop 1999) +John Hughes had to define the data type: + + data Set cxt a = Set [a] + | Unused (cxt a -> ()) + +The only use for the Unused constructor was to force the correct +kind for the type variable cxt. - - -clunky env var1 var1 - | Just val1 <- lookup env var1 - , Just val2 <- lookup env var2 - = val1 + val2 -...other equations for clunky... - - -The semantics should be clear enough. The qualifers are matched in order. -For a <- qualifier, which I call a pattern guard, the -right hand side is evaluated and matched against the pattern on the left. -If the match fails then the whole guard fails and the next equation is -tried. If it succeeds, then the appropriate binding takes place, and the -next qualifier is matched, in the augmented environment. Unlike list -comprehensions, however, the type of the expression to the right of the -<- is the same as the type of the pattern to its -left. The bindings introduced by pattern guards scope over all the -remaining guard qualifiers, and over the right hand side of the equation. +GHC now instead allows you to specify the kind of a type variable directly, wherever +a type variable is explicitly bound. Namely: + +data declarations: + + data Set (cxt :: * -> *) a = Set [a] + +type declarations: + + type T (f :: * -> *) = f Int + +class declarations: + + class (Eq a) => C (f :: * -> *) a where ... + +forall's in type signatures: + + f :: forall (cxt :: * -> *). Set cxt Int + + -Just as with list comprehensions, boolean expressions can be freely mixed -with among the pattern guards. For example: +The parentheses are required. Some of the spaces are required too, to +separate the lexemes. If you write (f::*->*) you +will get a parse error, because "::*->*" is a +single lexeme in Haskell. - -f x | [y] <- x - , y > 3 - , Just z <- h y - = ... - - -Haskell's current guards therefore emerge as a special case, in which the -qualifier list has just one element, a boolean expression. +As part of the same extension, you can put kind annotations in types +as well. Thus: + + f :: (Int :: *) -> Int + g :: forall a. a -> (a :: *) + +The syntax is + + atype ::= '(' ctype '::' kind ') + +The parentheses are required. - - - - Parallel List Comprehensions - list comprehensionsparallel - - parallel list comprehensions - - - Parallel list comprehensions are a natural extension to list - comprehensions. List comprehensions can be thought of as a nice - syntax for writing maps and filters. Parallel comprehensions - extend this to include the zipWith family. - - A parallel list comprehension has multiple independent - branches of qualifier lists, each separated by a `|' symbol. For - example, the following zips together two lists: - - - [ (x, y) | x <- xs | y <- ys ] - - - The behavior of parallel list comprehensions follows that of - zip, in that the resulting list will have the same length as the - shortest branch. - - We can define parallel list comprehensions by translation to - regular comprehensions. Here's the basic idea: - - Given a parallel comprehension of the form: - - - [ e | p1 <- e11, p2 <- e12, ... - | q1 <- e21, q2 <- e22, ... - ... - ] - - - This will be translated to: - - - [ e | ((p1,p2), (q1,q2), ...) <- zipN [(p1,p2) | p1 <- e11, p2 <- e12, ...] - [(q1,q2) | q1 <- e21, q2 <- e22, ...] - ... - ] - - - where `zipN' is the appropriate zip for the given number of - branches. + - - + Class method types @@ -654,9 +313,9 @@ class type variable (in this case a). With the GHC lifts this restriction. - + - + Multi-parameter type classes @@ -683,7 +342,7 @@ Thanks to him, and to many others who have offered very useful feedback. - + Types @@ -797,9 +456,9 @@ are perfectly OK This choice recovers principal types, a property that Haskell 1.4 does not have. - + - + Class declarations @@ -959,9 +618,9 @@ class like this: - + - + Instance declarations @@ -1224,11 +883,11 @@ with N. - + - + - + Implicit parameters @@ -1300,24 +959,45 @@ is (?x::a) => (a,a), and not class constraints. -An implicit parameter is bound using an expression of the form -expr with binds, -where with is a new keyword. This form binds the implicit -parameters arising in the body, not the free variables as a let or -where would do. For example, we define the min function by binding -cmp. +An implicit parameter is bound using the standard +let binding form, where the bindings must be a +collection of simple bindings to implicit-style variables (no +function-style bindings, and no type signatures); these bindings are +neither polymorphic or recursive. This form binds the implicit +parameters arising in the body, not the free variables as a +let or where would do. For +example, we define the min function by binding +cmp. min :: [a] -> a - min = least with ?cmp = (<=) + min = let ?cmp = (<=) in least -Syntactically, the binds part of a with construct must be a -collection of simple bindings to variables (no function-style -bindings, and no type signatures); these bindings are neither -polymorphic or recursive. - -Note the following additional constraints: +Note the following points: + +You may not mix implicit-parameter bindings with ordinary bindings in a +single let +expression; use two nested lets instead. + + + +You may put multiple implicit-parameter bindings in a +single let expression; they are not treated +as a mutually recursive group (as ordinary let bindings are). +Instead they are treated as a non-recursive group, each scoping over the bindings that +follow. For example, consider: + + f y = let { ?x = y; ?x = ?x+1 } in ?x + +This function adds one to its argument. + + + +You may not have an implicit-parameter binding in a where clause, +only in a let binding. + + You can't have an implicit parameter in the context of a class or instance declaration. For example, both these declarations are illegal: @@ -1333,9 +1013,9 @@ Easiest thing is to outlaw the offending types. - + - + Linear implicit parameters @@ -1359,12 +1039,14 @@ written '%x' instead of '?x'. For example: + import GHC.Exts( Splittable ) + data NameSupply = ... splitNS :: NameSupply -> (NameSupply, NameSupply) newName :: NameSupply -> Name - instance PrelSplit.Splittable NameSupply where + instance Splittable NameSupply where split = splitNS @@ -1395,7 +1077,7 @@ the parameter explicit: Notice the call to 'split' introduced by the type checker. How did it know to use 'splitNS'? Because what it really did was to introduce a call to the overloaded function 'split', -defined by +defined by the class Splittable: class Splittable a where split :: a -> (a,a) @@ -1409,8 +1091,8 @@ and GHC will infer g :: (Splittable a, %ns :: a) => b -> (b,a,a) -The Splittable class is built into GHC. It's defined in PrelSplit, -and exported by GlaExts. +The Splittable class is built into GHC. It's exported by module +GHC.Exts. Other points: @@ -1427,7 +1109,7 @@ are entirely distinct implicit parameters: you -Warnings +Warnings The monomorphism restriction is even more important than usual. @@ -1459,28 +1141,70 @@ parameters we have already lost beta reduction anyway, and Haskell programs without knowing their typing. - + - +Recursive functions +Linear implicit parameters can be particularly tricky when you have a recursive function +Consider + + foo :: %x::T => Int -> [Int] + foo 0 = [] + foo n = %x : foo (n-1) + +where T is some type in class Splittable. + +Do you get a list of all the same T's or all different T's +(assuming that split gives two distinct T's back)? + +If you supply the type signature, taking advantage of polymorphic +recursion, you get what you'd probably expect. Here's the +translated term, where the implicit param is made explicit: + + foo x 0 = [] + foo x n = let (x1,x2) = split x + in x1 : foo x2 (n-1) + +But if you don't supply a type signature, GHC uses the Hindley +Milner trick of using a single monomorphic instance of the function +for the recursive calls. That is what makes Hindley Milner type inference +work. So the translation becomes + + foo x = let + foom 0 = [] + foom n = x : foom (n-1) + in + foom + +Result: 'x' is not split, and you get a list of identical T's. So the +semantics of the program depends on whether or not foo has a type signature. +Yikes! + +You may say that this is a good reason to dislike linear implicit parameters +and you'd be right. That is why they are an experimental feature. + + - + + + Functional dependencies 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. +ESOP 2000, Berlin, Germany, March 2000, Springer-Verlag LNCS 1782, +. There should be more documentation, but there isn't (yet). Yell if you need it. - + - -Explicit universal quantification +<sect2 id="universal-quantification"> +<title>Arbitrary-rank polymorphism @@ -1554,7 +1278,7 @@ a type variable any more! - + Examples @@ -1686,9 +1410,9 @@ and bind to extract the polymorphic bind and return functions from the MonadT data structure, rather than using pattern matching. - + - + Type inference @@ -1732,10 +1456,10 @@ it is an argument of constructor T1 and that tells GHC all it needs to know. - + - + Implicit quantification @@ -1780,16 +1504,17 @@ but at least the rule is simple. If you want the latter type, you can write your for-alls explicitly. Indeed, doing so is strongly advised for rank-2 types. + - - -Type synonyms and hoisting +<sect2 id="type-synonyms"> +<title>Liberalised type synonyms -Type synonmys are like macros at the type level, and GHC is much more liberal -about them than Haskell 98. In particular: +Type synonmys are like macros at the type level, and +GHC does validity checking on types only after expanding type synonyms. +That means that GHC can be very much more liberal about type synonyms than Haskell 98: You can write a forall (including overloading) in a type synonym, thus: @@ -1814,11 +1539,56 @@ You can write an unboxed tuple in a type synonym: h x = (# x, x #) + + +You can apply a type synonym to a forall type: + + type Foo a = a -> a -> Bool + + f :: Foo (forall b. b->b) + +After expanding the synonym, f has the legal (in GHC) type: + + f :: (forall b. b->b) -> (forall b. b->b) -> Bool + + + + +You can apply a type synonym to a partially applied type synonym: + + type Generic i o = forall x. i x -> o x + type Id x = x + + foo :: Generic Id [] + +After epxanding the synonym, foo has the legal (in GHC) type: + + foo :: forall x. x -> [x] + + + + + +GHC currently does kind checking before expanding synonyms (though even that +could be changed.) + -GHC does validity checking on types after expanding type synonyms -so, for example, +After expanding type synonyms, GHC does validity checking on types, looking for +the following mal-formedness which isn't detected simply by kind checking: + + +Type constructor applied to a type involving for-alls. + + +Unboxed tuple on left of an arrow. + + +Partially-applied type synonym. + + +So, for example, this will be rejected: type Pr = (# Int, Int #) @@ -1828,9 +1598,12 @@ this will be rejected: because GHC does not allow unboxed tuples on the left of a function arrow. + + +For-all hoisting -However, it is often convenient to use these sort of generalised synonyms at the right hand +It is often convenient to use generalised type synonyms at the right hand end of an arrow, thus: type Discard a = forall b. a -> b -> a @@ -1862,10 +1635,22 @@ valid way to write g's type signature: g :: Int -> Int -> forall b. b -> Int - + +When doing this hoisting operation, GHC eliminates duplicate constraints. For +example: + + type Foo a = (?x::Int) => Bool -> a + g :: Foo (Foo Int) + +means + + g :: (?x::Int) => Bool -> Bool -> Int + + + - + Existentially quantified data constructors @@ -1955,7 +1740,7 @@ that collection of packages in a uniform manner. You can express quite a bit of object-oriented-like programming this way. - + Why existential? @@ -1978,9 +1763,9 @@ But Haskell programmers can safely think of the ordinary adding a new existential quantification construct. - + - + Type classes @@ -2040,9 +1825,9 @@ Notice the way that the syntax fits smoothly with that used for universal quantification earlier. - + - + Restrictions @@ -2113,8 +1898,13 @@ bindings. So this is illegal: f3 x = a==b where { Baz1 a b = x } +Instead, use a case expression: + + + f3 x = case x of Baz1 a b -> a==b + -You can only pattern-match +In general, you can only pattern-match on an existentially-quantified constructor in a case expression or in the patterns of a function definition. @@ -2186,12 +1976,12 @@ declarations. Define your own instances! - + - + - -Scoped Type Variables +<sect2 id="scoped-type-variables"> +<title>Scoped type variables @@ -2241,7 +2031,7 @@ are noted. So much for the basic idea. Here are the details. - + What a pattern type signature means A type variable brought into scope by a pattern type signature is simply @@ -2279,9 +2069,9 @@ For example, all of these are legal: w (x::a) = x -- a unifies with [b] - + - + Scope and implicit quantification @@ -2413,9 +2203,9 @@ scope over the methods defined in the where part. For exampl - + - + Result type signatures @@ -2456,9 +2246,9 @@ you want: Result type signatures are not yet implemented in Hugs. - + - + Where a pattern type signature can occur @@ -2501,219 +2291,560 @@ in case expressions: - + + + + +To avoid ambiguity, the type after the “::” in a result +pattern signature on a lambda or case must be atomic (i.e. a single +token or a parenthesised type of some sort). To see why, +consider how one would parse this: + + + + \ x :: a -> b -> x + + + + + + + + + + Pattern type signatures can bind existential type variables. +For example: + + + + data T = forall a. MkT [a] + + f :: T -> T + f (MkT [t::a]) = MkT t3 + where + t3::[a] = [t,t,t] + + + + + + + + + + +Pattern type signatures +can be used in pattern bindings: + + + f x = let (y, z::a) = x in ... + f1 x = let (y, z::Int) = x in ... + f2 (x::(Int,a)) = let (y, z::a) = x in ... + f3 :: (b->b) = \x -> x + + +In all such cases, the binding is not generalised over the pattern-bound +type variables. Thus f3 is monomorphic; f3 +has type b -> b for some type b, +and not forall b. b -> b. +In contrast, the binding + + f4 :: b->b + f4 = \x -> x + +makes a polymorphic function, but b is not in scope anywhere +in f4's scope. + + + + + + + + + + + + + + + + + +Assertions +<indexterm><primary>Assertions</primary></indexterm> + + + +If you want to make use of assertions in your standard Haskell code, you +could define a function like the following: + + + + + +assert :: Bool -> a -> a +assert False x = error "assertion failed!" +assert _ x = x + + + + + +which works, but gives you back a less than useful error message -- +an assertion failed, but which and where? + + + +One way out is to define an extended assert function which also +takes a descriptive string to include in the error message and +perhaps combine this with the use of a pre-processor which inserts +the source location where assert was used. + + + +Ghc offers a helping hand here, doing all of this for you. For every +use of assert in the user's source: + + + + + +kelvinToC :: Double -> Double +kelvinToC k = assert (k >= 0.0) (k+273.15) + + + + + +Ghc will rewrite this to also include the source location where the +assertion was made, + + + + + +assert pred val ==> assertError "Main.hs|15" pred val + + + + + +The rewrite is only performed by the compiler when it spots +applications of Control.Exception.assert, so you +can still define and use your own versions of +assert, should you so wish. If not, import +Control.Exception to make use +assert in your code. + + + +To have the compiler ignore uses of assert, use the compiler option +. -fignore-asserts +option That is, expressions of the form +assert pred e will be rewritten to +e. + + + +Assertion failures can be caught, see the documentation for the +Control.Exception library for the details. + + + + + + +Syntactic extensions + + + + + Hierarchical Modules + + GHC supports a small extension to the syntax of module + names: a module name is allowed to contain a dot + ‘.’. This is also known as the + “hierarchical module namespace” extension, because + it extends the normally flat Haskell module namespace into a + more flexible hierarchy of modules. + + This extension has very little impact on the language + itself; modules names are always fully + qualified, so you can just think of the fully qualified module + name as the module name. In particular, this + means that the full module name must be given after the + module keyword at the beginning of the + module; for example, the module A.B.C must + begin + +module A.B.C + + + It is a common strategy to use the as + keyword to save some typing when using qualified names with + hierarchical modules. For example: + + +import qualified Control.Monad.ST.Strict as ST + + + Hierarchical modules have an impact on the way that GHC + searches for files. For a description, see . + + GHC comes with a large collection of libraries arranged + hierarchically; see the accompanying library documentation. + There is an ongoing project to create and maintain a stable set + of core libraries used by several Haskell + compilers, and the libraries that GHC comes with represent the + current status of that project. For more details, see Haskell + Libraries. + + + + + + +Pattern guards + + +Pattern guards (Glasgow extension) +The discussion that follows is an abbreviated version of Simon Peyton Jones's original proposal. (Note that the proposal was written before pattern guards were implemented, so refers to them as unimplemented.) + + + +Suppose we have an abstract data type of finite maps, with a +lookup operation: + + +lookup :: FiniteMap -> Int -> Maybe Int + + +The lookup returns Nothing if the supplied key is not in the domain of the mapping, and (Just v) otherwise, +where v is the value that the key maps to. Now consider the following definition: + + + +clunky env var1 var2 | ok1 && ok2 = val1 + val2 +| otherwise = var1 + var2 +where + m1 = lookup env var1 + m2 = lookup env var2 + ok1 = maybeToBool m1 + ok2 = maybeToBool m2 + val1 = expectJust m1 + val2 = expectJust m2 + + + +The auxiliary functions are + + + +maybeToBool :: Maybe a -> Bool +maybeToBool (Just x) = True +maybeToBool Nothing = False + +expectJust :: Maybe a -> a +expectJust (Just x) = x +expectJust Nothing = error "Unexpected Nothing" + + + +What is clunky doing? The guard ok1 && +ok2 checks that both lookups succeed, using +maybeToBool to convert the Maybe +types to booleans. The (lazily evaluated) expectJust +calls extract the values from the results of the lookups, and binds the +returned values to val1 and val2 +respectively. If either lookup fails, then clunky takes the +otherwise case and returns the sum of its arguments. + + + +This is certainly legal Haskell, but it is a tremendously verbose and +un-obvious way to achieve the desired effect. Arguably, a more direct way +to write clunky would be to use case expressions: + + + +clunky env var1 var1 = case lookup env var1 of + Nothing -> fail + Just val1 -> case lookup env var2 of + Nothing -> fail + Just val2 -> val1 + val2 +where + fail = val1 + val2 + + + +This is a bit shorter, but hardly better. Of course, we can rewrite any set +of pattern-matching, guarded equations as case expressions; that is +precisely what the compiler does when compiling equations! The reason that +Haskell provides guarded equations is because they allow us to write down +the cases we want to consider, one at a time, independently of each other. +This structure is hidden in the case version. Two of the right-hand sides +are really the same (fail), and the whole expression +tends to become more and more indented. + - -To avoid ambiguity, the type after the “::” in a result -pattern signature on a lambda or case must be atomic (i.e. a single -token or a parenthesised type of some sort). To see why, -consider how one would parse this: - +Here is how I would write clunky: + - \ x :: a -> b -> x +clunky env var1 var1 + | Just val1 <- lookup env var1 + , Just val2 <- lookup env var2 + = val1 + val2 +...other equations for clunky... - + +The semantics should be clear enough. The qualifers are matched in order. +For a <- qualifier, which I call a pattern guard, the +right hand side is evaluated and matched against the pattern on the left. +If the match fails then the whole guard fails and the next equation is +tried. If it succeeds, then the appropriate binding takes place, and the +next qualifier is matched, in the augmented environment. Unlike list +comprehensions, however, the type of the expression to the right of the +<- is the same as the type of the pattern to its +left. The bindings introduced by pattern guards scope over all the +remaining guard qualifiers, and over the right hand side of the equation. - - - - Pattern type signatures can bind existential type variables. -For example: - +Just as with list comprehensions, boolean expressions can be freely mixed +with among the pattern guards. For example: + - data T = forall a. MkT [a] - - f :: T -> T - f (MkT [t::a]) = MkT t3 - where - t3::[a] = [t,t,t] +f x | [y] <- x + , y > 3 + , Just z <- h y + = ... - + +Haskell's current guards therefore emerge as a special case, in which the +qualifier list has just one element, a boolean expression. - + + - + +The recursive do-notation + + The recursive do-notation (also known as mdo-notation) is implemented as described in +"A recursive do for Haskell", +Levent Erkok, John Launchbury", +Haskell Workshop 2002, pages: 29-37. Pittsburgh, Pennsylvania. + -Pattern type signatures -can be used in pattern bindings: - +The do-notation of Haskell 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. + + +Here is a simple (yet contrived) example: + - f x = let (y, z::a) = x in ... - f1 x = let (y, z::Int) = x in ... - f2 (x::(Int,a)) = let (y, z::a) = x in ... - f3 :: (b->b) = \x -> x +justOnes = mdo xs <- Just (1:xs) + return xs + +As you can guess justOnes will evaluate to Just [1,1,1,.... + -In all such cases, the binding is not generalised over the pattern-bound -type variables. Thus f3 is monomorphic; f3 -has type b -> b for some type b, -and not forall b. b -> b. -In contrast, the binding + +The Control.Monad.Fix library introduces the MonadFix class. It's definition is: + - f4 :: b->b - f4 = \x -> x +class Monad m => MonadFix m where + mfix :: (a -> m a) -> m a -makes a polymorphic function, but b is not in scope anywhere -in f4's scope. - - - - + +The function mfix +dictates how the required recursion operation should be performed. If recursive bindings are required for a monad, +then that monad must be declared an instance of the MonadFix class. +For details, see the above mentioned reference. - - - - - -Explicitly-kinded quantification - -Haskell infers the kind of each type variable. Sometimes it is nice to be able -to give the kind explicitly as (machine-checked) documentation, -just as it is nice to give a type signature for a function. On some occasions, -it is essential to do so. For example, in his paper "Restricted Data Types in Haskell" (Haskell Workshop 1999) -John Hughes had to define the data type: - - data Set cxt a = Set [a] - | Unused (cxt a -> ()) - -The only use for the Unused constructor was to force the correct -kind for the type variable cxt. +The following instances of MonadFix are automatically provided: List, Maybe, IO, and +state monads (both lazy and strict). -GHC now instead allows you to specify the kind of a type variable directly, wherever -a type variable is explicitly bound. Namely: +There are three important points in using the recursive-do notation: -data declarations: - - data Set (cxt :: * -> *) a = Set [a] - -type declarations: - - type T (f :: * -> *) = f Int - -class declarations: - - class (Eq a) => C (f :: * -> *) a where ... - -forall's in type signatures: - - f :: forall (cxt :: * -> *). Set cxt Int - + +The recursive version of the do-notation uses the keyword mdo (rather +than do). + + + +If you want to declare an instance of the MonadFix class for one of +your own monads, or you need to refer to the class name MonadFix in any other way (for +instance when writing a type constraint), then your program should +import Control.Monad.MonadFix. +Otherwise, you don't need to import any special libraries to use the mdo-notation. That is, +as long as you only use the predefined instances mentioned above, the mdo-notation will +be automatically available. +To be on the safe side, of course, you can simply import it in all cases. + + + +As with other extensions, ghc should be given the flag -fglasgow-exts + -The parentheses are required. Some of the spaces are required too, to -separate the lexemes. If you write (f::*->*) you -will get a parse error, because "::*->*" is a -single lexeme in Haskell. +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 no longer supported. -As part of the same extension, you can put kind annotations in types -as well. Thus: - - f :: (Int :: *) -> Int - g :: forall a. a -> (a :: *) - -The syntax is - - atype ::= '(' ctype '::' kind ') - -The parentheses are required. +The web page: http://www.cse.ogi.edu/PacSoft/projects/rmb +contains up to date information on recursive monadic bindings. - - - -Assertions -<indexterm><primary>Assertions</primary></indexterm> - - -If you want to make use of assertions in your standard Haskell code, you -could define a function like the following: - + - + + + + Parallel List Comprehensions + list comprehensionsparallel + + parallel list comprehensions + + + Parallel list comprehensions are a natural extension to list + comprehensions. List comprehensions can be thought of as a nice + syntax for writing maps and filters. Parallel comprehensions + extend this to include the zipWith family. + + A parallel list comprehension has multiple independent + branches of qualifier lists, each separated by a `|' symbol. For + example, the following zips together two lists: -assert :: Bool -> a -> a -assert False x = error "assertion failed!" -assert _ x = x + [ (x, y) | x <- xs | y <- ys ] - + The behavior of parallel list comprehensions follows that of + zip, in that the resulting list will have the same length as the + shortest branch. - -which works, but gives you back a less than useful error message -- -an assertion failed, but which and where? - + We can define parallel list comprehensions by translation to + regular comprehensions. Here's the basic idea: - -One way out is to define an extended assert function which also -takes a descriptive string to include in the error message and -perhaps combine this with the use of a pre-processor which inserts -the source location where assert was used. - + Given a parallel comprehension of the form: - -Ghc offers a helping hand here, doing all of this for you. For every -use of assert in the user's source: - + + [ e | p1 <- e11, p2 <- e12, ... + | q1 <- e21, q2 <- e22, ... + ... + ] + - + This will be translated to: -kelvinToC :: Double -> Double -kelvinToC k = assert (k >= 0.0) (k+273.15) + [ e | ((p1,p2), (q1,q2), ...) <- zipN [(p1,p2) | p1 <- e11, p2 <- e12, ...] + [(q1,q2) | q1 <- e21, q2 <- e22, ...] + ... + ] - + where `zipN' is the appropriate zip for the given number of + branches. - -Ghc will rewrite this to also include the source location where the -assertion was made, - + - + +Rebindable syntax - -assert pred val ==> assertError "Main.hs|15" pred val - - + 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. - -The rewrite is only performed by the compiler when it spots -applications of Exception.assert, so you can still define and -use your own versions of assert, should you so wish. If not, -import Exception to make use assert in your code. - + You may want to define your own numeric class + hierarchy. It completely defeats that purpose if the + literal "1" means "Prelude.fromInteger + 1", which is what the Haskell Report specifies. + So the flag causes + the following pieces of built-in syntax to refer to + whatever is in scope, not the Prelude + versions: - -To have the compiler ignore uses of assert, use the compiler option -. -fignore-asserts option That is, -expressions of the form assert pred e will be rewritten to e. - + + + Integer and fractional literals mean + "fromInteger 1" and + "fromRational 3.2", not the + Prelude-qualified versions; both in expressions and in + patterns. + However, the standard Prelude Eq class + is still used for the equality test necessary for literal patterns. + - -Assertion failures can be caught, see the documentation for the -Exception library () -for the details. - + + Negation (e.g. "- (f x)") + means "negate (f x)" (not + Prelude.negate). + + + In an n+k pattern, the standard Prelude + Ord class is still used for comparison, + but the necessary subtraction uses whatever + "(-)" is in scope (not + "Prelude.(-)"). + + + + "Do" notation is translated using whatever + functions (>>=), + (>>), fail, and + return, are in scope (not the Prelude + versions). List comprehensions, and parallel array + comprehensions, are unaffected. + + + Be warned: this is an experimental facility, with fewer checks than + usual. In particular, it is essential that the functions GHC finds in scope + must have the appropriate types, namely: + + fromInteger :: forall a. (...) => Integer -> a + fromRational :: forall a. (...) => Rational -> a + negate :: forall a. (...) => a -> a + (-) :: forall a. (...) => a -> a -> a + (>>=) :: forall m a. (...) => m a -> (a -> m b) -> m b + (>>) :: forall m a. (...) => m a -> m b -> m b + return :: forall m a. (...) => a -> m a + fail :: forall m a. (...) => String -> m a + + (The (...) part can be any context including the empty context; that part + is up to you.) + If the functions don't have the right type, very peculiar things may + happen. Use -dcore-lint to + typecheck the desugared program. If Core Lint is happy you should be all right. + + + + Pragmas @@ -2996,6 +3127,8 @@ GHC will print the specified message. + + Rewrite rules @@ -3981,6 +4114,7 @@ classes usually have one "main" parameter for which deriving new instances is most interesting. </para> </sect2> + </sect1>