A single general modification function for Map and IntMap proposal

Shachaf Ben-Kiki shachaf at gmail.com
Tue Apr 30 15:45:32 CEST 2013


On Tue, Apr 30, 2013 at 6:18 AM, Nikita Volkov
<nikita.y.volkov at gmail.com> wrote:
> There is a list of problems with the current "Map" and "IntMap" modification
> interfaces:
>
>    - they are filled with quirky and too specialized functions
>
>    - they are not consistent in terms of how equally named functions behave:
> http://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-IntMap-Strict.html#v:updateLookupWithKey
>
>    - they still don't cover some important scenarios of use
>
> Because of the above I have very often found myself in requirement for the
> following function:
>
>    withItem ::
>      (Ord k) =>
>      k ->
>      (Maybe i -> (r, Maybe i)) ->
>      Map k i -> (r, Map k i)
>    withItem k f m =
>      let
>        item = Map.lookup k m
>        (r, item') = f item
>        m' = Map.update (const item') k m
>      in (r, m')
>
> It covers all the imaginable scenarios of modification operations: delete,
> update, replace, - yet it also provides one with ability to extract the
> modified data and not only. The problem is that this implementation involves
> a repeated lookup for the same item: first with "lookup", then with "update"
> - but the "containers" library exposes no functionality to get around that.
> So I suggest to implement an efficient version of "withItem" in the library.
>
> This function turns out to be far more generalized than any of the currently
> present in the library, so it can become a basic building block for all
> sorts of modifying functions, including all the already existing ones, e.g.:
>
>    alter :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a
>    alter f k = snd . withItem k (\i -> ((), f i))
>
>    delete :: Ord k => k -> Map k a -> Map k a
>    delete k = snd . withItem k (const ((), Nothing))
>
>    updateLookupWithKey ::
>      (Ord k) =>
>      (k -> a -> Maybe a) ->
>      k ->
>      Map k a -> (Maybe a, Map k a)
>    updateLookupWithKey f k =
>      withItem k $ \i -> case i of
>        Just i -> case f k i of
>          Nothing -> (Just i, Nothing)
>          Just i' -> (Just i', Just i')
>        _ -> (Nothing, Nothing)
>
> You can see how easy it makes to achieve any sort of specialized
> functionality. So, besides the evident benefits, this function can also
> become a replacement for a whole list of confusing specialized ones, thus
> greatly lightening the library.
>
> You might have also noticed how this function is based around the standard
> "a -> (b, a)" pattern of the "State" monad, thus making it easily composable
> with it using the "state" and "runState" functions.
>
> Summarizing, my suggestions are:
>
>    1. Implement an efficient version of "withItem" for lazy and strict
> versions of "Map" and "IntMap".
>
>    2. Change the order of parameters from "lambda -> key" to "key ->
> lambda". The "updateLookupWithKey" example implementation shows how this
> change can be benefitial.
>
>    3. Begin the deprecation process of the following functions: insertWith,
> insertWithKey, insertLookupWithKey, adjust, adjustWithKey, update,
> updateWithKey, updateLookupWithKey, alter.
>
> A deadline for discussion is set to 6 weeks.
>
> For a formatted version of this message please visit
> https://github.com/haskell/containers/issues/28.
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>

This is a good function, but there's a simple generalization:

    at :: (Ord k, Functor f) => k -> (Maybe i -> f (Maybe i)) -> M.Map
k i -> f (M.Map k i)

`lens` has this function with this name -- see
<https://github.com/ekmett/lens/blob/master/src/Control/Lens/At.hs#L561>
-- though it's just implemented in terms of the primitive Map
operations. The generalized version gives you a van Laarhoven lens,
though you don't have to care about that -- it's strictly more general
than the type you gave. With the right choice for the Functor you can
recover `withItem` ((r,)), `alter` (Identity), `lookup` (Const r),
etc. (`lens` has a bunch of utility functions for exactly this
purpose, but as you pointed out, you can easily write them on your
own).

I don't think all the functions you mentioned should be deprecated;
many of them are convenient by themselves. It's possible that some of
the more obscure ones are made unnecessary by the more general
function, but almost certainly not all of them -- most were already
"unnecessary", after all. Similarly, passing the key first is good for
some types but not for others. adjustWithKey's type has an fmap-like
shape -- (k -> a -> a) -> (k -> Map k a -> Map k a) -- and that sort
of thing is probably worthwhile. So I think 2/3 should be a separate
proposal.

(Also, I think Edward Kmett mentioned something about efficient
versions of this function having some unexpected trickiness, but I
don't remember exactly.)

Other than that, +1 to adding a function like this.

    Shachaf



More information about the Libraries mailing list