Difference between revisions of "Zipper monad"

From HaskellWiki
Jump to navigation Jump to search
m (Updating links to Zipper, according to its un-camelcase redirection)
(version 2)
Line 1: Line 1:
The TravelTree Monad is a monad proposed and designed by Paolo Martini (xerox), and coded by David House (davidhouse). It is based on the State monad and is used for navigating around data structures, using the concept of [[Zipper]].
+
The Travel Monad is a generic monad for navigating around arbitrary data structures. It supports movement, mutation and classification of nodes (is this node the top node or a child node?, etc). It was proposed and designed by Paolo Martini (xerox), and coded by David House (davidhouse). It's designed for use with [[Zipper|The Zipper]] but in fact there is no requirement to use such an idiom.
   
  +
At the moment there are two specific libraries that use the Travel monad: [[Zipper_monad/TravelTree|TravelTree]] for navigating around binary trees, and [[Zipper_monad/TravelBTree|TravelBTree]] for navigating around "B-Trees", trees where each node has an arbitrary number of branches.
As the only zipper currently available is for binary trees, this is what most of the article will be centred around.
 
   
 
== Definition ==
 
== Definition ==
 
<haskell>
 
<haskell>
newtype Travel t a = Travel { unT :: State t a }
+
data Loc c a = Loc { struct :: a,
  +
cxt :: c }
deriving (Functor, Monad, MonadState t)
 
  +
deriving (Show, Eq)
type TravelTree a = Travel (Loc a) (Tree a) -- for trees
 
</haskell>
 
 
Computations in <hask>TravelTree</hask> are stateful. <hask>Loc a</hask> and <hask>Tree a</hask> are defined as follows:
 
 
<haskell>
 
data Tree a = Leaf a | Branch (Tree a) (Tree a)
 
 
data Cxt a = Top
 
| L (Cxt a) (Tree a)
 
| R (Tree a) (Cxt a)
 
deriving (Show)
 
   
  +
newtype Travel loc a = Travel { unT :: State loc a }
type Loc a = (Tree a, Cxt a)
 
  +
deriving (Functor, Monad, MonadState loc, Eq)
 
</haskell>
 
</haskell>
   
  +
Computations in <hask>Travel</hask> are stateful. <hask>Loc c a</hask> is a type for storing the location within a structure. <hask>struct</hask> should be the substructure that the <hask>Loc</hask> is refering to, and <hask>cxt</hask> the "context" of the substructure; i.e. the rest of the structure. <hask>Loc</hask> is designed to hold a [[Zipper]] (although it doesn't have to; for example if you wanted to traverse a list it would probably be more natural to hold the entire structure and an index). Indeed, both of the libraries provided with the generic <hask>Travel</hask> monad use a zipper.
See [[Zipper]] for an explanation of the <hask>Cxt</hask> and <hask>Loc</hask> concepts.
 
   
 
== Functions ==
 
== Functions ==
=== Moving around ===
 
There are four main functions for stringing together <hask>TravelTree</hask> computations:
 
   
  +
=== Movement ===
<haskell>
 
  +
At the moment, movement is specific to the structure you are traversing and as such, the movement functions are provided by libraries implementing specific structures. Try the documentation for [[Zipper_monad/TravelTree|TravelTree]] (binary trees) or [[Zipper_monad/TravelBTree|TravelBTree]] (B-Trees; trees where each node has an arbitrary number of branches).
left, -- moves down a level, through the left branch
 
right, -- moves down a level, through the right branch
 
up, -- moves to the node's parent
 
top -- moves to the top node
 
:: TravelTree a
 
</haskell>
 
 
All four return the subtree at the new location.
 
   
 
=== Mutation ===
 
=== Mutation ===
There are also functions available for changing the tree:
+
There are three generic functions available for changing the structure:
   
 
<haskell>
 
<haskell>
getTree :: TravelTree a
+
getStruct :: Travel (Loc c a) a
putTree :: Tree a -> TravelTree a
+
putStruct :: a -> Travel (Loc c a) a
modifyTree :: (Tree a -> Tree a) -> TravelTree a
+
modifyStruct :: (a -> a) -> Travel (Loc c a) a
 
</haskell>
 
</haskell>
   
These are direct front-doors for State's <hask>get</hask>, <hask>put</hask> and <hask>modify</hask>, and all three return the subtree after any applicable modifications.
+
These are direct front-doors for State's <hask>get</hask>, <hask>put</hask> and <hask>modify</hask>, and all three return the substructure after any applicable modifications.
   
 
=== Exit points ===
 
=== Exit points ===
Line 54: Line 35:
   
 
<haskell>
 
<haskell>
traverse :: Tree a -> TravelTree a -> Tree a
+
traverse :: Loc c a -- starting location (initial state)
  +
-> Travel (Loc c a) a -- locational computation to use
  +
-> a -- resulting substructure
 
</haskell>
 
</haskell>
   
Again, this is just a front-door for <hask>evalState</hask>, with an initial state of <hask>(tt, Top)</hask> where <hask>tt</hask> is the <hask>TravelTree</hask> passed in.
+
Again, this is just a front-door for <hask>evalState</hask>. Note that you have to give a <hask>Loc</hask> as a starting state. Both the libraries provided supply a <hask>getTop</hask> function, which takes a tree and returns the <hask>Loc</hask> corresponding to the top of the tree. Thus a typical call to <hask>traverse</hask> might look like:
 
== Examples ==
 
The following examples use as the example tree:
 
   
 
<haskell>
 
<haskell>
t = Branch (Branch (Branch (Leaf 1) (Leaf 2))
+
let t = Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3))
  +
