Generic tries (long)

Adrian Hey ahey at iee.org
Sun Jun 22 02:54:27 EDT 2008


Hello apfelmus,

apfelmus wrote:
>> I've never been very keen on alter myself (on efficiency grounds) and
>> was wondering whether of not to include it. If the "altering" results
>> in an unchanged map it would be nice to just return the unchanged
>> map (rather than duplicate all nodes on the search path). There are
>> other possible alternatives to alter that are more efficient in this
>> respect.
> 
> You mean the case when
> 
>   f Nothing = Nothing

or, for some a ..

  f (Just a) = Just a

..but of course there's no way you can tell from inside the alter
function that the two a's are the same without an expensive equality
test, and even then that's not enough because you need to pass the
"no change" information back up the call chain (as a Nothing probably)
which means that if there is a change even more heap will be burned
by wrapping each intermediate result in a Just.

> in  alter f .. ? Hm, maybe some zipper-like extension of  lookup  can do 
> the trick
> 
>   focus :: k -> map a -> (Maybe a, Maybe a -> map a)
> 
>   lookup k    = fst . focus k
>   delete k m  = case focus k m of
>       (Nothing, _) -> m
>       (_      , g) -> g Nothing
>   alter f k m = case focus k m of
>       (Nothing, g) -> case f Nothing of
>            Nothing -> m
>            x       -> g x
>       (x      , g) -> g x

I think it depends if this can be implemented without burning
significant extra heap in either focus or the resulting g function.
Generally zippers do require quite a bit of heap (proportional to
trie/tree depth).

If you consider what people are actually trying to achieve with alter
I actually think it's rather easier to use as a 2 step process and
forget about the (Maybe a -> Maybe a) function. After having done
a lookup and examined the associated value (if any), you could do..

If search failed:
  1f - Do nothing (this is a v. cheap operation :-)
  2f - Insert a new association
If search succeeded:
  1s - Do nothing
  2s - Modify the associated value
  3s - Delete the association

Despite it's generality, alter still fails to properly capture all
the options, notably 1f and 1s. I guess it is conceivable that some
implementations might be able to deal with 1f efficiently.

For the Data.Map clone I wrote something like this ..

-- An "open" map (this is abstract)
data OMap k a = OMap k (Maybe a) (Map k a) Int#

-- This is just a lookup that encodes the path taken as an unboxed Int
open :: Ord k => k -> Map k a -> OMap k a

-- Get the current associated value (if any)
read :: OMap k a -> Maybe a

-- Change the current associated value and close the new map
-- This is v.fast. No comparisons, and no balance checking or
-- rebalancing either if this is a substitution rather than an
-- insertion.
write :: a -> OMap k a  -> Map k a

-- Delete the current association (if any) and close the new map
-- This is nop if there is no current association
delete :: OMap k a  -> Map k a

-- Not really needed if original map is still in scope
close :: OMap k a -> Map k a

open burns no heap at all other than to construct the OMap record
(possibly not even that) and possibly the (Just a). If it turns out
there's no need to write or delete then don't (end of story). Even if
a write is needed the whole combined process only takes about 10% longer
than a normal insert, and that's with cheap comparisons (Ints).

Admitedly for a trie the path would probably be something a bit more
complex than an unboxed Int, but we could use a similar API.

Regards
--
Adrian Hey




More information about the Libraries mailing list