Proposal #3999: Improved folds for Data.Map and Data.IntMap

Roman Leshchinskiy rl at cse.unsw.edu.au
Sat Apr 24 04:03:36 EDT 2010


On 24/04/2010, at 04:16, Louis Wasserman wrote:

> In the meantime, to refocus attention on the original proposal.... ;)

Yes, sorry sidetracking the thread.

> {-# 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.

I'm not sure why you don't just use curry directly here. Also, why not just implement toAscList like in the rule and INLINE it?

Roman




More information about the Libraries mailing list