Difference between revisions of "Arrow"

From HaskellWiki
Jump to navigation Jump to search
m (spell-check with ispell)
(Remove outdated information about upgrading to GHC 6.10)
 
(43 intermediate revisions by 13 users not shown)
Line 3: Line 3:
 
__TOC__
 
__TOC__
   
== Introduction ==
+
== Overview ==
   
  +
Arrows, or Freyd-categories, are a generalization of Monads.
[http://www.haskell.org/arrows/index.html Arrows: A General Interface to Computation] written by [http://www.soi.city.ac.uk/%7Eross/ Ross Peterson].
 
   
  +
"They can do everything monads can do, and more. They are roughly comparable to monads with a static component." However "Arrows do have some problems". ''(need a more useful comparison)''
HaWiki's [http://haskell.org/hawiki/UnderstandingArrows UnderstandingArrows].
 
   
  +
For an introduction, see [[#External links]].
Monad.Reader's [http://www.haskell.org/tmrwiki/ArrowsIntroduction ArrowsIntroduction] article.
 
   
 
== Library ==
[http://www.cse.ogi.edu/~magnus/ProdArrows/ ProdArrows -- Arrows for Fudgets] is also a good general material on the arrow concept (and also good for seeing, how arrows can be used to implement stream processors and Fudgets). It is written by [http://www.cse.ogi.edu/~magnus/ Magnus Carlsson].
 
   
 
* [http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Arrow.html Control.Arrow] is the standard library for arrows.
See also [[Research papers/Monads and arrows]].
 
 
* [http://www.haskell.org/arrows/download.html Arrow transformer library] (see the bottom of the page) is an extension with arrow transformers, subclasses, useful data types (Data.Stream, Data.Sequence).
  +
* [http://hackage.haskell.org/package/arrows arrows package]
   
== Practice ==
+
== Examples ==
   
 
Various concepts follow here, which can be seen as concrete examples covered by the arrow concept. Not all of them provide links to Haskell-related materials: some of them are here only to give a self-contained material (e.g. section [[#Automaton]] gives links only to the finite state concept itself.).
Reasons, when it may be worth of solving a specific problem with arrows (instead of monads) can be read in
 
[http://caml.inria.fr/pub/ml-archives/caml-list/2000/08/3c42f0fad3b3ecaca4f6043af65f6315.en.html a message from Daan Leijen].
 
   
== Library ==
+
=== Practice ===
   
 
Reasons, when it may be worth of solving a specific problem with arrows (instead of [[monad]]s) can be read in
[http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Arrow.html Control.Arrow] is the standard library for arrows.
 
 
[http://caml.inria.fr/pub/ml-archives/caml-list/2000/08/3c42f0fad3b3ecaca4f6043af65f6315.en.html a message from Daan Leijen].
  +
But Leijen's post is rather old (2000). Arrows are now significantly easier to understand and use than they were back then. Eg, his example might be rewritten
  +
test = proc _ -> do
  +
question <- ask -< "what is the question ?"
  +
answer <- ask -< question
  +
returnA -< ("the answer to '" ++ question ++ "' is " ++ answer)
  +
(or something vaguely like that).
   
  +
=== Function ===
[http://www.haskell.org/arrows/download.html#bottom Arrow transformer library] (see the bottom of the page) is an extension with arrow transformers, subclasses, useful data types (Data.Stream, Data.Sequence).
 
   
  +
Arrow operations <hask>arr</hask> and <hask>>>></hask> are rather straightforward. For implementing <hask>first</hask> and related concepts, see [[Prelude extensions#Tuples]].
== Examples ==
 
 
Various concepts follow here, which can be seen as concrete examples covered by the arrow concept. Not all of them provide links to Haskell-related materials: some of them are here only to give a self-contained material (e.g. section [[#Automaton]] gives links only to the finite state concept itself.).
 
   
 
=== Parser ===
 
=== Parser ===
   
The reasons why the arrow concept can solve important questions when designing a parser library are explained in [http://www.haskell.org/arrows/biblio.html Generalising Monads to Arrows] written by [http://www.cs.chalmers.se/~rjmh/ John Hughes].
+
The reasons why the arrow concept can solve important questions when designing a parser library are explained in [http://www.haskell.org/arrows/biblio.html Generalising Monads to Arrows] written by [http://www.cse.chalmers.se/~rjmh/ John Hughes].
   
 
A good example of the mentioned arrow parsers can be seen in [http://www.soi.city.ac.uk/~ross/papers/notation.html A New Notation for Arrows] written by [http://www.soi.city.ac.uk/%7Eross/ Ross Paterson]: figure 2, 4, 6 (page 3, 5, 6):
 
A good example of the mentioned arrow parsers can be seen in [http://www.soi.city.ac.uk/~ross/papers/notation.html A New Notation for Arrows] written by [http://www.soi.city.ac.uk/%7Eross/ Ross Paterson]: figure 2, 4, 6 (page 3, 5, 6):
Line 49: Line 55:
 
exprTail = proc e -> do
 
exprTail = proc e -> do
 
symbol PLUS -< ()
 
symbol PLUS -< ()
t <- term -< ()
+
t <- term -< ()
 
exprTail -< Plus e t
 
exprTail -< Plus e t
 
<+> do
 
<+> do
 
symbol MINUS -< ()
 
symbol MINUS -< ()
t <- term -< ()
+
t <- term -< ()
 
exprTail -< Minus e t
 
exprTail -< Minus e t
 
<+> returnA -< e
 
<+> returnA -< e
 
</haskell>
 
</haskell>
   
An arrow parser library: [http://www.cs.helsinki.fi/u/ekarttun/PArrows/ PArrows] written by [http://www.haskell.org/tmrwiki/EinarKarttunen Einar Karttunen].
+
An arrow parser library: [http://hackage.haskell.org/package/PArrows PArrows] written by Einar Karttunen.
  +
  +
Another arrow parser implementation: [http://antti-juhani.kaijanaho.fi/tmp/LLParser.hs LLParser.hs] written by [http://antti-juhani.kaijanaho.fi/newblog/ Antti-Juhani Kaijanaho] (I read the [http://www.scannedinavian.com/~shae/blog/2006-03-14.html reference] to it in [http://www.scannedinavian.com/~shae/blog/index.html Shae Erisson's blog / journal]).
   
 
The funny thing which took a long time for me to understand arrow parsers is a sort of differential approach -- in contrast to the [http://www.willamette.edu/~fruehr/haskell/seuss.html well-known parser approaches]. (I mean, in some way well-known parsers are of differential approach too, in the sense that they manage state transitions where the states are remainder streams -- but here I mean being differential in another sense: arrow parsers seem to me differential in the way how they consume and produce values -- their input and output.)
 
The funny thing which took a long time for me to understand arrow parsers is a sort of differential approach -- in contrast to the [http://www.willamette.edu/~fruehr/haskell/seuss.html well-known parser approaches]. (I mean, in some way well-known parsers are of differential approach too, in the sense that they manage state transitions where the states are remainder streams -- but here I mean being differential in another sense: arrow parsers seem to me differential in the way how they consume and produce values -- their input and output.)
Line 64: Line 72:
 
The idea of borrowing this image from mathematical analysis comes from another topic: the version control systems article [http://sourcefrog.net/weblog/software/vc/derivatives.html Integrals and derivatives] written by Martin Pool uses a similar image.
 
The idea of borrowing this image from mathematical analysis comes from another topic: the version control systems article [http://sourcefrog.net/weblog/software/vc/derivatives.html Integrals and derivatives] written by Martin Pool uses a similar image.
   
[http://www.soi.city.ac.uk/~ross/papers/fop.html Arrows and Computation] written by [http://www.soi.city.ac.uk/%7Eross/ Ross Paterson] (pages 2, 6, 7) mentions that computation (e.g. state) is threaded through the operands of <hask>&&&</hask>. I think this can be exemplified very well with parser arrows. See an example found in [http://www.cs.helsinki.fi/u/ekarttun/PArrows/ PArrows] written by [http://www.haskell.org/tmrwiki/EinarKarttunen Einar Karttunen] (see module <hask>Text.ParserCombinators.PArrow.Combinator</hask>):
+
[http://www.soi.city.ac.uk/~ross/papers/fop.html Arrows and Computation] written by [http://www.soi.city.ac.uk/%7Eross/ Ross Paterson] (pages 2, 6, 7) and [http://www.carlssonia.org/ogi/ProdArrows/ ProdArrows -- Arrows for Fudgets]
  +
written by [http://www.carlssonia.org/ Magnus Carlsson] (page 9) mentions that computation (e.g. state) is threaded through the operands of <hask>&&&</hask> operation.
  +
I mean, even the mere definition of <hask>&&&</hask> operation
  +
<haskell>
  +
p &&& q = arr dup >>> first p >>> second q
  +
</haskell>
  +
shows that the order of the computation (the side effects) is important when using <hask>&&&</hask>, and this can be exemplified very well with parser arrows. See an example found in [http://hackage.haskell.org/package/PArrows PArrows] written by Einar Karttunen (see module <hask>Text.ParserCombinators.PArrow.Combinator</hask>):
 
<haskell>
 
<haskell>
 
-- | Match zero or more occurrences of the given parser.
 
-- | Match zero or more occurrences of the given parser.
Line 74: Line 88:
 
many1 x = (x &&& MStar x) >>> pure (\(b,bs) -> (b:bs))
 
many1 x = (x &&& MStar x) >>> pure (\(b,bs) -> (b:bs))
 
</haskell>
 
</haskell>
The definition of <hask>between</hask> parser combinator can show another example for the non-commutativeness of <hask>&&&</hask> operation:
+
The definition of <hask>between</hask> parser combinator can show another example for the importance of the order in which the computation (e.g. the side effects) take place using <hask>&&&</hask> operation:
 
<haskell>
 
<haskell>
 
between :: MD i t -> MD t close -> MD t o -> MD i o
 
between :: MD i t -> MD t close -> MD t o -> MD i o
Line 85: Line 99:
 
sepBy1 p s = (many (p &&& s >>^ fst) &&& p) >>^ (\(bs,b) -> bs++[b])
 
sepBy1 p s = (many (p &&& s >>^ fst) &&& p) >>^ (\(bs,b) -> bs++[b])
 
</haskell>
 
</haskell>
This makes clear that the order of the operands of <hask>&&&</hask> operation can be important. Of course, in some cases (e.g. nondeterministic functions arrows, or more generally, at the various implementations of binary relation arrows) the order of the operands of fan-in and fan-out is not important.
+
This makes clear that the order of effects of the operands of <hask>&&&</hask> operation can be important. But let us mention also a counterexample, e.g. nondeterministic functions arrows, or more generally, the various implementations of binary relation arrows -- there is no such sequencing of effect orders. Now let us see this fact on the mere mathematical concept of binary relations (not minding how it implemented):
  +
:<math>(\rho</math> <hask>&&&</hask> <math>\sigma) x \left\langle y_0, y_1\right\rangle \Leftrightarrow x \rho y_0 \land x \sigma y_1</math>
  +
:<math>(\rho</math> <hask>|||</hask> <math>\sigma) \left(i:x\right) y \Leftrightarrow i\begin{cases}0:&x\rho y\\1:&x\sigma y\end{cases}</math>
  +
  +
The picture illustrating <hask>***</hask> in [http://en.wikibooks.org/wiki/Haskell/Understanding_arrows#.2A.2A.2A Haskell/Understanding arrows] article of Wikibooks suggests exactly such a view: order of side effects can be unimportant at some arrow instances, and the symmetry of the figure reflects this. In generally, however, the figure should use a notation for threading through side effects in a sequence.
   
 
=== Stream processor ===
 
=== Stream processor ===
Line 91: Line 109:
 
The [http://homepages.cwi.nl/~tromp/cl/lazy-k.html Lazy K programming language] is an interesting esoteric language (from the family of pure, lazy functional languages), whose I/O concept is approached by streams.
 
The [http://homepages.cwi.nl/~tromp/cl/lazy-k.html Lazy K programming language] is an interesting esoteric language (from the family of pure, lazy functional languages), whose I/O concept is approached by streams.
   
Arrows are useful also to grasp the concept of stream processors. See details in [http://www.cse.ogi.edu/~magnus/ProdArrows/ ProdArrows -- Arrows for Fudgets]
+
Arrows are useful also to grasp the concept of stream processors. See details in
written by [http://www.cse.ogi.edu/~magnus/ Magnus Carlsson], 2001.
+
* [http://www.carlssonia.org/ogi/ProdArrows/ ProdArrows -- Arrows for Fudgets] written by [http://www.carlssonia.org/ Magnus Carlsson], 2001.
  +
* [http://www.haskell.org/arrows/biblio.html Generalising Monads to Arrows] written by [http://www.cse.chalmers.se/~rjmh/ John Hughes] (section 6, pages 20--24)
   
 
==== Functional I/O, graphical user interfaces ====
 
==== Functional I/O, graphical user interfaces ====
   
[http://citeseer.ist.psu.edu/hudak89expressiveness.html On the Expressiveness of Purely Functional I/O Systems] written by Paul Hudak and Raman S. Sundaresh.
+
* [http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.49.695 On the Expressiveness of Purely Functional I/O Systems] written by Paul Hudak and Raman S. Sundaresh.
 
* [http://www.altocumulus.org/Fudgets/ Fudgets] written by [http://www.altocumulus.org/~hallgren/ Thomas Hallgren] and [http://www.carlssonia.org/ Magnus Carlsson]. See also [http://www.carlssonia.org/ogi/ProdArrows/ Arrows for Fudgets] written by [http://www.carlssonia.org/ Magnus Carlsson], mentioning how these two concepts relate to each other.
 
  +
* [http://kevin.atkinson.dhs.org/fg/doc/FG.html FG]
[http://www.cs.chalmers.se/Cs/Research/Functional/Fudgets/ Fudgets] written by [http://www.cs.chalmers.se/~hallgren/ Thomas Hallgren] and [http://www.cs.chalmers.se/~magnus/ Magnus Carlsson]. See also [http://www.cse.ogi.edu/PacSoft/seminar/magnus_abstract.html Arrows for Fudgets] written by [http://www.cse.ogi.edu/~magnus/ Magnus Carlsson], mentioning how these two concepts relate to each other.
 
  +
* [[Phooey]]
  +
* [[Grapefruit]]
   
 
==== Dataflow languages ====
 
==== Dataflow languages ====
Line 104: Line 125:
 
[http://www.soi.city.ac.uk/~ross/papers/fop.html Arrows and Computation] written by [http://www.soi.city.ac.uk/%7Eross/ Ross Paterson] mentions how to mimic dataflow programming in (lazy) functional languages. See more on Lucid's own HaskellWiki page: [[Lucid]].
 
[http://www.soi.city.ac.uk/~ross/papers/fop.html Arrows and Computation] written by [http://www.soi.city.ac.uk/%7Eross/ Ross Paterson] mentions how to mimic dataflow programming in (lazy) functional languages. See more on Lucid's own HaskellWiki page: [[Lucid]].
   
== Automaton ==
+
=== Automaton ===
   
 
To see what the concept itself means, see the Wikipedia articles [http://en.wikipedia.org/wiki/Finite_state_machine Finite state machine] and also [http://en.wikipedia.org/wiki/Automata_theory Automata theory].
 
To see what the concept itself means, see the Wikipedia articles [http://en.wikipedia.org/wiki/Finite_state_machine Finite state machine] and also [http://en.wikipedia.org/wiki/Automata_theory Automata theory].
Line 110: Line 131:
 
How these concepts can be implemented using the concept of arrow, can be found in the introductory articles on arrows mentioned above.
 
How these concepts can be implemented using the concept of arrow, can be found in the introductory articles on arrows mentioned above.
   
  +
=== Haskell XML Toolbox ===
[[Category:Standard classes]]
 
  +
[[HXT]] is an example of a real application using Arrows
  +
  +
== External links ==
  +
* [http://www.cse.chalmers.se/~rjmh/afp-arrows.pdf ''Programming with Arrows''] - A tutorial introduction to arrows and arrow notation. Very didactic, introducing the arrow subclasses with detailed examples and rich explanations on the motivations of each decision.
 
* [http://www.haskell.org/arrows/ Arrows: A General Interface to Computation] written by [http://www.soi.city.ac.uk/%7Eross/ Ross Paterson].
  +
* [http://www.haskell.org/arrows/biblio.html ''Generalising Monads to Arrows'', and other papers]
 
* [http://www.carlssonia.org/ogi/ProdArrows/ ProdArrows -- Arrows for Fudgets] is also a good general material on the arrow concept (and also good for seeing, how arrows can be used to implement stream processors and Fudgets). It is written by [http://www.carlssonia.org/ Magnus Carlsson].
  +
* [http://en.wikibooks.org/wiki/Haskell/Arrows Haskell/Arrows] on Wikibooks, followed by [http://en.wikibooks.org/wiki/Haskell/Understanding_arrows Understanding arrows], which uses a factory/conveyor belt metaphor for arrows. We know this image for [[monad]]s, but it is modified here for arrows, too.
 
* HaWiki's [http://web.archive.org/web/20060901030914/http://haskell.org/hawiki/UnderstandingArrows UnderstandingArrows]. (An old page in the Web Archive (slow))
  +
  +
  +
== See also ==
  +
  +
* [[Causal Commutative Arrows]]
 
* [[Research papers/Monads and arrows#Arrows]].
  +
* [[Arrow tutorial]].
  +
 
[[Category:Arrow]]

Latest revision as of 20:01, 13 May 2020

Arrow class (base)
import Control.Arrow

Overview

Arrows, or Freyd-categories, are a generalization of Monads.

"They can do everything monads can do, and more. They are roughly comparable to monads with a static component." However "Arrows do have some problems". (need a more useful comparison)

For an introduction, see #External links.

Library

Examples

Various concepts follow here, which can be seen as concrete examples covered by the arrow concept. Not all of them provide links to Haskell-related materials: some of them are here only to give a self-contained material (e.g. section #Automaton gives links only to the finite state concept itself.).

Practice

Reasons, when it may be worth of solving a specific problem with arrows (instead of monads) can be read in a message from Daan Leijen. But Leijen's post is rather old (2000). Arrows are now significantly easier to understand and use than they were back then. Eg, his example might be rewritten

test = proc _ -> do
           question <- ask -< "what is the question ?"
           answer   <- ask -< question
           returnA -< ("the answer to '" ++ question ++ "' is " ++ answer)

(or something vaguely like that).

Function

Arrow operations arr and >>> are rather straightforward. For implementing first and related concepts, see Prelude extensions#Tuples.

Parser

The reasons why the arrow concept can solve important questions when designing a parser library are explained in Generalising Monads to Arrows written by John Hughes.

A good example of the mentioned arrow parsers can be seen in A New Notation for Arrows written by Ross Paterson: figure 2, 4, 6 (page 3, 5, 6):

is represented with arrow parsers this way:

 data Expr = Plus Expr Expr | Minus Expr Expr | ...

 expr :: ParseArrow () Expr
 expr = proc () -> do
         t <- term -< ()
         exprTail -< t

 exprTail :: ParseArrow Expr Expr
 exprTail = proc e -> do
         symbol PLUS -< ()
         t <- term   -< ()
         exprTail -< Plus e t
    <+> do
         symbol MINUS -< ()
         t <- term    -< ()
         exprTail -< Minus e t
    <+> returnA -< e

An arrow parser library: PArrows written by Einar Karttunen.

Another arrow parser implementation: LLParser.hs written by Antti-Juhani Kaijanaho (I read the reference to it in Shae Erisson's blog / journal).

The funny thing which took a long time for me to understand arrow parsers is a sort of differential approach -- in contrast to the well-known parser approaches. (I mean, in some way well-known parsers are of differential approach too, in the sense that they manage state transitions where the states are remainder streams -- but here I mean being differential in another sense: arrow parsers seem to me differential in the way how they consume and produce values -- their input and output.)

The idea of borrowing this image from mathematical analysis comes from another topic: the version control systems article Integrals and derivatives written by Martin Pool uses a similar image.

Arrows and Computation written by Ross Paterson (pages 2, 6, 7) and ProdArrows -- Arrows for Fudgets written by Magnus Carlsson (page 9) mentions that computation (e.g. state) is threaded through the operands of &&& operation. I mean, even the mere definition of &&& operation

 p &&& q = arr dup >>> first p >>> second q

shows that the order of the computation (the side effects) is important when using &&&, and this can be exemplified very well with parser arrows. See an example found in PArrows written by Einar Karttunen (see module Text.ParserCombinators.PArrow.Combinator):

 -- | Match zero or more occurrences of the given parser.
 many :: MD i o -> MD i [o]
 many = MStar

 -- | Match one or more occurrences of the given parser.
 many1 :: MD i o -> MD i [o]
 many1 x = (x &&& MStar x) >>> pure (\(b,bs) -> (b:bs))

The definition of between parser combinator can show another example for the importance of the order in which the computation (e.g. the side effects) take place using &&& operation:

 between :: MD i t -> MD t close -> MD t o -> MD i o
 between open close real = open >>> (real &&& close) >>^ fst

A more complicated example (from the same module):

 -- | Match one or more occurrences of the given parser separated by the separator.
 sepBy1 :: MD i o -> MD i o' -> MD i [o]
 sepBy1 p s = (many (p &&& s >>^ fst) &&& p) >>^ (\(bs,b) -> bs++[b])

This makes clear that the order of effects of the operands of &&& operation can be important. But let us mention also a counterexample, e.g. nondeterministic functions arrows, or more generally, the various implementations of binary relation arrows -- there is no such sequencing of effect orders. Now let us see this fact on the mere mathematical concept of binary relations (not minding how it implemented):

&&&
|||

The picture illustrating *** in Haskell/Understanding arrows article of Wikibooks suggests exactly such a view: order of side effects can be unimportant at some arrow instances, and the symmetry of the figure reflects this. In generally, however, the figure should use a notation for threading through side effects in a sequence.

Stream processor

The Lazy K programming language is an interesting esoteric language (from the family of pure, lazy functional languages), whose I/O concept is approached by streams.

Arrows are useful also to grasp the concept of stream processors. See details in

Functional I/O, graphical user interfaces

Dataflow languages

Arrows and Computation written by Ross Paterson mentions how to mimic dataflow programming in (lazy) functional languages. See more on Lucid's own HaskellWiki page: Lucid.

Automaton

To see what the concept itself means, see the Wikipedia articles Finite state machine and also Automata theory.

How these concepts can be implemented using the concept of arrow, can be found in the introductory articles on arrows mentioned above.

Haskell XML Toolbox

HXT is an example of a real application using Arrows

External links


See also