in (getTop t) `traverse` (left >> swap >> right)
(Leaf 3))
 
(Branch (Leaf 4)
 
(Leaf 5))
 
 
</haskell>
 
</haskell>
   
  +
== Examples ==
[[Image:Tree.png|frame|right|The example tree]]
 
 
=== A simple path ===
 
This is a very simple example showing how to use the movement functions:
 
<haskell>
 
leftLeftRight :: TravelTree a
 
leftLeftRight = do left
 
left
 
right
 
</haskell>
 
 
Result of evaluation:
 
 
*Tree> t `traverse` leftLeftRight
 
Leaf 2
 
 
=== Tree reverser ===
 
This is a more in-depth example showing <hask>getTree</hask> and <hask>putTree</hask>, but is still rather contrived as it's easily done without the zipper (the zipper-less version is shown below).
 
 
The algorithm ''reverses'' the tree, in the sense that at every branch, the two subtrees are swapped over.
 
 
<haskell>
 
revTree :: Tree a -> Tree a
 
revTree t = t `traverse` revTree' where
 
revTree' :: TravelTree a
 
revTree' = do t <- getTree
 
case t of
 
Branch _ _ -> do left
 
l' <- revTree'
 
up
 
right
 
r' <- revTree'
 
up
 
putTree $ Branch r' l'
 
Leaf x -> return $ Leaf x
 
 
-- without using the zipper:
 
revTreeZipless :: Tree a -> Tree a
 
revTreeZipless (Leaf x) = Leaf x
 
revTreeZipless (Branch xs ys) = Branch (revTreeZipless ys) (revTreeZipless xs)
 
</haskell>
 
 
Result of evaluation:
 
 
*Tree> revTree $ Branch (Leaf 1) (Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 4))
 
Branch (Branch (Leaf 4) (Branch (Leaf 3) (Leaf 2))) (Leaf 1)
 
 
==== Generalisation ====
 
Einar Karttunen (musasabi) suggested generalising this to a recursive tree combinator:
 
 
<haskell>
 
treeComb :: (a -> Tree a) -- what to put at leaves
 
-> (Tree a -> Tree a -> Tree a) -- what to put at branches
 
-> (Tree a -> Tree a) -- combinator function
 
treeComb leaf branch = \t -> t `traverse` treeComb' where
 
treeComb' = do t <- getTree
 
case t of
 
Branch _ _ -> do left
 
l' <- treeComb'
 
up
 
right
 
r' <- treeComb'
 
up
 
putTree $ branch l' r'
 
Leaf x -> return $ leaf x
 
</haskell>
 
 
<hask>revTree</hask> is then easy:
 
 
<haskell>
 
revTreeZipper :: Tree a -> Tree a
 
revTreeZipper = treeComb Leaf (flip Branch)
 
</haskell>
 
 
It turns out this is a fairly powerful combinator. As with <hask>revTree</hask>, it can change the structure of a tree. Here's another example which turns a tree into one where siblings are sorted, i.e. given a <hask>Branch l r</hask>, if <hask>l</hask> and <hask>r</hask> are leaves, then the value of <hask>l</hask> is less than or equal to that of <hask>r</hask>. Also, if one of <hask>l</hask> or <hask>r</hask> is a <hask>Branch</hask> and the other a <hask>Leaf</hask>, then <hask>l</hask> is the <hask>Leaf</hask> and <hask>r</hask> the <hask>Branch</hask>:
 
 
<haskell>
 
