[Haskell-cafe] Zippers from any traversable [Was: Looking for practical examples of Zippers]

oleg at okmij.org oleg at okmij.org
Wed Apr 1 02:59:46 EDT 2009


wren ng thornton wrote:
> > how, for instance, turn a nested Map like
> >
> > Map Int (Map Int (Map String Double)
> >
> > into a "zipped" version.
> You can't. Or rather, you can't unless you have access to the
> implementation of the datastructure itself; and Data.Map doesn't provide
> enough details to do it.

Actually Data.Map does provide enough details: Data.Map is a member of
Traversable and anything that supports Traversable (at the very least,
provides something like mapM) can be turned into a
Zipper. Generically. We do not need to know any details of a data
structure (or if it is a data structure: the collection may well
be ephemeral, whose elements are computed on the fly). Please see the
enclosed code; the code defines a function tmod to interactively
traverse the collection, displaying the elements one by one and
offering to modify the current element, or quit the traversal.

The enclosed code implements the zipper that can only move
forward. Chung-chieh Shan has well described how to turn any
one-directional zipper into bi-directional. Again generically.
	http://conway.rutgers.edu/~ccshan/wiki/blog/posts/WalkZip3/


Although the enclosed code demonstrates the possibility of turning a Data.Map
into a Zipper, one may wonder about the merits of that
endeavour. Data.Map is a very rich data structure, with
efficient means to focus on any given element and replace it (e.g.,
elemAt, replaceAt) and to incrementally deconstruct the map
(deleteMax, deleteMin, minView, etc). Triple-nested maps can
be processed just as effectively. The case for a tree of maps (which
is essentially a file system) is described in
	http://okmij.org/ftp/Computation/Continuations.html#zipper-fs


module ZT where 

import qualified Data.Traversable as T
import Control.Monad.Cont
import qualified Data.Map as M


-- In the variant Z a k, a is the current, focused value
-- evaluate (k Nothing) to move forward
-- evaluate (k v)       to replace the current value with v and move forward.

data Zipper t a = ZDone (t a) 
                | Z a (Maybe a -> Zipper t a)

make_zipper :: T.Traversable t => t a -> Zipper t a
make_zipper t = reset $ T.mapM f t >>= return . ZDone
 where
 f a = shift (\k -> return $ Z a (k . maybe a id))

zip_up :: Zipper t a -> t a
zip_up (ZDone t) = t
zip_up (Z _ k) = zip_up $ k Nothing


reset :: Cont r r -> r
reset m = runCont m id

shift :: ((a -> r) -> Cont r r) -> Cont r a
shift e = Cont (\k -> reset (e k))

-- Tests

-- sample collections

tmap = M.fromList [ (v,product [1..v]) | v <- [1..10] ]

-- extract a few sample elements from the collection
trav t = 
    let (Z a1 k1) = make_zipper t
        (Z a2 k2) = k1 Nothing
        (Z a3 k3) = k2 Nothing
        (Z a4 k4) = k3 Nothing
     in [a1,a3,a4]

travm = trav tmap

-- Traverse and possibly modify elements of a collection
tmod t = loop (make_zipper t)
 where
 loop (ZDone t) = putStrLn $ "Done\n: " ++ show t
 loop (Z a k) = do
                putStrLn $ "Current element: " ++ show a
                ask k

 ask k =        do
                putStrLn "Enter Return, q or the replacement value: "
                getLine >>= check k

 check k ""   = loop $ k Nothing
 check k "\r" = loop $ k Nothing
 check k ('q':_) = loop . ZDone . zip_up $ k Nothing
 check k s  | [(n,_)] <- reads s = loop $ k (Just n) -- replace
 check k _    = putStrLn "Repeat" >> ask k

testm = tmod tmap



More information about the Haskell-Cafe mailing list