export toDescList from Data.Map

Benedikt Huber benjovi at gmx.net
Fri Sep 26 14:29:48 EDT 2008


Ross Paterson schrieb:
> On Fri, Sep 26, 2008 at 04:12:17PM +0200, Benedikt Huber wrote:
>> I think that having a function
>>
>>> treeView :: Map k v -> T (k,v)
>> s.t. T is an instance of Foldable, supports efficient left and right  
>> folds, and additional operations like subrange queries (all pairs (k,v)  
>> s.t. l <= k <= u) would be useful.
>> I'd like to have all functions from Data.Foldable available for folds  
>> with key, e.g fold[lr]MWithKey.
> 
> Map has split and splitLookup for subrange queries, and you could get
> the folds with
> 
> 	mapWithKey (,) :: Map k v -> Map k (k,v)

Thanks for the pointing this out.

While browsing Data.Map I noted that the Foldable instance only defines 
foldMap - it is notably slower to use Data.Map - Foldable.foldr 
compared to Map.fold. Adding

 > instance Foldable (Map k) where
 >  foldMap = ...
 >  foldr f = foldr (const f)
 >  foldl f = foldl (\b _ a -> f b a)

really helps.
There is also a notable performance penalty using mapWithKey as you 
suggested, but otherwise it does the job. I still think that toTree or 
treeView would be interesting, but others might disagree of course.

For range queries, split should indeed be sufficient, though a 
specialized function might be faster.

Finally I've attached a (very simple) microbenchmark to demonstrate the 
need for adding foldr,foldl to the Foldable instance of Data.Map.

best regards,
benedikt


-- Timings {without additional Foldable definitions}/{with foldl,foldr 
definitions for foldable}

-- fold asc-list
-- {1.35}
testFold_1 = foldr (uncurry f) 0 . M.toAscList

-- foldWithKey (foldWithKey)
-- {1.45}
testFold_2 = M.foldWithKey f 0

-- fold M.mapWithKey (,)
-- {9.0 / 3.25}
testFold_3 = foldr (uncurry f) 0 . M.mapWithKey (,)

-- fold without key (Foldable.foldr)
-- {5.06 / 1.35}
testFold_4 = foldr (f 0) 0

-- fold (elems.mapWithKey)
-- {3.75}
testFold_6 = foldr (uncurry f) 0 . M.elems . M.mapWithKey (,)

f k v b = b*7+k+2*v
main = go testFold_1 0 (M.empty) where
   go f 5000 = putStrLn ""
   go f k m  = putStr (show (f m) ++ " ") >>
               go f (succ k) (M.insert k (2*k) m)




More information about the Libraries mailing list