sortSiblings :: Ord a => Tree a -> Tree a
 
sortSiblings = treeComb Leaf minLeaves where
 
minLeaves l@(Branch _ _) r@(Leaf _ ) = Branch r l
 
minLeaves l@(Leaf _) r@(Branch _ _ ) = Branch l r
 
minLeaves l@(Branch _ _) r@(Branch _ _ ) = Branch l r
 
minLeaves l@(Leaf x) r@(Leaf y ) = Branch (Leaf $ min x y)
 
(Leaf $ max x y)
 
</haskell>
 
   
  +
<hask>Travel</hask> is too general to be used in itself, so there are examples given on the documentation pages for the libraries. Here are the links again:
Result of evaluation:
 
   
  +
* [[Zipper_monad/TravelTree|TravelTree]] for binary trees.
*Tree> sortSiblings t
 
  +
* [[Zipper_monad/TravelBTree|TravelBTree]] for B-Trees; trees where each node has an arbitrary number of branches.
Branch (Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2))) (Branch (Leaf 4) (Leaf 5))
 
   
 
== Code ==
 
== Code ==
   
Here's the Zipper Monad in full:
+
Here's the base Zipper monad in full ([http://haskell.org/sitewiki/images/3/36/Zipper.hs download]):
   
 
<haskell>
 
<haskell>
  +
{-# OPTIONS_GHC -fglasgow-exts #-}
 
module Zipper where
 
module Zipper where
   
-- A monad implementing The Zipper.
+
-- A monad implementing for traversing data structures
-- http://haskell.org/haskellwiki/ZipperMonad
+
-- http://haskell.org/haskellwiki/Zipper_monad
 
--------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------
   
 
import Control.Monad.State
 
import Control.Monad.State
import Control.Arrow (first, second)
 
   
data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Show, Eq)
+
data Loc c a = Loc { struct :: a,
  +
cxt :: c }
  +
deriving (Show, Eq)
   
  +
newtype Travel loc a = Travel { unT :: State loc a }
data Cxt a = Top
 
  +
deriving (Functor, Monad, MonadState loc, Eq)
| L (Cxt a) (Tree a)
 
| R (Tree a) (Cxt a)
 
deriving (Show)
 
   
  +
-- Exit Points
type Loc a = (Tree a, Cxt a)
 
 
newtype Travel t a = Travel { unT :: State t a }
 
deriving (Functor, Monad, MonadState t)
 
type TravelTree a = Travel (Loc a) (Tree a)
 
 
-- Movement around the tree
 
 
--
 
--
   
-- move down a level, through the left branch
+
-- get out of the monad
  +
traverse :: Loc c a -- starting location (initial state)
left :: TravelTree a
 
  +
-> Travel (Loc c a) a -- locational computation to use
left = modify left' >> liftM fst get where
 
  +
-> a -- resulting substructure
left' (Branch l r, c) = (l, L c r)
 
  +
traverse start tt = evalState (unT tt) start
   
  +
-- Mutation
-- move down a level, through the left branch
 
  +
--
right :: TravelTree a
 
right = modify right' >> liftM fst get where
 
right' (Branch l r, c) = (r, R l c)
 
   
  +
-- modify the substructure at the current node
-- move to a node's parent
 
  +
modifyStruct :: (a -> a) -> Travel (Loc c a) a
up :: TravelTree a
 
up = modify up' >> liftM fst get where
+
modifyStruct f = modify editStruct >> liftM struct get where
up' (t, L c r) = (Branch t r, c)
+
editStruct (Loc s c) = Loc (f s) c
up' (t, R l c) = (Branch l t, c)
 
   
-- move to the top node
+
-- put a new substructure at the current node
  +
putStruct :: a -> Travel (Loc c a) a
top :: TravelTree a
 
top = modify (second $ const Top) >> liftM fst get
+
putStruct t = modifyStruct $ const t
   
-- Mutation of the tree
+
-- get the current substructure
  +
getStruct :: Travel (Loc c a) a
--
 
  +
getStruct = modifyStruct id -- works because modifyTree returns the 'new' tree
 
-- modify the subtree at the current node
 
