Data.Tree.AVL

Adrian Hey ahey at iee.org
Thu Jan 19 18:24:03 EST 2006


Hello Christian

On Thursday 19 Jan 2006 9:38 pm, Christian Maeder wrote:
> I've found some time to try out (part of) your library (below). And it
> speeded up my whole application for about 5%!

Thanks. The current AVL implementation isn't specialised for Maps (you
get an extra indirection overhead by using pairs), but AVL does seem to
more or less hold it's own against Data.Map despite this handicap for
basic operations like insert and lookup. Where I think you should
see significant improvement is in tree balancing if you end up
growing a tree from a sorted list (that you don't know is sorted)
and in Set operations (union etc). The Hedge algorithm seems to
require many more comparisons. Of course how much this contributes
to overall program speedup depends on a lot of things (what else
program is doing, how much comparison costs..)

> insert :: Ord a => a -> b -> Map a b -> Map a b
> insert k v m = AVL.pushWith (\ (a, _) (c, _) ->
>             case compare a c of
>               LT -> Lt
>               EQ -> Eq (k, v)
>               GT -> Gt) (k, v) m

I deprecated pushWith. The Data.Map clone I started (but haven't
got around to finishing) has insert defined thus..

newtype Map k a = Map (AVL.AVL (k,a))

insert :: Ord k => k -> a -> Map k a -> Map k a
insert k a (Map t) = Map (AVL.genPush cc (k,a) t)
 where cc (k',_) = case compare k k' of
                   LT -> COrdering.Lt
                   EQ -> COrdering.Eq (k',a)
                   GT -> COrdering.Gt

Here's my versions of some of the other functions (not
that I think there's anything wrong with yours).

> lookup :: Ord a => a -> Map a b -> Maybe b
> lookup k m = AVL.genTryRead m (\ (a, b) ->
>             case compare k a of
>               LT -> Lt
>               EQ -> Eq b
>               GT -> Gt)

> findWithDefault :: Ord a => b -> a -> Map a b -> b
> findWithDefault d k = maybe d id . lookup k

readValCC :: Ord k => k -> (k,a) -> COrdering.COrdering a
readValCC k (k',a) = case compare k k' of
                     LT -> COrdering.Lt
                     EQ -> COrdering.Eq a
                     GT -> COrdering.Gt

lookup :: (Monad m,Ord k) => k -> Map k a -> m a
lookup k (Map t) = case AVL.genTryRead t (readValCC k) of
                   Just a  -> return a
                   Nothing -> fail "AvlMap.lookup: Key not found"

findWithDefault :: Ord k => a -> k -> Map k a -> a
findWithDefault def k (Map t) = AVL.genDefaultRead def t (readValCC k)

> insertWith :: Ord a => (b -> b -> b) -> a -> b -> Map a b -> Map a b
> insertWith f k v m = AVL.pushWith (\ (a, b) (c, d) ->
>             case compare a c of
>               LT -> Lt
>               EQ -> Eq (k, f b d)
>               GT -> Gt) (k, v) m

insertWith :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWith f k a (Map t) = Map (AVL.genPush cc (k,a) t)
 where cc (k',a') = case compare k k' of
                    LT -> COrdering.Lt
                    EQ -> COrdering.Eq (k',f a a')
                    GT -> COrdering.Gt

Regards
--
Adrian Hey



More information about the Libraries mailing list