looking for data structure advice

Derek Elkins ddarius at hotpop.com
Fri Dec 12 14:17:13 EST 2003


On Fri, 12 Dec 2003 07:24:04 -0500
David Roundy <droundy at abridgegame.org> wrote:

Other libraries are Daan's DData, http://www.cs.uu.nl/~daan/ddata.html,
and Edison, http://cvs.sourceforge.net/viewcvs.py/hfl/hfl/edison/ (or
the version in the old hslibs), however nothing jumps out at me as doing
exactly what you need.

> In case I haven't been clear enough, the algorithm I want to speed up
> looks like (when simplified a tad)
>
> commute :: ([Patch], [Patch]) -> Maybe ([Patch], [Patch])
> commute (a:as, bs) = case commuteOneMany a bs of
>                      Nothing -> Nothing
>                      Just (bs', a') ->
>                        case commute (as, bs') of
>                        Nothing -> Nothing
>                        Just (bs'', as') -> Just (bs'', a':as')
> commuteOneMany a (b:bs) = case commuteOne a b of
>                           Nothing -> Nothing
>                           Just (b', a') ->
>                             case commuteOneMany a' bs of
>                             Nothing -> Nothing
>                             Just (bs', a'') -> Just (b':bs', a'')
> commuteOne :: Patch -> Patch -> (Patch, Patch)

Ack! This code is screaming that you should treat Maybe as a monad.
commute :: ([Patch],[Patch]) -> Maybe ([Patch],[Patch])
commute (a:as,bs) = do
    (bs',a') <- commuteOneMany a bs
    (bs'',as') <- commute as bs'
    return (bs'',a':as')
commuteOneMany a (b:bs) = do
    (b',a') <- commuteOne a b
    (bs',a'') <- commuteOneMany a' bs
    return (b':bs',a'')

This will also provide a migration path if you want a more featureful
monad.  (or_maybe is mplus, fail or mzero can be used for Nothing when
you explicitly want to fail).

strict_commute for example can be simplified to
strict_commute (NamedP n1 d1 p1) (NamedP n2 d2 p2) = do
    guard (not (n2 `elem` d1 || n1 `elem` d2))
    (p2',p1') <- commute (p1,p2)
    return (NamedP n2 d2 p2',NamedP n1 d1 p1')
strict_commute p2 p1 = msum $ map (\f -> clever_commute f (p2,p1)) fs
    where fs = [commute_nameconflict,
                commute_filedir,
                etc...]



More information about the Haskell-Cafe mailing list