Difference between revisions of "Arrow tutorial"

From HaskellWiki
Jump to navigation Jump to search
(The example I added may not be helpful; removed it.)
(18 intermediate revisions by 7 users not shown)
Line 1: Line 1:
  +
[[Category:Tutorials]]
  +
[[Category:Arrow]]
 
<haskell>
 
<haskell>
  +
  +
> {-# LANGUAGE Arrows #-}
 
> module ArrowFun where
 
> module ArrowFun where
 
> import Control.Arrow
 
> import Control.Arrow
  +
> import Control.Category
  +
> import Prelude hiding (id,(.))
  +
 
</haskell>
 
</haskell>
   
  +
== The Arrow ==
 
Arrow a b c represents a process that takes as input something of
 
Arrow a b c represents a process that takes as input something of
 
type b and outputs something of type c.
 
type b and outputs something of type c.
   
 
Arr builds an arrow out of a function. This function is
 
Arr builds an arrow out of a function. This function is
arrow-specific. It's signature is
+
arrow-specific. Its signature is
   
 
<haskell>
 
<haskell>
  +
> -- arr :: (Arrow a) => (b -> c) -> a b c
 
  +
arr :: (Arrow a) => (b -> c) -> a b c
  +
 
</haskell>
 
</haskell>
   
 
Arrow composition is achieved with (>>>). This takes two arrows
 
Arrow composition is achieved with (>>>). This takes two arrows
 
and chains them together, one after another. It is also arrow-
 
and chains them together, one after another. It is also arrow-
specific. It's signature is:
+
specific. Its signature is:
   
 
<haskell>
 
<haskell>
  +
> -- (>>>) :: (Arrow a) => a b c -> a c d -> a b d
 
  +
(>>>) :: (Arrow a) => a b c -> a c d -> a b d
  +
 
</haskell>
 
</haskell>
   
Line 28: Line 40:
   
 
<haskell>
 
<haskell>
  +
> -- first :: (Arrow a) => a b c -> a (b, d) (c, d)
 
> -- second :: (Arrow a) => a b c -> a (d, b) (d, c)
+
first :: (Arrow a) => a b c -> a (b, d) (c, d)
  +
second :: (Arrow a) => a b c -> a (d, b) (d, c)
  +
 
</haskell>
 
</haskell>
   
Line 37: Line 51:
 
That's it for the arrow-specific definitions.
 
That's it for the arrow-specific definitions.
   
  +
== A Simple Arrow ==
 
Let's define a really simple arrow as an example. Our simple arrow is
 
Let's define a really simple arrow as an example. Our simple arrow is
 
just a function mapping an input to an output. We don't really need
 
just a function mapping an input to an output. We don't really need
Line 43: Line 58:
   
 
<haskell>
 
<haskell>
  +
 
> newtype SimpleFunc a b = SimpleFunc {
 
> newtype SimpleFunc a b = SimpleFunc {
 
> runF :: (a -> b)
 
> runF :: (a -> b)
Line 53: Line 69:
 
> second (SimpleFunc f) = SimpleFunc (mapSnd f)
 
> second (SimpleFunc f) = SimpleFunc (mapSnd f)
 
> where mapSnd g (a,b) = (a, g b)
 
> where mapSnd g (a,b) = (a, g b)
  +
>
> (SimpleFunc f) >>> (SimpleFunc g) = SimpleFunc (g . f)
 
  +
> instance Category SimpleFunc where
  +
> (SimpleFunc g) . (SimpleFunc f) = SimpleFunc (g . f)
  +
> id = arr id
  +
 
</haskell>
 
</haskell>
   
  +
== Some Arrow Operations ==
 
Now lets define some operations that are generic to all arrows.
 
Now lets define some operations that are generic to all arrows.
   
Line 62: Line 83:
   
 
<haskell>
 
<haskell>
  +
 
> split :: (Arrow a) => a b (b, b)
 
> split :: (Arrow a) => a b (b, b)
 
> split = arr (\x -> (x,x))
 
> split = arr (\x -> (x,x))
  +
 
</haskell>
 
</haskell>
   
Line 70: Line 93:
   
 
<haskell>
 
<haskell>
  +
 
> unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
 
> unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
 
> unsplit = arr . uncurry
 
> unsplit = arr . uncurry
 
> -- arr (\op (x,y) -> x `op` y)
 
> -- arr (\op (x,y) -> x `op` y)
  +
 
</haskell>
 
</haskell>
   
 
(***) combines two arrows into a new arrow by running the two arrows
 
(***) combines two arrows into a new arrow by running the two arrows
on a pair of values (one arrow on the first pair and one arrow on the
+
on a pair of values (one arrow on the first item of the pair and one arrow on the
second pair).
+
second item of the pair).
   
 
<haskell>
 
<haskell>
  +
> -- f *** g = first f >>> second g
 
  +
f *** g = first f >>> second g
  +
 
</haskell>
 
</haskell>
   
Line 87: Line 114:
   
 
<haskell>
 
<haskell>
  +
> -- f &&& g = split >>> first f >>> second g
 
> -- split >>> f *** g
+
f &&& g = split >>> first f >>> second g
  +
-- = split >>> f *** g
  +
 
</haskell>
 
</haskell>
   
Line 96: Line 125:
   
 
<haskell>
 
<haskell>
  +
 
> liftA2 :: (Arrow a) => (b -> c -> d) -> a e b -> a e c -> a e d
 
> liftA2 :: (Arrow a) => (b -> c -> d) -> a e b -> a e c -> a e d
 
> liftA2 op f g = split >>> first f >>> second g >>> unsplit op
 
> liftA2 op f g = split >>> first f >>> second g >>> unsplit op
> -- f &&& g >>> unsplit op
+
> -- = f &&& g >>> unsplit op
  +
 
</haskell>
 
</haskell>
   
   
  +
== An Example ==
 
 
Now let's build something using our simple arrow definition and
 
Now let's build something using our simple arrow definition and
 
some of the tools we just created. We start with two simple
 
some of the tools we just created. We start with two simple
Line 109: Line 140:
   
 
<haskell>
 
<haskell>
  +
 
> f, g :: SimpleFunc Int Int
 
> f, g :: SimpleFunc Int Int
 
> f = arr (`div` 2)
 
> f = arr (`div` 2)
 
> g = arr (\x -> x*3 + 1)
 
> g = arr (\x -> x*3 + 1)
  +
 
</haskell>
 
</haskell>
   
Line 117: Line 150:
   
 
<haskell>
 
<haskell>
  +
  +
> h :: SimpleFunc Int Int
 
> h = liftA2 (+) f g
 
> h = liftA2 (+) f g
  +
>
  +
> hOutput :: Int
 
> hOutput = runF h 8
 
> hOutput = runF h 8
  +
 
</haskell>
 
</haskell>
   
Line 130: Line 168:
 
(4, 25) -> 29 applies (+) to tuple elements.
 
(4, 25) -> 29 applies (+) to tuple elements.
   
+------> f --------------+
+
+------> f ---------+
| v
+
| v
8 ---> (split) ---> g -----> (unsplit (+)) ----> 29
+
8 ---> (split) (unsplit (+)) ----> 29
  +
| ^
  +
+------> g ---------+
   
 
so we see that h is a new arrow that when applied to 8, applies 8 to f
 
so we see that h is a new arrow that when applied to 8, applies 8 to f
 
and applies 8 to g and adds the results.
 
and applies 8 to g and adds the results.
   
  +
A lot of juggling occurred to get the plumbing right since
  +
h wasn't defined as a linear combination of arrows. GHC has
  +
a do-notation that simplifies this in a similar way to how
  +
do-notation simplifies monadic computation. The h function
  +
can be defined as:
   
  +
<haskell>
  +
  +
> h' :: SimpleFunc Int Int
  +
> h' = proc x -> do
  +
> fx <- f -< x
  +
> gx <- g -< x
  +
> returnA -< (fx + gx)
  +
>
  +
> hOutput' :: Int
  +
> hOutput' = runF h' 8
  +
  +
</haskell>
  +
  +
== Kleisli Arrows ==
 
Let's move on to something a little fancier now: Kleisli arrows.
 
Let's move on to something a little fancier now: Kleisli arrows.
 
A Kleisli arrow (Kleisli m a b) is the arrow (a -> m b) for all
 
A Kleisli arrow (Kleisli m a b) is the arrow (a -> m b) for all
Line 143: Line 202:
   
 
<haskell>
 
<haskell>
  +
> -- newtype Kleisli m a b = Kleisli {
 
  +
newtype Kleisli m a b = Kleisli {
> -- runKleisli :: (a -> m b)
 
  +
runKleisli :: (a -> m b)
> -- }
 
  +
}
  +
 
</haskell>
 
</haskell>
   
Line 155: Line 216:
   
 
<haskell>
 
<haskell>
> -- XXX I am getting type problems with split, unsplit and liftA2! why?
 
> split' = arr (\x -> (x,x))
 
> unsplit' = arr . uncurry
 
> --liftA2' :: (Arrow a) => (b -> c -> d) -> a e b -> a e c -> a e d
 
> liftA2' op f g = split' >>> first f >>> second g >>> unsplit' op
 
</haskell>
 
   
<haskell>
 
 
> plusminus, double, h2 :: Kleisli [] Int Int
 
> plusminus, double, h2 :: Kleisli [] Int Int
 
> plusminus = Kleisli (\x -> [x, -x])
 
> plusminus = Kleisli (\x -> [x, -x])
> double = arr (* 2)
+
> double = arr (* 2)
> h2 = liftA2' (+) plusminus double
+
> h2 = liftA2 (+) plusminus double
  +
>
  +
> h2Output :: [Int]
 
> h2Output = runKleisli h2 8
 
> h2Output = runKleisli h2 8
  +
 
</haskell>
 
</haskell>
   
  +
== A Teaser ==
Finally, here's a little teaser. There's an arrow function called
 
  +
Finally, here is a little teaser. There is an arrow function called
returnA which returns an identity arrow. There's a ArrowPlus class
 
  +
returnA which returns an identity arrow. There is an ArrowPlus class
 
that includes a zeroArrow (which for the list monad is an arrow that
 
that includes a zeroArrow (which for the list monad is an arrow that
 
always returns the empty list) and a <+> operator (which takes the
 
always returns the empty list) and a <+> operator (which takes the
results from two arrows and concatenates them). We can build up
+
results from two arrows and concatenates them). We can build up
 
some pretty interesting string transformations (the multi-valued
 
some pretty interesting string transformations (the multi-valued
 
function String -> [String]) using Kleisli arrows:
 
function String -> [String]) using Kleisli arrows:
   
 
<haskell>
 
<haskell>
  +
  +
> main :: IO ()
 
> main = do
 
> main = do
 
> let
 
> let
 
> prepend x = arr (x ++)
 
> prepend x = arr (x ++)
> append x = arr (++ x)
+
> append x = arr (++ x)
> withId t = returnA <+> t
+
> withId t = returnA <+> t
 
> xform = (withId $ prepend "<") >>>
 
> xform = (withId $ prepend "<") >>>
 
> (withId $ append ">") >>>
 
> (withId $ append ">") >>>
Line 189: Line 249:
 
> xs = ["test", "foobar"] >>= (runKleisli xform)
 
> xs = ["test", "foobar"] >>= (runKleisli xform)
 
> mapM_ putStrLn xs
 
> mapM_ putStrLn xs
  +
 
</haskell>
 
</haskell>
   
 
An important observation here is that
 
An important observation here is that
f >> g
+
f >>> g
   
 
is multi-valued composition (g . f), and
 
is multi-valued composition (g . f), and
Line 204: Line 265:
   
 
which are all permutations of using arrows f and g.
 
which are all permutations of using arrows f and g.
  +
  +
== Tutorial Meta ==
  +
The wiki file source is literate Haskell. Save the source in a file called ArrowFun.lhs to compile it (or run in GHCi).
  +
  +
The code is adapted to GHC 6.10.1; use [http://www.haskell.org/haskellwiki/?title=Arrow_tutorial&oldid=15443] for older versions of GHC and other Haskell implementations.
  +
  +
* Original version - Nov 19, 2006, Tim Newsham.
  +
\

Revision as of 18:05, 15 July 2014

> {-# LANGUAGE Arrows #-}
> module ArrowFun where
> import Control.Arrow
> import Control.Category
> import Prelude hiding (id,(.))

The Arrow

Arrow a b c represents a process that takes as input something of type b and outputs something of type c.

Arr builds an arrow out of a function. This function is arrow-specific. Its signature is

arr :: (Arrow a) => (b -> c) -> a b c

Arrow composition is achieved with (>>>). This takes two arrows and chains them together, one after another. It is also arrow- specific. Its signature is:

(>>>) :: (Arrow a) => a b c -> a c d -> a b d

First and second make a new arrow out of an existing arrow. They perform a transformation (given by their argument) on either the first or the second item of a pair. These definitions are arrow-specific. Their signatures are:

first :: (Arrow a) => a b c -> a (b, d) (c, d)
second :: (Arrow a) => a b c -> a (d, b) (d, c)

First and second may seem pretty strange at first, but they'll make sense in a few minutes.

That's it for the arrow-specific definitions.

A Simple Arrow

Let's define a really simple arrow as an example. Our simple arrow is just a function mapping an input to an output. We don't really need arrows for something this simple, but we could use something this simple to explain arrows.

> newtype SimpleFunc a b = SimpleFunc {
>     runF :: (a -> b)
> }
>
> instance Arrow SimpleFunc where
>     arr f = SimpleFunc f
>     first (SimpleFunc f) = SimpleFunc (mapFst f)
>                   where mapFst g (a,b) = (g a, b)
>     second (SimpleFunc f) = SimpleFunc (mapSnd f)
>                   where mapSnd g (a,b) = (a, g b)
>
> instance Category SimpleFunc where
>     (SimpleFunc g) . (SimpleFunc f) = SimpleFunc (g . f)
>     id = arr id

Some Arrow Operations

Now lets define some operations that are generic to all arrows.

Split is an arrow that splits a single value into a pair of duplicate values:

> split :: (Arrow a) => a b (b, b)
> split = arr (\x -> (x,x))

Unsplit is an arrow that takes a pair of values and combines them to return a single value:

> unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
> unsplit = arr . uncurry       
>           -- arr (\op (x,y) -> x `op` y)

(***) combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).

f *** g = first f >>> second g

(&&&) combines two arrows into a new arrow by running the two arrows on the same value:

f &&& g = split >>> first f >>> second g
     -- = split >>> f *** g

LiftA2 makes a new arrow that combines the output from two arrows using a binary operation. It works by splitting a value and operating on both halfs and then combining the result:

> liftA2 :: (Arrow a) => (b -> c -> d) -> a e b -> a e c -> a e d
> liftA2 op f g = split >>> first f >>> second g >>> unsplit op
>            -- = f &&& g >>> unsplit op


An Example

Now let's build something using our simple arrow definition and some of the tools we just created. We start with two simple arrows, f and g. F halves its input and g triples its input and adds one:

> f, g :: SimpleFunc Int Int
> f = arr (`div` 2)
> g = arr (\x -> x*3 + 1)

We can combine these together using liftA2:

> h :: SimpleFunc Int Int
> h = liftA2 (+) f g
>
> hOutput :: Int
> hOutput = runF h 8

What is h? How does it work? The process defined by h is (split >>> first f >>> second g >>> unsplit (+)). Lets work through an application of h to some value, 8:

   8 -> (8, 8)             split
   (8, 8) -> (4, 8)        first f (x `div` 2 of the first element)
   (4, 8) -> (4, 25)       second g (3*x + 1 of the second element)
   (4, 25) -> 29           applies (+) to tuple elements.
             +------> f ---------+
             |                   v
   8 ---> (split)          (unsplit (+)) ----> 29
             |                   ^
             +------> g ---------+

so we see that h is a new arrow that when applied to 8, applies 8 to f and applies 8 to g and adds the results.

A lot of juggling occurred to get the plumbing right since h wasn't defined as a linear combination of arrows. GHC has a do-notation that simplifies this in a similar way to how do-notation simplifies monadic computation. The h function can be defined as:

> h' :: SimpleFunc Int Int
> h' = proc x -> do
>       fx <- f -< x
>       gx <- g -< x
>       returnA -< (fx + gx)
>
> hOutput' :: Int
> hOutput' = runF h' 8

Kleisli Arrows

Let's move on to something a little fancier now: Kleisli arrows. A Kleisli arrow (Kleisli m a b) is the arrow (a -> m b) for all monads. It's defined in Control.Arrows similarly to our SimpleFunc:

newtype Kleisli m a b = Kleisli {
  runKleisli :: (a -> m b) 
}

It comes complete with its own definitions for arr, first, second and (>>>). This means that all multi-value functions (a -> [b]) are already defined as Kleisli arrows (because [] is a monad)! (>>>) performs composition, keeping track of all the multiple results. Split, (&&&) and (***) are all defined as before. So for example:

> plusminus, double, h2 :: Kleisli [] Int Int
> plusminus = Kleisli (\x -> [x, -x])
> double    = arr (* 2)
> h2        = liftA2 (+) plusminus double 
>
> h2Output :: [Int]
> h2Output = runKleisli h2 8

A Teaser

Finally, here is a little teaser. There is an arrow function called returnA which returns an identity arrow. There is an ArrowPlus class that includes a zeroArrow (which for the list monad is an arrow that always returns the empty list) and a <+> operator (which takes the results from two arrows and concatenates them). We can build up some pretty interesting string transformations (the multi-valued function String -> [String]) using Kleisli arrows:

> main :: IO ()
> main = do
>    let
>        prepend x = arr (x ++)
>        append  x = arr (++ x)
>        withId  t = returnA <+> t
>        xform = (withId $ prepend "<") >>>
>                (withId $ append ">") >>>
>                (withId $ ((prepend "!") >>> (append "!")))
>        xs = ["test", "foobar"] >>= (runKleisli xform)
>    mapM_ putStrLn xs

An important observation here is that

   f >>> g

is multi-valued composition (g . f), and

   (withId f) >>> (withId g) =
   (returnA <+> f) >>> (returnA <+> g) =
   ((arr id) <+> f) >>> ((arr id) <+> g)

which, when applied to an input x, returns all values:

   ((id . id) x) ++ ((id . f) x) ++ ((id . g) x) ++ ((g . f) x) =
   x ++ (f x) ++ (g x) ++ ((g . f) x)

which are all permutations of using arrows f and g.

Tutorial Meta

The wiki file source is literate Haskell. Save the source in a file called ArrowFun.lhs to compile it (or run in GHCi).

The code is adapted to GHC 6.10.1; use [1] for older versions of GHC and other Haskell implementations.

  • Original version - Nov 19, 2006, Tim Newsham.

\