[Haskell] ANNOUNCE: PEZ, the Potentially Excellent Zipper library

Brandon Simmons brandon.m.simmons at gmail.com
Sat Apr 23 02:35:42 CEST 2011


I'm happy to present my long-languishing-on-the-harddrive generic
zipper library I'm calling pez:

   http://hackage.haskell.org/package/pez

The library brings together the 'fclabels' and 'thrist' packages with
the Typeable class to enable a zipper library that is (I hope)
intuitive and requiring a minimum of boilerplate. Get it with:

   $ cabal install pez

There is still much to do, in particular I have not looked at the
performance characteristics of this approach at all, but I hope others
find it interesting or useful. Please send any feature requests, or
bug reports.


  EXAMPLE USAGE
================

First you need to enable some extensions, the first two for generating
and using 'fclabels' lenses, the second for easy deriving of Typeable
instances on custom types:

> {-# LANGUAGE TemplateHaskell, TypeOperators, DeriveDataTypeable #-}
>
> module Main where
>
> -- import pez
> import Data.Typeable.Zipper
> -- for prettiness:
> import Control.Arrow
> import Control.Applicative

Now we define a tree that we want to use in our zipper. We want it to be an
instance of Typeable which we can derive, and we want 'fclabels' lenses to be
generated with TH for the branches, so we name the records with underdashes
(see:  http://hackage.haskell.org/package/fclabels )

> data Tree a = Node {
>                      _leftNode :: Tree a,
>                      _val      :: a,
>                      _rightNode :: Tree a }
>             | Nil
>             deriving (Typeable,Show)
>
> $(mkLabelsNoTypes [''Tree])

At this point we can use all of our zipper functions on the Tree type. The
following returns the value at the left-most Node, along with a SavedPath back
to that Node. It returns Nothing if the tree is empty:

> -- 'a' must be Typeable because we actually "moveTo" it here:
> getLeftmost :: Typeable a=> Tree a -> Maybe (a, SavedPath (Tree a) a)
> getLeftmost = fmap (viewf &&& save) . descendLeft . zipper
>     where descendLeft z =
>               case viewf z of
>                    Nil -> moveTo val <$> moveUp 1 z
>                    _   -> descendLeft $ moveTo leftNode z

A `SavedPath` can be restored moving the focus back to the location it points
to, or it can be collapsed into a lens itself.

Let's use the function we defined above to make sure it works:

> tree = Node (Node Nil 'a' Nil) 'b' (Node Nil 'c' Nil)
>
> main = do
>     putStr "This should show 'a': "
>     putStrLn $ maybe "FAIL" (show . fst) $ getLeftmost tree

You can also experiment with "zipping through" computations. It's as
simple as defining a new fclabel lens for a reversible computation,
e.g.:

> reversible :: (Show b, Read b) => b :-> String
> reversible = lens show (const . read)

Thanks,
Brandon Simmons
http://coder.bsimmons.name



More information about the Haskell mailing list