Difference between revisions of "Zipper monad"

From HaskellWiki
Jump to navigation Jump to search
(version 2)
(Added ref to the generic zipper.)
 
(4 intermediate revisions by 2 users not shown)
Line 1: Line 1:
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.
+
The Zipper 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.
+
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. Please see below for an alternative zipper implementation that works for any data structure whatsoever.
  +
  +
You can [http://haskell.org/sitewiki/images/b/b7/Zipper.tar.gz download] the library in its entirety. To run the tests:
  +
  +
tar xzf Zipper.tar.gz
  +
cd Zipper
  +
ghc -o test --make Main.hs
  +
./test
   
 
== Definition ==
 
== Definition ==
Line 56: Line 63:
 
== Code ==
 
== Code ==
   
Here's the base Zipper monad in full ([http://haskell.org/sitewiki/images/3/36/Zipper.hs download]):
+
Here's the base Zipper monad in full ([http://haskell.org/sitewiki/images/3/36/Zipper.hs download] or download the [http://haskell.org/sitewiki/images/b/b7/Zipper.tar.gz entire library]):
   
 
<haskell>
 
<haskell>
Line 100: Line 107:
 
getStruct = modifyStruct id -- works because modifyTree returns the 'new' tree
 
getStruct = modifyStruct id -- works because modifyTree returns the 'new' tree
 
</haskell>
 
</haskell>
  +
  +
== Alternative implementation ==
  +
  +
An alternative implementation, which is polymorphic over data structures
  +
and so can be written once and for all, is available at
  +
[http://pobox.com/~oleg/ftp/Computation/Continuations.html#zipper Generic Zipper and its applications]
  +
The code on that page served as the basis for a Zipper-based file system.
   
 
[[Category:Idioms]]
 
[[Category:Idioms]]
  +
[[Category:Monad]]

Latest revision as of 01:00, 9 October 2006

The Zipper 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. Please see below for an alternative zipper implementation that works for any data structure whatsoever.

You can download the library in its entirety. To run the tests:

tar xzf Zipper.tar.gz
cd Zipper
ghc -o test --make Main.hs
./test

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 or download the entire library):

{-# 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

Alternative implementation

An alternative implementation, which is polymorphic over data structures and so can be written once and for all, is available at Generic Zipper and its applications The code on that page served as the basis for a Zipper-based file system.