modifyTree :: (Tree a -> Tree a) -> TravelTree a
 
modifyTree f = modify (first f) >> liftM fst get
 
 
-- put a new subtree at the current node
 
putTree :: Tree a -> TravelTree a
 
putTree t = modifyTree $ const t
 
 
-- get the current node and its descendants
 
getTree :: TravelTree a
 
getTree = modifyTree id -- works because modifyTree returns the 'new' tree
 
 
-- Exit points
 
--
 
 
-- get out of the monad
 
traverse :: Tree a -> TravelTree a -> Tree a
 
traverse t tt = evalState (unT tt) (t, Top)
 
 
</haskell>
 
</haskell>
   

Revision as of 21:21, 19 April 2006

The Travel Monad is a generic monad for navigating around arbitrary data structures. It supports movement, mutation and classification of nodes (is this node the top node or a child node?, etc). It was proposed and designed by Paolo Martini (xerox), and coded by David House (davidhouse). It's designed for use with The Zipper but in fact there is no requirement to use such an idiom.

At the moment there are two specific libraries that use the Travel monad: TravelTree for navigating around binary trees, and TravelBTree for navigating around "B-Trees", trees where each node has an arbitrary number of branches.

Definition

data Loc c a = Loc { struct :: a,
                     cxt    :: c }
             deriving (Show, Eq)

newtype Travel loc a = Travel { unT :: State loc a }
     deriving (Functor, Monad, MonadState loc, Eq)

Computations in Travel are stateful. Loc c a is a type for storing the location within a structure. struct should be the substructure that the Loc is refering to, and cxt the "context" of the substructure; i.e. the rest of the structure. Loc is designed to hold a Zipper (although it doesn't have to; for example if you wanted to traverse a list it would probably be more natural to hold the entire structure and an index). Indeed, both of the libraries provided with the generic Travel monad use a zipper.

Functions

Movement

At the moment, movement is specific to the structure you are traversing and as such, the movement functions are provided by libraries implementing specific structures. Try the documentation for TravelTree (binary trees) or TravelBTree (B-Trees; trees where each node has an arbitrary number of branches).

Mutation

There are three generic functions available for changing the structure:

getStruct    :: Travel (Loc c a) a
putStruct    :: a -> Travel (Loc c a) a
modifyStruct :: (a -> a) -> Travel (Loc c a) a

These are direct front-doors for State's get, put and modify, and all three return the substructure after any applicable modifications.

Exit points

To get out of the monad, use traverse:

traverse :: Loc c a            -- starting location (initial state)
         -> Travel (Loc c a) a -- locational computation to use
         -> a                  -- resulting substructure

Again, this is just a front-door for evalState. Note that you have to give a Loc as a starting state. Both the libraries provided supply a getTop function, which takes a tree and returns the Loc corresponding to the top of the tree. Thus a typical call to traverse might look like:

let t = Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3))
in (getTop t) `traverse` (left >> swap >> right)

Examples

Travel is too general to be used in itself, so there are examples given on the documentation pages for the libraries. Here are the links again:

  • TravelTree for binary trees.
  • TravelBTree for B-Trees; trees where each node has an arbitrary number of branches.

Code

Here's the base Zipper monad in full (download):

{-# OPTIONS_GHC -fglasgow-exts #-}
module Zipper where

-- A monad implementing for traversing data structures
-- http://haskell.org/haskellwiki/Zipper_monad
--------------------------------------------------------------------------------

import Control.Monad.State

data Loc c a = Loc { struct :: a,
                     cxt    :: c }
             deriving (Show, Eq)

newtype Travel loc a = Travel { unT :: State loc a }
     deriving (Functor, Monad, MonadState loc, Eq)

-- Exit Points
--

-- get out of the monad
traverse :: Loc c a            -- starting location (initial state)
         -> Travel (Loc c a) a -- locational computation to use
         -> a                  -- resulting substructure
traverse start tt = evalState (unT tt) start

-- Mutation
-- 

-- modify the substructure at the current node
modifyStruct :: (a -> a) -> Travel (Loc c a) a
modifyStruct f = modify editStruct >> liftM struct get where
    editStruct (Loc s c) = Loc (f s) c

-- put a new substructure at the current node
putStruct :: a -> Travel (Loc c a) a
putStruct t = modifyStruct $ const t

-- get the current substructure
getStruct :: Travel (Loc c a) a
getStruct = modifyStruct id -- works because modifyTree returns the 'new' tree