[[project @ 2003-06-30 09:31:46 by ross]
ross**20030630093146
documentation for -farrows
] {
hunk ./ghc/docs/users_guide/flags.sgml 459
+
+
+ Enable arrow notation extension
+ dynamic
+
+
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 112
+
+
+
+
+ See . Independent of
+ .
+
+
+
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3347
+
+
+
+
+
+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.
+
+
+
+
+
+
+
+
}