X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fdocs%2Fusers_guide%2Fglasgow_exts.sgml;h=063527bc7d9a183b9d7086ce07f3aa8859bab6a0;hb=b866a9bcc1ec7fa6c5d26410eb4c0e49e08795c9;hp=5af763382c6433993ad76751520f85a634f66750;hpb=5cc4210033d275b55fb3229817315b817357cbaf;p=ghc-hetmet.git diff --git a/ghc/docs/users_guide/glasgow_exts.sgml b/ghc/docs/users_guide/glasgow_exts.sgml index 5af7633..063527b 100644 --- a/ghc/docs/users_guide/glasgow_exts.sgml +++ b/ghc/docs/users_guide/glasgow_exts.sgml @@ -152,675 +152,1307 @@ with GHC. -&primitives; - - - - -Type system extensions - - -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 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". - - - -Infix type constructors + + + Unboxed types and primitive operations + +GHC is built on a raft of primitive data types and operations. +While you really can use this stuff to write fast code, + we generally find it a lot less painful, and more satisfying in the + long run, to use higher-level language features and libraries. With + any luck, the code you write will be optimised to the efficient + unboxed version in any case. And if it isn't, we'd like to know + about it. + +We do not currently have good, up-to-date documentation about the +primitives, perhaps because they are mainly intended for internal use. +There used to be a long section about them here in the User Guide, but it +became out of date, and wrong information is worse than none. + +The Real Truth about what primitive types there are, and what operations +work over those types, is held in the file +fptools/ghc/compiler/prelude/primops.txt. +This file is used directly to generate GHC's primitive-operation definitions, so +it is always correct! It is also intended for processing into text. + + Indeed, +the result of such processing is part of the description of the + External + Core language. +So that document is a good place to look for a type-set version. +We would be very happy if someone wanted to volunteer to produce an SGML +back end to the program that processes primops.txt so that +we could include the results here in the User Guide. + +What follows here is a brief summary of some main points. + + +Unboxed types + -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. - - - +Unboxed types (Glasgow extension) - - - -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. +Most types in GHC are boxed, which means +that values of that type are represented by a pointer to a heap +object. The representation of a Haskell Int, for +example, is a two-word heap object. An unboxed +type, however, is represented by the value itself, no pointers or heap +allocation are involved. + -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 - - +Unboxed types correspond to the “raw machine” types you +would use in C: Int# (long int), +Double# (double), Addr# +(void *), etc. The primitive operations +(PrimOps) on these types are what you might expect; e.g., +(+#) is addition on +Int#s, and is the machine-addition that we all +know and love—usually one instruction. -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. +Primitive (unboxed) types cannot be defined in Haskell, and are +therefore built into the language and compiler. Primitive types are +always unlifted; that is, a value of a primitive type cannot be +bottom. We use the convention that primitive types, values, and +operations have a # suffix. -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. +Primitive values are often represented by a simple bit-pattern, such +as Int#, Float#, +Double#. But this is not necessarily the case: +a primitive value might be represented by a pointer to a +heap-allocated object. Examples include +Array#, the type of primitive arrays. A +primitive array is heap-allocated because it is too big a value to fit +in a register, and would be too expensive to copy around; in a sense, +it is accidental that it is represented by a pointer. If a pointer +represents a primitive value, then it really does point to that value: +no unevaluated thunks, no indirections…nothing can be at the +other end of the pointer than the primitive value. - - - -Class method types - -Haskell 98 prohibits class method types to mention constraints on the -class type variable, thus: - - class Seq s a where - fromList :: [a] -> s a - elem :: Eq a => a -> s a -> Bool - -The type of elem is illegal in Haskell 98, because it -contains the constraint Eq a, constrains only the -class type variable (in this case a). +There are some restrictions on the use of primitive types, the main +one being that you can't pass a primitive value to a polymorphic +function or store one in a polymorphic data type. This rules out +things like [Int#] (i.e. lists of primitive +integers). The reason for this restriction is that polymorphic +arguments and constructor fields are assumed to be pointers: if an +unboxed integer is stored in one of these, the garbage collector would +attempt to follow it, leading to unpredictable space leaks. Or a +seq operation on the polymorphic component may +attempt to dereference the pointer, with disastrous results. Even +worse, the unboxed value might be larger than a pointer +(Double# for instance). + -With the GHC lifts this restriction. +Nevertheless, A numerically-intensive program using unboxed types can +go a lot faster than its “standard” +counterpart—we saw a threefold speedup on one example. - -Multi-parameter type classes +<sect2 id="unboxed-tuples"> +<title>Unboxed Tuples -This section documents GHC's implementation of multi-parameter type -classes. There's lots of background in the paper Type -classes: exploring the design space (Simon Peyton Jones, Mark -Jones, Erik Meijer). +Unboxed tuples aren't really exported by GHC.Exts, +they're available by default with . An +unboxed tuple looks like this: -I'd like to thank people who reported shorcomings in the GHC 3.02 -implementation. Our default decisions were all conservative ones, and -the experience of these heroic pioneers has given useful concrete -examples to support several generalisations. (These appear below as -design choices not implemented in 3.02.) - - -I've discussed these notes with Mark Jones, and I believe that Hugs -will migrate towards the same design choices as I outline here. -Thanks to him, and to many others who have offered very useful -feedback. - + +(# e_1, ..., e_n #) + - -Types + -There are the following restrictions on the form of a qualified -type: +where e_1..e_n are expressions of any +type (primitive or non-primitive). The type of an unboxed tuple looks +the same. - - - forall tv1..tvn (c1, ...,cn) => type - - +Unboxed tuples are used for functions that need to return multiple +values, but they avoid the heap allocation normally associated with +using fully-fledged tuples. When an unboxed tuple is returned, the +components are put directly into registers or on the stack; the +unboxed tuple itself does not have a composite representation. Many +of the primitive operations listed in this section return unboxed +tuples. -(Here, I write the "foralls" explicitly, although the Haskell source -language omits them; in Haskell 1.4, 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 ). +There are some pretty stringent restrictions on the use of unboxed tuples: - + - Each universally quantified type variable -tvi must be mentioned (i.e. appear free) in type. - -The reason for this is that a value with a type that does not obey -this restriction could not be used without introducing -ambiguity. Here, for example, is an illegal type: - - - - forall a. Eq a => Int - - - -When a value with this type was used, the constraint Eq tv -would be introduced where tv is a fresh type variable, and -(in the dictionary-translation implementation) the value would be -applied to a dictionary for Eq tv. The difficulty is that we -can never know which instance of Eq to use because we never -get any more information about tv. + Unboxed tuple types are subject to the same restrictions as +other unboxed types; i.e. they may not be stored in polymorphic data +structures or passed to polymorphic functions. - Every constraint ci must mention at least one of the -universally quantified type variables tvi. - -For example, this type is OK because C a b mentions the -universally quantified type variable b: + Unboxed tuples may only be constructed as the direct result of +a function, and may only be deconstructed with a case expression. +eg. the following are valid: - forall a. C a b => burble +f x y = (# x+1, y-1 #) +g x = case f x x of { (# a, b #) -> a + b } -The next type is illegal because the constraint Eq b does not -mention a: +but the following are invalid: - forall a. Eq b => burble +f x y = g (# x, y #) +g (# x, y #) = x + y -The reason for this restriction is milder than the other one. The -excluded types are never useful or necessary (because the offending -context doesn't need to be witnessed at this point; it can be floated -out). Furthermore, floating them out increases sharing. Lastly, -excluding them is a conservative choice; it leaves a patch of -territory free in case we need it later. - - - - - - - -These restrictions apply to all types, whether declared in a type signature -or inferred. - + -Unlike Haskell 1.4, constraints in types do not have to be of -the form (class type-variables). Thus, these type signatures -are perfectly OK - + No variable can have an unboxed tuple type. This is illegal: - - f :: Eq (m a) => [m a] -> [m a] - g :: Eq [a] => ... +f :: (# Int, Int #) -> (# Int, Int #) +f x = x - - -This choice recovers principal types, a property that Haskell 1.4 does not have. +because x has an unboxed tuple type. + + - + - -Class declarations + - - - +Note: we may relax some of these restrictions in the future. + - Multi-parameter type classes are permitted. For example: +The IO and ST monads use unboxed +tuples to avoid unnecessary allocation during sequences of operations. + + + - - class Collection c a where - union :: c a -> c a -> c a - ...etc. - + + +Syntactic extensions + + - - - - - - The class hierarchy must be acyclic. However, the definition -of "acyclic" involves only the superclass relationships. For example, -this is OK: + + 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. - - class C a where { - op :: D b => a -> b -> b - } + 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 - class C a => D a where { ... } - +module A.B.C -Here, C is a superclass of D, but it's OK for a -class operation op of C to mention D. (It -would not be OK for D to be a superclass of 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 + - - 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: + 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. - - class Functor (m k) => FiniteMap m k where - ... + - class (Monad m, Monad (t m)) => Transform t m where - lift :: m a -> (t m) a - + + +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.) - - - In the signature of a class operation, every constraint -must mention at least one type variable that is not a class type -variable. - -Thus: - +Suppose we have an abstract data type of finite maps, with a +lookup operation: - class Collection c a where - mapC :: Collection c b => (a->b) -> c a -> c b +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: + -is OK because the constraint (Collection a b) mentions -b, even though it also mentions the class variable -a. On the other hand: + +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 + - class C a where - op :: Eq a => (a,b) -> (a,b) - +maybeToBool :: Maybe a -> Bool +maybeToBool (Just x) = True +maybeToBool Nothing = False +expectJust :: Maybe a -> a +expectJust (Just x) = x +expectJust Nothing = error "Unexpected Nothing" + -is not OK because the constraint (Eq a) mentions on the class -type variable a, but not b. However, any such -example is easily fixed by moving the offending context up to the -superclass context: + +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: + - class Eq a => C a where - op ::(a,b) -> (a,b) +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 - -A yet more relaxed rule would allow the context of a class-op signature -to mention only class type variables. However, that conflicts with -Rule 1(b) for types above. - + +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. - - - The type of each class operation must mention all of -the class type variables. For example: - +Here is how I would write clunky: + - class Coll s a where - empty :: s - insert :: s -> a -> s +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. + -is not OK, because the type of empty doesn't mention -a. This rule is a consequence of Rule 1(a), above, for -types, and has the same motivation. - -Sometimes, offending class declarations exhibit misunderstandings. For -example, Coll might be rewritten - + +Just as with list comprehensions, boolean expressions can be freely mixed +with among the pattern guards. For example: + - class Coll s a where - empty :: s a - insert :: s a -> a -> s a +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. + + -which makes the connection between the type of a collection of -a's (namely (s a)) and the element type a. -Occasionally this really doesn't work, in which case you can split the -class like this: + + +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. + + +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: + - class CollE s where - empty :: s +import Control.Monad.Fix - class CollE s => Coll s a where - insert :: s -> a -> s +justOnes = mdo xs <- Just (1:xs) + return xs + +As you can guess justOnes will evaluate to Just [1,1,1,.... + - + +The Control.Monad.Fix library introduces the MonadFix class. It's definition is: - + +class Monad m => MonadFix m where + mfix :: (a -> m a) -> m a + + +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. + + +The following instances of MonadFix are automatically provided: List, Maybe, IO. +Furthermore, the Control.Monad.ST and Control.Monad.ST.Lazy modules provide the instances of the MonadFix class +for Haskell's internal state monad (strict and lazy, respectively). + + +There are three important points in using the recursive-do notation: + + +The recursive version of the do-notation uses the keyword mdo (rather +than do). + - + +You should import Control.Monad.Fix. +(Note: Strictly speaking, this import is required only when you need to refer to the name +MonadFix in your program, but the import is always safe, and the programmers +are encouraged to always import this module when using the mdo-notation.) + + +As with other extensions, ghc should be given the flag -fglasgow-exts + + - - - -Instance declarations + +The web page: http://www.cse.ogi.edu/PacSoft/projects/rmb +contains up to date information on recursive monadic bindings. + +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. + - - + - - Instance declarations may not overlap. The two instance -declarations + Infix type constructors +GHC supports infix type constructors, much as it supports infix data constructors. For example: - instance context1 => C type1 where ... - instance context2 => C type2 where ... - - - -"overlap" if type1 and type2 unify + infixl 5 :+: -However, if you give the command line option --fallow-overlapping-instances -option then overlapping instance declarations are permitted. -However, GHC arranges never to commit to using an instance declaration -if another instance declaration also applies, either now or later. - - - + data a :+: b = Inl a | Inr b - - EITHER type1 and type2 do not unify + f :: a `Either` b -> a :+: b + f (Left x) = Inl x + - - +The lexical +syntax of an infix type constructor is just like that of an infix data constructor: either +it's an operator beginning with ":", or it is an ordinary (alphabetic) type constructor enclosed in +back-quotes. - OR type2 is a substitution instance of type1 -(but not identical to type1), or vice versa. +When you give a fixity declaration, the fixity applies to both the data constructor and the +type constructor with the specified name. You cannot give different fixities to the type constructor T +and the data constructor T. - - -Notice that these rules - - - - - make it clear which instance decl to use -(pick the most specific one that matches) - - - - - do not mention the contexts context1, context2 -Reason: you can pick which instance decl -"matches" based on the type. - - + - -However the rules are over-conservative. Two instance declarations can overlap, -but it can still be clear in particular situations which to use. For example: - - instance C (Int,a) where ... - instance C (a,Bool) where ... - -These are rejected by GHC's rules, but it is clear what to do when trying -to solve the constraint C (Int,Int) because the second instance -cannot apply. Yell if this restriction bites you. - - -GHC is also conservative about committing to an overlapping instance. For example: - - class C a where { op :: a -> a } - instance C [Int] where ... - instance C a => C [a] where ... - - f :: C b => [b] -> [b] - f x = op x - -From the RHS of f we get the constraint C [b]. But -GHC does not commit to the second instance declaration, because in a paricular -call of f, b might be instantiate to Int, so the first instance declaration -would be appropriate. So GHC rejects the program. If you add -GHC will instead silently pick the second instance, without complaining about -the problem of subsequent instantiations. - - -Regrettably, GHC doesn't guarantee to detect overlapping instance -declarations if they appear in different modules. GHC can "see" the -instance declarations in the transitive closure of all the modules -imported by the one being compiled, so it can "see" all instance decls -when it is compiling Main. However, it currently chooses not -to look at ones that can't possibly be of use in the module currently -being compiled, in the interests of efficiency. (Perhaps we should -change that decision, at least for Main.) + - - - + + Parallel List Comprehensions + list comprehensionsparallel + + parallel list comprehensions + - - There are no restrictions on the type in an instance -head, except that at least one must not be a type variable. -The instance "head" is the bit after the "=>" in an instance decl. For -example, these are OK: + 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: - instance C Int a where ... - - instance D (Int, Int) where ... - - instance E [[a]] where ... + [ (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. -Note that instance heads may contain repeated type variables. -For example, this is OK: + We can define parallel list comprehensions by translation to + regular comprehensions. Here's the basic idea: + Given a parallel comprehension of the form: - instance Stateful (ST s) (MutVar s) where ... + [ e | p1 <- e11, p2 <- e12, ... + | q1 <- e21, q2 <- e22, ... + ... + ] - -The "at least one not a type variable" restriction is to ensure that -context reduction terminates: each reduction step removes one type -constructor. For example, the following would make the type checker -loop if it wasn't excluded: - + This will be translated to: - instance C a => C a where ... + [ 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. -There are two situations in which the rule is a bit of a pain. First, -if one allows overlapping instance declarations then it's quite -convenient to have a "default instance" declaration that applies if -something more specific does not: + + +Rebindable syntax - - instance C a where - op = ... -- Default - + 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. -Second, sometimes you might want to use the following to get the -effect of a "class synonym": + 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. + However, the standard Prelude Eq class + is still used for the equality test necessary for literal patterns. + - - class (C1 a, C2 a, C3 a) => C a where { } + + Negation (e.g. "- (f x)") + means "negate (f x)" (not + Prelude.negate). + - instance (C1 a, C2 a, C3 a) => C a where { } - + + 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. + -This allows you to write shorter signatures: + 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. + + - - f :: C a => ... - + + +Type system extensions -instead of + +Data types with no constructors +With the flag, GHC lets you declare +a data type with no constructors. For example: - f :: (C1 a, C2 a, C3 a) => ... + data S -- S :: * + data T a -- T :: * -> * +Syntactically, the declaration lacks the "= constrs" part. The +type can be parameterised over types of any kind, but if the kind is +not * then an explicit kind annotation must be used +(see ). -I'm on the lookout for a simple rule that preserves decidability while -allowing these idioms. The experimental flag --fallow-undecidable-instances -option lifts this restriction, allowing all the types in an -instance head to be type variables. +Such data types have only one value, namely bottom. +Nevertheless, they can be useful when defining "phantom types". + - - - + +Infix type constructors - Unlike Haskell 1.4, instance heads may use type -synonyms. As always, using a type synonym is just shorthand for -writing the RHS of the type synonym definition. For example: - - - - type Point = (Int,Int) - instance C Point where ... - instance C [Point] where ... - - - +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. + + + + + + + +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. + + +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 + + + + + +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. + + + +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. + + + + + +Class method types + + +Haskell 98 prohibits class method types to mention constraints on the +class type variable, thus: + + class Seq s a where + fromList :: [a] -> s a + elem :: Eq a => a -> s a -> Bool + +The type of elem is illegal in Haskell 98, because it +contains the constraint Eq a, constrains only the +class type variable (in this case a). + + +With the GHC lifts this restriction. + + + + + +Multi-parameter type classes + + + +This section documents GHC's implementation of multi-parameter type +classes. There's lots of background in the paper Type +classes: exploring the design space (Simon Peyton Jones, Mark +Jones, Erik Meijer). + + + +I'd like to thank people who reported shorcomings in the GHC 3.02 +implementation. Our default decisions were all conservative ones, and +the experience of these heroic pioneers has given useful concrete +examples to support several generalisations. (These appear below as +design choices not implemented in 3.02.) + + + +I've discussed these notes with Mark Jones, and I believe that Hugs +will migrate towards the same design choices as I outline here. +Thanks to him, and to many others who have offered very useful +feedback. + + + +Types + + +There are the following restrictions on the form of a qualified +type: + + + + + + forall tv1..tvn (c1, ...,cn) => type + + + + + +(Here, I write the "foralls" explicitly, although the Haskell source +language omits them; in Haskell 1.4, 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 ). + + + + + + + + + Each universally quantified type variable +tvi must be mentioned (i.e. appear free) in type. + +The reason for this is that a value with a type that does not obey +this restriction could not be used without introducing +ambiguity. Here, for example, is an illegal type: + + + + forall a. Eq a => Int + + + +When a value with this type was used, the constraint Eq tv +would be introduced where tv is a fresh type variable, and +(in the dictionary-translation implementation) the value would be +applied to a dictionary for Eq tv. The difficulty is that we +can never know which instance of Eq to use because we never +get any more information about tv. + + + + + + + Every constraint ci must mention at least one of the +universally quantified type variables tvi. + +For example, this type is OK because C a b mentions the +universally quantified type variable b: + + + + forall a. C a b => burble + + + +The next type is illegal because the constraint Eq b does not +mention a: + + + + forall a. Eq b => burble + + + +The reason for this restriction is milder than the other one. The +excluded types are never useful or necessary (because the offending +context doesn't need to be witnessed at this point; it can be floated +out). Furthermore, floating them out increases sharing. Lastly, +excluding them is a conservative choice; it leaves a patch of +territory free in case we need it later. + + + + + + + + + +These restrictions apply to all types, whether declared in a type signature +or inferred. + + + +Unlike Haskell 1.4, constraints in types do not have to be of +the form (class type-variables). Thus, these type signatures +are perfectly OK + + + + + + f :: Eq (m a) => [m a] -> [m a] + g :: Eq [a] => ... + + + + + +This choice recovers principal types, a property that Haskell 1.4 does not have. + + + + + +Class declarations + + + + + + + + Multi-parameter type classes are permitted. For example: + + + + class Collection c a where + union :: c a -> c a -> c a + ...etc. + + + + + + + + + + The class hierarchy must be acyclic. However, the definition +of "acyclic" involves only the superclass relationships. For example, +this is OK: + + + + class C a where { + op :: D b => a -> b -> b + } + + class C a => D a where { ... } + + + +Here, C is a superclass of D, but it's OK for a +class operation op of C to mention D. (It +would not be OK for D to be a superclass of C.) + + + + + + + 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: + + + + class Functor (m k) => FiniteMap m k where + ... + + class (Monad m, Monad (t m)) => Transform t m where + lift :: m a -> (t m) a + + + + + + + + + In the signature of a class operation, every constraint +must mention at least one type variable that is not a class type +variable. + +Thus: + + + + class Collection c a where + mapC :: Collection c b => (a->b) -> c a -> c b + + + +is OK because the constraint (Collection a b) mentions +b, even though it also mentions the class variable +a. On the other hand: + + + + class C a where + op :: Eq a => (a,b) -> (a,b) + + + +is not OK because the constraint (Eq a) mentions on the class +type variable a, but not b. However, any such +example is easily fixed by moving the offending context up to the +superclass context: + + + + class Eq a => C a where + op ::(a,b) -> (a,b) + + + +A yet more relaxed rule would allow the context of a class-op signature +to mention only class type variables. However, that conflicts with +Rule 1(b) for types above. + + + + + + + The type of each class operation must mention all of +the class type variables. For example: + + + + class Coll s a where + empty :: s + insert :: s -> a -> s + + + +is not OK, because the type of empty doesn't mention +a. This rule is a consequence of Rule 1(a), above, for +types, and has the same motivation. + +Sometimes, offending class declarations exhibit misunderstandings. For +example, Coll might be rewritten + + + + class Coll s a where + empty :: s a + insert :: s a -> a -> s a + + + +which makes the connection between the type of a collection of +a's (namely (s a)) and the element type a. +Occasionally this really doesn't work, in which case you can split the +class like this: + + + + class CollE s where + empty :: s + + class CollE s => Coll s a where + insert :: s -> a -> s + + + + + + + + + + + + + +Instance declarations + + + + + + + + Instance declarations may not overlap. The two instance +declarations + + + + instance context1 => C type1 where ... + instance context2 => C type2 where ... + + + +"overlap" if type1 and type2 unify + +However, if you give the command line option +-fallow-overlapping-instances +option then overlapping instance declarations are permitted. +However, GHC arranges never to commit to using an instance declaration +if another instance declaration also applies, either now or later. + + + + + + EITHER type1 and type2 do not unify + + + + + + OR type2 is a substitution instance of type1 +(but not identical to type1), or vice versa. + + + +Notice that these rules + + + + + make it clear which instance decl to use +(pick the most specific one that matches) + + + + + + + do not mention the contexts context1, context2 +Reason: you can pick which instance decl +"matches" based on the type. + + + + +However the rules are over-conservative. Two instance declarations can overlap, +but it can still be clear in particular situations which to use. For example: + + instance C (Int,a) where ... + instance C (a,Bool) where ... + +These are rejected by GHC's rules, but it is clear what to do when trying +to solve the constraint C (Int,Int) because the second instance +cannot apply. Yell if this restriction bites you. + + +GHC is also conservative about committing to an overlapping instance. For example: + + class C a where { op :: a -> a } + instance C [Int] where ... + instance C a => C [a] where ... + + f :: C b => [b] -> [b] + f x = op x + +From the RHS of f we get the constraint C [b]. But +GHC does not commit to the second instance declaration, because in a paricular +call of f, b might be instantiate to Int, so the first instance declaration +would be appropriate. So GHC rejects the program. If you add +GHC will instead silently pick the second instance, without complaining about +the problem of subsequent instantiations. + + +Regrettably, GHC doesn't guarantee to detect overlapping instance +declarations if they appear in different modules. GHC can "see" the +instance declarations in the transitive closure of all the modules +imported by the one being compiled, so it can "see" all instance decls +when it is compiling Main. However, it currently chooses not +to look at ones that can't possibly be of use in the module currently +being compiled, in the interests of efficiency. (Perhaps we should +change that decision, at least for Main.) + + + + + + + There are no restrictions on the type in an instance +head, except that at least one must not be a type variable. +The instance "head" is the bit after the "=>" in an instance decl. For +example, these are OK: + + + + instance C Int a where ... + + instance D (Int, Int) where ... + + instance E [[a]] where ... + + + +Note that instance heads may contain repeated type variables. +For example, this is OK: + + + + instance Stateful (ST s) (MutVar s) where ... + + + +The "at least one not a type variable" restriction is to ensure that +context reduction terminates: each reduction step removes one type +constructor. For example, the following would make the type checker +loop if it wasn't excluded: + + + + instance C a => C a where ... + + + +There are two situations in which the rule is a bit of a pain. First, +if one allows overlapping instance declarations then it's quite +convenient to have a "default instance" declaration that applies if +something more specific does not: + + + + instance C a where + op = ... -- Default + + + +Second, sometimes you might want to use the following to get the +effect of a "class synonym": + + + + class (C1 a, C2 a, C3 a) => C a where { } + + instance (C1 a, C2 a, C3 a) => C a where { } + + + +This allows you to write shorter signatures: + + + + f :: C a => ... + + + +instead of + + + + f :: (C1 a, C2 a, C3 a) => ... + + + +I'm on the lookout for a simple rule that preserves decidability while +allowing these idioms. The experimental flag +-fallow-undecidable-instances +option lifts this restriction, allowing all the types in an +instance head to be type variables. + + + + + + + Unlike Haskell 1.4, instance heads may use type +synonyms. As always, using a type synonym is just shorthand for +writing the RHS of the type synonym definition. For example: + + + + type Point = (Int,Int) + instance C Point where ... + instance C [Point] where ... + + + is legal. However, if you added @@ -923,10 +1555,12 @@ implicitly parameterized by a comparison function named cmp. The dynamic binding constraints are just a new form of predicate in the type class system. -An implicit parameter is introduced by the special form ?x, +An implicit parameter occurs in an exprssion using the special form ?x, where x is -any valid identifier. Use if this construct also introduces new -dynamic binding constraints. For example, the following definition +any valid identifier (e.g. ord ?x is a valid expression). +Use of this construct also introduces a new +dynamic-binding constraint in the type of the expression. +For example, the following definition shows how we can define an implicitly parameterized sort function in terms of an explicitly parameterized sortBy function: @@ -935,6 +1569,11 @@ terms of an explicitly parameterized sortBy function: sort :: (?cmp :: a -> a -> Bool) => [a] -> [a] sort = sortBy ?cmp + + + +Implicit-parameter type constraints + Dynamic binding constraints behave just like other type class constraints in that they are automatically propagated. Thus, when a function is used, its implicit parameters are inherited by the @@ -951,31 +1590,14 @@ propagated. With implicit parameters, the default is to always propagate them. -An implicit parameter differs from other type class constraints in the +An implicit-parameter type constraint differs from other type class constraints in the following way: All uses of a particular implicit parameter must have the same type. This means that the type of (?x, ?x) is (?x::a) => (a,a), and not (?x::a, ?x::b) => (a, b), as would be the case for type class constraints. - -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 = let ?cmp = (<=) in least - - -Note the following additional constraints: - - + You can't have an implicit parameter in the context of a class or instance declaration. For example, both these declarations are illegal: @@ -986,10 +1608,62 @@ Reason: exactly which implicit parameter you pick up depends on exactly where you invoke a function. But the ``invocation'' of instance declarations is done behind the scenes by the compiler, so it's hard to figure out exactly where it is done. Easiest thing is to outlaw the offending types. - + + + +Implicit-parameter bindings + + +An implicit parameter is bound using the standard +let or where binding forms. +For example, we define the min function by binding +cmp. + + min :: [a] -> a + min = let ?cmp = (<=) in least + + + +A group of implicit-parameter bindings may occur anywhere a normal group of Haskell +bindings can occur, except at top level. That is, they can occur in a let +(including in a list comprehension, or do-notation, or pattern guards), +or a where clause. +Note the following points: + + +An implicit-parameter binding group 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. + + +You may not mix implicit-parameter bindings with ordinary bindings in a +single let +expression; use two nested lets instead. +(In the case of where you are stuck, since you can't nest where clauses.) + + + +You may put multiple implicit-parameter bindings in a +single binding group; but they are not treated +as a mutually recursive group (as ordinary let bindings are). +Instead they are treated as a non-recursive group, simultaneously binding all the implicit +parameter. The bindings are not nested, and may be re-ordered without changing +the meaning of the program. +For example, consider: + + f t = let { ?x = t; ?y = ?x+(1::Int) } in ?x + ?y + +The use of ?x in the binding for ?y does not "see" +the binding for ?x, so the type of f is + + f :: (?x::Int) => Int -> Int + + + @@ -1120,6 +1794,47 @@ 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. + + + @@ -1127,9 +1842,10 @@ Haskell programs without knowing their typing. 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, +. @@ -1570,6 +2286,18 @@ 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 + + @@ -1821,8 +2549,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. @@ -2281,401 +3014,366 @@ 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: - + +Generalised derived instances for newtypes +When you define an abstract type using newtype, you may want +the new type to inherit some instances from its representation. In +Haskell 98, you can inherit instances of Eq, Ord, +Enum and Bounded by deriving them, but for any +other classes you have to write an explicit instance declaration. For +example, if you define - -assert :: Bool -> a -> a -assert False x = error "assertion failed!" -assert _ x = x - + + newtype Dollars = Dollars Int + - +and you want to use arithmetic on Dollars, you have to +explicitly define an instance of Num: - -which works, but gives you back a less than useful error message -- -an assertion failed, but which and where? + + instance Num Dollars where + Dollars a + Dollars b = Dollars (a+b) + ... + +All the instance does is apply and remove the newtype +constructor. It is particularly galling that, since the constructor +doesn't appear at run-time, this instance declaration defines a +dictionary which is wholly equivalent to the Int +dictionary, only slower! - -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. - + Generalising the deriving clause -Ghc offers a helping hand here, doing all of this for you. For every -use of assert in the user's source: - +GHC now permits such instances to be derived instead, so one can write + + newtype Dollars = Dollars Int deriving (Eq,Show,Num) + - +and the implementation uses the same Num dictionary +for Dollars as for Int. Notionally, the compiler +derives an instance declaration of the form - -kelvinToC :: Double -> Double -kelvinToC k = assert (k >= 0.0) (k+273.15) - + + instance Num Int => Num Dollars + +which just adds or removes the newtype constructor according to the type. - -Ghc will rewrite this to also include the source location where the -assertion was made, - - +We can also derive instances of constructor classes in a similar +way. For example, suppose we have implemented state and failure monad +transformers, such that - -assert pred val ==> assertError "Main.hs|15" pred val - + + instance Monad m => Monad (State s m) + instance Monad m => Monad (Failure m) + +In Haskell 98, we can define a parsing monad by + + type Parser tok m a = State [tok] (Failure m) a + - +which is automatically a monad thanks to the instance declarations +above. With the extension, we can make the parser type abstract, +without needing to write an instance of class Monad, via - -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. - + + newtype Parser tok m a = Parser (State [tok] (Failure m) a) + deriving Monad + +In this case the derived instance declaration is of the form + + instance Monad (State [tok] (Failure m)) => Monad (Parser tok m) + - -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. +Notice that, since Monad is a constructor class, the +instance is a partial application of the new type, not the +entire left hand side. We can imagine that the type declaration is +``eta-converted'' to generate the context of the instance +declaration. - -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 +We can even derive instances of multi-parameter classes, provided the +newtype is the last class parameter. In this case, a ``partial +application'' of the class appears in the deriving +clause. For example, given the class + + class StateMonad s m | m -> s where ... + instance Monad m => StateMonad s (State s m) where ... + +then we can derive an instance of StateMonad for Parsers by + + newtype Parser tok m a = Parser (State [tok] (Failure m) a) + deriving (Monad, StateMonad [tok]) + - It is a common strategy to use the as - keyword to save some typing when using qualified names with - hierarchical modules. For example: +The derived instance is obtained by completing the application of the +class to the new type: - -import qualified Control.Monad.ST.Strict as ST + + instance StateMonad [tok] (State [tok] (Failure m)) => + StateMonad [tok] (Parser tok m) + + - 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. +As a result of this extension, all derived instances in newtype +declarations are treated uniformly (and implemented just by reusing +the dictionary for the representation type), except +Show and Read, which really behave differently for +the newtype and its representation. + + - + A more precise specification + +Derived instance declarations are constructed as follows. Consider the +declaration (after expansion of any type synonyms) - + + newtype T v1...vn = T' (S t1...tk vk+1...vn) deriving (c1...cm) + - -Pattern guards +where S is a type constructor, t1...tk are +types, +vk+1...vn are type variables which do not occur in any of +the ti, and the ci are partial applications of +classes of the form C t1'...tj'. The derived instance +declarations are, for each ci, - -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.) + + instance ci (S t1...tk vk+1...v) => ci (T v1...vp) + +where p is chosen so that T v1...vp is of the +right kind for the last parameter of class Ci. - -Suppose we have an abstract data type of finite maps, with a -lookup operation: - -lookup :: FiniteMap -> Int -> Maybe Int - +As an example which does not work, consider + + newtype NonMonad m s = NonMonad (State s m s) deriving Monad + +Here we cannot derive the instance + + instance Monad (State s m) => Monad (NonMonad m) + -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: +because the type variable s occurs in State s m, +and so cannot be "eta-converted" away. It is a good thing that this +deriving clause is rejected, because NonMonad m is +not, in fact, a monad --- for the same reason. Try defining +>>= with the correct type: you won't be able to. + - -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 +Notice also that the order of class parameters becomes +important, since we can only derive instances for the last one. If the +StateMonad class above were instead defined as + + + class StateMonad m s | m -> s where ... - -The auxiliary functions are +then we would not have been able to derive an instance for the +Parser type above. We hypothesise that multi-parameter +classes usually have one "main" parameter for which deriving new +instances is most interesting. + - -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. + + + + + + +Template Haskell + +Template Haskell allows you to do compile-time meta-programming in Haskell. The background +the main technical innovations are discussed in " +Template Meta-programming for Haskell", in +Proc Haskell Workshop 2002. + + + +The documentation here describes the realisation in GHC. (It's rather sketchy just now; +Tim Sheard is going to expand it.) + + + Syntax + + Template Haskell has the following new syntactic constructions. You need to use the flag + -fglasgow-exts to switch these syntactic extensions on. + + + + A splice is written $x, where x is an + identifier, or $(...), where the "..." is an arbitrary expression. + There must be no space between the "$" and the identifier or parenthesis. This use + of "$" overrides its meaning as an infix operator, just as "M.x" overrides the meaning + of "." as an infix operator. If you want the infix operator, put spaces around it. + + A splice can occur in place of + + an expression; + a list of top-level declarations; + a pattern; + a type; + + + + + + A expression quotation is written in Oxford brackets, thus: + + [| ... |], where the "..." is an expression; + [d| ... |], where the "..." is a list of top-level declarations; + [p| ... |], where the "..." is a pattern; + [t| ... |], where the "..." is a type; + + + + Reification is written thus: + + reifyDecl T, where T is a type constructor; this expression + has type Dec. + reifyDecl C, where C is a class; has type Dec. + reifyType f, where f is an identifier; has type Typ. + Still to come: fixities + + + + + + + + Using Template Haskell -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: + + + The data types and monadic constructor functions for Template Haskell are in the library + Language.Haskell.THSyntax. + + + + If the module contains any top-level splices that must be run, you must use GHC with + --make or --interactive flags. (Reason: that + means it walks the dependency tree and knows what modules must be linked etc.) + + + + You can only run a function at compile time if it is imported from another module. That is, + you can't define a function in a module, and call it from within a splice in the same module. + (It would make sense to do so, but it's hard to implement.) + + + + The flag -ddump-splices shows the expansion of all top-level splices as they happen. + + + + + - -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 - + + + +Assertions +<indexterm><primary>Assertions</primary></indexterm> + -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. +If you want to make use of assertions in your standard Haskell code, you +could define a function like the following: -Here is how I would write clunky: - -clunky env var1 var1 - | Just val1 <- lookup env var1 - , Just val2 <- lookup env var2 - = val1 + val2 -...other equations for clunky... +assert :: Bool -> a -> a +assert False x = error "assertion failed!" +assert _ x = x - -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. -Just as with list comprehensions, boolean expressions can be freely mixed -with among the pattern guards. For example: +which works, but gives you back a less than useful error message -- +an assertion failed, but which and where? - -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. +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. - - - - - - 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, ... - ... - ] - + +Ghc offers a helping hand here, doing all of this for you. For every +use of assert in the user's source: + - This will be translated to: + - [ e | ((p1,p2), (q1,q2), ...) <- zipN [(p1,p2) | p1 <- e11, p2 <- e12, ...] - [(q1,q2) | q1 <- e21, q2 <- e22, ...] - ... - ] +kelvinToC :: Double -> Double +kelvinToC k = assert (k >= 0.0) (k+273.15) - where `zipN' is the appropriate zip for the given number of - branches. - - - - -Rebindable syntax - + - GHC allows most kinds of built-in syntax to be rebound by - the user, to facilitate replacing the Prelude - with a home-grown version, for example. + +Ghc will rewrite this to also include the source location where the +assertion was made, + - 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. - However, the standard Prelude Eq class - is still used for the equality test necessary for literal patterns. - + +assert pred val ==> assertError "Main.hs|15" pred val + - - 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.(-)"). - + +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. + - - "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. - + +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. + - 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. + +Assertion failures can be caught, see the documentation for the +Control.Exception library for the details. + - + @@ -3776,179 +4474,6 @@ Just to finish with, here's another example I rather like: - -Generalised derived instances for newtypes - - -When you define an abstract type using newtype, you may want -the new type to inherit some instances from its representation. In -Haskell 98, you can inherit instances of Eq, Ord, -Enum and Bounded by deriving them, but for any -other classes you have to write an explicit instance declaration. For -example, if you define - - - newtype Dollars = Dollars Int - - -and you want to use arithmetic on Dollars, you have to -explicitly define an instance of Num: - - - instance Num Dollars where - Dollars a + Dollars b = Dollars (a+b) - ... - -All the instance does is apply and remove the newtype -constructor. It is particularly galling that, since the constructor -doesn't appear at run-time, this instance declaration defines a -dictionary which is wholly equivalent to the Int -dictionary, only slower! - - - Generalising the deriving clause - -GHC now permits such instances to be derived instead, so one can write - - newtype Dollars = Dollars Int deriving (Eq,Show,Num) - - -and the implementation uses the same Num dictionary -for Dollars as for Int. Notionally, the compiler -derives an instance declaration of the form - - - instance Num Int => Num Dollars - - -which just adds or removes the newtype constructor according to the type. - - - -We can also derive instances of constructor classes in a similar -way. For example, suppose we have implemented state and failure monad -transformers, such that - - - instance Monad m => Monad (State s m) - instance Monad m => Monad (Failure m) - -In Haskell 98, we can define a parsing monad by - - type Parser tok m a = State [tok] (Failure m) a - - -which is automatically a monad thanks to the instance declarations -above. With the extension, we can make the parser type abstract, -without needing to write an instance of class Monad, via - - - newtype Parser tok m a = Parser (State [tok] (Failure m) a) - deriving Monad - -In this case the derived instance declaration is of the form - - instance Monad (State [tok] (Failure m)) => Monad (Parser tok m) - - -Notice that, since Monad is a constructor class, the -instance is a partial application of the new type, not the -entire left hand side. We can imagine that the type declaration is -``eta-converted'' to generate the context of the instance -declaration. - - - -We can even derive instances of multi-parameter classes, provided the -newtype is the last class parameter. In this case, a ``partial -application'' of the class appears in the deriving -clause. For example, given the class - - - class StateMonad s m | m -> s where ... - instance Monad m => StateMonad s (State s m) where ... - -then we can derive an instance of StateMonad for Parsers by - - newtype Parser tok m a = Parser (State [tok] (Failure m) a) - deriving (Monad, StateMonad [tok]) - - -The derived instance is obtained by completing the application of the -class to the new type: - - - instance StateMonad [tok] (State [tok] (Failure m)) => - StateMonad [tok] (Parser tok m) - - - - -As a result of this extension, all derived instances in newtype -declarations are treated uniformly (and implemented just by reusing -the dictionary for the representation type), except -Show and Read, which really behave differently for -the newtype and its representation. - - - - A more precise specification - -Derived instance declarations are constructed as follows. Consider the -declaration (after expansion of any type synonyms) - - - newtype T v1...vn = T' (S t1...tk vk+1...vn) deriving (c1...cm) - - -where S is a type constructor, t1...tk are -types, -vk+1...vn are type variables which do not occur in any of -the ti, and the ci are partial applications of -classes of the form C t1'...tj'. The derived instance -declarations are, for each ci, - - - instance ci (S t1...tk vk+1...v) => ci (T v1...vp) - -where p is chosen so that T v1...vp is of the -right kind for the last parameter of class Ci. - - - -As an example which does not work, consider - - newtype NonMonad m s = NonMonad (State s m s) deriving Monad - -Here we cannot derive the instance - - instance Monad (State s m) => Monad (NonMonad m) - - -because the type variable s occurs in State s m, -and so cannot be "eta-converted" away. It is a good thing that this -deriving clause is rejected, because NonMonad m is -not, in fact, a monad --- for the same reason. Try defining ->>= with the correct type: you won't be able to. - - - -Notice also that the order of class parameters becomes -important, since we can only derive instances for the last one. If the -StateMonad class above were instead defined as - - - class StateMonad m s | m -> s where ... - - -then we would not have been able to derive an instance for the -Parser type above. We hypothesise that multi-parameter -classes usually have one "main" parameter for which deriving new -instances is most interesting. - - - -