Difference between revisions of "Arrow tutorial"

From HaskellWiki
Jump to navigation Jump to search
 
Line 1: Line 1:
  +
<haskell>
Tutorial on Arrows, content to be filled in by Tim :)
 
  +
> module ArrowFun where
  +
> import Control.Arrow
  +
</haskell>
  +
  +
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. It's signature is
  +
  +
<haskell>
  +
> -- arr :: (Arrow a) => (b -> c) -> a b c
  +
</haskell>
  +
  +
Arrow composition is achieved with (>>>). This takes two arrows
  +
and chains them together, one after another. It is also arrow-
  +
specific. It's signature is:
  +
  +
<haskell>
  +
> -- (>>>) :: (Arrow a) => a b c -> a c d -> a b d
  +
</haskell>
  +
  +
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:
  +
  +
<haskell>
  +
> -- first :: (Arrow a) => a b c -> a (b, d) (c, d)
  +
> -- second :: (Arrow a) => a b c -> a (d, b) (d, c)
  +
</haskell>
  +
  +
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.
  +
  +
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.
  +
  +
<haskell>
  +
> 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)
  +
> (SimpleFunc f) >>> (SimpleFunc g) = SimpleFunc (g . f)
  +
</haskell>
  +
  +
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:
  +
  +
<haskell>
  +
> split :: (Arrow a) => a b (b, b)
  +
> split = arr (\x -> (x,x))
  +
</haskell>
  +
  +
Unsplit is an arrow that takes a pair of values and combines them
  +
to return a single value:
  +
  +
<haskell>
  +
> unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
  +
> unsplit = arr . uncurry
  +
> -- arr (\op (x,y) -> x `op` y)
  +
</haskell>
  +
  +
(***) 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
  +
second pair).
  +
  +
<haskell>
  +
> -- f *** g = first f >>> second g
  +
</haskell>
  +
  +
(&&&) combines two arrows into a new arrow by running the two arrows on
  +
the same value:
  +
  +
<haskell>
  +
> -- f &&& g = split >>> first f >>> second g
  +
> -- split >>> f *** g
  +
</haskell>
  +
  +
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:
  +
  +
<haskell>
  +
> 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
  +
</haskell>
  +
  +
  +
  +
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:
  +
  +
<haskell>
  +
> f, g :: SimpleFunc Int Int
  +
> f = arr (`div` 2)
  +
> g = arr (\x -> x*3 + 1)
  +
</haskell>
  +
  +
We can combine these together using liftA2:
  +
  +
<haskell>
  +
> h = liftA2 (+) f g
  +
> hOutput = runF h 8
  +
</haskell>
  +
  +
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) ---> g -----> (unsplit (+)) ----> 29
  +
  +
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.
  +
  +
  +
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:
  +
  +
<haskell>
  +
> -- newtype Kleisli m a b = Kleisli {
  +
> -- runKleisli :: (a -> m b)
  +
> -- }
  +
</haskell>
  +
  +
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:
  +
  +
<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 = Kleisli (\x -> [x, -x])
  +
> double = arr (* 2)
  +
> h2 = liftA2' (+) plusminus double
  +
> h2Output = runKleisli h2 8
  +
</haskell>
  +
  +
Finally, here's a little teaser. There's an arrow function called
  +
returnA which returns an identity arrow. There's a 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:
  +
  +
<haskell>
  +
> 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
  +
</haskell>
  +
  +
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.

Revision as of 23:31, 19 November 2006

> module ArrowFun where
> import Control.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. It's 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. It's 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.

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)
>     (SimpleFunc f) >>> (SimpleFunc g) = SimpleFunc (g . f)

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 pair and one arrow on the second 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


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 = liftA2 (+) f g
> 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) ---> g -----> (unsplit (+)) ----> 29

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.


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:

> -- 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
> plusminus, double, h2 :: Kleisli [] Int Int
> plusminus = Kleisli (\x -> [x, -x])
> double = arr (* 2)
> h2 = liftA2' (+) plusminus double 
> h2Output = runKleisli h2 8

Finally, here's a little teaser. There's an arrow function called returnA which returns an identity arrow. There's a 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 = 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.