tags:

views:

269

answers:

1

I wrote some toy code to play with the concept of Arrows. I wanted to see if I could write an Arrow which encoded the concept of a stateful function - giving a different value after different calls.

{-# LANGUAGE Arrows#-}
module StatefulFunc where

import Control.Category
import Control.Arrow

newtype StatefulFunc a b = SF { unSF :: a -> (StatefulFunc a b, b) }

idSF :: StatefulFunc a a
idSF = SF $ \a -> (idSF, a)

dotSF :: StatefulFunc b c -> StatefulFunc a b -> StatefulFunc a c
dotSF f g = SF $ \a -> 
    let (g', b) = unSF g a
        (f', c) = unSF f b
    in (dotSF f' g', c)

instance Category StatefulFunc where
  id = idSF
  (.) = dotSF

arrSF :: (a -> b) -> StatefulFunc a b
arrSF f = ret
  where ret = SF fun
        fun a = (ret, f a)

bothSF :: StatefulFunc a b -> StatefulFunc a' b' -> StatefulFunc (a, a') (b, b')
bothSF f g = SF $ \(a,a') ->
    let (f', b) = unSF f a
        (g', b') = unSF g a'
    in (bothSF f' g', (b, b'))

splitSF :: StatefulFunc a b -> StatefulFunc a b' -> StatefulFunc a (b, b')
splitSF f g = SF $ \a ->
    let (f', b) = unSF f a
        (g', b') = unSF g a
    in (splitSF f' g', (b, b'))

instance Arrow StatefulFunc where
  arr  = arrSF
  first = flip bothSF idSF
  second = bothSF idSF
  (***) = bothSF
  (&&&) = splitSF

eitherSF :: StatefulFunc a b -> StatefulFunc a' b' -> StatefulFunc (Either a a') (Either b b')
eitherSF f g = SF $ \e -> case e of
      Left a -> let (f', b) = unSF f a in (eitherSF f' g, Left b)
      Right a' -> let (g', b') = unSF g a' in (eitherSF f g', Right b')

mergeSF :: StatefulFunc a b -> StatefulFunc a' b -> StatefulFunc (Either a a') b
mergeSF f g = SF $ \e -> case e of 
      Left a -> let (f', b) = unSF f a in (mergeSF f' g, b)
      Right a' -> let (g', b) = unSF g a' in (mergeSF f g', b)

instance ArrowChoice StatefulFunc where
  left = flip eitherSF idSF
  right = eitherSF idSF
  (+++) = eitherSF
  (|||) = mergeSF

So after I went through the various type class definitions (not sure whether or how ArrowZero would work for this, so I skipped it), I defined some helper functions

evalSF :: (StatefulFunc a b) -> a -> b
evalSF f a = snd (unSF f a)

givenState :: s -> (s -> a -> (s, b)) -> StatefulFunc a b
givenState s f = SF $ \a -> let (s', b) = f s a in (givenState s' f, b)

And worked out an example of use

count :: StatefulFunc a Integer
count = givenState 1 $ \c _ -> (c+1, c)

countExample :: StatefulFunc a Integer
countExample = proc _ -> do
                  (count', one) <- count -< ()
                  (count'', two) <- count' -< ()
                  (count''', three) <- count'' -< ()
                  returnA -< three

However, when I try to compile countExample, I get "Not in scope" errors for count' and count'', which I suppose means that I need to go back to the tutorial and read up on what can be used when. I think what I'd really like anyway is something more like

countExample :: Integer
countExample =
  let (count', one) = unSF count ()
      (count'', two) = unSF count' ()
      (count''', three) = unSF count'' ()
  in three

But that's kind of awkward, and I was hoping for something a bit more natural.

Can anyone explain how I'm misunderstanding how Arrows work, and how they might be used? Is there fundamental philosophy to Arrows that I'm missing?

+9  A: 

Can anyone explain how I'm misunderstanding how Arrows work, and how they might be used? Is there fundamental philosophy to Arrows that I'm missing?

I get the impression that you're treating this Arrow like you would a Monad. I don't know if this counts as a "fundamental philosophy", but there's a significant difference between the two, despite how often they overlap. In a sense the key thing that defines a Monad is the join function; how to collapse a nested structure into a single layer. They're useful because of what join allows: you can create new monadic layers in a recursive function, alter the Functor structure based on its contents, and so on. But this isn't about Monads, so we'll leave it at that.

The essence of an Arrow, on the other hand, is a generalized version of a function. The Category type class defines generalized versions of function composition and the identity function, while the Arrow type class defines how to lift a regular function to an Arrow and how to work with Arrows that take multiple arguments (in the form of tuples--Arrows can't necessarily be curried!).

When combining Arrows in a basic manner, as in your first countExample function, all you're really doing is something like elaborate function composition. Look back at your definition of (.)--you're taking two stateful functions and connecting them into a single stateful function, with the state change behavior handled automatically.

So, the main problem with your countExample is that it even mentions count' and such. That's all done behind the scenes, just like you don't need to explicitly pass the state parameter along when using do notation in the State monad.

Now, because the proc notation just lets you construct large composite Arrows, to actually use your stateful function you'll need to work outside the Arrow syntax, just like you need runState or such in order to actually run a computation in the State monad. Your second countExample is along these lines, but too specialized. In the general case, your stateful function maps a stream of inputs to a stream of outputs, making it a finite state transducer, so runStatefulFunction would probably take a lazy list of input values and convert them into a lazy list of output values using a right fold with unSF to feed each to the transducer in turn.

If you'd like to see an example, the arrows package includes an Arrow transformer Automaton that defines something almost identical to your StatefulFunction, except with an arbitrary Arrow in place of the plain function you've used.


Oh, and to briefly revisit the relationship between Arrows and Monads:

Plain Arrows are only "first-order" function-like things. As I said before, they can't always be curried, and likewise they can't always be "applied" in the same sense that the ($) function applies functions. If you do actually want higher-order Arrows, the type class ArrowApply defines an application Arrow. This adds a great deal of power to an Arrow and, among other things, allows the same "collapse nested structure" feature that Monad provides, making it possible to define generally a Monad instance for any ArrowApply instance.

In the other direction, because Monads allow combining functions that create new monadic structure, for any Monad m you can talk about a "Kleisli arrow", which is a function of type a -> m b. Kleisli arrows for a Monad can be given an Arrow instance in a pretty obvious way.

Other than ArrowApply and Kleisli arrows, there's no particularly interesting relationship between the type classes.

camccann
awesome, thank you, exactly what I was looking for.
rampion