
In the meantime, to refocus attention on the original proposal.... ;) For the moment, if only because it's currently the more standard approach, I'll concede and use the foldr/build approach. {-# INLINE [0] pairCons #-} pairCons :: ((a, b) -> c -> c) -> a -> b -> c -> c pairCons = curry {-# RULES "Data.Map.toAscList->build" [~1] toAscList = \ m -> GHC.build (\ c n -> foldrWithKey (pairCons c) n m); #-} Since the normal definition of toAscList is just foldrWithKey (curry (:)) [], there's no need to rewrite it back to toAscList. A few possible additional modifications: - Pull a similar trick for toDescList. It's not as if it'd be all that difficult... - Reimplement the (==) and compare functions for Data.Map as follows: m1 == m2 = size m1 == size m2 && and (zipWith (==) (toAscList m1) (toAscList m2)) m1 `compare` m2 = foldr mappend (compare (size m1) (size m2)) (zipWith compare (toAscList m1) (toAscList m2)) which gets some deforesting. Louis Wasserman wasserman.louis@gmail.com http://profiles.google.com/wasserman.louis