Question

Arrows seem to be gaining popularity in the Haskell community, but it seems to me like Monads are more powerful. What is gained by using Arrows? Why can't Monads be used instead?

Was it helpful?

Solution 2

I've always found it difficult to think of the issue in these terms: what is gained by using arrows. As other commenters have mentioned, every monad can trivially be turned into an arrow. So a monad can do all the arrow-y things. However, we can make Arrows that are not monads. That is to say, we can make types that can do these arrow-y things without making them support monadic binding. It might not seem like the case, but the monadic bind function is actually a pretty restrictive (hence powerful) operation that disqualifies many types.

See, to support bind, you have to be able to assert that that regardless of the input type, what's going to come out is going to be wrapped in the monad.

(>>=) :: forall a b. m a -> (a -> m b) -> m b

But, how would we define bind for a type like data Foo a = F Bool a Surely, we could combine one Foo's a with another's but how would we combine the Bools. Imagine that the Bool marked, say, whether or not the value of the other parameter had changed. If I have a = Foo False whatever and I bind it into a function, I have no idea whether or not that function is going to change whatever. I can't write a bind that correctly sets the Bool. This is often called the problem of static meta-information. I cannot inspect the function being bound into to determine whether or not it will alter whatever.

There are several other cases like this: types that represent mutating functions, parsers that can exit early, etc. But the basic idea is this: monads set a high bar that not all types can clear. Arrows allow you to compose types (that may or may not be able to support this high, binding standard) in powerful ways without having to satisfy bind. Of course, you do lose some of the power of monads.

Moral of the story: there's nothing an arrow can do that monad cannot, because a monad can always be made into an arrow. However, sometimes you can't make your types into monads but you still want to allow them to have most of the compositional flexibility and power of monads.

Many of these ideas were inspired by the superb Understanding Haskell Arrows (backup)

OTHER TIPS

Every monad gives rise to an arrow

newtype Kleisli m a b = Kleisli (a -> m b)
instance Monad m => Category (Kleisli m) where
   id = Kleisli return
   (Kleisli f) . (Kleisli g) = Kleisli (\x -> (g x) >>= f)
instance Monad m => Arrow (Kleisli m) where
   arr f = Kleisli (return . f)
   first (Kleisli f) = Kleisli (\(a,b) -> (f a) >>= \fa -> return (fa,b))

But, there are arrows which are not monads. Thus, there are arrows which do things that you can't do with monads. A good example is the arrow transformer to add some static information

data StaticT m c a b = StaticT m (c a b)
instance (Category c, Monoid m) => Category (StaticT m c) where
   id = StaticT mempty id
   (StaticT m1 f) . (StaticT m2 g) = StaticT (m1 <> m2) (f . g)
instance (Arrow c, Monoid m) => Arrow (StaticT m c) where
   arr f = StaticT mempty (arr f)
   first (StaticT m f) = StaticT m (first f)

this arrow tranformer is usefull because it can be used to keep track of static properties of a program. For example, you can use this to instrument your API to statically measure how many calls you are making.

Well, I'm going to cheat slightly here by changing the question from Arrow to Applicative. A lot of the same motives apply, and I know applicatives better than arrows. (And in fact, every Arrow is also an Applicative but not vice-versa, so I'm just taking it down a bit further down the slope to Functor.)

Just like every Monad is an Arrow, every Monad is also an Applicative. There are Applicatives that are not Monads (e.g., ZipList), so that's one possible answer.

But assume we're dealing with a type that admits of a Monad instance as well as an Applicative. Why might we sometime use the Applicative instance instead of Monad? Because Applicative is less powerful, and that comes with benefits:

  1. There are things that we know that the Monad can do which the Applicative cannot. For example, if we use the Applicative instance of IO to assemble a compound action from simpler ones, none of the actions we compose may use the results of any of the others. All that applicative IO can do is execute the component actions and combine their results with pure functions.
  2. Applicative types can be written so that we can do powerful static analysis of the actions before executing them. So you can write a program that inspects an Applicative action before executing it, figures out what it's going to do, and uses that to improve performance, tell the user what's going to be done, etc.

