A single general modification function for Map and IntMap proposal

Milan Straka fox at ucw.cz
Wed May 1 20:23:58 CEST 2013


Hi all,

> -----Original message-----
> From: Shachaf Ben-Kiki <shachaf at gmail.com>
> Sent: 30 Apr 2013, 23:49
>
> ...
> 
> However: I just wrote a quick direct version:
> 
>     alterF :: (Ord k, Functor f) => k -> (Maybe a -> f (Maybe a)) ->
> Map k a -> f (Map k a)
>     STRICT_1_OF_2(alterF)
>     alterF k f = go
>       where
>         go Tip = maybe Tip (singleton k) <$> f Nothing
>         go (Bin sx kx x l r) =
>           case compare k kx of
>             LT -> (\l' -> balance kx x l' r) <$> go l
>             GT -> (\r' -> balance kx x l r') <$> go r
>             EQ -> maybe (glue l r) (\x' -> Bin sx kx x' l r) <$> f (Just x)
> 
> And benchmarked lookup-via-alterF, insert-via-alterF, etc. -- they
> come out much slower. However, if I add an INLINE pragma or SPECIALIZE
> pragmas for common/relevant functors (e.g. Const r, Identity, (r,)),
> then they come out almost the same speed as the primitive function.
> 
> I don't think INLINE is necessarily bad for this function. (I don't
> like the idea of using SPECIALIZE here because I don't think e.g.
> Identity should have special privileges over some other newtype with
> the same Functor instance.) So maybe the direct implementation should
> be reconsidered. I can do a more thorough benchmark later if people
> are interested.

The right pragma is probably INLINABLE, which is used a lot throughout
the containers. It exposes the unfolding of alterF and if a Ord k or
Functor f is known when calling alterF, specialization is created for
that Ord or Functor and this specialization is reused in this and
dependant modules.

Results of my benchmarks are

insert: ~ +5% increase using alterF
delete: ~ +10% increase using alterF

> > I am also a bit worried whether withItem is the "right" general
> > function. For example Shachaf Ben-Kiki mentions the
> >   at :: (Ord k, Functor f) => k -> (Maybe i -> f (Maybe i)) -> Map k i -> f (Map k i)
> > from the lens package in other mail, but maybe there are others.
> >
> 
> I think that alterF almost certainly *a* right function -- it's just a
> monadic/functorial version of `alter`, which is the most general
> "simple" updating function. Possibly there should be others too, but
> this one is useful and general. Although it needs a better name. :-)

I feel convinced, alterF seems to offer additional functionality by
being quite general, and it is reasonably efficient because
a specialization is created for calls with known functor instance.
I like it :)

Cheers,
Milan



More information about the Libraries mailing list