Proper Treatment 正當作法/ blog/ posts/ From walking to zipping, Part 1: Moving right
標籤 Tags:
2008-08-17 19:19

New York subway track map, detail of 47th-63rd Street

In a series of posts, Oleg and I will continue his earlier work on the generic zipper. We will use delimited continuations to convert any monadic traversal into a zipper that can traverse a complex data structure—up and down, left and right—and update it purely functionally. We will use the programming language Haskell: every post will be a literate program that you can run as is. For example, you can download this post as a program.

{-# OPTIONS -W -fglasgow-exts #-}
module WalkZip1 where
import Control.Monad (liftM)
import Control.Monad.Trans (MonadTrans(lift))
import Control.Monad.Writer (WriterT(runWriterT), tell)
import Data.Generics (Typeable, Data, gmapM, mkM)
import Data.Monoid (Any(Any))
import Data.Maybe (isJust, fromMaybe)

Our running example will be a familiar data type, that of untyped λ-terms.

data Term = V String | L String Term | A Term Term
    deriving (Eq, Read, Show, Typeable, Data)

This data type has a familiar inhabitant, the infinite loop (λx.xx)(λx.xx).

term :: Term                                     
term = A t t where t = L "x" (A (V "x") (V "x"))

A monadic traversal, or a walk for short, is a way to enumerate parts of a value. To a first approximation, if part and whole are two types, then a function of the type

type Walk part whole = forall m. (Monad m)
  => (part -> m part) -> whole -> m whole

is a way to enumerate parts (of type part) of a value (of type whole). Such a function takes two arguments: a visitor (a callback function of type part -> m part, where m is any monad) and the value whose parts to enumerate (of type whole). The function produces a monadic action comprised of visiting each part of the given value. Each visit to a part yields a new, updated part; the resulting monadic action yields a new, updated whole. For example, the Prelude function

mapM :: (Monad m) => (a -> m b) -> [a] -> m [b]

is a walk because it has the type Walk a [a]. It enumerates the elements of a list as its parts. We depict such a walk as follows, moving across a list from left to right.

picture-000001g.png

For that matter, the identity function

id :: a -> a

is also a walk because it has the type Walk a a. It enumerates a value itself as its only part. We depict such a trivial walk as follows.

picture-000002g.png

The actual type of walks is a bit more complex than this approximation, for three reasons. First, a walk may proceed in multiple directions from the same part, and we want to let the visitor decide where to go next. So the visitor should yield not just a new part but also an outgoing direction, of type to.

type Walk to part whole = forall m. (Monad m)
  => (part -> m (part, to)) -> whole -> m whole

To express the simplest case where only one outgoing direction is available, we define a singleton type After. We also define a type class To for a default outgoing direction after.

data After = After deriving (Eq, Ord, Read, Show)
class (Eq to) => To to where after :: to
instance To After where after = After

Second, a walk may arrive from multiple directions at the same part, and we want to let the visitor know whence. So the visitor should be passed not just an old part but also an incoming direction, of type from.

type Walk from to part whole = forall m. (Monad m)
  => (from -> part -> m (part, to)) -> whole -> m whole

We treat outgoing and incoming directions separately. To express the simplest case where only one incoming direction is available, we define a singleton type Before. We also define a type class From for a default incoming direction before.

data Before = Before deriving (Eq, Ord, Read, Show)
class (Eq from) => From from where before :: from
instance From Before where before = Before

The final complication is that, to preserve sharing and save memory, we want to avoid copying values, so we want to distinguish between changed and unchanged values. Thus, the visitor should yield not a part but a Maybe part, and the traversal should yield not a whole but a Maybe whole. The result Nothing signals no change.

type Walk from to part whole = forall m. (Monad m)
  => (from -> part -> m (Maybe part, to)) -> whole -> m (Maybe whole)

The definition above is final. Instead of id, the trivial, one-stop walk from an incoming direction from is now defined by

stop :: from -> Walk from After a a
stop from visit = liftM fst . visit from

To test the definitions so far and engender a sense of achievement, let us write a visitor that simply prints out the visited part and continues. To describe what it means to continue, we define a type class Next.

class (From from, To to, Show from, Read to)
  => Next from to where
  next :: from -> to

instance Next Before After where
  next Before = After

To exalt the beauty of each visited part, our tourist operates in the IO monad.

tourist :: (Next from to, Show part)
  => from -> part -> IO (Maybe part, to)
tourist from part = do
  putStrLn (show from ++ ": " ++ show part)
  return (Nothing, next from)

Look! After paying an exorbitant admission fee, you can see an entire term all at once from the observation deck.

*WalkZip1> stop Before tourist term
Before: A (L "x" (A (V "x") (V "x"))) (L "x" (A (V "x") (V "x")))
Nothing

We can also define a more hands-on visitor.

tourist' :: (Next from to)
  => from -> Term -> IO (Maybe Term, to)
tourist' from part = do
  putStrLn (show from ++ ": " ++ show part)
  return (Just (V "poof"), next from)

This visitor just can’t help but wonder what that button over there is for.

*WalkZip1> stop Before tourist' term
Before: A (L "x" (A (V "x") (V "x"))) (L "x" (A (V "x") (V "x")))
Just (V "poof")

To finish off this post, let us define a less trivial walk: given a data value of type b, we can visit each of its components of type a. The code below performs the actual traversal using gmapM and mkM from the Scrap Your Boilerplate library. The rest of the code looks messy, but it’s just using the writer monad transformer (runWriterT, lift, tell) over the logical-or monoid (Any) to remember whether any part changed (dirty). What’s more interesting is that gwalk defined below is a walk transformer: it maps one walk (such as stop Before) to another.

gwalk :: (Typeable a, Data b)
  => Walk from to part a -> Walk from to part b
gwalk walk visit a = do
  (a', Any dirty) <- runWriterT (gmapM (mkM f) a)
  return (scavenge dirty a')
  where f part = do
          part' <- lift (walk visit part)
          tell (Any (isJust part'))
          return (fromMaybe part part')

The helper function scavenge throws away a new whole if no part changed.

scavenge :: Bool -> a -> Maybe a
scavenge True a = Just a
scavenge False _ = Nothing

We can now traverse the immediate subterms of a term and change them.

*WalkZip1> gwalk (stop Before) tourist' term
Before: L "x" (A (V "x") (V "x"))
Before: L "x" (A (V "x") (V "x"))
Just (A (V "poof") (V "poof"))

As depicted in the pictures above, so far we can only move right. The next post will show how to move down and up. We will then turn (from) walks to zippers.