As an example of the first, I've been working on designing a kind of OLAP calculation language using Applicatives. The type admits of a Monad instance, but I've deliberately avoided having that, because I want the queries to be less powerful than what Monad would allow. Applicative means that each calculation will bottom out to a predictable number of queries.

As an example of the latter, I'll use a toy example from my still-under-development operational Applicative library. If you write the Reader monad as an operational Applicative program instead, you can examine the resulting Readers to count how many times they use the ask operation:

{-# LANGUAGE GADTs, RankNTypes, ScopedTypeVariables #-}

import Control.Applicative.Operational

-- | A 'Reader' is an 'Applicative' program that uses the 'ReaderI' 
-- instruction set.
type Reader r a = ProgramAp (ReaderI r) a

-- | The only 'Reader' instruction is 'Ask', which requires both the
-- environment and result type to be @r@.
data ReaderI r a where
    Ask :: ReaderI r r

ask :: Reader r r
ask = singleton Ask

-- | We run a 'Reader' by translating each instruction in the instruction set
-- into an @r -> a@ function.  In the case of 'Ask' the translation is 'id'.
runReader :: forall r a. Reader r a -> r -> a
runReader = interpretAp evalI
    where evalI :: forall x. ReaderI r x -> r -> x
          evalI Ask = id

-- | Count how many times a 'Reader' uses the 'Ask' instruction.  The 'viewAp'
-- function translates a 'ProgramAp' into a syntax tree that we can inspect.
countAsk :: forall r a. Reader r a -> Int
countAsk = count . viewAp
    where count :: forall x. ProgramViewAp (ReaderI r) x -> Int
          -- Pure :: a -> ProgamViewAp instruction a
          count (Pure _) = 0
          -- (:<**>) :: instruction a 
          --         -> ProgramViewAp instruction (a -> b)
          --         -> ProgramViewAp instruction b
          count (Ask :<**> k) = succ (count k)

As best as I understand, you can't write countAsk if you implement Reader as a monad. (My understanding comes from asking right here in Stack Overflow, I'll add.)

This same motive is actually one of the ideas behind Arrows. One of the big motivating examples for Arrow was a parser combinator design that uses "static information" to get better performance than monadic parsers. What they mean by "static information" is more or less the same as in my Reader example: it's possible to write an Arrow instance where the parsers can be inspected very much like my Readers can. Then the parsing library can, before executing a parser, inspect it to see if it can predict ahead of time that it will fail, and skip it in that case.

In one of the direct comments to your question, jberryman mentions that arrows may in fact be losing popularity. I'd add that as I see it, Applicative is what arrows are losing popularity to.


References:

The question isn't quite right. It's like asking why would you eat oranges instead of apples, since apples seem more nutritious all around.

Arrows, like monads, are a way of expressing computations, but they have to obey a different set of laws. In particular, the laws tend to make arrows nicer to use when you have function-like things.

The Haskell Wiki lists a few introductions to arrows. In particular, the Wikibook is a nice high level introduction, and the tutorial by John Hughes is a good overview of the various kinds of arrows.

For a real world example, compare this tutorial which uses Hakyll 3's arrow-based interface, with roughly the same thing in Hakyll 4's monad-based interface.

I always found one of the really practical use cases of arrows to be stream programming.

Look at this:

data Stream a = Stream a (Stream a)
data SF a b = SF (a -> (b, SF a b))

SF a b is a synchronous stream function. You can define a function from it that transforms Stream a into Stream b that never hangs and always outputs one b for one a:

(<<$>>) :: SF a b -> Stream a -> Stream b
SF f <<$>> Stream a as = let (b, sf') = f a
                         in  Stream b $ sf' <<$>> as

There is an Arrow instance for SF. In particular, you can compose SFs:

(>>>) :: SF a b -> SF b c -> SF a c

Now try to do this in monads. It doesn't work well. You might say that Stream a == Reader Nat a and thus it's a monad, but the monad instance is very inefficient. Imagine the type of join:

join :: Stream (Stream a) -> Stream a

You have to extract the diagonal from a stream of streams. This means O(n) complexity for the nth element, but using the Arrow instance for SFs gives you O(1) in principle! (And also deals with time and space leaks.)

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top