
+1 Really nice idea!
(The following is just some brainstorming)
Why not store the value in the Location as in:
data Location k a
= Empty !k !(Path k a)
| Full {-# UNPACK #-} !Size !k a !(Path k a) !(Map k a) !(Map k a)
Search doesn't need to return a tuple with a Maybe but simply:
search :: Ord k => k -> Map k a -> Location k a
search k = k `seq` go Root
where
go path Tip = Empty k path
go path (Bin sx kx x l r) = case compare k kx of
LT -> go (LeftBin sx kx x path r) l
GT -> go (RightBin sx kx x l path) r
EQ -> Full sx kx x path l r
We do need a function to retrieve the value:
value :: Localtion k a -> Maybe a
value (Empty _ _) = Nothing
value (Full _ _ v _ _ _) = Just v
min- and maxLocation are also simplified:
minLocation :: Map k a -> Location k a
minLocation = go Root
where
go _path Tip = error "Map.least: empty map"
go path (Bin sx kx x Tip r) = Full sx kx x path Tip r
go path (Bin sx kx x l r) = go (LeftBin sx kx x path r) l
maxLocation :: Map k a -> Location k a
maxLocation = go Root
where
go _path Tip = error "Map.greatest: empty map"
go path (Bin sx kx x l Tip) = Full sx kx x path l Tip
go path (Bin sx kx x l r) = go (RightBin sx kx x l path) r
On Fri, Jan 7, 2011 at 6:37 PM, Ross Paterson
This is a variant of a suggestion by apfelmus:
http://www.haskell.org/pipermail/libraries/2010-September/014510.html
To avoid proliferation of variants of element-wise operations, the idea is to split these operations into two phases mediated by a new Location type, so that users can do whatever they like between these phases. Documentation is here:
http://code.haskell.org/~ross/containers_doc/Data-Map.html#3
This adds a type and 9 functions to the interface, but makes possible monadic updates and much more. As an illustration, the file MapOps.hs attached to the ticket gives definitions of 30 of the public functions of Data.Map in terms of the new interface. At least in the case of insert, this definition is slightly faster than the current one.
Discussion period: 4 weeks (to 4 February)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries