language, GHC extensions, GHC As with all known Haskell systems, GHC implements some extensions to the language. To use them, you'll need to give a -fglasgow-exts option option. Virtually all of the Glasgow extensions serve to give you access to the underlying facilities with which we implement Haskell. Thus, you can get at the Raw Iron, if you are willing to write some non-standard code at a more primitive level. You need not be “stuck” on performance because of the implementation costs of Haskell's “high-level” features—you can always code “under” them. In an extreme case, you can write all your time-critical code in C, and then just glue it together with Haskell! 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: Multi-parameter type classes: Functional dependencies: 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 . Language options languageoption optionslanguage extensionsoptions controlling These flags control what variation of the language are permitted. Leaving out all of them gives you standard Haskell 98. : This simultaneously enables all of the extensions to Haskell 98 described in , except where otherwise noted. : Switch off the Haskell 98 monomorphism restriction. Independent of the flag. See . Only relevant if you also use . See . Only relevant if you also use . See . Independent of . -fno-implicit-prelude option GHC normally imports Prelude.hi files for you. If you'd rather it didn't, then give it a option. The idea is that you can then import a Prelude of your own. (But don't call it Prelude; the Haskell module namespace is flat, and you must not conflict with any Prelude module.) Even though you have not imported the Prelude, all 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] still means Prelude.[] Int; tuples continue to refer to the standard Prelude tuples; the 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). &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. 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. 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" 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. 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... 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: 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. 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. 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 two overlapping instance declarations are permitted iff 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. 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 instance C (Int,Int) where ... as well, then the compiler will complain about the overlapping (actually, identical) instance declarations. As always, type synonyms must be fully applied. You cannot, for example, write: type P a = [[a]] instance Monad P where ... This design decision is independent of all the others, and easily reversed, but it makes sense to me. The types in an instance-declaration context must all be type variables. Thus instance C a b => Eq (a,b) where ... is OK, but instance C Int b => Foo b where ... is not OK. Again, the intent here is to make sure that context reduction terminates. Voluminous correspondence on the Haskell mailing list has convinced me that it's worth experimenting with a more liberal rule. If you use the flag can use arbitrary types in an instance context. Termination is ensured by having a fixed-depth recursion stack. If you exceed the stack depth you get a sort of backtrace, and the opportunity to increase the stack depth with N. Implicit parameters Implicit paramters are implemented as described in "Implicit parameters: dynamic scoping with static types", J Lewis, MB Shields, E Meijer, J Launchbury, 27th ACM Symposium on Principles of Programming Languages (POPL'00), Boston, Jan 2000. There should be more documentation, but there isn't (yet). Yell if you need it. You can't have an implicit parameter in the context of a class or instance declaration. For example, both these declarations are illegal: class (?x::Int) => C a where ... instance (?x::a) => Foo [a] where ... 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. Functional dependencies Functional dependencies are implemented as described by Mark 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. There should be more documentation, but there isn't (yet). Yell if you need it. Explicit universal quantification GHC's type system supports explicit universal quantification in constructor fields and function arguments. This is useful for things like defining runST from the state-thread world. GHC's syntax for this now agrees with Hugs's, namely: forall a b. (Ord a, Eq b) => a -> b -> a The context is, of course, optional. You can't use forall as a type variable any more! Haskell type signatures are implicitly quantified. The forall allows us to say exactly what this means. For example: g :: b -> b means this: g :: forall b. (b -> b) The two are treated identically. Universally-quantified data type fields In a data or newtype declaration one can quantify the types of the constructor arguments. Here are several examples: data T a = T1 (forall b. b -> b -> b) a data MonadT m = MkMonad { return :: forall a. a -> m a, bind :: forall a b. m a -> (a -> m b) -> m b } newtype Swizzle = MkSwizzle (Ord a => [a] -> [a]) The constructors now have so-called rank 2 polymorphic types, in which there is a for-all in the argument types.: T1 :: forall a. (forall b. b -> b -> b) -> a -> T a MkMonad :: forall m. (forall a. a -> m a) -> (forall a b. m a -> (a -> m b) -> m b) -> MonadT m MkSwizzle :: (Ord a => [a] -> [a]) -> Swizzle Notice that you don't need to use a forall if there's an explicit context. For example in the first argument of the constructor MkSwizzle, an implicit "forall a." is prefixed to the argument type. The implicit forall quantifies all type variables that are not already in scope, and are mentioned in the type quantified over. As for type signatures, implicit quantification happens for non-overloaded types too. So if you write this: data T a = MkT (Either a b) (b -> b) it's just as if you had written this: data T a = MkT (forall b. Either a b) (forall b. b -> b) That is, since the type variable b isn't in scope, it's implicitly universally quantified. (Arguably, it would be better to require explicit quantification on constructor arguments where that is what is wanted. Feedback welcomed.) Construction You construct values of types T1, MonadT, Swizzle by applying the constructor to suitable values, just as usual. For example, (T1 (\xy->x) 3) :: T Int (MkSwizzle sort) :: Swizzle (MkSwizzle reverse) :: Swizzle (let r x = Just x b m k = case m of Just y -> k y Nothing -> Nothing in MkMonad r b) :: MonadT Maybe The type of the argument can, as usual, be more general than the type required, as (MkSwizzle reverse) shows. (reverse does not need the Ord constraint.) Pattern matching When you use pattern matching, the bound variables may now have polymorphic types. For example: f :: T a -> a -> (a, Char) f (T1 f k) x = (f k x, f 'c' 'd') g :: (Ord a, Ord b) => Swizzle -> [a] -> (a -> b) -> [b] g (MkSwizzle s) xs f = s (map f (s xs)) h :: MonadT m -> [m a] -> m [a] h m [] = return m [] h m (x:xs) = bind m x $ \y -> bind m (h m xs) $ \ys -> return m (y:ys) In the function h we use the record selectors return and bind to extract the polymorphic bind and return functions from the MonadT data structure, rather than using pattern matching. You cannot pattern-match against an argument that is polymorphic. For example: newtype TIM s a = TIM (ST s (Maybe a)) runTIM :: (forall s. TIM s a) -> Maybe a runTIM (TIM m) = runST m Here the pattern-match fails, because you can't pattern-match against an argument of type (forall s. TIM s a). Instead you must bind the variable and pattern match in the right hand side: runTIM :: (forall s. TIM s a) -> Maybe a runTIM tm = case tm of { TIM m -> runST m } The tm on the right hand side is (invisibly) instantiated, like any polymorphic value at its occurrence site, and now you can pattern-match against it. The partial-application restriction There is really only one way in which data structures with polymorphic components might surprise you: you must not partially apply them. For example, this is illegal: map MkSwizzle [sort, reverse] The restriction is this: every subexpression of the program must have a type that has no for-alls, except that in a function application (f e1…en) the partial applications are not subject to this rule. The restriction makes type inference feasible. In the illegal example, the sub-expression MkSwizzle has the polymorphic type (Ord b => [b] -> [b]) -> Swizzle and is not a sub-expression of an enclosing application. On the other hand, this expression is OK: map (T1 (\a b -> a)) [1,2,3] even though it involves a partial application of T1, because the sub-expression T1 (\a b -> a) has type Int -> T Int. Type signatures Once you have data constructors with universally-quantified fields, or constants such as runST that have rank-2 types, it isn't long before you discover that you need more! Consider: mkTs f x y = [T1 f x, T1 f y] mkTs is a fuction that constructs some values of type T, using some pieces passed to it. The trouble is that since f is a function argument, Haskell assumes that it is monomorphic, so we'll get a type error when applying T1 to it. This is a rather silly example, but the problem really bites in practice. Lots of people trip over the fact that you can't make "wrappers functions" for runST for exactly the same reason. In short, it is impossible to build abstractions around functions with rank-2 types. The solution is fairly clear. We provide the ability to give a rank-2 type signature for ordinary functions (not only data constructors), thus: mkTs :: (forall b. b -> b -> b) -> a -> [T a] mkTs f x y = [T1 f x, T1 f y] This type signature tells the compiler to attribute f with the polymorphic type (forall b. b -> b -> b) when type checking the body of mkTs, so now the application of T1 is fine. There are two restrictions: You can only define a rank 2 type, specified by the following grammar: rank2type ::= [forall tyvars .] [context =>] funty funty ::= ([forall tyvars .] [context =>] ty) -> funty | ty ty ::= ...current Haskell monotype syntax... Informally, the universal quantification must all be right at the beginning, or at the top level of a function argument. There is a restriction on the definition of a function whose type signature is a rank-2 type: the polymorphic arguments must be matched on the left hand side of the "=" sign. You can't define mkTs like this: mkTs :: (forall b. b -> b -> b) -> a -> [T a] mkTs = \ f x y -> [T1 f x, T1 f y] The same partial-application rule applies to ordinary functions with rank-2 types as applied to data constructors. Type synonyms and hoisting GHC also allows you to write a forall in a type synonym, thus: type Discard a = forall b. a -> b -> a f :: Discard a f x y = x However, it is often convenient to use these sort of synonyms at the right hand end of an arrow, thus: type Discard a = forall b. a -> b -> a g :: Int -> Discard Int g x y z = x+y Simply expanding the type synonym would give g :: Int -> (forall b. Int -> b -> Int) but GHC "hoists" the forall to give the isomorphic type g :: forall b. Int -> Int -> b -> Int In general, the rule is this: to determine the type specified by any explicit user-written type (e.g. in a type signature), GHC expands type synonyms and then repeatedly performs the transformation: type1 -> forall a. type2 ==> forall a. type1 -> type2 (In fact, GHC tries to retain as much synonym information as possible for use in error messages, but that is a usability issue.) This rule applies, of course, whether or not the forall comes from a synonym. For example, here is another valid way to write g's type signature: g :: Int -> Int -> forall b. b -> Int Existentially quantified data constructors The idea of using existential quantification in data type declarations was suggested by Laufer (I believe, thought doubtless someone will correct me), and implemented in Hope+. It's been in Lennart Augustsson's hbc Haskell compiler for several years, and proved very useful. Here's the idea. Consider the declaration: data Foo = forall a. MkFoo a (a -> Bool) | Nil The data type Foo has two constructors with types: MkFoo :: forall a. a -> (a -> Bool) -> Foo Nil :: Foo Notice that the type variable a in the type of MkFoo does not appear in the data type itself, which is plain Foo. For example, the following expression is fine: [MkFoo 3 even, MkFoo 'c' isUpper] :: [Foo] Here, (MkFoo 3 even) packages an integer with a function even that maps an integer to Bool; and MkFoo 'c' isUpper packages a character with a compatible function. These two things are each of type Foo and can be put in a list. What can we do with a value of type Foo?. In particular, what happens when we pattern-match on MkFoo? f (MkFoo val fn) = ??? Since all we know about val and fn is that they are compatible, the only (useful) thing we can do with them is to apply fn to val to get a boolean. For example: f :: Foo -> Bool f (MkFoo val fn) = fn val What this allows us to do is to package heterogenous values together with a bunch of functions that manipulate them, and then treat that collection of packages in a uniform manner. You can express quite a bit of object-oriented-like programming this way. Why existential? What has this to do with existential quantification? Simply that MkFoo has the (nearly) isomorphic type MkFoo :: (exists a . (a, a -> Bool)) -> Foo But Haskell programmers can safely think of the ordinary universally quantified type given above, thereby avoiding adding a new existential quantification construct. Type classes An easy extension (implemented in hbc) is to allow arbitrary contexts before the constructor. For example: data Baz = forall a. Eq a => Baz1 a a | forall b. Show b => Baz2 b (b -> b) The two constructors have the types you'd expect: Baz1 :: forall a. Eq a => a -> a -> Baz Baz2 :: forall b. Show b => b -> (b -> b) -> Baz But when pattern matching on Baz1 the matched values can be compared for equality, and when pattern matching on Baz2 the first matched value can be converted to a string (as well as applying the function to it). So this program is legal: f :: Baz -> String f (Baz1 p q) | p == q = "Yes" | otherwise = "No" f (Baz1 v fn) = show (fn v) Operationally, in a dictionary-passing implementation, the constructors Baz1 and Baz2 must store the dictionaries for Eq and Show respectively, and extract it on pattern matching. Notice the way that the syntax fits smoothly with that used for universal quantification earlier. Restrictions There are several restrictions on the ways in which existentially-quantified constructors can be use. When pattern matching, each pattern match introduces a new, distinct, type for each existential type variable. These types cannot be unified with any other type, nor can they escape from the scope of the pattern match. For example, these fragments are incorrect: f1 (MkFoo a f) = a Here, the type bound by MkFoo "escapes", because a is the result of f1. One way to see why this is wrong is to ask what type f1 has: f1 :: Foo -> a -- Weird! What is this "a" in the result type? Clearly we don't mean this: f1 :: forall a. Foo -> a -- Wrong! The original program is just plain wrong. Here's another sort of error f2 (Baz1 a b) (Baz1 p q) = a==q It's ok to say a==b or p==q, but a==q is wrong because it equates the two distinct types arising from the two Baz1 constructors. You can't pattern-match on an existentially quantified constructor in a let or where group of bindings. So this is illegal: f3 x = a==b where { Baz1 a b = x } You can only pattern-match on an existentially-quantified constructor in a case expression or in the patterns of a function definition. The reason for this restriction is really an implementation one. Type-checking binding groups is already a nightmare without existentials complicating the picture. Also an existential pattern binding at the top level of a module doesn't make sense, because it's not clear how to prevent the existentially-quantified type "escaping". So for now, there's a simple-to-state restriction. We'll see how annoying it is. You can't use existential quantification for newtype declarations. So this is illegal: newtype T = forall a. Ord a => MkT a Reason: a value of type T must be represented as a pair of a dictionary for Ord t and a value of type t. That contradicts the idea that newtype should have no concrete representation. You can get just the same efficiency and effect by using data instead of newtype. If there is no overloading involved, then there is more of a case for allowing an existentially-quantified newtype, because the data because the data version does carry an implementation cost, but single-field existentially quantified constructors aren't much use. So the simple restriction (no existential stuff on newtype) stands, unless there are convincing reasons to change it. You can't use deriving to define instances of a data type with existentially quantified data constructors. Reason: in most cases it would not make sense. For example:# data T = forall a. MkT [a] deriving( Eq ) To derive Eq in the standard way we would need to have equality between the single component of two MkT constructors: instance Eq T where (MkT a) == (MkT b) = ??? But a and b have distinct types, and so can't be compared. It's just about possible to imagine examples in which the derived instance would make sense, but it seems altogether simpler simply to prohibit such declarations. Define your own instances! 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 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. 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 Exception library () for the details. Scoped Type Variables A pattern type signature can introduce a scoped type variable. For example f (xs::[a]) = ys ++ ys where ys :: [a] ys = reverse xs The pattern (xs::[a]) includes a type signature for xs. This brings the type variable a into scope; it scopes over all the patterns and right hand sides for this equation for f. In particular, it is in scope at the type signature for y. Pattern type signatures are completely orthogonal to ordinary, separate type signatures. The two can be used independently or together. At ordinary type signatures, such as that for ys, any type variables mentioned in the type signature that are not in scope are implicitly universally quantified. (If there are no type variables in scope, all type variables mentioned in the signature are universally quantified, which is just as in Haskell 98.) In this case, since a is in scope, it is not universally quantified, so the type of ys is the same as that of xs. In Haskell 98 it is not possible to declare a type for ys; a major benefit of scoped type variables is that it becomes possible to do so. Scoped type variables are implemented in both GHC and Hugs. Where the implementations differ from the specification below, those differences 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 the name for a type. The restriction they express is that all occurrences of the same name mean the same type. For example: f :: [Int] -> Int -> Int f (xs::[a]) (y::a) = (head xs + y) :: a The pattern type signatures on the left hand side of f express the fact that xs must be a list of things of some type a; and that y must have this same type. The type signature on the expression (head xs) specifies that this expression must have the same type a. There is no requirement that the type named by "a" is in fact a type variable. Indeed, in this case, the type named by "a" is Int. (This is a slight liberalisation from the original rather complex rules, which specified that a pattern-bound type variable should be universally quantified.) For example, all of these are legal: t (x::a) (y::a) = x+y*2 f (x::a) (y::b) = [x,y] -- a unifies with b g (x::a) = x + 1::Int -- a unifies with Int h x = let k (y::a) = [x,y] -- a is free in the in k x -- environment k (x::a) True = ... -- a unifies with Int k (x::Int) False = ... w :: [b] -> [b] w (x::a) = x -- a unifies with [b] Scope and implicit quantification All the type variables mentioned in a pattern, that are not already in scope, are brought into scope by the pattern. We describe this set as the type variables bound by the pattern. For example: f (x::a) = let g (y::(a,b)) = fst y in g (x,True) The pattern (x::a) brings the type variable a into scope, as well as the term variable x. The pattern (y::(a,b)) contains an occurrence of the already-in-scope type variable a, and brings into scope the type variable b. The type variables thus brought into scope may be mentioned in ordinary type signatures or pattern type signatures anywhere within their scope. In ordinary type signatures, any type variable mentioned in the signature that is in scope is not universally quantified. Ordinary type signatures do not bring any new type variables into scope (except in the type signature itself!). So this is illegal: f :: a -> a f x = x::a It's illegal because a is not in scope in the body of f, so the ordinary signature x::a is equivalent to x::forall a.a; and that is an incorrect typing. There is no implicit universal quantification on pattern type signatures, nor may one write an explicit forall type in a pattern type signature. The pattern type signature is a monotype. The type variables in the head of a class or instance declaration scope over the methods defined in the where part. For example: class C a where op :: [a] -> a op xs = let ys::[a] ys = reverse xs in head ys (Not implemented in Hugs yet, Dec 98). Result type signatures The result type of a function can be given a signature, thus: f (x::a) :: [a] = [x,x,x] The final :: [a] after all the patterns gives a signature to the result type. Sometimes this is the only way of naming the type variable you want: f :: Int -> [a] -> [a] f n :: ([a] -> [a]) = let g (x::a, y::a) = (y,x) in \xs -> map g (reverse xs `zip` xs) Result type signatures are not yet implemented in Hugs. Where a pattern type signature can occur A pattern type signature can occur in any pattern, but there are restrictions on pattern bindings: A pattern type signature can be on an arbitrary sub-pattern, not ust on a variable: f ((x,y)::(a,b)) = (y,x) :: (b,a) Pattern type signatures, including the result part, can be used in lambda abstractions: (\ (x::a, y) :: a -> x) Pattern type signatures, including the result part, can be used in case expressions: case e of { (x::a, y) :: a -> x } 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 that bind new type variables may not be used in pattern bindings at all. So this is illegal: f x = let (y, z::a) = x in ... But these are OK, because they do not bind fresh type variables: f1 x = let (y, z::Int) = x in ... f2 (x::(Int,a)) = let (y, z::a) = x in ... However a single variable is considered a degenerate function binding, rather than a degerate pattern binding, so this is permitted, even though it binds a type variable: f :: (b->b) = \(x::b) -> x Such degnerate function bindings do not fall under the monomorphism restriction. Thus: g :: a -> a -> Bool = \x y. x==y Here g has type forall a. Eq a => a -> a -> Bool, just as if g had a separate type signature. Lacking a type signature, g would get a monomorphic type. Pragmas pragma GHC supports several pragmas, or instructions to the compiler placed in the source code. Pragmas don't normally affect the meaning of the program, but they might affect the efficiency of the generated code. Pragmas all take the form {-# word ... #-} where word indicates the type of pragma, and is followed optionally by information specific to that type of pragma. Case is ignored in word. The various values for word that GHC understands are described in the following sections; any pragma encountered with an unrecognised word is (silently) ignored. INLINE pragma <indexterm><primary>INLINE pragma</primary></indexterm> <indexterm><primary>pragma, INLINE</primary></indexterm> GHC (with , as always) tries to inline (or “unfold”) functions/values that are “small enough,” thus avoiding the call overhead and possibly exposing other more-wonderful optimisations. You will probably see these unfoldings (in Core syntax) in your interface files. Normally, if GHC decides a function is “too expensive” to inline, it will not do so, nor will it export that unfolding for other modules to use. The sledgehammer you can bring to bear is the INLINEINLINE pragma pragma, used thusly: key_function :: Int -> String -> (Bool, Double) #ifdef __GLASGOW_HASKELL__ {-# INLINE key_function #-} #endif (You don't need to do the C pre-processor carry-on unless you're going to stick the code through HBC—it doesn't like INLINE pragmas.) The major effect of an INLINE pragma is to declare a function's “cost” to be very low. The normal unfolding machinery will then be very keen to inline it. An INLINE pragma for a function can be put anywhere its type signature could be put. INLINE pragmas are a particularly good idea for the then/return (or bind/unit) functions in a monad. For example, in GHC's own UniqueSupply monad code, we have: #ifdef __GLASGOW_HASKELL__ {-# INLINE thenUs #-} {-# INLINE returnUs #-} #endif NOINLINE pragma NOINLINE pragma pragmaNOINLINE NOTINLINE pragma pragmaNOTINLINE The NOINLINE pragma does exactly what you'd expect: it stops the named function from being inlined by the compiler. You shouldn't ever need to do this, unless you're very cautious about code size. NOTINLINE is a synonym for NOINLINE (NOTINLINE is specified by Haskell 98 as the standard way to disable inlining, so it should be used if you want your code to be portable). SPECIALIZE pragma SPECIALIZE pragma pragma, SPECIALIZE overloading, death to (UK spelling also accepted.) For key overloaded functions, you can create extra versions (NB: more code space) specialised to particular types. Thus, if you have an overloaded function: hammeredLookup :: Ord key => [(key, value)] -> key -> value If it is heavily used on lists with Widget keys, you could specialise it as follows: {-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-} To get very fancy, you can also specify a named function to use for the specialised value, as in: {-# RULES hammeredLookup = blah #-} where blah is an implementation of hammerdLookup written specialy for Widget lookups. It's Your Responsibility to make sure that blah really behaves as a specialised version of hammeredLookup!!! Note we use the RULE pragma here to indicate that hammeredLookup applied at a certain type should be replaced by blah. See for more information on RULES. An example in which using RULES for specialisation will Win Big: toDouble :: Real a => a -> Double toDouble = fromRational . toRational {-# SPECIALIZE toDouble :: Int -> Double = i2d #-} i2d (I# i) = D# (int2Double# i) -- uses Glasgow prim-op directly The i2d function is virtually one machine instruction; the default conversion—via an intermediate Rational—is obscenely expensive by comparison. A SPECIALIZE pragma for a function can be put anywhere its type signature could be put. SPECIALIZE instance pragma SPECIALIZE pragma overloading, death to Same idea, except for instance declarations. For example: instance (Eq a) => Eq (Foo a) where { ... usual stuff ... } {-# SPECIALIZE instance Eq (Foo [(Int, Bar)] #-} Compatible with HBC, by the way. LINE pragma LINE pragma pragma, LINE This pragma is similar to C's #line pragma, and is mainly for use in automatically generated Haskell code. It lets you specify the line number and filename of the original code; for example {-# LINE 42 "Foo.vhs" #-} if you'd generated the current file from something called Foo.vhs and this line corresponds to line 42 in the original. GHC will adjust its error messages to refer to the line/file named in the LINE pragma. RULES pragma The RULES pragma lets you specify rewrite rules. It is described in . DEPRECATED pragma The DEPRECATED pragma lets you specify that a particular function, class, or type, is deprecated. There are two forms. You can deprecate an entire module thus: module Wibble {-# DEPRECATED "Use Wobble instead" #-} where ... When you compile any module that import Wibble, GHC will print the specified message. You can deprecate a function, class, or type, with the following top-level declaration: {-# DEPRECATED f, C, T "Don't use these" #-} When you compile any module that imports and uses any of the specifed entities, GHC will print the specified message. You can suppress the warnings with the flag . Rewrite rules <indexterm><primary>RULES pagma</primary></indexterm> <indexterm><primary>pragma, RULES</primary></indexterm> <indexterm><primary>rewrite rules</primary></indexterm> The programmer can specify rewrite rules as part of the source program (in a pragma). GHC applies these rewrite rules wherever it can. Here is an example: {-# RULES "map/map" forall f g xs. map f (map g xs) = map (f.g) xs #-} Syntax From a syntactic point of view: Each rule has a name, enclosed in double quotes. The name itself has no significance at all. It is only used when reporting how many times the rule fired. There may be zero or more rules in a RULES pragma. Layout applies in a RULES pragma. Currently no new indentation level is set, so you must lay out your rules starting in the same column as the enclosing definitions. Each variable mentioned in a rule must either be in scope (e.g. map), or bound by the forall (e.g. f, g, xs). The variables bound by the forall are called the pattern variables. They are separated by spaces, just like in a type forall. A pattern variable may optionally have a type signature. If the type of the pattern variable is polymorphic, it must have a type signature. For example, here is the foldr/build rule: "fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . foldr k z (build g) = g k z Since g has a polymorphic type, it must have a type signature. The left hand side of a rule must consist of a top-level variable applied to arbitrary expressions. For example, this is not OK: "wrong1" forall e1 e2. case True of { True -> e1; False -> e2 } = e1 "wrong2" forall f. f True = True In "wrong1", the LHS is not an application; in "wrong2", the LHS has a pattern variable in the head. A rule does not need to be in the same module as (any of) the variables it mentions, though of course they need to be in scope. Rules are automatically exported from a module, just as instance declarations are. Semantics From a semantic point of view: Rules are only applied if you use the flag. Rules are regarded as left-to-right rewrite rules. When GHC finds an expression that is a substitution instance of the LHS of a rule, it replaces the expression by the (appropriately-substituted) RHS. By "a substitution instance" we mean that the LHS can be made equal to the expression by substituting for the pattern variables. The LHS and RHS of a rule are typechecked, and must have the same type. GHC makes absolutely no attempt to verify that the LHS and RHS of a rule have the same meaning. That is undecideable in general, and infeasible in most interesting cases. The responsibility is entirely the programmer's! GHC makes no attempt to make sure that the rules are confluent or terminating. For example: "loop" forall x,y. f x y = f y x This rule will cause the compiler to go into an infinite loop. If more than one rule matches a call, GHC will choose one arbitrarily to apply. GHC currently uses a very simple, syntactic, matching algorithm for matching a rule LHS with an expression. It seeks a substitution which makes the LHS and expression syntactically equal modulo alpha conversion. The pattern (rule), but not the expression, is eta-expanded if necessary. (Eta-expanding the epression can lead to laziness bugs.) But not beta conversion (that's called higher-order matching). Matching is carried out on GHC's intermediate language, which includes type abstractions and applications. So a rule only matches if the types match too. See below. GHC keeps trying to apply the rules as it optimises the program. For example, consider: let s = map f t = map g in s (t xs) The expression s (t xs) does not match the rule "map/map", but GHC will substitute for s and t, giving an expression which does match. If s or t was (a) used more than once, and (b) large or a redex, then it would not be substituted, and the rule would not fire. In the earlier phases of compilation, GHC inlines nothing that appears on the LHS of a rule, because once you have substituted for something you can't match against it (given the simple minded matching). So if you write the rule "map/map" forall f,g. map f . map g = map (f.g) this won't match the expression map f (map g xs). It will only match something written with explicit use of ".". Well, not quite. It will match the expression wibble f g xs where wibble is defined: wibble f g = map f . map g because wibble will be inlined (it's small). Later on in compilation, GHC starts inlining even things on the LHS of rules, but still leaves the rules enabled. This inlining policy is controlled by the per-simplification-pass flag n. All rules are implicitly exported from the module, and are therefore in force in any module that imports the module that defined the rule, directly or indirectly. (That is, if A imports B, which imports C, then C's rules are in force when compiling A.) The situation is very similar to that for instance declarations. List fusion The RULES mechanism is used to implement fusion (deforestation) of common list functions. If a "good consumer" consumes an intermediate list constructed by a "good producer", the intermediate list should be eliminated entirely. The following are good producers: List comprehensions Enumerations of Int and Char (e.g. ['a'..'z']). Explicit lists (e.g. [True, False]) The cons constructor (e.g 3:4:[]) ++ map filter iterate, repeat zip, zipWith The following are good consumers: List comprehensions array (on its second argument) length ++ (on its first argument) foldr map filter concat unzip, unzip2, unzip3, unzip4 zip, zipWith (but on one argument only; if both are good producers, zip will fuse with one but not the other) partition head and, or, any, all sequence_ msum sortBy So, for example, the following should generate no intermediate lists: array (1,10) [(i,i*i) | i <- map (+ 1) [0..9]] This list could readily be extended; if there are Prelude functions that you use a lot which are not included, please tell us. If you want to write your own good consumers or producers, look at the Prelude definitions of the above functions to see how to do so. Specialisation Rewrite rules can be used to get the same effect as a feature present in earlier version of GHC: {-# SPECIALIZE fromIntegral :: Int8 -> Int16 = int8ToInt16 #-} This told GHC to use int8ToInt16 instead of fromIntegral whenever the latter was called with type Int8 -> Int16. That is, rather than specialising the original definition of fromIntegral the programmer is promising that it is safe to use int8ToInt16 instead. This feature is no longer in GHC. But rewrite rules let you do the same thing: {-# RULES "fromIntegral/Int8/Int16" fromIntegral = int8ToInt16 #-} This slightly odd-looking rule instructs GHC to replace fromIntegral by int8ToInt16 whenever the types match. Speaking more operationally, GHC adds the type and dictionary applications to get the typed rule forall (d1::Integral Int8) (d2::Num Int16) . fromIntegral Int8 Int16 d1 d2 = int8ToInt16 What is more, this rule does not need to be in the same file as fromIntegral, unlike the SPECIALISE pragmas which currently do (so that they have an original definition available to specialise). Controlling what's going on Use to see what transformation rules GHC is using. Use to see what rules are being fired. If you add you get a more detailed listing. The defintion of (say) build in PrelBase.lhs looks llike this: build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] {-# INLINE build #-} build g = g (:) [] Notice the INLINE! That prevents (:) from being inlined when compiling PrelBase, so that an importing module will “see” the (:), and can match it on the LHS of a rule. INLINE prevents any inlining happening in the RHS of the INLINE thing. I regret the delicacy of this. In ghc/lib/std/PrelBase.lhs look at the rules for map to see how to write rules that will do fusion and yet give an efficient program even if fusion doesn't happen. More rules in PrelList.lhs. Generic classes (Note: support for generic classes is currently broken in GHC 5.02). The ideas behind this extension are described in detail in "Derivable type classes", Ralf Hinze and Simon Peyton Jones, Haskell Workshop, Montreal Sept 2000, pp94-105. An example will give the idea: import Generics class Bin a where toBin :: a -> [Int] fromBin :: [Int] -> (a, [Int]) toBin {| Unit |} Unit = [] toBin {| a :+: b |} (Inl x) = 0 : toBin x toBin {| a :+: b |} (Inr y) = 1 : toBin y toBin {| a :*: b |} (x :*: y) = toBin x ++ toBin y fromBin {| Unit |} bs = (Unit, bs) fromBin {| a :+: b |} (0:bs) = (Inl x, bs') where (x,bs') = fromBin bs fromBin {| a :+: b |} (1:bs) = (Inr y, bs') where (y,bs') = fromBin bs fromBin {| a :*: b |} bs = (x :*: y, bs'') where (x,bs' ) = fromBin bs (y,bs'') = fromBin bs' This class declaration explains how toBin and fromBin work for arbitrary data types. They do so by giving cases for unit, product, and sum, which are defined thus in the library module Generics: data Unit = Unit data a :+: b = Inl a | Inr b data a :*: b = a :*: b Now you can make a data type into an instance of Bin like this: instance (Bin a, Bin b) => Bin (a,b) instance Bin a => Bin [a] That is, just leave off the "where" clasuse. Of course, you can put in the where clause and over-ride whichever methods you please. Using generics To use generics you need to Use the flags (to enable the extra syntax), (to generate extra per-data-type code), and (to make the Generics library available. Import the module Generics from the lang package. This import brings into scope the data types Unit, :*:, and :+:. (You don't need this import if you don't mention these types explicitly; for example, if you are simply giving instance declarations.) Changes wrt the paper Note that the type constructors :+: and :*: can be written infix (indeed, you can now use any operator starting in a colon as an infix type constructor). Also note that the type constructors are not exactly as in the paper (Unit instead of 1, etc). Finally, note that the syntax of the type patterns in the class declaration uses "{|" and "|}" brackets; curly braces alone would ambiguous when they appear on right hand sides (an extension we anticipate wanting). Terminology and restrictions Terminology. A "generic default method" in a class declaration is one that is defined using type patterns as above. A "polymorphic default method" is a default method defined as in Haskell 98. A "generic class declaration" is a class declaration with at least one generic default method. Restrictions: Alas, we do not yet implement the stuff about constructor names and field labels. A generic class can have only one parameter; you can't have a generic multi-parameter class. A default method must be defined entirely using type patterns, or entirely without. So this is illegal: class Foo a where op :: a -> (a, Bool) op {| Unit |} Unit = (Unit, True) op x = (x, False) However it is perfectly OK for some methods of a generic class to have generic default methods and others to have polymorphic default methods. The type variable(s) in the type pattern for a generic method declaration scope over the right hand side. So this is legal (note the use of the type variable ``p'' in a type signature on the right hand side: class Foo a where op :: a -> Bool op {| p :*: q |} (x :*: y) = op (x :: p) ... The type patterns in a generic default method must take one of the forms: a :+: b a :*: b Unit where "a" and "b" are type variables. Furthermore, all the type patterns for a single type constructor (:*:, say) must be identical; they must use the same type variables. So this is illegal: class Foo a where op :: a -> Bool op {| a :+: b |} (Inl x) = True op {| p :+: q |} (Inr y) = False The type patterns must be identical, even in equations for different methods of the class. So this too is illegal: class Foo a where op1 :: a -> Bool op1 {| a :*: b |} (x :*: y) = True op2 :: a -> Bool op2 {| p :*: q |} (x :*: y) = False (The reason for this restriction is that we gather all the equations for a particular type consructor into a single generic instance declaration.) A generic method declaration must give a case for each of the three type constructors. The type for a generic method can be built only from: Function arrows Type variables Tuples Arbitrary types not involving type variables Here are some example type signatures for generic methods: op1 :: a -> Bool op2 :: Bool -> (a,Bool) op3 :: [Int] -> a -> a op4 :: [a] -> Bool Here, op1, op2, op3 are OK, but op4 is rejected, because it has a type variable inside a list. This restriction is an implementation restriction: we just havn't got around to implementing the necessary bidirectional maps over arbitrary type constructors. It would be relatively easy to add specific type constructors, such as Maybe and list, to the ones that are allowed. In an instance declaration for a generic class, the idea is that the compiler will fill in the methods for you, based on the generic templates. However it can only do so if The instance type is simple (a type constructor applied to type variables, as in Haskell 98). No constructor of the instance type has unboxed fields. (Of course, these things can only arise if you are already using GHC extensions.) However, you can still give an instance declarations for types which break these rules, provided you give explicit code to override any generic default methods. The option dumps incomprehensible stuff giving details of what the compiler does with generic declarations. Another example Just to finish with, here's another example I rather like: class Tag a where nCons :: a -> Int nCons {| Unit |} _ = 1 nCons {| a :*: b |} _ = 1 nCons {| a :+: b |} _ = nCons (bot::a) + nCons (bot::b) tag :: a -> Int tag {| Unit |} _ = 1 tag {| a :*: b |} _ = 1 tag {| a :+: b |} (Inl x) = tag x tag {| a :+: b |} (Inr y) = nCons (bot::a) + tag y