X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fdocs%2Fusers_guide%2Fglasgow_exts.xml;h=beaaad616a393caf66fc20809d502363266087fb;hb=8e512635b618e1daa97022265f268ad4eafda6b4;hp=b9862477ba022340af1a5c87e15d31536ae1b970;hpb=ede08656f90d99fbafc54cf00085ab53e2504d71;p=ghc-hetmet.git diff --git a/ghc/docs/users_guide/glasgow_exts.xml b/ghc/docs/users_guide/glasgow_exts.xml index b986247..beaaad6 100644 --- a/ghc/docs/users_guide/glasgow_exts.xml +++ b/ghc/docs/users_guide/glasgow_exts.xml @@ -825,68 +825,68 @@ This name is not supported by GHC. So the flag causes the following pieces of built-in syntax to refer to whatever is in scope, not the Prelude - versions: + 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. - + An integer literal 368 means + "fromInteger (368::Integer)", rather than + "Prelude.fromInteger (368::Integer)". + - - Negation (e.g. "- (f x)") - means "negate (f x)" (not - Prelude.negate). - + Fractional literals are handed in just the same way, + except that the translation is + fromRational (3.68::Rational). + + + The equality test in an overloaded numeric pattern + uses whatever (==) is in scope. + + + The subtraction operation, and the + greater-than-or-equal test, in n+k patterns + use whatever (-) and (>=) are in scope. + - 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.(-)"). - + Negation (e.g. "- (f x)") + means "negate (f x)", both in numeric + patterns, and expressions. + "Do" notation is translated using whatever functions (>>=), - (>>), fail, and - return, are in scope (not the Prelude - versions). List comprehensions, and parallel array + (>>), and fail, + are in scope (not the Prelude + versions). List comprehensions, mdo (), and parallel array comprehensions, are unaffected. - Similarly recursive do notation (see - ) uses whatever - mfix function is in scope, and arrow + Arrow notation (see ) uses whatever arr, (>>>), first, app, (|||) and - loop functions are in scope. - + loop functions are in scope. But unlike the + other constructs, the types of these functions must match the + Prelude types very closely. Details are in flux; if you want + to use this, ask! + - - The functions with these names that GHC finds in scope - must have types matching those of the originals, namely: - - fromInteger :: Integer -> N - fromRational :: Rational -> N - negate :: N -> N - (-) :: N -> N -> N - (>>=) :: forall a b. M a -> (a -> M b) -> M b - (>>) :: forall a b. M a -> M b -> M b - return :: forall a. a -> M a - fail :: forall a. String -> M a - - (Here N may be any type, - and M any type constructor.) - +In all cases (apart from arrow notation), the static semantics should be that of the desugared form, +even if that is a little unexpected. For emample, the +static semantics of the literal 368 +is exactly that of fromInteger (368::Integer); it's fine for +fromInteger to have any of the types: + +fromInteger :: Integer -> Integer +fromInteger :: forall a. Foo a => Integer -> a +fromInteger :: Num a => a -> Integer +fromInteger :: Integer -> Bool -> Bool + + + Be warned: this is an experimental facility, with fewer checks than usual. Use -dcore-lint to typecheck the desugared program. If Core Lint is happy @@ -925,11 +925,11 @@ Nevertheless, they can be useful when defining "phantom types". -Infix type constructors and classes +Infix type constructors, classes, and type variables -GHC allows type constructors and classes to be operators, and to be written infix, very much -like expressions. More specifically: +GHC allows type constructors, classes, and type variables to be operators, and +to be written infix, very much like expressions. More specifically: A type constructor or class can be an operator, beginning with a colon; e.g. :*:. @@ -955,6 +955,21 @@ like expressions. More specifically: + A type variable can be an (unqualified) operator e.g. +. + The lexical syntax is the same as that for variable operators, excluding "(.)", + "(!)", and "(*)". In a binding position, the operator must be + parenthesised. For example: + + type T (+) = Int + Int + f :: T Either + f = Left 3 + + liftA2 :: Arrow (~>) + => (a -> b -> c) -> (e ~> a) -> (e ~> b) -> (e ~> c) + liftA2 = ... + + + 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. @@ -973,14 +988,6 @@ like expressions. More specifically: Function arrow is infixr with fixity 0. (This might change; I'm not sure what it should be.) - - 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. - @@ -1085,8 +1092,12 @@ because GHC does not allow unboxed tuples on the left of a function arrow. 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 +was suggested by Perry, and implemented in Hope+ (Nigel Perry, The Implementation +of Practical Functional Programming Languages, PhD Thesis, University of +London, 1991). It was later formalised by Laufer and Odersky +(Polymorphic type inference and abstract data types, +TOPLAS, 16(5), pp1411-1430, 1994). +It's been in Lennart Augustsson's hbc Haskell compiler for several years, and proved very useful. Here's the idea. Consider the declaration: @@ -1198,7 +1209,7 @@ adding a new existential quantification construct. Type classes -An easy extension (implemented in hbc) is to allow +An easy extension is to allow arbitrary contexts before the constructor. For example: @@ -1257,6 +1268,86 @@ universal quantification earlier. +Record Constructors + + +GHC allows existentials to be used with records syntax as well. For example: + + +data Counter a = forall self. NewCounter + { _this :: self + , _inc :: self -> self + , _display :: self -> IO () + , tag :: a + } + +Here tag is a public field, with a well-typed selector +function tag :: Counter a -> a. The self +type is hidden from the outside; any attempt to apply _this, +_inc or _output as functions will raise a +compile-time error. In other words, GHC defines a record selector function +only for fields whose type does not mention the existentially-quantified variables. +(This example used an underscore in the fields for which record selectors +will not be defined, but that is only programming style; GHC ignores them.) + + + +To make use of these hidden fields, we need to create some helper functions: + + +inc :: Counter a -> Counter a +inc (NewCounter x i d t) = NewCounter + { _this = i x, _inc = i, _display = d, tag = t } + +display :: Counter a -> IO () +display NewCounter{ _this = x, _display = d } = d x + + +Now we can define counters with different underlying implementations: + + +counterA :: Counter String +counterA = NewCounter + { _this = 0, _inc = (1+), _display = print, tag = "A" } + +counterB :: Counter String +counterB = NewCounter + { _this = "", _inc = ('#':), _display = putStrLn, tag = "B" } + +main = do + display (inc counterA) -- prints "1" + display (inc (inc counterB)) -- prints "##" + + +In GADT declarations (see ), the explicit +forall may be omitted. For example, we can express +the same Counter a using GADT: + + +data Counter a where + NewCounter { _this :: self + , _inc :: self -> self + , _display :: self -> IO () + , tag :: a + } + :: Counter a + + +At the moment, record update syntax is only supported for Haskell 98 data types, +so the following function does not work: + + +-- This is invalid; use explicit NewCounter instead for now +setTag :: Counter a -> a -> Counter a +setTag obj t = obj{ tag = t } + + + + + + + + Restrictions @@ -1418,19 +1509,20 @@ declarations. Define your own instances! Class declarations -This section documents GHC's implementation of multi-parameter type -classes. There's lots of background in the paper Type +This section, and the next one, documents GHC's type-class extensions. +There's lots of background in the paper Type classes: exploring the design space (Simon Peyton Jones, Mark Jones, Erik Meijer). -There are the following constraints on class declarations: - - +All the extensions are enabled by the flag. + + +Multi-parameter type classes - Multi-parameter type classes are permitted. For example: +Multi-parameter type classes are permitted. For example: @@ -1439,14 +1531,30 @@ There are the following constraints on class declarations: ...etc. + + + + +The superclasses of a class declaration + +There are no restrictions on the context in a class declaration +(which introduces superclasses), except that the class hierarchy must +be acyclic. So these class declarations are OK: - - - + + class Functor (m k) => FiniteMap m k where + ... + + class (Monad m, Monad (t m)) => Transform t m where + lift :: m a -> (t m) a + + + + - The class hierarchy must be acyclic. However, the definition +As in Haskell 98, The class hierarchy must be acyclic. However, the definition of "acyclic" involves only the superclass relationships. For example, this is OK: @@ -1463,37 +1571,60 @@ this is OK: 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 + +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). +GHC lifts this restriction. + + + + + +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, +. - + +Functional dependencies are introduced by a vertical bar in the syntax of a +class declaration; e.g. + + class (Monad m) => MonadState s m | m -> s where ... - + class Foo a b c | a b -> c where ... + +There should be more documentation, but there isn't (yet). Yell if you need it. + +Rules for functional dependencies - All of the class type variables must be reachable (in the sense +In a class declaration, all of the class type variables must be reachable (in the sense mentioned in ) -from the free variables of each method type -. For example: - +from the free variables of each method type. +For example: class Coll s a where @@ -1501,14 +1632,16 @@ from the free variables of each method type 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 +a. Functional dependencies can make the type variable +reachable: + + class Coll s a | s -> a where + empty :: s + insert :: s -> a -> s + +Alternatively Coll might be rewritten class Coll s a where @@ -1530,208 +1663,439 @@ class like this: class CollE s => Coll s a where insert :: s -> a -> s + + - - + +Background on functional dependencies - +The following description of the motivation and use of functional dependencies is taken +from the Hugs user manual, reproduced here (with minor changes) by kind +permission of Mark Jones. - - -Class method types - -Haskell 98 prohibits class method types to mention constraints on the -class type variable, thus: + +Consider the following class, intended as part of a +library for collection types: - class Seq s a where - fromList :: [a] -> s a - elem :: Eq a => a -> s a -> Bool + class Collects e ce where + empty :: ce + insert :: e -> ce -> ce + member :: e -> ce -> 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). +The type variable e used here represents the element type, while ce is the type +of the container itself. Within this framework, we might want to define +instances of this class for lists or characteristic functions (both of which +can be used to represent collections of any equality type), bit sets (which can +be used to represent collections of characters), or hash tables (which can be +used to represent any collection whose elements have a hash function). Omitting +standard implementation details, this would lead to the following declarations: + + instance Eq e => Collects e [e] where ... + instance Eq e => Collects e (e -> Bool) where ... + instance Collects Char BitSet where ... + instance (Hashable e, Collects a ce) + => Collects e (Array Int ce) where ... + +All this looks quite promising; we have a class and a range of interesting +implementations. Unfortunately, there are some serious problems with the class +declaration. First, the empty function has an ambiguous type: + + empty :: Collects e ce => ce + +By "ambiguous" we mean that there is a type variable e that appears on the left +of the => symbol, but not on the right. The problem with +this is that, according to the theoretical foundations of Haskell overloading, +we cannot guarantee a well-defined semantics for any term with an ambiguous +type. -With the GHC lifts this restriction. +We can sidestep this specific problem by removing the empty member from the +class declaration. However, although the remaining members, insert and member, +do not have ambiguous types, we still run into problems when we try to use +them. For example, consider the following two functions: + + f x y = insert x . insert y + g = f True 'a' + +for which GHC infers the following types: + + f :: (Collects a c, Collects b c) => a -> b -> c -> c + g :: (Collects Bool c, Collects Char c) => c -> c + +Notice that the type for f allows the two parameters x and y to be assigned +different types, even though it attempts to insert each of the two values, one +after the other, into the same collection. If we're trying to model collections +that contain only one type of value, then this is clearly an inaccurate +type. Worse still, the definition for g is accepted, without causing a type +error. As a result, the error in this code will not be flagged at the point +where it appears. Instead, it will show up only when we try to use g, which +might even be in a different module. - - - +An attempt to use constructor classes - -Type signatures - -The context of a type signature -Unlike Haskell 98, constraints in types do not have to be of -the form (class type-variable) or -(class (type-variable type-variable ...)). Thus, -these type signatures are perfectly OK +Faced with the problems described above, some Haskell programmers might be +tempted to use something like the following version of the class declaration: - g :: Eq [a] => ... - g :: Ord (T a ()) => ... + class Collects e c where + empty :: c e + insert :: e -> c e -> c e + member :: e -> c e -> Bool +The key difference here is that we abstract over the type constructor c that is +used to form the collection type c e, and not over that collection type itself, +represented by ce in the original class declaration. This avoids the immediate +problems that we mentioned above: empty has type Collects e c => c +e, which is not ambiguous. -GHC imposes the following restrictions on the constraints in a type signature. -Consider the type: - +The function f from the previous section has a more accurate type: - forall tv1..tvn (c1, ...,cn) => type + f :: (Collects e c) => e -> e -> c e -> c e - -(Here, we write the "foralls" explicitly, although the Haskell source -language omits them; in Haskell 98, all the free type variables of an -explicit source-language type signature are universally quantified, -except for the class type variables in a class declaration. However, -in GHC, you can give the foralls if you want. See ). +The function g from the previous section is now rejected with a type error as +we would hope because the type of f does not allow the two arguments to have +different types. +This, then, is an example of a multiple parameter class that does actually work +quite well in practice, without ambiguity problems. +There is, however, a catch. This version of the Collects class is nowhere near +as general as the original class seemed to be: only one of the four instances +for Collects +given above can be used with this version of Collects because only one of +them---the instance for lists---has a collection type that can be written in +the form c e, for some type constructor c, and element type e. + +Adding functional dependencies + + +To get a more useful version of the Collects class, Hugs provides a mechanism +that allows programmers to specify dependencies between the parameters of a +multiple parameter class (For readers with an interest in theoretical +foundations and previous work: The use of dependency information can be seen +both as a generalization of the proposal for `parametric type classes' that was +put forward by Chen, Hudak, and Odersky, or as a special case of Mark Jones's +later framework for "improvement" of qualified types. The +underlying ideas are also discussed in a more theoretical and abstract setting +in a manuscript [implparam], where they are identified as one point in a +general design space for systems of implicit parameterization.). + +To start with an abstract example, consider a declaration such as: + + class C a b where ... + +which tells us simply that C can be thought of as a binary relation on types +(or type constructors, depending on the kinds of a and b). Extra clauses can be +included in the definition of classes to add information about dependencies +between parameters, as in the following examples: + + class D a b | a -> b where ... + class E a b | a -> b, b -> a where ... + +The notation a -> b used here between the | and where +symbols --- not to be +confused with a function type --- indicates that the a parameter uniquely +determines the b parameter, and might be read as "a determines b." Thus D is +not just a relation, but actually a (partial) function. Similarly, from the two +dependencies that are included in the definition of E, we can see that E +represents a (partial) one-one mapping between types. + - - - - +More generally, dependencies take the form x1 ... xn -> y1 ... ym, +where x1, ..., xn, and y1, ..., yn are type variables with n>0 and +m>=0, meaning that the y parameters are uniquely determined by the x +parameters. Spaces can be used as separators if more than one variable appears +on any single side of a dependency, as in t -> a b. Note that a class may be +annotated with multiple dependencies using commas as separators, as in the +definition of E above. Some dependencies that we can write in this notation are +redundant, and will be rejected because they don't serve any useful +purpose, and may instead indicate an error in the program. Examples of +dependencies like this include a -> a , +a -> a a , +a -> , etc. There can also be +some redundancy if multiple dependencies are given, as in +a->b, + b->c , a->c , and +in which some subset implies the remaining dependencies. Examples like this are +not treated as errors. Note that dependencies appear only in class +declarations, and not in any other part of the language. In particular, the +syntax for instance declarations, class constraints, and types is completely +unchanged. + - Each universally quantified type variable -tvi must be reachable from type. - -A type variable a is "reachable" if it it appears -in the same constraint as either a type variable free in in -type, or another reachable type variable. -A value with a type that does not obey -this reachability restriction cannot be used without introducing -ambiguity; that is why the type is rejected. -Here, for example, is an illegal type: - - +By including dependencies in a class declaration, we provide a mechanism for +the programmer to specify each multiple parameter class more precisely. The +compiler, on the other hand, is responsible for ensuring that the set of +instances that are in scope at any given point in the program is consistent +with any declared dependencies. For example, the following pair of instance +declarations cannot appear together in the same scope because they violate the +dependency for D, even though either one on its own would be acceptable: - forall a. Eq a => Int + instance D Bool Int where ... + instance D Bool Char where ... - - -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. +Note also that the following declaration is not allowed, even by itself: + + instance D [a] b where ... + +The problem here is that this instance would allow one particular choice of [a] +to be associated with more than one choice for b, which contradicts the +dependency specified in the definition of D. More generally, this means that, +in any instance of the form: + + instance D t s where ... + +for some particular types t and s, the only variables that can appear in s are +the ones that appear in t, and hence, if the type t is known, then s will be +uniquely determined. -Note -that the reachability condition is weaker than saying that a is -functionally dependent on a type variable free in -type (see ). The reason for this is there -might be a "hidden" dependency, in a superclass perhaps. So -"reachable" is a conservative approximation to "functionally dependent". -For example, consider: +The benefit of including dependency information is that it allows us to define +more general multiple parameter classes, without ambiguity problems, and with +the benefit of more accurate types. To illustrate this, we return to the +collection class example, and annotate the original definition of Collects +with a simple dependency: - class C a b | a -> b where ... - class C a b => D a b where ... - f :: forall a b. D a b => a -> a + class Collects e ce | ce -> e where + empty :: ce + insert :: e -> ce -> ce + member :: e -> ce -> Bool -This is fine, because in fact a does functionally determine b -but that is not immediately apparent from f's type. +The dependency ce -> e here specifies that the type e of elements is uniquely +determined by the type of the collection ce. Note that both parameters of +Collects are of kind *; there are no constructor classes here. Note too that +all of the instances of Collects that we gave earlier can be used +together with this new definition. + + +What about the ambiguity problems that we encountered with the original +definition? The empty function still has type Collects e ce => ce, but it is no +longer necessary to regard that as an ambiguous type: Although the variable e +does not appear on the right of the => symbol, the dependency for class +Collects tells us that it is uniquely determined by ce, which does appear on +the right of the => symbol. Hence the context in which empty is used can still +give enough information to determine types for both ce and e, without +ambiguity. More generally, we need only regard a type as ambiguous if it +contains a variable on the left of the => that is not uniquely determined +(either directly or indirectly) by the variables on the right. - - - - 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: - - +Dependencies also help to produce more accurate types for user defined +functions, and hence to provide earlier detection of errors, and less cluttered +types for programmers to work with. Recall the previous definition for a +function f: + + f x y = insert x y = insert x . insert y + +for which we originally obtained a type: - forall a. C a b => burble + f :: (Collects a c, Collects b c) => a -> b -> c -> c + +Given the dependency information that we have for Collects, however, we can +deduce that a and b must be equal because they both appear as the second +parameter in a Collects constraint with the same first parameter c. Hence we +can infer a shorter and more accurate type for f: + + f :: (Collects a c) => a -> a -> c -> c +In a similar way, the earlier definition of g will now be flagged as a type error. + + +Although we have given only a few examples here, it should be clear that the +addition of dependency information can help to make multiple parameter classes +more useful in practice, avoiding ambiguity problems, and allowing more general +sets of instance declarations. + + + + + +Instance declarations -The next type is illegal because the constraint Eq b does not -mention a: + +Relaxed rules for instance declarations +An instance declaration has the form + + instance ( assertion1, ..., assertionn) => class type1 ... typem where ... + +The part before the "=>" is the +context, while the part after the +"=>" is the head of the instance declaration. + + + +In Haskell 98 the head of an instance declaration +must be of the form C (T a1 ... an), where +C is the class, T is a type constructor, +and the a1 ... an are distinct type variables. +Furthermore, the assertions in the context of the instance declaration +must be of the form C a where a +is a type variable that occurs in the head. + + +The flag loosens these restrictions +considerably. Firstly, multi-parameter type classes are permitted. Secondly, +the context and head of the instance declaration can each consist of arbitrary +(well-kinded) assertions (C t1 ... tn) subject only to the +following rules: + + +For each assertion in the context: + +No type variable has more occurrences in the assertion than in the head +The assertion has fewer constructors and variables (taken together + and counting repetitions) than the head + + +The coverage condition. For each functional dependency, +tvsleft -> +tvsright, of the class, +every type variable in +S(tvsright) must appear in +S(tvsleft), where S is the +substitution mapping each type variable in the class declaration to the +corresponding type in the instance declaration. + + +These restrictions ensure that context reduction terminates: each reduction +step makes the problem smaller by at least one +constructor. For example, the following would make the type checker +loop if it wasn't excluded: - forall a. Eq b => burble + instance C a => C a where ... +For example, these are OK: + + instance C Int [a] -- Multiple parameters + instance Eq (S [a]) -- Structured type in head + -- Repeated type variable in head + instance C4 a a => C4 [a] [a] + instance Stateful (ST s) (MutVar s) -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. + -- Head can consist of type variables only + instance C a + instance (Eq a, Show b) => C2 a b + -- Non-type variables in context + instance Show (s a) => Show (Sized s a) + instance C2 Int a => C3 Bool [a] + instance C2 Int a => C3 [a] b + +But these are not: + + -- Context assertion no smaller than head + instance C a => C a where ... + -- (C b b) has more more occurrences of b than the head + instance C b b => Foo [b] where ... + - - + +The same restrictions apply to instances generated by +deriving clauses. Thus the following is accepted: + + data MinHeap h a = H a (h a) + deriving (Show) + +because the derived instance + + instance (Show a, Show (h a)) => Show (MinHeap h a) + +conforms to the above rules. + + +A useful idiom permitted by the above rules is as follows. +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 + - -For-all hoisting + +Undecidable instances + -It is often convenient to use generalised type synonyms (see ) at the right hand -end of an arrow, thus: +Sometimes even the rules of are too onerous. +For example, sometimes you might want to use the following to get the +effect of a "class synonym": - type Discard a = forall b. a -> b -> a + class (C1 a, C2 a, C3 a) => C a where { } - g :: Int -> Discard Int - g x y z = x+y + instance (C1 a, C2 a, C3 a) => C a where { } -Simply expanding the type synonym would give +This allows you to write shorter signatures: - g :: Int -> (forall b. Int -> b -> Int) + f :: C a => ... -but GHC "hoists" the forall to give the isomorphic type +instead of - g :: forall b. Int -> Int -> b -> Int + f :: (C1 a, C2 a, C3 a) => ... -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: +The restrictions on functional dependencies () are particularly troublesome. +It is tempting to introduce type variables in the context that do not appear in +the head, something that is excluded by the normal rules. For example: - type1 -> forall a1..an. context2 => type2 -==> - forall a1..an. context2 => type1 -> type2 + class HasConverter a b | a -> b where + convert :: a -> b + + data Foo a = MkFoo a + + instance (HasConverter a b,Show b) => Show (Foo a) where + show (MkFoo value) = show (convert value) -(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: +This is dangerous territory, however. Here, for example, is a program that would make the +typechecker loop: - g :: Int -> Int -> forall b. b -> Int - - - -When doing this hoisting operation, GHC eliminates duplicate constraints. For -example: + class D a + class F a b | a->b + instance F [a] [[a]] + instance (D c, F a c) => D [a] -- 'c' is not mentioned in the head + +Similarly, it can be tempting to lift the coverage condition: - type Foo a = (?x::Int) => Bool -> a - g :: Foo (Foo Int) + class Mul a b c | a b -> c where + (.*.) :: a -> b -> c + + instance Mul Int Int Int where (.*.) = (*) + instance Mul Int Float Float where x .*. y = fromIntegral x * y + instance Mul a b c => Mul a [b] [c] where x .*. v = map (x.*.) v -means +The third instance declaration does not obey the coverage condition; +and indeed the (somewhat strange) definition: - g :: (?x::Int) => Bool -> Bool -> Int + f = \ b x y -> if b then x .*. [y] else y +makes instance inference go into a loop, because it requires the constraint +(Mul a [b] b). + + +Nevertheless, GHC allows you to experiment with more liberal rules. If you use +the experimental flag +-fallow-undecidable-instances +option, you can use arbitrary +types in both an instance context and instance head. 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. - - - + - -Instance declarations - + Overlapping instances In general, GHC requires that that it be unambiguous which instance @@ -1755,7 +2119,8 @@ these declarations: instance context3 => C Int [a] where ... -- (C) instance context4 => C Int [Int] where ... -- (D) -The instances (A) and (B) match the constraint C Int Bool, but (C) and (D) do not. When matching, GHC takes +The instances (A) and (B) match the constraint C Int Bool, +but (C) and (D) do not. When matching, GHC takes no account of the context of the instance declaration (context1 etc). GHC's default behaviour is that exactly one instance must match the @@ -1787,153 +2152,244 @@ So GHC rejects the program. If you add the flag + +The willingness to be overlapped or incoherent is a property of +the instance declaration itself, controlled by the +presence or otherwise of the +and flags when that mdodule is +being defined. Neither flag is required in a module that imports and uses the +instance declaration. Specifically, during the lookup process: + + +An instance declaration is ignored during the lookup process if (a) a more specific +match is found, and (b) the instance declaration was compiled with +. The flag setting for the +more-specific instance does not matter. + + +Suppose an instance declaration does not matche the constraint being looked up, but +does unify with it, so that it might match when the constraint is further +instantiated. Usually GHC will regard this as a reason for not committing to +some other constraint. But if the instance declaration was compiled with +, GHC will skip the "does-it-unify?" +check for that declaration. + + +All this makes it possible for a library author to design a library that relies on +overlapping instances without the library client having to know. + +The flag implies the + flag, but not vice versa. + Type synonyms in the instance head - -Unlike Haskell 98, instance heads may use type -synonyms. (The instance "head" is the bit after the "=>" in an instance decl.) -As always, using a type synonym is just shorthand for -writing the RHS of the type synonym definition. For example: + +Unlike Haskell 98, instance heads may use type +synonyms. (The instance "head" is the bit after the "=>" in an instance decl.) +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. + + + + + + + + +Type signatures + +The context of a type signature + +Unlike Haskell 98, constraints in types do not have to be of +the form (class type-variable) or +(class (type-variable type-variable ...)). Thus, +these type signatures are perfectly OK + + g :: Eq [a] => ... + g :: Ord (T a ()) => ... + + + +GHC imposes the following restrictions on the constraints in a type signature. +Consider the type: + + + forall tv1..tvn (c1, ...,cn) => type + + +(Here, we write the "foralls" explicitly, although the Haskell source +language omits them; in Haskell 98, all the free type variables of an +explicit source-language type signature are universally quantified, +except for the class type variables in a class declaration. However, +in GHC, you can give the foralls if you want. See ). + + + + + + + + + Each universally quantified type variable +tvi must be reachable from type. + +A type variable a is "reachable" if it it appears +in the same constraint as either a type variable free in in +type, or another reachable type variable. +A value with a type that does not obey +this reachability restriction cannot be used without introducing +ambiguity; that is why the type is rejected. +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. + + +Note +that the reachability condition is weaker than saying that a is +functionally dependent on a type variable free in +type (see ). The reason for this is there +might be a "hidden" dependency, in a superclass perhaps. So +"reachable" is a conservative approximation to "functionally dependent". +For example, consider: - type Point = (Int,Int) - instance C Point where ... - instance C [Point] where ... + class C a b | a -> b where ... + class C a b => D a b where ... + f :: forall a b. D a b => a -> a +This is fine, because in fact a does functionally determine b +but that is not immediately apparent from f's type. + + + + + Every constraint ci must mention at least one of the +universally quantified type variables tvi. -is legal. However, if you added +For example, this type is OK because C a b mentions the +universally quantified type variable b: - instance C (Int,Int) where ... + forall a. C a b => burble -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: +The next type is illegal because the constraint Eq b does not +mention a: - type P a = [[a]] - instance Monad P where ... + forall a. Eq b => burble -This design decision is independent of all the others, and easily -reversed, but it makes sense to me. +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. - + - -Undecidable instances + -An instance declaration must normally obey the following rules: - -At least one of the types in the head of -an instance declaration must not be a type variable. -For example, these are OK: + + + +For-all hoisting + +It is often convenient to use generalised type synonyms (see ) at the right hand +end of an arrow, thus: - instance C Int a where ... - - instance D (Int, Int) where ... + type Discard a = forall b. a -> b -> a - instance E [[a]] where ... + g :: Int -> Discard Int + g x y z = x+y -but this is not: +Simply expanding the type synonym would give - instance F a where ... + g :: Int -> (forall b. Int -> b -> Int) -Note that instance heads may contain repeated type variables. -For example, this is OK: +but GHC "hoists" the forall to give the isomorphic type - instance Stateful (ST s) (MutVar s) where ... + g :: forall b. Int -> Int -> b -> Int - - - - - -All of the types in the context of -an instance declaration must be type variables. -Thus +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: -instance C a b => Eq (a,b) where ... + type1 -> forall a1..an. context2 => type2 +==> + forall a1..an. context2 => type1 -> type2 -is OK, but +(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: -instance C Int b => Foo b where ... + g :: Int -> Int -> forall b. b -> Int -is not OK. - - -These restrictions 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: - - + +When doing this hoisting operation, GHC eliminates duplicate constraints. For +example: - f :: C a => ... + type Foo a = (?x::Int) => Bool -> a + g :: Foo (Foo Int) - - -instead of - - +means - f :: (C1 a, C2 a, C3 a) => ... + g :: (?x::Int) => Bool -> Bool -> Int - - -Voluminous correspondence on the Haskell mailing list has convinced me -that it's worth experimenting with more liberal rules. If you use -the experimental flag --fallow-undecidable-instances -option, you can use arbitrary -types in both an instance context and instance head. 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. - - -I'm on the lookout for a less brutal solution: a simple rule that preserves decidability while -allowing these idioms interesting idioms. @@ -2103,6 +2559,68 @@ the binding for ?x, so the type of f is + +Implicit parameters and polymorphic recursion + + +Consider these two definitions: + + len1 :: [a] -> Int + len1 xs = let ?acc = 0 in len_acc1 xs + + len_acc1 [] = ?acc + len_acc1 (x:xs) = let ?acc = ?acc + (1::Int) in len_acc1 xs + + ------------ + + len2 :: [a] -> Int + len2 xs = let ?acc = 0 in len_acc2 xs + + len_acc2 :: (?acc :: Int) => [a] -> Int + len_acc2 [] = ?acc + len_acc2 (x:xs) = let ?acc = ?acc + (1::Int) in len_acc2 xs + +The only difference between the two groups is that in the second group +len_acc is given a type signature. +In the former case, len_acc1 is monomorphic in its own +right-hand side, so the implicit parameter ?acc is not +passed to the recursive call. In the latter case, because len_acc2 +has a type signature, the recursive call is made to the +polymoprhic version, which takes ?acc +as an implicit parameter. So we get the following results in GHCi: + + Prog> len1 "hello" + 0 + Prog> len2 "hello" + 5 + +Adding a type signature dramatically changes the result! This is a rather +counter-intuitive phenomenon, worth watching out for. + + + +Implicit parameters and monomorphism + +GHC applies the dreaded Monomorphism Restriction (section 4.5.5 of the +Haskell Report) to implicit parameters. For example, consider: + + f :: Int -> Int + f v = let ?x = 0 in + let y = ?x + v in + let ?x = 5 in + y + +Since the binding for y falls under the Monomorphism +Restriction it is not generalised, so the type of y is +simply Int, not (?x::Int) => Int. +Hence, (f 9) returns result 9. +If you add a type signature for y, then y +will get type (?x::Int) => Int, so the occurrence of +y in the body of the let will see the +inner binding of ?x, so (f 9) will return +14. + + @@ -2275,30 +2793,6 @@ and you'd be right. That is why they are an experimental feature. - -Functional dependencies - - - Functional dependencies are implemented as described by Mark Jones -in “Type Classes with Functional Dependencies”, Mark P. Jones, -In Proceedings of the 9th European Symposium on Programming, -ESOP 2000, Berlin, Germany, March 2000, Springer-Verlag LNCS 1782, -. - - -Functional dependencies are introduced by a vertical bar in the syntax of a -class declaration; e.g. - - class (Monad m) => MonadState s m | m -> s where ... - - class Foo a b c | a b -> c where ... - -There should be more documentation, but there isn't (yet). Yell if you need it. - - - - - Explicitly-kinded quantification @@ -3106,9 +3600,23 @@ classes Eq, Ord, GHC extends this list with two more classes that may be automatically derived (provided the flag is specified): Typeable, and Data. These classes are defined in the library -modules Data.Dynamic and Data.Generics respectively, and the +modules Data.Typeable and Data.Generics respectively, and the appropriate class must be in scope before it can be mentioned in the deriving clause. +An instance of Typeable can only be derived if the +data type has seven or fewer type parameters, all of kind *. +The reason for this is that the Typeable class is derived using the scheme +described in + +Scrap More Boilerplate: Reflection, Zips, and Generalised Casts +. +(Section 7.4 of the paper describes the multiple Typeable classes that +are used, and only Typeable1 up to +Typeable7 are provided in the library.) +In other cases, there is nothing to stop the programmer writing a TypableX +class, whose kind suits that of the data type constructor, and +then writing the data type instance by hand. + @@ -3221,7 +3729,7 @@ class to the new type: As a result of this extension, all derived instances in newtype -declarations are treated uniformly (and implemented just by reusing + 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. @@ -3302,10 +3810,80 @@ then we would not have been able to derive an instance for the classes usually have one "main" parameter for which deriving new instances is most interesting. +Lastly, all of this applies only for classes other than +Read, Show, Typeable, +and Data, for which the built-in derivation applies (section +4.3.3. of the Haskell Report). +(For the standard classes Eq, Ord, +Ix, and Bounded it is immaterial whether +the standard method is used or the one described here.) + + +Generalised typing of mutually recursive bindings + + +The Haskell Report specifies that a group of bindings (at top level, or in a +let or where) should be sorted into +strongly-connected components, and then type-checked in dependency order +(Haskell +Report, Section 4.5.1). +As each group is type-checked, any binders of the group that +have +an explicit type signature are put in the type environment with the specified +polymorphic type, +and all others are monomorphic until the group is generalised +(Haskell Report, Section 4.5.2). + + +Following a suggestion of Mark Jones, in his paper +Typing Haskell in +Haskell, +GHC implements a more general scheme. If is +specified: +the dependency analysis ignores references to variables that have an explicit +type signature. +As a result of this refined dependency analysis, the dependency groups are smaller, and more bindings will +typecheck. For example, consider: + + f :: Eq a => a -> Bool + f x = (x == x) || g True || g "Yes" + + g y = (y <= y) || f True + +This is rejected by Haskell 98, but under Jones's scheme the definition for +g is typechecked first, separately from that for +f, +because the reference to f in g's right +hand side is ingored by the dependency analysis. Then g's +type is generalised, to get + + g :: Ord a => a -> Bool + +Now, the defintion for f is typechecked, with this type for +g in the type environment. + + + +The same refined dependency analysis also allows the type signatures of +mutually-recursive functions to have different contexts, something that is illegal in +Haskell 98 (Section 4.5.2, last sentence). With + +GHC only insists that the type signatures of a refined group have identical +type signatures; in practice this means that only variables bound by the same +pattern binding must have the same context. For example, this is fine: + + f :: Eq a => a -> Bool + f x = (x == x) || g True + + g :: Ord a => a -> Bool + g y = (y <= y) || f True + + + @@ -3332,9 +3910,9 @@ for these Terms: eval :: Term a -> a eval (Lit i) = i eval (Succ t) = 1 + eval t - eval (IsZero i) = eval i == 0 + eval (IsZero t) = eval t == 0 eval (If b e1 e2) = if eval b then eval e1 else eval e2 - eval (Pair e1 e2) = (eval e2, eval e2) + eval (Pair e1 e2) = (eval e1, eval e2) These and many other examples are given in papers by Hongwei Xi, and Tim Sheard. @@ -3366,9 +3944,55 @@ type above, the type of each constructor must end with ... -> Term ... -You cannot use a deriving clause on a GADT-style data type declaration, -nor can you use record syntax. (It's not clear what these constructs would mean. For example, -the record selectors might ill-typed.) However, you can use strictness annotations, in the obvious places +You can use record syntax on a GADT-style data type declaration: + + + data Term a where + Lit { val :: Int } :: Term Int + Succ { num :: Term Int } :: Term Int + Pred { num :: Term Int } :: Term Int + IsZero { arg :: Term Int } :: Term Bool + Pair { arg1 :: Term a + , arg2 :: Term b + } :: Term (a,b) + If { cnd :: Term Bool + , tru :: Term a + , fls :: Term a + } :: Term a + +For every constructor that has a field f, (a) the type of +field f must be the same; and (b) the +result type of the constructor must be the same; both modulo alpha conversion. +Hence, in our example, we cannot merge the num and arg +fields above into a +single name. Although their field types are both Term Int, +their selector functions actually have different types: + + + num :: Term Int -> Term Int + arg :: Term Bool -> Term Int + + +At the moment, record updates are not yet possible with GADT, so support is +limited to record construction, selection and pattern matching: + + + someTerm :: Term Bool + someTerm = IsZero { arg = Succ { num = Lit { val = 0 } } } + + eval :: Term a -> a + eval Lit { val = i } = i + eval Succ { num = t } = eval t + 1 + eval Pred { num = t } = eval t - 1 + eval IsZero { arg = t } = eval t == 0 + eval Pair { arg1 = t1, arg2 = t2 } = (eval t1, eval t2) + eval t@If{} = if eval (cnd t) then eval (tru t) else eval (fls t) + + + + + +You can use strictness annotations, in the obvious places in the constructor type: data Term a where @@ -3379,6 +4003,23 @@ in the constructor type: +You can use a deriving clause on a GADT-style data type +declaration, but only if the data type could also have been declared in +Haskell-98 syntax. For example, these two declarations are equivalent + + data Maybe1 a where { + Nothing1 :: Maybe a ; + Just1 :: a -> Maybe a + } deriving( Eq, Ord ) + + data Maybe2 a = Nothing2 | Just2 a + deriving( Eq, Ord ) + +This simply allows you to declare a vanilla Haskell-98 data type using the +where form without losing the deriving clause. + + + Pattern matching causes type refinement. For example, in the right hand side of the equation eval :: Term a -> a @@ -3406,7 +4047,7 @@ the result type of the case expression. Hence the addition < Notice that GADTs generalise existential types. For example, these two declarations are equivalent: data T a = forall b. MkT b (b->a) - data T' a where { MKT :: b -> (b->a) -> T a } + data T' a where { MKT :: b -> (b->a) -> T' a } @@ -3462,9 +4103,11 @@ Tim Sheard is going to expand it.) A splice can occur in place of - an expression; the spliced expression must have type Expr + an expression; the spliced expression must + have type Q Exp a list of top-level declarations; ; the spliced expression must have type Q [Dec] - a type; the spliced expression must have type Type. + [Planned, but not implemented yet.] a + type; the spliced expression must have type Q Typ. (Note that the syntax for a declaration splice uses "$" not "splice" as in the paper. Also the type of the enclosed expression must be Q [Dec], not [Q Dec] @@ -3479,7 +4122,7 @@ Tim Sheard is going to expand it.) the quotation has type Expr. [d| ... |], where the "..." is a list of top-level declarations; the quotation has type Q [Dec]. - [t| ... |], where the "..." is a type; + [Planned, but not implemented yet.] [t| ... |], where the "..." is a type; the quotation has type Type. @@ -3641,7 +4284,7 @@ What follows is a brief introduction to the notation; it won't make much sense unless you've read Hughes's paper. This notation is translated to ordinary Haskell, using combinators from the -Control.Arrow +Control.Arrow module. @@ -3725,7 +4368,7 @@ proc x -> f x -<< x+1 which is equivalent to -arr (\ x -> (f, x+1)) >>> app +arr (\ x -> (f x, x+1)) >>> app so in this case the arrow must belong to the ArrowApply class. @@ -3754,7 +4397,7 @@ the arrow f, and matches its output against y. In the next line, the output is discarded. The arrow returnA is defined in the -Control.Arrow +Control.Arrow module as arr id. The above example is treated as an abbreviation for @@ -3771,7 +4414,7 @@ arr (\ x -> (x, x)) >>> Note that variables not used later in the composition are projected out. After simplification using rewrite rules (see ) defined in the -Control.Arrow +Control.Arrow module, this reduces to arr (\ x -> (x+1, x)) >>> @@ -4066,7 +4709,7 @@ additional restrictions: The module must import -Control.Arrow. +Control.Arrow. @@ -4162,12 +4805,13 @@ can still define and use your own versions of -To have the compiler ignore uses of assert, use the compiler option -. -fignore-asserts -option That is, expressions of the form +GHC ignores assertions when optimisation is turned on with the + flag. That is, expressions of the form assert pred e will be rewritten to -e. - +e. You can also disable assertions using the + + option + . Assertion failures can be caught, see the documentation for the @@ -4224,7 +4868,7 @@ Assertion failures can be caught, see the documentation for the - You can deprecate a function, class, or type, with the + You can deprecate a function, class, type, or data constructor, with the following top-level declaration: {-# DEPRECATED f, C, T "Don't use these" #-} @@ -4232,6 +4876,13 @@ Assertion failures can be caught, see the documentation for the When you compile any module that imports and uses any of the specified entities, GHC will print the specified message. + You can only depecate entities declared at top level in the module + being compiled, and you can only use unqualified names in the list of + entities being deprecated. A capitalised name, such as T + refers to either the type constructor T + or the data constructor T, or both if + both are in scope. If both are in scope, there is currently no way to deprecate + one without the other (c.f. fixities ). Any use of the deprecated item, or of anything from a deprecated @@ -4423,6 +5074,29 @@ key_function :: Int -> String -> (Bool, Double) + + LANGUAGE pragma + + LANGUAGEpragma + pragmaLANGUAGE + + This allows language extensions to be enabled in a portable way. + It is the intention that all Haskell compilers support the + LANGUAGE pragma with the same syntax, although not + all extensions are supported by all compilers, of + course. The LANGUAGE pragma should be used instead + of OPTIONS_GHC, if possible. + + For example, to enable the FFI and preprocessing with CPP: + +{-# LANGUAGE ForeignFunctionInterface, CPP #-} + + Any extension from the Extension type defined in + Language.Haskell.Extension may be used. GHC will report an error if any of the requested extensions are not supported. + + + LINE pragma @@ -4433,9 +5107,7 @@ key_function :: Int -> String -> (Bool, Double) code. It lets you specify the line number and filename of the original code; for example - -{-# LINE 42 "Foo.vhs" #-} - +{-# LINE 42 "Foo.vhs" #-} if you'd generated the current file from something called Foo.vhs and this line corresponds to line @@ -4480,7 +5152,7 @@ key_function :: Int -> String -> (Bool, Double) overloaded function: -hammeredLookup :: Ord key => [(key, value)] -> key -> value + hammeredLookup :: Ord key => [(key, value)] -> key -> value If it is heavily used on lists with @@ -4488,7 +5160,7 @@ hammeredLookup :: Ord key => [(key, value)] -> key -> value follows: -{-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-} + {-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-} A SPECIALIZE pragma for a function can @@ -4499,7 +5171,64 @@ hammeredLookup :: Ord key => [(key, value)] -> key -> value (see ) that rewrites a call to the un-specialised function into a call to the specialised one. - In earlier versions of GHC, it was possible to provide your own + The type in a SPECIALIZE pragma can be any type that is less + polymorphic than the type of the original function. In concrete terms, + if the original function is f then the pragma + + {-# SPECIALIZE f :: <type> #-} + + is valid if and only if the defintion + + f_spec :: <type> + f_spec = f + + is valid. Here are some examples (where we only give the type signature + for the original function, not its code): + + f :: Eq a => a -> b -> b + {-# SPECIALISE f :: Int -> b -> b #-} + + g :: (Eq a, Ix b) => a -> b -> b + {-# SPECIALISE g :: (Eq a) => a -> Int -> Int #-} + + h :: Eq a => a -> a -> a + {-# SPECIALISE h :: (Eq a) => [a] -> [a] -> [a] #-} + +The last of these examples will generate a +RULE with a somewhat-complex left-hand side (try it yourself), so it might not fire very +well. If you use this kind of specialisation, let us know how well it works. + + +A SPECIALIZE pragma can optionally be followed with a +INLINE or NOINLINE pragma, optionally +followed by a phase, as described in . +The INLINE pragma affects the specialised verison of the +function (only), and applies even if the function is recursive. The motivating +example is this: + +-- A GADT for arrays with type-indexed representation +data Arr e where + ArrInt :: !Int -> ByteArray# -> Arr Int + ArrPair :: !Int -> Arr e1 -> Arr e2 -> Arr (e1, e2) + +(!:) :: Arr e -> Int -> e +{-# SPECIALISE INLINE (!:) :: Arr Int -> Int -> Int #-} +{-# SPECIALISE INLINE (!:) :: Arr (a, b) -> Int -> (a, b) #-} +(ArrInt _ ba) !: (I# i) = I# (indexIntArray# ba i) +(ArrPair _ a1 a2) !: i = (a1 !: i, a2 !: i) + +Here, (!:) is a recursive function that indexes arrays +of type Arr e. Consider a call to (!:) +at type (Int,Int). The second specialisation will fire, and +the specialised function will be inlined. It has two calls to +(!:), +both at type Int. Both these calls fire the first +specialisation, whose body is also inlined. The result is a type-based +unrolling of the indexing function. +Warning: you can make GHC diverge by using SPECIALISE INLINE +on an ordinarily-recursive function. + + Note: In earlier versions of GHC, it was possible to provide your own specialised function for a given type: