Saturday 31 January 2015

Life by Comonads: 3

Conways game of life is a cellular automata - an environment with a synchronous update scheme. The status of the cell in the next time-step is decided by its current status and its environment. This makes it a perfect candidate for some comonadic power play. The rules are quite simple and you can find them online.
A cells status is simply that of dead or alive for which we will use booleans.
Deciding whether a cell is alive or dead in the next iteration will be a function of the form
decide :: Conway -> Bool 
In order to view the environment we need to be able to step up and down as well as the left and right we wrote previously.
This is where duplicate of the list zipper comes into play. A duplicated zipper will represent the environment.
type Conway = LZip (LZip Bool)
shiftU :: LZip (LZip Bool) -> LZip (LZip Bool)
shiftU = fmap shiftR
shiftD :: LZip (LZip Bool) -> LZip (LZip Bool)
shiftD = fmap shiftL

We can finally decide whether or not a cell stays alive for the next iteration by viewing the environment - We obtain a list of the status of the surrounding cells in 'doa', then count the ones alive and finally use that to determine its status according to the rules.

decide :: Conway -> Bool 
decide z | count < 2 = False 
         | count == 3 = True 
         | alive && count == 2 = True 
         | otherwise = False 
         where 
           alive = extract . extract $ z 
           count = if alive then count' - 1 else count'
           count' = foldl (\s b -> if b then (s+1) else s) 0 doa 
           doa = g <$> [shiftL, shiftR, id] <*> [shiftL, shiftR, id] 
           g s s' = case s' z of 
                        LZip _ z' _ -> extract (s z') 

The last piece is the decideLZip function. In order to extend the current state to get the new one we need a function that decides a column of the board for the given focus. 'decideColumn' must traverse the board vertically in order to decide the status of each of the cells in the column.

decideColumn :: Conway -> LZip Bool
decideColumn v = LZip l c r
  where 
    c = decide v
    l = fmap decide (tail $ iterate shiftD v)
    r = fmap decide (tail $ iterate shiftU v)

Finally our step function simply extends the current state using decideColumn.
step :: Conway -> Conway
step = extend decideColumn

We can then step the state as many times as we want by iteratively extending it with the step function.
The board at the nth time step would be (step^n) $ initial, according to the redefinition of (^) as defined below. We can pretty print the board in a certain neighborhood:
visual = (\c -> if c then 'o' else ' ')
pretty :: Int -> Conway -> [String]
pretty n c@(LZip l v r) = (map . map) visual b
    where
      b :: [[Bool]]
      b = crop2D n c
pp :: Int -> Conway -> IO ()
pp i c = mapM_ putStrLn (pretty i c)
_ ^ 0 = id
f ^ n = f . (f ^ (n-1))
And voila, thats the conway game of life modelled beautifully using commands.
A sample starting state - The Blinker - is presented below.

initial :: Conway
initial = LZip (repeat allFalses) blinker (repeat allFalses)
    where 
      allFalses = LZip (repeat False) False (repeat False)
      blinker = LZip (True:repeat False) True (True:repeat False)

Life by Comonads: 2

