X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fdocs%2Fusers_guide%2Fglasgow_exts.xml;h=1e0e5b94c7069473afe37eb9f8650b2e434ee2cc;hb=0f965da50e02edda7cd4e441dfdc379ba77f5d98;hp=073003d0ab3b9549dde490f926d56ff342f552a3;hpb=a7d05b769e676db271ca1f4d0f88a1c80843c2f8;p=ghc-hetmet.git diff --git a/ghc/docs/users_guide/glasgow_exts.xml b/ghc/docs/users_guide/glasgow_exts.xml index 073003d..1e0e5b9 100644 --- a/ghc/docs/users_guide/glasgow_exts.xml +++ b/ghc/docs/users_guide/glasgow_exts.xml @@ -1092,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: @@ -1205,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: @@ -1264,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 @@ -1425,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 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: @@ -1446,39 +1531,16 @@ There are the following constraints on class declarations: ...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.) + - - - + +The superclasses of a class declaration - There are no restrictions on the context in 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: +be acyclic. So these class declarations are OK: @@ -1491,62 +1553,33 @@ be acyclic. So these class declarations are OK: - - - - - All of the class type variables must be reachable (in the sense -mentioned in ) -from the free variables of each method type -. For example: +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: - 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 C a where { + op :: D b => a -> b -> b + } - - class Coll s a where - empty :: s a - insert :: s a -> a -> s a + class C a => D a where { ... } -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 +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.) + + - class CollE s => Coll s a where - insert :: s -> a -> s - - - - - - Class method types + Haskell 98 prohibits class method types to mention constraints on the class type variable, thus: @@ -1558,186 +1591,120 @@ class type variable, thus: 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. - -With the GHC lifts this restriction. - + - - -Type signatures + +Functional dependencies + -The context of a type signature + 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, +. + -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 +Functional dependencies are introduced by a vertical bar in the syntax of a +class declaration; e.g. - g :: Eq [a] => ... - g :: Ord (T a ()) => ... + 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. -GHC imposes the following restrictions on the constraints in a type signature. -Consider the type: +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: - forall tv1..tvn (c1, ...,cn) => type + class Coll s a where + empty :: s + insert :: s -> a -> s -(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: - - +is not OK, because the type of empty doesn't mention +a. Functional dependencies can make the type variable +reachable: - forall a. Eq a => Int + class Coll s a | s -> a where + empty :: s + insert :: s -> a -> s +Alternatively Coll might be rewritten -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: - 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 Coll s a where + empty :: s a + insert :: s a -> a -> s 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. -For example, this type is OK because C a b mentions the -universally quantified type variable b: +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: - forall a. C a b => burble - + class CollE s where + empty :: s + class CollE s => Coll s a where + insert :: s -> a -> s + + + -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. - - - + - + +Instance declarations - - + +Instance heads - -For-all hoisting -It is often convenient to use generalised type synonyms (see ) 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 a1..an. context2 => type2 -==> - forall a1..an. context2 => 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 - +The head of an instance declaration is the part to the +right of the "=>". 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. -When doing this hoisting operation, GHC eliminates duplicate constraints. For -example: - - type Foo a = (?x::Int) => Bool -> a - g :: Foo (Foo Int) - -means +The flag lifts this restriction and allows the +instance head to be of form C t1 ... tn where t1 +... tn are arbitrary types (provided, of course, everything is +well-kinded). In particular, types ti can be type variables +or structured types, and can contain repeated occurrences of a single type +variable. +Examples: - g :: (?x::Int) => Bool -> Bool -> Int + instance Eq (T a a) where ... + -- Repeated type variable + + instance Eq (S [a]) where ... + -- Structured type + + instance C Int [a] where ... + -- Multiple parameters - - - - -Instance declarations - Overlapping instances @@ -1888,7 +1855,7 @@ but this is not: instance F a where ... -Note that instance heads may contain repeated type variables. +Note that instance heads may contain repeated type variables (). For example, this is OK: instance Stateful (ST s) (MutVar s) where ... @@ -1899,16 +1866,21 @@ For example, this is OK: All of the types in the context of -an instance declaration must be type variables. +an instance declaration must be type variables, and +there must be no repeated type variables in any one constraint. Thus instance C a b => Eq (a,b) where ... is OK, but -instance C Int b => Foo b where ... +instance C Int b => Foo [b] where ... + +is not OK (because of the non-type-variable Int in the context), and nor is + +instance C b b => Foo [b] where ... -is not OK. +(because of the repeated type variable). @@ -1977,6 +1949,174 @@ allowing these idioms interesting idioms. + +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: + + 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. + +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. + + + + + + + + + + +For-all hoisting + +It is often convenient to use generalised type synonyms (see ) 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 a1..an. context2 => type2 +==> + forall a1..an. context2 => 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 + + + +When doing this hoisting operation, GHC eliminates duplicate constraints. For +example: + + type Foo a = (?x::Int) => Bool -> a + g :: Foo (Foo Int) + +means + + g :: (?x::Int) => Bool -> Bool -> Int + + + + + + + Implicit parameters @@ -2374,30 +2514,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 @@ -3208,6 +3324,20 @@ GHC extends this list with two more classes that may be automatically derived 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. + @@ -3413,6 +3543,68 @@ 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 + + + @@ -3439,9 +3631,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. @@ -3473,9 +3665,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 @@ -3486,6 +3724,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 @@ -3569,9 +3824,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] @@ -3586,7 +3843,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. @@ -3748,7 +4005,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. @@ -3861,7 +4118,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 @@ -3878,7 +4135,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)) >>> @@ -4173,7 +4430,7 @@ additional restrictions: The module must import -Control.Arrow. +Control.Arrow. @@ -4269,12 +4526,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 @@ -4537,6 +4795,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 @@ -4547,9 +4828,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 @@ -4594,7 +4873,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 @@ -4602,7 +4881,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 @@ -4613,7 +4892,35 @@ 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 g :: 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. + + + Note: In earlier versions of GHC, it was possible to provide your own specialised function for a given type: