[Haskell-cafe] Best representation of graph for use in a zipper?

Daniel McAllansmith dagda at xtra.co.nz
Thu Feb 23 23:36:32 EST 2006


Hi

I've been having a look at zippers over homogenous tree data types, and was 
wondering how best to represent a heterogeneous graph for manipulation with a 
zipper.

The main example of zippers I've been looking at is
http://okmij.org/ftp/Computation/Continuations.html#zipper-fs
and
http://okmij.org/ftp/Computation/Continuations.html#zipper
from which I've included a small extract at the end of this email to provide 
extra context if necessary.


For contrived example, given a relational model:

.Album
.  |1
.  |
.  |
.  |1..n    0..n   1
.Performance--------Song
.     |0..n           |1
.     |               |
.     |               |0..n
.     |1       WritingCredit
. Performer       |0..n
.  ^     ^        |
.  |     |------  |
.  |           |  |
.  |  1   1..n |  |1
.Group--------Artist

I could write a data type:

> data MC
>     = Album       {perfs ::[MC]}
>     | Performance {album :: MC, song :: MC, performer :: MC}
>     | Song        {perfs :: [MC], artistCredits :: [MC]}
>     | Group       {perfs ::[MC], artists :: [MC]}
>     | Artist      {perfs :: [MC], songCredits :: [MC]}
>     | Root        {albums :: [MC]}

The first problem I have with this is that it doesn't enforce enough 
structural constraints.
Secondly, as I understand it, whilst zippers can handle cyclic structures they 
do so by doing a 'copy-on-write'.  I would like to maintain shared instances.

I could flatten the data type graph to a minimal spanning tree:

> data MCFK = MCFK
> data MC
>     = Album       {fKey :: MCFK, perfs ::[MC]}
>     | Performance {fKey :: MCFK, songFK :: MCFK, performer :: MCFK}
>     | Song        {fKey :: MCFK, artistCredits :: [MCFK]}
>     | Group       {fKey :: MCFK, artists :: [MC]}
>     | Artist      {fKey :: MCFK}
>     | Root        {albums :: [MC], songs :: [MC], groups :: [MC], 
soloArtists :: [MC]}

This seems a bit better.  The traversal function doesn't have to worry about 
cycles and there's less mainenance updates to do.  But it still doesn't offer 
any structural or foreign key guarantees.

I thought that I would be able to use a GADT to give structural guarantees, 
though not FK guarantees, but once I move to a GADT I don't know how to write 
a traversal function as the next node could be of several different types.

Any advice on how to get a safer data structure, and write the necessary 
traversal function, would be much appreciated.

Cheers
Daniel



Following is an extract from the links above.  Note that I have floated the 
functions local to traverse up to the top level to get at them with GHCi


> data Term = Var String | A Term Term | L String Term deriving (Show)
> 
> data Direction = Down | DownRight | Up | Next deriving (Eq, Show)
> 
> traverse :: (Monad m) => (Direction -> Term -> m (Maybe Term, Direction)) -> 
Term -> m Term
> traverse tf term = traverse' tf id Down term >>= maybeM term id
> 
> 
> traverse' tf next_dir init_dir term = do
>     (term', direction) <- tf init_dir term
>     let new_term = maybe term id term'
>     select tf (next_dir direction) new_term >>= maybeM term' Just
> 
> next next_dir dir = if dir == Next then next_dir else dir
> 
> maybeM onn onj v = return $ maybe onn onj v
> 
> select tf Up t = return Nothing
> select tf Next t@(Var _) = return Nothing
> select tf dir t@(L v t1) | dir == Next || dir == Down = do
>     t' <- traverse' tf id Down t1 >>= (return . fmap (L v))
>     traverse' tf (next Up) Up (maybe t id t') >>= maybeM t' Just
> select tf DownRight t@(A t1 t2) = do
>     t' <- traverse' tf id DownRight t2 >>=
>         (return . fmap (\t2'->(A t1 t2')))
>     traverse' tf (next Up) Up (maybe t id t') >>= maybeM t' Just
> select tf dir t@(A t1 t2) | dir == Next || dir == Down = do
>     t' <- traverse' tf id Down t1 >>=
>         (return . fmap (\t1'->(A t1' t2)))
>     traverse' tf (next DownRight) Up (maybe t id t') >>=
>         maybeM t' Just
> 
> 
> --Testing
> trav dir term = do print dir; print term; return (Nothing,Next)
> 
> 
> term1 = A (Var "v1") (L "l1" (A (Var "v2") (Var "v3")))
> 
> test1 = traverse trav term1


More information about the Haskell-Cafe mailing list