X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fdocs%2Fusers_guide%2Fglasgow_exts.sgml;h=38aa5b138405904c84e9d1ace4984711fcb5e46a;hb=bcfa0eea78dac7114c4d59f95a3f16ca78c3faf4;hp=063527bc7d9a183b9d7086ce07f3aa8859bab6a0;hpb=b866a9bcc1ec7fa6c5d26410eb4c0e49e08795c9;p=ghc-hetmet.git diff --git a/ghc/docs/users_guide/glasgow_exts.sgml b/ghc/docs/users_guide/glasgow_exts.sgml index 063527b..38aa5b1 100644 --- a/ghc/docs/users_guide/glasgow_exts.sgml +++ b/ghc/docs/users_guide/glasgow_exts.sgml @@ -110,6 +110,15 @@ with GHC. + + + + See . Independent of + . + + + + @@ -635,32 +644,6 @@ This name is not supported by GHC. - Infix type constructors - -GHC supports infix type constructors, much as it supports infix data constructors. For example: - - infixl 5 :+: - - data a :+: b = Inl a | Inr b - - f :: a `Either` b -> a :+: b - f (Left x) = Inl x - - -The lexical -syntax of an infix type constructor is just like that of an infix data constructor: either -it's an operator beginning with ":", or it is an ordinary (alphabetic) type constructor enclosed in -back-quotes. - - -When you give a fixity declaration, the fixity applies to both the data constructor and the -type constructor with the specified name. You cannot give different fixities to the type constructor T -and the data constructor T. - - - - - @@ -959,38 +942,19 @@ 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: - - - +GHC imposes the following restrictions on the form of a qualified +type, whether declared in a type signature +or inferred. Consider the 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, @@ -1005,11 +969,15 @@ in GHC, you can give the foralls if you want. See ) +on the type variables 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: +ambiguity. +Here, for example, is an illegal type: @@ -1064,10 +1032,6 @@ 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 @@ -1154,56 +1118,14 @@ be acyclic. So these class declarations are OK: - - - - 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: + All of the class type variables must be reachable (in the sense +mentioned in ) +from the free varibles of each method type +. For example: @@ -1379,63 +1301,8 @@ 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. - +See for an experimental +extension to lift this restriction. @@ -1497,16 +1364,10 @@ instance C Int b => Foo b where ... -is not OK. Again, the intent here is to make sure that context -reduction terminates. +is not OK. See for an experimental +extension to lift this restriction. + -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. @@ -1519,6 +1380,80 @@ with N. + +Undecidable instances + +The rules for instance declarations state that: + +At least one of the types in the head of +an instance declaration must not be a type variable. + +All of the types in the context of +an instance declaration must be type variables. + + +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: + + + + f :: C a => ... + + + +instead of + + + + f :: (C1 a, C2 a, C3 a) => ... + + + +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. + + + Implicit parameters @@ -1555,7 +1490,7 @@ implicitly parameterized by a comparison function named cmp. The dynamic binding constraints are just a new form of predicate in the type class system. -An implicit parameter occurs in an exprssion using the special form ?x, +An implicit parameter occurs in an expression using the special form ?x, where x is any valid identifier (e.g. ord ?x is a valid expression). Use of this construct also introduces a new @@ -1608,6 +1543,19 @@ Reason: exactly which implicit parameter you pick up depends on exactly where you invoke a function. But the ``invocation'' of instance declarations is done behind the scenes by the compiler, so it's hard to figure out exactly where it is done. Easiest thing is to outlaw the offending types. + +Implicit-parameter constraints do not cause ambiguity. For example, consider: + + f :: (?x :: [a]) => Int -> Int + f n = n + length ?x + + g :: (Read a, Show a) => String -> String + g s = show (read s) + +Here, g has an ambiguous type, and is rejected, but f +is fine. The binding for ?x at f's call site is +quite unambiguous, and fixes the type a. + @@ -1847,8 +1795,14 @@ 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. @@ -2857,49 +2811,6 @@ scope over the methods defined in the where part. For exampl -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 @@ -3012,41 +2923,96 @@ in f4's scope. - - -Generalised derived instances for newtypes + +Result type signatures -When you define an abstract type using newtype, you may want -the new type to inherit some instances from its representation. In -Haskell 98, you can inherit instances of Eq, Ord, -Enum and Bounded by deriving them, but for any -other classes you have to write an explicit instance declaration. For -example, if you define - - - newtype Dollars = Dollars Int - +The result type of a function can be given a signature, thus: -and you want to use arithmetic on Dollars, you have to -explicitly define an instance of Num: - - instance Num Dollars where - Dollars a + Dollars b = Dollars (a+b) - ... + + f (x::a) :: [a] = [x,x,x] -All the instance does is apply and remove the newtype -constructor. It is particularly galling that, since the constructor -doesn't appear at run-time, this instance declaration defines a -dictionary which is wholly equivalent to the Int -dictionary, only slower! - - Generalising the deriving clause - +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) + + + + +The type variables bound in a result type signature scope over the right hand side +of the definition. However, consider this corner-case: + + rev1 :: [a] -> [a] = \xs -> reverse xs + + foo ys = rev (ys::[a]) + +The signature on rev1 is considered a pattern type signature, not a result +type signature, and the type variables it binds have the same scope as rev1 +itself (i.e. the right-hand side of rev1 and the rest of the module too). +In particular, the expression (ys::[a]) is OK, because the type variable a +is in scope (otherwise it would mean (ys::forall a.[a]), which would be rejected). + + +As mentioned above, rev1 is made monomorphic by this scoping rule. +For example, the following program would be rejected, because it claims that rev1 +is polymorphic: + + rev1 :: [b] -> [b] + rev1 :: [a] -> [a] = \xs -> reverse xs + + + + +Result type signatures are not yet implemented in Hugs. + + + + + + + +Generalised derived instances for newtypes + + +When you define an abstract type using newtype, you may want +the new type to inherit some instances from its representation. In +Haskell 98, you can inherit instances of Eq, Ord, +Enum and Bounded by deriving them, but for any +other classes you have to write an explicit instance declaration. For +example, if you define + + + newtype Dollars = Dollars Int + + +and you want to use arithmetic on Dollars, you have to +explicitly define an instance of Num: + + + instance Num Dollars where + Dollars a + Dollars b = Dollars (a+b) + ... + +All the instance does is apply and remove the newtype +constructor. It is particularly galling that, since the constructor +doesn't appear at run-time, this instance declaration defines a +dictionary which is wholly equivalent to the Int +dictionary, only slower! + + + + Generalising the deriving clause + GHC now permits such instances to be derived instead, so one can write newtype Dollars = Dollars Int deriving (Eq,Show,Num) @@ -3140,13 +3106,26 @@ declaration (after expansion of any type synonyms) newtype T v1...vn = T' (S t1...tk vk+1...vn) deriving (c1...cm) -where S is a type constructor, t1...tk are -types, -vk+1...vn are type variables which do not occur in any of -the ti, and the ci are partial applications of -classes of the form C t1'...tj'. The derived instance -declarations are, for each ci, - +where + + + S is a type constructor, + + + t1...tk are types, + + + vk+1...vn are type variables which do not occur in any of + the ti, and + + + the ci are partial applications of + classes of the form C t1'...tj', where the arity of C + is exactly j+1. That is, C lacks exactly one type argument. + + +Then, for each ci, the derived instance +declaration is: instance ci (S t1...tk vk+1...v) => ci (T v1...vp) @@ -3205,6 +3184,9 @@ Template Meta-programming for Haskell", in Proc Haskell Workshop 2002. + The first example from that paper is set out below as a worked example to help get you started. + + The documentation here describes the realisation in GHC. (It's rather sketchy just now; Tim Sheard is going to expand it.) @@ -3225,21 +3207,25 @@ Tim Sheard is going to expand it.) A splice can occur in place of - an expression; - a list of top-level declarations; - a pattern; - a type; + an expression; the spliced expression must have type Expr + a list of top-level declarations; ; the spliced expression must have type Q [Dec] + a type; the spliced expression must have type Type. + (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] + as in the paper.) A expression quotation is written in Oxford brackets, thus: - [| ... |], where the "..." is an expression; - [d| ... |], where the "..." is a list of top-level declarations; - [p| ... |], where the "..." is a pattern; - [t| ... |], where the "..." is a type; + [| ... |], where the "..." is an expression; + 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; + the quotation has type Type. @@ -3268,12 +3254,6 @@ Tim Sheard is going to expand it.) - If the module contains any top-level splices that must be run, you must use GHC with - --make or --interactive flags. (Reason: that - means it walks the dependency tree and knows what modules must be linked etc.) - - - You can only run a function at compile time if it is imported from another module. That is, you can't define a function in a module, and call it from within a splice in the same module. (It would make sense to do so, but it's hard to implement.) @@ -3282,12 +3262,541 @@ Tim Sheard is going to expand it.) The flag -ddump-splices shows the expansion of all top-level splices as they happen. + + If you are building GHC from source, you need at least a stage-2 bootstrap compiler to + run Template Haskell. A stage-1 compiler will reject the TH constructs. Reason: TH + compiles and runs a program, and then looks at the result. So it's important that + the program it compiles produces results whose representations are identical to + those of the compiler itself. + + Template Haskell works in any mode (--make, --interactive, + or file-at-a-time). There used to be a restriction to the former two, but that restriction + has been lifted. + + + + A Template Haskell Worked Example +To help you get over the confidence barrier, try out this skeletal worked example. + First cut and paste the two modules below into "Main.hs" and "Printf.hs": + + +{- Main.hs -} +module Main where + +-- Import our template "pr" +import Printf ( pr ) + +-- The splice operator $ takes the Haskell source code +-- generated at compile time by "pr" and splices it into +-- the argument of "putStrLn". +main = putStrLn ( $(pr "Hello") ) + + + +{- Printf.hs -} +module Printf where + +-- Skeletal printf from the paper. +-- It needs to be in a separate module to the one where +-- you intend to use it. + +-- Import some Template Haskell syntax +import Language.Haskell.THSyntax + +-- Describe a format string +data Format = D | S | L String + +-- Parse a format string. This is left largely to you +-- as we are here interested in building our first ever +-- Template Haskell program and not in building printf. +parse :: String -> [Format] +parse s = [ L s ] + +-- Generate Haskell source code from a parsed representation +-- of the format string. This code will be spliced into +-- the module which calls "pr", at compile time. +gen :: [Format] -> Expr +gen [D] = [| \n -> show n |] +gen [S] = [| \s -> s |] +gen [L s] = string s + +-- Here we generate the Haskell code for the splice +-- from an input format string. +pr :: String -> Expr +pr s = gen (parse s) + + +Now run the compiler (here we are using a "stage three" build of GHC, at a Cygwin prompt on Windows): + + +ghc/compiler/stage3/ghc-inplace --make -fglasgow-exts -package haskell-src main.hs -o main.exe + + +Run "main.exe" and here is your output: + + + +$ ./main +Hello + + + + + +Arrow notation + + +Arrows are a generalization of monads introduced by John Hughes. +For more details, see + + + + +“Generalising Monads to Arrows”, +John Hughes, in Science of Computer Programming 37, +pp67–111, May 2000. + + + + + +“A New Notation for Arrows”, +Ross Paterson, in ICFP, Sep 2001. + + + + + +“Arrows and Computation”, +Ross Paterson, in The Fun of Programming, +Palgrave, 2003. + + + + +and the arrows web page at +http://www.haskell.org/arrows/. +With the flag, GHC supports the arrow +notation described in the second of these papers. +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 +module. + + +The extension adds a new kind of expression for defining arrows, +of the form proc pat -> cmd, +where proc is a new keyword. +The variables of the pattern are bound in the body of the +proc-expression, +which is a new sort of thing called a command. +The syntax of commands is as follows: + +cmd ::= exp1 -< exp2 + | exp1 -<< exp2 + | do { cstmt1 .. cstmtn ; cmd } + | let decls in cmd + | if exp then cmd1 else cmd2 + | case exp of { calts } + | cmd1 qop cmd2 + | (| exp |) cmd1 .. cmdn + | \ pat1 .. patn -> cmd + | ( cmd ) + +cstmt ::= let decls + | pat <- cmd + | rec { cstmt1 .. cstmtn } + | cmd + +Commands produce values, but (like monadic computations) +may yield more than one value, +or none, and may do other things as well. +For the most part, familiarity with monadic notation is a good guide to +using commands. +However the values of expressions, even monadic ones, +are determined by the values of the variables they contain; +this is not necessarily the case for commands. + + + +A simple example of the new notation is the expression + +proc x -> f -< x+1 + +We call this a procedure or +arrow abstraction. +As with a lambda expression, the variable x +is a new variable bound within the proc-expression. +It refers to the input to the arrow. +In the above example, -< is not an identifier but an +new reserved symbol used for building commands from an expression of arrow +type and an expression to be fed as input to that arrow. +(The weird look will make more sense later.) +It may be read as analogue of application for arrows. +The above example is equivalent to the Haskell expression + +arr (\ x -> x+1) >>> f + +That would make no sense if the expression to the left of +-< involves the bound variable x. +More generally, the expression to the left of -< +may not involve any local variable, +i.e. a variable bound in the current arrow abstraction. +For such a situation there is a variant -<<, as in + +proc x -> f x -<< x+1 + +which is equivalent to + +arr (\ x -> (f, x+1)) >>> app + +so in this case the arrow must belong to the ArrowApply +class. +Such an arrow is equivalent to a monad, so if you're using this form +you may find a monadic formulation more convenient. + + + +do-notation for commands + + +Another form of command is a form of do-notation. +For example, you can write + +proc x -> do + y <- f -< x+1 + g -< 2*y + let z = x+y + t <- h -< x*z + returnA -< t+z + +You can read this much like ordinary do-notation, +but with commands in place of monadic expressions. +The first line sends the value of x+1 as an input to +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 +module as arr id. +The above example is treated as an abbreviation for + +arr (\ x -> (x, x)) >>> + first (arr (\ x -> x+1) >>> f) >>> + arr (\ (y, x) -> (y, (x, y))) >>> + first (arr (\ y -> 2*y) >>> g) >>> + arr snd >>> + arr (\ (x, y) -> let z = x+y in ((x, z), z)) >>> + first (arr (\ (x, z) -> x*z) >>> h) >>> + arr (\ (t, z) -> t+z) >>> + returnA + +Note that variables not used later in the composition are projected out. +After simplification using rewrite rules (see ) +defined in the +Control.Arrow +module, this reduces to + +arr (\ x -> (x+1, x)) >>> + first f >>> + arr (\ (y, x) -> (2*y, (x, y))) >>> + first g >>> + arr (\ (_, (x, y)) -> let z = x+y in (x*z, z)) >>> + first h >>> + arr (\ (t, z) -> t+z) + +which is what you might have written by hand. +With arrow notation, GHC keeps track of all those tuples of variables for you. + + + +Note that although the above translation suggests that +let-bound variables like z must be +monomorphic, the actual translation produces Core, +so polymorphic variables are allowed. + + + +It's also possible to have mutually recursive bindings, +using the new rec keyword, as in the following example: + +counter :: ArrowCircuit a => a Bool Int +counter = proc reset -> do + rec output <- returnA -< if reset then 0 else next + next <- delay 0 -< output+1 + returnA -< output + +The translation of such forms uses the loop combinator, +so the arrow concerned must belong to the ArrowLoop class. + + + + + +Conditional commands + + +In the previous example, we used a conditional expression to construct the +input for an arrow. +Sometimes we want to conditionally execute different commands, as in + +proc (x,y) -> + if f x y + then g -< x+1 + else h -< y+2 + +which is translated to + +arr (\ (x,y) -> if f x y then Left x else Right y) >>> + (arr (\x -> x+1) >>> f) ||| (arr (\y -> y+2) >>> g) + +Since the translation uses |||, +the arrow concerned must belong to the ArrowChoice class. + + + +There are also case commands, like + +case input of + [] -> f -< () + [x] -> g -< x+1 + x1:x2:xs -> do + y <- h -< (x1, x2) + ys <- k -< xs + returnA -< y:ys + +The syntax is the same as for case expressions, +except that the bodies of the alternatives are commands rather than expressions. +The translation is similar to that of if commands. + + + + + +Defining your own control structures + + +As we're seen, arrow notation provides constructs, +modelled on those for expressions, +for sequencing, value recursion and conditionals. +But suitable combinators, +which you can define in ordinary Haskell, +may also be used to build new commands out of existing ones. +The basic idea is that a command defines an arrow from environments to values. +These environments assign values to the free local variables of the command. +Thus combinators that produce arrows from arrows +may also be used to build commands from commands. +For example, the ArrowChoice class includes a combinator + +ArrowChoice a => (<+>) :: a e c -> a e c -> a e c + +so we can use it to build commands: + +expr' = proc x -> + returnA -< x + <+> do + symbol Plus -< () + y <- term -< () + expr' -< x + y + <+> do + symbol Minus -< () + y <- term -< () + expr' -< x - y + +This is equivalent to + +expr' = (proc x -> returnA -< x) + <+> (proc x -> do + symbol Plus -< () + y <- term -< () + expr' -< x + y) + <+> (proc x -> do + symbol Minus -< () + y <- term -< () + expr' -< x - y) + +It is essential that this operator be polymorphic in e +(representing the environment input to the command +and thence to its subcommands) +and satisfy the corresponding naturality property + +arr k >>> (f <+> g) = (arr k >>> f) <+> (arr k >>> g) + +at least for strict k. +(This should be automatic if you're not using seq.) +This ensures that environments seen by the subcommands are environments +of the whole command, +and also allows the translation to safely trim these environments. +The operator must also not use any variable defined within the current +arrow abstraction. + + + +We could define our own operator + +untilA :: ArrowChoice a => a e () -> a e Bool -> a e () +untilA body cond = proc x -> + if cond x then returnA -< () + else do + body -< x + untilA body cond -< x + +and use it in the same way. +Of course this infix syntax only makes sense for binary operators; +there is also a more general syntax involving special brackets: + +proc x -> do + y <- f -< x+1 + (|untilA|) (increment -< x+y) (within 0.5 -< x) + + + + +Some operators will need to pass additional inputs to their subcommands. +For example, in an arrow type supporting exceptions, +the operator that attaches an exception handler will wish to pass the +exception that occurred to the handler. +Such an operator might have a type + +handleA :: ... => a e c -> a (e,Ex) c -> a e c + +where Ex is the type of exceptions handled. +You could then use this with arrow notation by writing a command + +body `handleA` \ ex -> handler + +so that if an exception is raised in the command body, +the variable ex is bound to the value of the exception +and the command handler, +which typically refers to ex, is entered. +Though the syntax here looks like a functional lambda, +we are talking about commands, and something different is going on. +The input to the arrow represented by a command consists of values for +the free local variables in the command, plus a stack of anonymous values. +In all the prior examples, this stack was empty. +In the second argument to handleA, +this stack consists of one value, the value of the exception. +The command form of lambda merely gives this value a name. + + + +More concretely, +the values on the stack are paired to the right of the environment. +So when designing operators like handleA that pass +extra inputs to their subcommands, +More precisely, the type of each argument of the operator (and its result) +should have the form + +a (...(e,t1), ... tn) t + +where e is the polymorphic variable +(representing the environment) +and ti are the types of the values on the stack, +with t1 being the top. +The polymorphic variable e must not occur in +a, ti or +t. +However the arrows involved need not be the same. +Here are some more examples of suitable operators: + +bracketA :: ... => a e b -> a (e,b) c -> a (e,c) d -> a e d +runReader :: ... => a e c -> a' (e,State) c +runState :: ... => a e c -> a' (e,State) (c,State) + +How can we supply the extra input required by the last two? +We can define yet another operator, a counterpart of the monadic +>>= operator: + +bind :: Arrow a => a e b -> a (e,b) c -> a e c +u `bind` f = returnA &&& u >>> f + +and then build commands like + +proc x -> + (mkState -< x) `bind` (|runReader|) (do { ... }) + +which uses the arrow mkState to create a state, +and then provides this as an extra input to the command built using +runReader. + + + + + +Differences with the paper + + + + +Instead of a single form of arrow application (arrow tail) with two +translations, the implementation provides two forms +-< (first-order) +and -<< (higher-order). + + + + +User-defined operators are flagged with banana brackets instead of +a new form keyword. + + + + + + + + +Portability + + +Although only GHC implements arrow notation directly, +there is also a preprocessor +(available from the +arrows web page>) +that translates arrow notation into Haskell 98 +for use with other Haskell systems. +You would still want to check arrow programs with GHC; +tracing type errors in the preprocessor output is not easy. +Modules intended for both GHC and the preprocessor must observe some +additional restrictions: + + + + +The module must import +Control.Arrow. + + + + + +The preprocessor cannot cope with other Haskell extensions. +These would have to go in separate modules. + + + + + +Because the preprocessor targets Haskell (rather than Core), +let-bound variables are monomorphic. + + + + + + + + + + @@ -3399,32 +3908,64 @@ Assertion failures can be caught, see the documentation for the unrecognised word is (silently) ignored. - -INLINE pragma + <sect2 id="deprecated-pragma"> + <title>DEPRECATED pragma + DEPRECATED + -INLINE pragma -pragma, INLINE + The DEPRECATED pragma lets you specify that a particular + function, class, or type, is deprecated. There are two + forms. - -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 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 will probably see these unfoldings (in Core syntax) in your -interface files. - + + 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. + + - -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. - + You can suppress the warnings with the flag + . + - -The sledgehammer you can bring to bear is the -INLINEINLINE pragma pragma, used thusly: + + INLINE and NOINLINE pragmas + + These pragmas control the inlining of function + definitions. + + + INLINE pragma + INLINE + + 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. + 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) @@ -3434,25 +3975,25 @@ key_function :: Int -> String -> (Bool, Double) #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.) - + (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. - + 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. - + Syntactially, 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: + 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__ @@ -3461,32 +4002,140 @@ For example, in GHC's own UniqueSupply monad code, we have: #endif - + See also the NOINLINE pragma (). + + + + NOINLINE pragma + + NOINLINE + NOTINLINE + + 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). + + + + Phase control + + Sometimes you want to control exactly when in GHC's + pipeline the INLINE pragma is switched on. Inlining happens + only during runs of the simplifier. Each + run of the simplifier has a different phase + number; the phase number decreases towards zero. + If you use you'll see the + sequence of phase numbers for successive runs of the + simpifier. In an INLINE pragma you can optionally specify a + phase number, thus: - + + + You can say "inline f in Phase 2 + and all subsequent phases": + + {-# INLINE [2] f #-} + + + - -NOINLINE pragma - + + You can say "inline g in all + phases up to, but not including, Phase 3": + + {-# INLINE [~3] g #-} + + + -NOINLINE pragma -pragmaNOINLINE -NOTINLINE pragma -pragmaNOTINLINE + + If you omit the phase indicator, you mean "inline in + all phases". + + - -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. - + You can use a phase number on a NOINLINE pragma too: -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). + + + You can say "do not inline f + until Phase 2; in Phase 2 and subsequently behave as if + there was no pragma at all": + + {-# NOINLINE [2] f #-} + + + - + + You can say "do not inline g in + Phase 3 or any subsequent phase; before that, behave as if + there was no pragma": + + {-# NOINLINE [~3] g #-} + + + + + + If you omit the phase indicator, you mean "never + inline this function". + + + + The same phase-numbering control is available for RULES + (). + + + + + LINE pragma + + LINEpragma + pragmaLINE + 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. + + + + OPTIONS pragma + OPTIONS + + pragmaOPTIONS + + + The OPTIONS pragma is used to specify + additional options that are given to the compiler when compiling + this source file. See for + details. + + + + RULES pragma + + The RULES pragma lets you specify rewrite rules. It is + described in . + SPECIALIZE pragma @@ -3512,11 +4161,14 @@ hammeredLookup :: Ord key => [(key, value)] -> key -> value {-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-} + A SPECIALIZE pragma for a function can + be put anywhere its type signature could be put. + To get very fancy, you can also specify a named function to use for the specialised value, as in: -{-# RULES hammeredLookup = blah #-} +{-# RULES "hammeredLookup" hammeredLookup = blah #-} where blah is an implementation of @@ -3539,7 +4191,7 @@ hammeredLookup :: Ord key => [(key, value)] -> key -> value toDouble :: Real a => a -> Double toDouble = fromRational . toRational -{-# SPECIALIZE toDouble :: Int -> Double = i2d #-} +{-# RULES "toDouble/Int" toDouble = i2d #-} i2d (I# i) = D# (int2Double# i) -- uses Glasgow prim-op directly @@ -3548,9 +4200,6 @@ i2d (I# i) = D# (int2Double# i) -- uses Glasgow prim-op directly Rational—is obscenely expensive by comparison. - A SPECIALIZE pragma for a function can - be put anywhere its type signature could be put. - @@ -3578,83 +4227,7 @@ of the pragma. - -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 . - - @@ -3693,16 +4266,34 @@ From a syntactic point of view: + There may be zero or more rules in a RULES pragma. + + + + + + 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. +A rule may optionally have a phase-control number (see ), +immediately after the name of the rule. Thus: + + {-# RULES + "map/map" [2] forall f g xs. map f (map g xs) = map (f.g) xs + #-} + +The "[2]" means that the rule is active in Phase 2 and subsequent phases. The inverse +notation "[~2]" is also accepted, meaning that the rule is active up to, but not including, +Phase 2. + + @@ -3711,6 +4302,7 @@ is set, so you must lay out your rules starting in the same column as the enclosing definitions. + @@ -4186,7 +4778,7 @@ If you add you get a more detailed listing. - The defintion of (say) build in PrelBase.lhs looks llike this: + The defintion of (say) build in GHC/Base.lhs looks llike this: build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] @@ -4204,9 +4796,9 @@ in the RHS of the INLINE thing. I regret the delicacy of thi - In ghc/lib/std/PrelBase.lhs look at the rules for map to + In libraries/base/GHC/Base.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. +program even if fusion doesn't happen. More rules in GHC/List.lhs. @@ -4216,6 +4808,69 @@ program even if fusion doesn't happen. More rules in PrelList.lhs + + CORE pragma + + CORE pragma + pragma, CORE + core, annotation + + + The external core format supports Note annotations; + the CORE pragma gives a way to specify what these + should be in your Haskell source code. Syntactically, core + annotations are attached to expressions and take a Haskell string + literal as an argument. The following function definition shows an + example: + + +f x = ({-# CORE "foo" #-} show) ({-# CORE "bar" #-} x) + + + Sematically, this is equivalent to: + + +g x = show x + + + + + However, when external for is generated (via + ), there will be Notes attached to the + expressions show and x. + The core function declaration for f is: + + + + f :: %forall a . GHCziShow.ZCTShow a -> + a -> GHCziBase.ZMZN GHCziBase.Char = + \ @ a (zddShow::GHCziShow.ZCTShow a) (eta::a) -> + (%note "foo" + %case zddShow %of (tpl::GHCziShow.ZCTShow a) + {GHCziShow.ZCDShow + (tpl1::GHCziBase.Int -> + a -> + GHCziBase.ZMZN GHCziBase.Char -> GHCziBase.ZMZN GHCziBase.Cha +r) + (tpl2::a -> GHCziBase.ZMZN GHCziBase.Char) + (tpl3::GHCziBase.ZMZN a -> + GHCziBase.ZMZN GHCziBase.Char -> GHCziBase.ZMZN GHCziBase.Cha +r) -> + tpl2}) + (%note "foo" + eta); + + + + Here, we can see that the function show (which + has been expanded out to a case expression over the Show dictionary) + has a %note attached to it, as does the + expression eta (which used to be called + x). + + + + @@ -4264,7 +4919,7 @@ 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 +That is, just leave off the "where" clause. Of course, you can put in the where clause and over-ride whichever methods you please.