{-# LANGUAGE DeriveFunctor #-}

In the last post we developed an intuition about comonads which we will now put to use.
So comonads allow us calculate values that are the focus within some context.
The extend function allows us to uniformly apply this computation across all values in the comonad as though they had the focus.

One example of a context dependent calculation is Pascals triangle. A value at the next level is the sum of itself and an adjacent value.

List Zipper


Before we go any further we're going to develop another interesting comonadic structure, a zipper over a stream. The zipper has as its focus some element and extends infintely in both directions. Thus our zipper consists of a stream that extends infinitely in the left direction, the current focus and a list that extends infinitely in the right direction.


import Control.Comonad
data LZip a = LZip [a] a [a] deriving (Eq, Ord, Show, Functor)


We want to be able to move around in the structure; we develop two utility functions,

shiftL :: LZip a -> LZip a
shiftL (LZip l a r) = LZip (tail l) (head l) (a:r)

This moves the focus to the left pushing the current value to the left.

shiftR :: LZip a -> LZip a
shiftR (LZip l a r) = LZip (a:l) (head r) (tail r)

This moves the focus to the right pushing the current value to the left.

So this zipper has an element it focuses on, and has a context (its position in the stream).
The comonadic instance is:

instance Comonad LZip where
   extract (LZip _ a _) = a

Extract gives us the current focus in the zipper.

Duplicate has to give us a LZip (LZip a). That structure gives us a stream of parallel streams.
After duplicate the structure that we obtain is such that, the stream that is focused on as we move to the right is the original stream shifted to the right and vice versa for the left.

   duplicate z@(LZip l v r)
       = LZip left z right
         where
           left = tail $ iterate shiftL z
           right = tail $ iterate shiftR z


Pascals Triangle


If we represent one layer of Pascals triangle as an infinite stream focused on some relevant location, the step function to compute the value at the cell for next layer in the triangle is the sum of itself and its left/right neighbor:

addLeft :: LZip Int -> Int
addLeft z = extract z + extract (shiftL z)

Now the triangle is a 2D object which we can represent by parallel layers. Duplicate allows us to create these parallel layers. Now the step function to create the next layer in the triangle is simply:

nextLayer :: LZip (LZip Int) -> LZip Int
nextLayer = extend addLeft . extract . shiftL

Finally, the triangle itself consists of the initial value to kick start the process while the successive layers are the result of extending using 'nextLayer'.

pTri :: LZip (LZip Int)
pTri = LZip (repeat all0s) gen right
    where 
      (_:right) = map nextLayer $ iterate shiftR pTri
      all0s = LZip (repeat 0) 0 (1:repeat 0)
      gen = LZip (repeat 0) 1 (repeat 0)

And that's all there is to it. The next we would want to do is crop an area of interest. For a one dimensional zipper we have:

crop :: Int -> LZip a -> [a]
crop n z = (reverse $ map extract left) ++ (focus:map extract right)
    where 
      left = take n (tail $ iterate shiftL z)
      right = take n (tail $ iterate shiftR z)
      focus = extract z


Extending this to the two dimensional case is simple, we crop along the second dimesion, and along each of the firsts thus generated:

crop2D :: Int -> LZip (LZip Int) -> [[Int]]
crop2D n = map (crop n) . crop n


And that's it, Pascals triangle using comonads. The takeaway is that comonads allow us to use a context around a value to determine a result as opposed to monads which focus on creating context from some values. 

Friday 30 January 2015

Life by Comonads: 1

Intro

Why did the chicken cross the Mobius Strip? 
 - To get to the same side


Prepping the Intuition


Comonads are the categorical duals are monads. So it pretty much means we have to reverse the notions that persist related to monads.

Well, from a computational perspective, monads allow us to:
  • Execute actions using  some input, producing an output wrapped in a context. Functions of the form a -> m b
  • Allow us to use the results of previous computations as inputs to further actions that produce some more context and subsequently resolve the nested contexts into a single context (>>=), in a sensible manner; for a sequence of actions the order in which we resolve the contexts is irrelevant a.k.a. the monad laws.

Thus in some sense the opposite of the above intuitions gives: 
  • Comonads allow us to consume values wrapped in a context producing some output, values for the form (w a -> b)
  • Duplicate a context and extract a value from the inner context such that using extract on the inner context yeilds the original comonadic value:   A function of the form = (w a -> b) -> w a -> w b
  • We invert the 'm' to get a 'w' for type-constructor variables


Comonad Instances


Looking at the source we see that (e,) and ((->) m) are instances of the Comonad class. 
Now that's the writer and the reader monads except the Monoid constraint is required of the 'reader' comonad.

Let's go ahead and implement them:
instance Comonad (e,) where
  extract (_, a) = a
  duplicate (e, a) = (e, (e, a))
  extend (e, a) f = (e, f (e, a))

The (e,) comonad carries around an e with it. When extracting a value we simply ignore the environment. 
Duplicate, duplicates the environment. But thats exactly what the reader monad does, but in a somewhat opposite sense. That oppositeness is clarified on reversing the arrows for the respective functions.
return' :: a -> r -> a
return' :: a -> r -> a
return' :: r -> a -> a
return' :: (r, a) -> a
extract :: (r, a) -> a

(>>=)' :: m a -> (a -> m b) -> m b
(>>=)' :: w b -> (w b -> a) -> w a
extend :: w b -> (w b -> a) -> w a

While this probably shouldn't be surprising, one has to admire the magnificent machinery of category theory. Something as innocent as looking the other way has divine repercussions. 

Armed with that knowledge we're going in to Monoid m => ((->) m), expecting a Writer monad like behavior. 

instance Monoid m => Comonad ((->) m) where
  extract f = f mempty
  duplicate m f = \w -> \w' -> f (w <> w')
  extend m f = \w -> f (\w' -> m (w <> w'))

Sure enough, we see the same sort've writing behavior but with more emphasis on viewing the result than accumulating. 

Conclusion


So that's pretty cool, reading and writing are duals of each other and in some sense opposite notions which is made formal by their representation as mathematical objects. I always find it fascinating to see mathematics - a pure and exact - describe something I thought was really vague, though granted in the projection we loose some nuances of the concepts.

So while that's helped my understanding of the duality between monads and commands, comonads haven't distinguished themselves apart from being interesting theoretical specimen. They simply appear to be the other side of the same strip. 

Next up, we move on to a real Life algorithm.