Question

I reinvented some sort of 'state arrow':

import Prelude hiding (id, (.))
import Control.Monad.State
import Control.Arrow
import Control.Category

data StateA s a b = StateA {runStateA :: s -> a -> (b, s)}

instance Category (StateA s) where
  id = StateA (\s a -> (a, s))

  (StateA f) . (StateA g) = StateA $ \s x -> let (b, s') = g s x in f s' b

instance Arrow (StateA s) where
  arr f = StateA $ \s a -> (f a, s)

  first (StateA f) = StateA $ \s (b, d) -> let (c, s') = f s b in ((c, d), s)

put' :: s -> StateA s b ()
put' s = StateA $ \_ _ -> ((), s)

get' :: StateA s b s
get' = StateA $ \s _ -> (s, s)

merge :: (s -> s -> s) -> StateA s a b -> StateA s a c -> StateA s a (b, c)
merge f (StateA a) (StateA b) = StateA $ \s x ->
  let (ra, sa) = a s x
      (rb, sb) = b s x 
  in ((ra, rb), f sa sb)


 test = (flip runStateA) s bar 
   where bar = ((put' 7) >>> get') &&& get'

It seems like this definition works as I desired: at least test 3 5 yields

((7,3), 3)

Note, that this behavior is intentionally unlike ordinary State monad wrapped into arrow like this:

liftKC = Kleisli . const

putM :: a -> Kleisli (State a) b ()
putM = liftKC . put

getM :: Kleisli (State a) b a
getM = liftKC get

foo :: (Num a) => Kleisli (State a) a (a, a)
foo = (putM 7 >>> getM) &&& getM

testKleisli a b = (flip runState) a $
                  (flip runKleisli) b foo

as testKleisli 3 5 returns

((7, 7), 7).

The point is that one can manipulate state in some 'parallel branches of computation' separately, and then merge it somehow.

I am not familiar with arrow notation, but it is inconvenient here: it looks like it desugars creating new 'branch' for every computation. Is it possible to rewrite 'bar' function (from the where clause of test) using arrow notation?

Was it helpful?

Solution

Let's draw a picture of

bar = ((put' 7) >>> get') &&& get'

to give us an idea of how to write it in arrow notation.

put

Just as with monadic do notation, proc notation introduces named variables, replacing combinators such as >>= with explicit passing of values.

Anyway, we can see that we need to feed the input, x, to the two sides, giving:

bar' = proc x -> do
        wasput <- put' 7 >>> get' -< x
        justgot <- get' -< x
        returnA -< (wasput,justgot)

or if we want everything to go from right to left, equivalently

bar'' = proc x -> do
        wasput <- get' <<< put' 7 -< x
        justgot <- get' -< x
        returnA -< (wasput,justgot)

Testing

I'll refactor test for multiple testing:

test s b = (flip runStateA) s b

So we get

ghci> test bar 3 5
((7,3),3)
ghci> test bar' 3 5
((7,3),3)
ghci> test bar'' 3 5
((7,3),3)

Can we write it without >>>?

We might be tempted to factor out the (>>>):

bar''' = proc x -> do
        put7 <- put' 7 -< x
        wasput <- get' -< put7
        justgot <- get' -< x
        returnA -< (wasput,justgot)

oops, no:

ghci> test bar''' 3 5
((3,3),3)

As you pointed out, your state is localised, and the put' 7 doesn't thread through to either get', so we haven't managed to get rid of the >>> or <<< combinator.

I can't help feeling that's breaking some Arrow law or other. Hmmm...

Broken Arrow law

It took me a while to track down, but after a great deal of hand desugaring and frowning at diagrams, I've found an arrow law staring me in the face that your instance breaks:

first (f >>> g) = first f >>> first g

If we define

dup :: Arrow a => a t (t, t)
dup = arr (\x -> (x,x))    

we get

ghci> test (dup >>> (first (put' 7    >>>     get'))) 1 3
((7,3),1)
ghci> test (dup >>> (first (put' 7) >>> first get')) 1 3
((1,3),1)

This is because the localised state in put' 7 in the second example doesn't make it into the second first, if you can follow all those firsts and seconds!

Conclusion:

You found that arrow notation is less useful for your arrow instance because it assumes it's OK to transform via laws that don't hold.

Sadly, whist very interesting indeed, and extraordinarily diverting, it's not a true Arrow.

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