looking for data structure advice

David Roundy droundy at abridgegame.org
Fri Dec 12 07:24:04 EST 2003


Hello everyone,

I am trying to restructure some of my code to eliminate some O(n^2)
operations, and have realized that this will require a change in how my
data is represented, but I don't see any standard data types (in Data) that
will really suit my needs.

Currently I have a sequence of patches is just a list, so when two
sequences or patches are reordered, I have an O(n^2) operation (where n is
the length of each sequence).  I would like to reduce this, since most
patches are orthogonal, since they modify a single file, but this isn't
possible as long as the data is represented in lists.

What I'd like would be to have a data structure that holds an ordered list,
but has a mapping from keys to its members, a sort of ordered FiniteMap.
Each member would have to match several keys.  I don't think this
multiplicity of keys can be hidden in a single key, since I want to be able
to search by any key in O(log n).  Then I'd want to be able to extract its
contents matching some keys,

extractKeys :: [key] -> OrderedFiniteMap key elem -> [elem]

with the above preserving the order of the elements.

And to be able to modify only those patches matching a given key

modifyOFM :: [key] -> a -> ((elem, a) -> ([key],elem,a))
          -> OrderedFiniteMap key elem -> (OrderedFiniteMap key elem, a)

where the second argument indicates how the first element to be modified
changes, and possibly changes the keys when matching the second
element... this is looking pretty complicated... maybe what I want is some
sort of a monad.

Of course I'd need "normal" access functions too, but those are more
obvious.

Is there an existing set of algorithms that might serve my needs (or some
existing data structure, that would adequately suit my needs)? I really
would rather not right my own data structure module for this purpose.
Creating multiple references to a given data element to describe its list
and all its keys is a bit intimidating...

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)

where there exists a function

patchModifies :: Patch -> [Key]

such that

commuteOne a b
    | null (patchModifies a `intersect` patchModifies b) = (b, a)

Any suggestions would be appreciated.  At this point I've gotten myself
pretty confused as to what exactly I want to do.  :(
-- 
David Roundy
http://www.abridgegame.org


More information about the Haskell-Cafe mailing list