Adding manual worker/wrapper transforms to Data.Map

Hi all, I tried doing the "standard" worker/wrapper transform to some functions in Data.Map. For example, by transforming insertWith' :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a insertWith' f k x m = insertWithKey' (\_ x' y' -> f x' y') k x m -- | Same as 'insertWithKey', but the combining function is applied strictly. insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a insertWithKey' f kx x t0 = case t of Tip -> singleton kx $! x Bin sy ky y l r -> case compare kx ky of LT -> balance ky y (insertWithKey' f kx x l) r GT -> balance ky y l (insertWithKey' f kx x r) EQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r) to insertWith' :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a insertWith' f k x m = insertWithKey' (\_ x' y' -> f x' y') k x m {-# INLINE insertWith' #-} insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a insertWithKey' f kx x t0 = kx `seq` go t0 where go t = case t of Tip -> singleton kx $! x Bin sy ky y l r -> case compare kx ky of LT -> balance ky y (go l) r GT -> balance ky y l (go r) EQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r) {-# INLINE insertWithKey' #-} I got a 16% speedup on this benchmark: {-# LANGUAGE BangPatterns #-} module Main where import Criterion.Main import qualified Data.Map as M main = defaultMain [ bench "insertWith20k/size" $ whnf (M.size . insertWith) n ] where -- Number of elements n = 20000 insertWith :: Int -> M.Map Int Int insertWith max = go 0 M.empty where go :: Int -> M.Map Int Int -> M.Map Int Int go n !m | n >= max = m | otherwise = go (n + 1) $ M.insertWith' (+) (n `mod` 20) n m There are lots of other functions in Data.Map that could benefit from the same transform, in particular some of the folds. Does anyone see a reason for me to not go ahead and try to create a patch that performs this transformation on all functions that could benefit from it? I would include a Criterion benchmark that shows the gains. Cheers, Johan

johan.tibell:
Does anyone see a reason for me to not go ahead and try to create a patch that performs this transformation on all functions that could benefit from it? I would include a Criterion benchmark that shows the gains.
I think it is long overdue. Also, though, QuickChecks :)

On Thu, Aug 19, 2010 at 11:38:10AM +0200, Johan Tibell wrote:
I tried doing the "standard" worker/wrapper transform to some functions in Data.Map. For example, by transforming
insertWithKey' f kx x t0 = case t of
to
insertWithKey' f kx x t0 = kx `seq` go t0 where go t = case t of
I got a 16% speedup on this benchmark:
Looks like as well as W/W you've also made it strict in the key, so this speedup isn't all W/W. Thanks Ian

On Thu, Aug 19, 2010 at 6:52 PM, Ian Lynagh
On Thu, Aug 19, 2010 at 11:38:10AM +0200, Johan Tibell wrote:
I tried doing the "standard" worker/wrapper transform to some functions
in
Data.Map. For example, by transforming
insertWithKey' f kx x t0 = case t of
to
insertWithKey' f kx x t0 = kx `seq` go t0 where go t = case t of
I got a 16% speedup on this benchmark:
Looks like as well as W/W you've also made it strict in the key, so this speedup isn't all W/W.
Right. Like Milan did in his work on containers I made the function key strict. This doesn't really make a difference in practice as far as semantics go as the function is already key strict iff the map isn't empty. I'll make a libraries proposal with the code changes so people can decide if this is something we want. Note: Most of the speedup comes from W/W though. -- Johan

Johan Tibell wrote:
insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a insertWithKey' f kx x t0 = kx `seq` go t0 where go t = case t of Tip -> singleton kx $! x Bin sy ky y l r -> case compare kx ky of LT -> balance ky y (go l) r GT -> balance ky y l (go r) EQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r)
As a style issue, I'd suggest using a pattern instead of the first case: go Tip = singleton kx $! x go (Bin sy ky y l r) = case compare kx ky of LT -> balance ky y (go l) r GT -> balance ky y l (go r) EQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r) -- Live well, ~wren

On Thu, Aug 19, 2010 at 11:46 PM, wren ng thornton < wren@community.haskell.org> wrote:
Johan Tibell wrote:
insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a insertWithKey' f kx x t0 = kx `seq` go t0 where go t = case t of Tip -> singleton kx $! x Bin sy ky y l r -> case compare kx ky of LT -> balance ky y (go l) r GT -> balance ky y l (go r) EQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r)
As a style issue, I'd suggest using a pattern instead of the first case:
go Tip = singleton kx $! x go (Bin sy ky y l r) =
case compare kx ky of LT -> balance ky y (go l) r GT -> balance ky y l (go r) EQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r)
I'll definitely do that in the final version. -- Johan

On 19/08/2010, at 19:38, Johan Tibell wrote:
Hi all,
I tried doing the "standard" worker/wrapper transform to some functions in Data.Map. For example, by transforming
insertWith' :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a insertWith' f k x m = insertWithKey' (\_ x' y' -> f x' y') k x m
-- | Same as 'insertWithKey', but the combining function is applied strictly. insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a insertWithKey' f kx x t0 = case t of Tip -> singleton kx $! x Bin sy ky y l r -> case compare kx ky of LT -> balance ky y (insertWithKey' f kx x l) r GT -> balance ky y l (insertWithKey' f kx x r) EQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r)
Out of curiosity, is balance strict in the third argument? If not, does it make a difference if you make it strict? Roman

On Fri, Aug 20, 2010 at 11:13 AM, Roman Leshchinskiy
On 19/08/2010, at 19:38, Johan Tibell wrote:
Hi all,
I tried doing the "standard" worker/wrapper transform to some functions in Data.Map. For example, by transforming
insertWith' :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a insertWith' f k x m = insertWithKey' (\_ x' y' -> f x' y') k x m
-- | Same as 'insertWithKey', but the combining function is applied strictly. insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a insertWithKey' f kx x t0 = case t of Tip -> singleton kx $! x Bin sy ky y l r -> case compare kx ky of LT -> balance ky y (insertWithKey' f kx x l) r GT -> balance ky y l (insertWithKey' f kx x r) EQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r)
Out of curiosity, is balance strict in the third argument? If not, does it make a difference if you make it strict?
I haven't checked since Milan completely rewrote balance but hasn't integrated his changes yet. I'll have a look at balance once those changes are in. -- Johan

On Fri, Aug 20, 2010 at 11:20 AM, Johan Tibell
On Fri, Aug 20, 2010 at 11:13 AM, Roman Leshchinskiy
wrote: Out of curiosity, is balance strict in the third argument? If not, does it make a difference if you make it strict?
I haven't checked since Milan completely rewrote balance but hasn't integrated his changes yet. I'll have a look at balance once those changes are in.
$ ghc --show-iface dist/build/Data/Map.hi <snip> balance :: forall k a. k -> a -> Data.Map.Map k a -> Data.Map.Map k a -> Data.Map.Map k a {- Arity: 4 Strictness: SLSS -} <snip> So I guess it's strict in the 3rd (and 4th) argument. -- Johan
participants (5)
-
Don Stewart
-
Ian Lynagh
-
Johan Tibell
-
Roman Leshchinskiy
-
wren ng thornton