Adding manual worker/wrapper transforms to Data.Map
wren ng thornton
wren at community.haskell.org
Thu Aug 19 17:46:48 EDT 2010
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
More information about the Libraries
mailing list