Arrows

Let's find our way towards arrows from the perspective of monads. Consider the following IO code:

import System.IO
main = do 
main = liftM (length . words)
                   (readFile "jabberwocky.txt" )
            >>= print
-- regular functions: length, words
-- Monadic functions: readFile, print

We use liftM to lift the composed function length . words into the monadic function readFile and then feed the result to another monadic function, print.

We can compose the regular functions with (.), but we know well that we cannot do the following:

  print . length . words . readFile "jabberwocky.txt"
  -- INVALID - types don't align

Let's make the preceding code possible!

Note

The following code is based on a combination of Programming with Arrows by John Hughes, and a blog post by John Wiegley at http://www.newartisans.com/2012/10/arrows-are-simpler-than-they-appear/.

The crux of our approach will be to create a "meta type" to represent monadic IO functions and then define composition for that type:

  data IOF a b = IOF {runIOF :: a -> IO b}

IOF wraps a function (a -> IO b) and places the input and output types a and b on an equal footing, while also hiding the IO Monad. Next, we define our own composition operator:

  (<<<<) :: IOF a b -> IOF c a -> IOF c b
  (IOF f) <<<< (IOF g) = IOF $ f <=< g

This function takes two IO functions, composes them, and wraps the resulting IO function.

Finally we need a function to lift a Monadic IO function into an IOF type:

  lift' :: (a -> b) -> IOF a b
  lift' f = IOF $ return . f -- uses IO Monad's return

Now we can compose regular and IO functions:

main = do
  let f =  IOF print <<<< lift' length <<<< 
           lift' words <<<< IOF readFile
  runIOF f "jabberwocky.txt"
  return ()

By doing this, we have started to reinvent Arrows. Let's do the same as we just did, but this time using the arrow type-class.

Implementing an Arrow

To write our first arrow, we'll need the IOF type from the previous example. This time we call our meta type for IO functions IOArrow:

  data IOArrow a b = IOArrow {runIOArrow :: a -> IO b}

To make IOArrow a true Arrow, we need to implement Category and Arrow. Category describes function composition (.).

instance Category IOArrow where
  id = IOArrow return
  -- (.) = (<<<<)
  IOArrow f . IOArrow g = IOArrow $ f <=< g

instance Arrow IOArrow where
  -- arr = lift'
  arr f = IOArrow $ return . f 
  first (IOArrow f) = IOArrow $ (a, c) -> do
    x <- f a
    return (x, c)

The arr function is just lift' from earlier (using IOArrow instead of IOF). Recall that return lifts a value into a Monad and pure lifts a value into an Applicative. The arr function is to Arrow what return and pure are to Monad and Applicative, respectively.

Before we delve into the meaning of the first function and the other key Arrow operators, let's use our IOArrow function:

import Prelude hiding ((.), id)
import Control.Category
import Control.Applicative
import Control.Arrow
import Control.Monad
import System.IO

main = do
 let f = IOArrow print . 
           arr length . 
           arr words . 
           IOArrow readFile
  -- vs print . length . words . readFile
  runIOArrow f "jabberwocky.txt"

Arrow operators

By defining arr, first, and (.) on the Category instance, we get many other operators for free. For example, the (<<<) operator defines Arrow composition. It is another name for the (.) composition function that we defined in the arrow's Category instance:

  (<<<) :: Category cat => cat b c -> cat a b -> cat a c

Instead of using (.), we could have composed our arrows with the (<<<) operator:

main = do
 let f = (IOArrow print) <<< (arr length) <<< 
           (arr words) <<< (IOArrow readFile)
  runIOArrow f "jabberwocky.txt"

The (>>>) operator is simply composition, reversed:

  (>>>) = flip (.)

For example:

main = do
let f = (IOArrow readFile) >>> 
          (arr words) >>> 
          (arr length) >>> 
          (IOArrow print)
  runIOArrow f "jabberwocky.txt"

To understand the first operator, let's tweak our arrow pipeline:

main = do
 let f = (IOArrow readFile) >>> 
           (arr words) >>>
           (arr (x -> (x,x))) >>> -– split stream in 2
           (arr length) >>> 
           (IOArrow print)
  runIOArrow f "jabberwocky.txt"
  – INVALID code  

After computing (arr words), we split the result into a 2-tuple, with both parts containing the words in the file. This won't work anymore because (arr length) expects to be fed a single value and will now be given a tuple instead.

But we can tell the (arr length) arrow to only act on the first element in the tuple:

main = do
  let f = (IOArrow readFile) >>> (arr words) >>>
      (arr (x -> (x,x))) >>>  -– split stream in 2
      (first (arr length)) >>> -- act on first tuple value
      (IOArrow print)
  runIOArrow f "jabberwocky.txt"

Now our final result is a tuple, the first part containing the word count, and the second the original words, which remained untouched. In this way, we can create "side channels" in our pipelines, which enable us to share state across arrows in a pipeline. Similarly, the second operator works on the second part of the arrow's input:

main = do
  let f = (IOArrow readFile)   >>> (arr words) >>>
      (arr (x -> (x,x)))  >>> -– split stream in 2
      (first (arr length)) >>> –- act on fst tuple value
      (second (arr head))  >>> –- act on snd tuple value
      (IOArrow print)
  runIOArrow f "jabberwocky.txt"

Now we're doing two different arrow computations on the different branches. The final operator we'll look at is (***):

main = do
  let f = (IOArrow readFile) >>> (arr words) >>> 
      (arr (x -> (x,x))) >>>
      (arr length *** arr head) >>>   
      (IOArrow print)
  runIOArrow f "jabberwocky.txt"

This operator does what we did earlier with first and second: it enables us to compute on both the first and second tuple values.

The ability of arrows to take multiple inputs enables us to build intricate pipelines with branching and merging of stream values.

Kleisli Arrows and Monad Arrows

Our IOArrow type:

  data IOArrow a b = IOArrow {runIOArrow :: a -> IO b}

is unnecessary because there is already the Kleisli Arrow, which generalizes IOArrow to all Monad:

-– (already defined in Control.Arrow)
data Kleisli m a b = K {runKleisli :: a -> m b}
instance Monad m => Arrow (Kleisli m) where 
  arr f = K (x -> return (f x)) 
  K f >>> K g = K (x -> f x >>= g)

Thanks to Kleisli arrows, we could have just said this:

main = do
       let f = Kleisli print . arr length . 
               arr words . Kleisli readFile
       runKleisli f "jabberwocky.txt"
 

"This shows that arrows do indeed generalize monads; for every monad type, there is a corresponding arrow type. (Of course, it does not follow that every monadic program can be rewritten in terms of arr and >>>.)"

 
 --John Hughes, Generalising Monads to Arrows

All Monad have a corresponding Kleisli Arrow, but there are more instances of Arrow than of Monad. In the same way, there are more Applicative Functor than Arrow instances, and more Functor than Applicative Functor.

 

NOTE: "idiom" means "applicative functor"

"idioms embed into arrows and arrows embed into monads"

"We have characterized idioms, monads and arrows as variations on a single calculus, establishing the relative order of strength as idiom, arrow, monad..."

"Idioms are oblivious, Arrows are meticulous, Monads are promiscuous"

 
 --Sam Lindley, Philip Wadler, and Jeremy Yallop
Kleisli Arrows and Monad Arrows

Despite Arrow being more generic than Monad, we left this pattern until last because it is easier to understand from the perspective of Monad. Also, Monad has been around in Haskell (early 1990s) for much longer than Arrow (early 2000s).

We can now add arrows to the list of ways of doing "effectful programming" (IO). Moreover, in the same way that we could compose different monads together into monad stacks, we can combine different arrows into stacks using transformer arrows.

Returning to the abstraction hierarchy, as the types get more powerful (from Functor to Monad) the means of composition becomes poorer!

Why Arrows?

In 1996, Swierstra and Duponcheel published an optimization to deal with the space leaks prevalent in monadic parsers. Their solution avoided the use of monads.

(S.D. Swierstra, L. Duponcheel. Deterministic, error-correcting combinator parsers, Advanced Functional Programming, Lecture Notes in Computer Science Tutorial, Vol. 1129, Springer, Berlin, 1996, pages 184–207).

John Hughes generalized their ideas, and in the process, generalized Monad to Arrow. Hughes published the first Arrow paper in 2000. It took a few more years for Arrow to become established in Haskell.

 

"...When libraries emerge which cannot, for fundamental reasons, use the monad interface… Swierstra and Duponcheel have developed a very interesting library for parsing LL-1 grammars … Yet Swierstra and Duponcheel's optimization is incompatible with the monad interface. We believe that their library is not just an isolated example, but demonstrates a generally useful paradigm for combinator design that falls outside the world of monads."

"While arrows are a little less convenient to use than monads, they have significantly wider applicability. They can therefore be used to bring the benefits of monad-like programming to a much wider class of applications."

 
 --John Hughes, Generalising Monads to Arrows

Arrows have been useful in parsers, streaming applications, and user interfaces, and in recent years they have featured prominently as an approach to functional reactive programming. (See https://wiki.haskell.org/Yampa, https://wiki.haskell.org/Netwire).

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset