A single general modification function for Map and IntMap proposal

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

On Tue, 30 Apr 2013 17:18:48 +0400 Nikita Volkov
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')
That's lens' At. http://hackage.haskell.org/packages/archive/lens/latest/doc/html/Control-Len...

On Tue, Apr 30, 2013 at 6:18 AM, Nikita Volkov
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-...
- 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@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

Hi all,
-----Original message----- From: Nikita Volkov
Sent: 30 Apr 2013, 17:18 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')
last time we talked about adding lens :: k -> Map k a -> (Maybe a -> Map k a, Maybe a) the performance of the direct implementation was actually worse than using lookup+insert or such, see the thread http://www.haskell.org/pipermail/libraries/2012-January/017423.html and the benchmark results at http://www.haskell.org/pipermail/libraries/2012-January/017435.html 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.
1. Implement an efficient version of "withItem" for lazy and strict versions of "Map" and "IntMap".
Maybe we will need a benchmark to see whether withItem is really faster than combination of lookup+update.
3. Begin the deprecation process of the following functions: insertWith, insertWithKey, insertLookupWithKey, adjust, adjustWithKey, update, updateWithKey, updateLookupWithKey, alter.
I am against deprecating insertWith, insertWithKey, updateWithKey, updateWithKey, because they are useful. I am against deprecating adjust, adjustWithKey and alter, mostly because of compatibility reasons, although I agree that their name is not descriptive. I am indifferent about insertLookupWithKey and updateLookupWithKey. It would be nice to show that their implementation is really faster than lookup+insert / lookup+update combo. Cheers, Milan

On Tue, Apr 30, 2013 at 8:20 AM, Milan Straka
Hi all,
-----Original message----- From: Nikita Volkov
Sent: 30 Apr 2013, 17:18 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')
last time we talked about adding lens :: k -> Map k a -> (Maybe a -> Map k a, Maybe a) the performance of the direct implementation was actually worse than using lookup+insert or such, see the thread http://www.haskell.org/pipermail/libraries/2012-January/017423.html and the benchmark results at http://www.haskell.org/pipermail/libraries/2012-January/017435.html
If this is a good API, and the direct implementation is slower than an indirect implementation in terms of lookup+insert+delete, then the indirect implementation should be exported. Keep in mind that this operation is just `alterM` (except generalized to Functor -- `alterF`?). 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.
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. :-) (Note that e.g. adjustF :: (Ord k, Applicative f) => k -> (a -> f a) -> M.Map k a -> f (M.Map k a) can just be \k -> alterF k . traverse just as with alter/adjust. )
1. Implement an efficient version of "withItem" for lazy and strict versions of "Map" and "IntMap".
Maybe we will need a benchmark to see whether withItem is really faster than combination of lookup+update.
3. Begin the deprecation process of the following functions: insertWith, insertWithKey, insertLookupWithKey, adjust, adjustWithKey, update, updateWithKey, updateLookupWithKey, alter.
I am against deprecating insertWith, insertWithKey, updateWithKey, updateWithKey, because they are useful.
I am against deprecating adjust, adjustWithKey and alter, mostly because of compatibility reasons, although I agree that their name is not descriptive.
I am indifferent about insertLookupWithKey and updateLookupWithKey. It would be nice to show that their implementation is really faster than lookup+insert / lookup+update combo.
Shachaf

I find generalizing even more with "at" or "alterF" a very interesting
suggestion and I'm fine with either title. I however was not able to trace
any practical use of it, because in my imagination the original proposal
covered all scenarios, so it'd be helpful to see some examples. Also since
the performance turned out to be such an intricate issue in this case I
think it is worth benchmarking both the functorial and the simple version.
But either way I like the idea.
I also want to highlight the expressed idea that either version of this
function should make it into the library no matter whether we're able to
come up with an efficient implementation, since those functions also
provide another important benefit by abstracting over a common pattern,
thus simplifying the client code.
Schachaf, concerning your implementation. Great! It looks like a beginning
of an implementation process. What do you think about posting it with the
benchmark as a branch of your fork of "containers" project on GitHub? This
way other participants will be able to fork from you and continue on with
experiments, so it'll be easier for us to manage code and to keep in sync.
2013/5/1 Shachaf Ben-Kiki
Hi all,
-----Original message----- From: Nikita Volkov
Sent: 30 Apr 2013, 17:18 Because of the above I have very often found myself in requirement for
On Tue, Apr 30, 2013 at 8:20 AM, Milan Straka
wrote: 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')
last time we talked about adding lens :: k -> Map k a -> (Maybe a -> Map k a, Maybe a) the performance of the direct implementation was actually worse than using lookup+insert or such, see the thread http://www.haskell.org/pipermail/libraries/2012-January/017423.html and the benchmark results at http://www.haskell.org/pipermail/libraries/2012-January/017435.html
If this is a good API, and the direct implementation is slower than an indirect implementation in terms of lookup+insert+delete, then the indirect implementation should be exported. Keep in mind that this operation is just `alterM` (except generalized to Functor -- `alterF`?).
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.
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. :-)
(Note that e.g. adjustF :: (Ord k, Applicative f) => k -> (a -> f a) -> M.Map k a -> f (M.Map k a) can just be \k -> alterF k . traverse just as with alter/adjust. )
1. Implement an efficient version of "withItem" for lazy and strict
versions of "Map" and "IntMap".
Maybe we will need a benchmark to see whether withItem is really faster than combination of lookup+update.
3. Begin the deprecation process of the following functions:
insertWith, insertWithKey, insertLookupWithKey, adjust, adjustWithKey, update, updateWithKey, updateLookupWithKey, alter.
I am against deprecating insertWith, insertWithKey, updateWithKey, updateWithKey, because they are useful.
I am against deprecating adjust, adjustWithKey and alter, mostly because of compatibility reasons, although I agree that their name is not descriptive.
I am indifferent about insertLookupWithKey and updateLookupWithKey. It would be nice to show that their implementation is really faster than lookup+insert / lookup+update combo.
Shachaf

Hi all,
-----Original message----- From: Shachaf Ben-Kiki
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

Hello guys! A deadline of a discusssion on this has been reached. To review the discussion you can visit the archives. Following is a summarization. 1. Following is an implementation proposed by Schachaf Ben-Kiki, which in a combination with an `INLINABLE` pragma produces very impressive results by making even the primitive operations reimplemented in terms of it perform better: insert: ~ +5% increase using alterF delete: ~ +10% increase using alterF 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) 2. `alterF` seems to be a mutually accepted title for the function 3. There was one downvote for implementing `alterF` with a changed order of parameters to "key -> lambda", as compared to "lambda -> key" of other modification functions in the library. Others seemed to be neutral about it. The implementation above is in that changed order. After some thinking my vote can be counted as a downvote too on that. 4. People seem to be indifferent to functions `insertLookupWithKey` and `updateLookupWithKey`, concerning their deprecation. The other proposed functions from the list following, however, generally are not wished to deprecate: insertWith, insertWithKey, adjust, adjustWithKey, update, updateWithKey, alter. Best regards, Nikita Volkov

Hi all,
-----Original message----- From: Nikita Volkov
Sent: 19 Jun 2013, 13:47 Hello guys!
A deadline of a discusssion on this has been reached. To review the discussion you can visit the archives. Following is a summarization.
1. Following is an implementation proposed by Schachaf Ben-Kiki, which in a combination with an `INLINABLE` pragma produces very impressive results by making even the primitive operations reimplemented in terms of it perform better:
insert: ~ +5% increase using alterF delete: ~ +10% increase using alterF
I probably did not make myself clear enough -- the insert reimplemented with alterF runs 5% slower (the running time is increased by 5%) and similarly for delete.
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)
2. `alterF` seems to be a mutually accepted title for the function
3. There was one downvote for implementing `alterF` with a changed order of parameters to "key -> lambda", as compared to "lambda -> key" of other modification functions in the library. Others seemed to be neutral about it. The implementation above is in that changed order. After some thinking my vote can be counted as a downvote too on that.
Looking at alterF, I think we should be consistent with the rest of the API and use lambda -> key. Cheers, Milan

Flipping to lambda -> key means that you cannot compose these for nested lookups.
alterF in its current form is a valid lens.
A very common idiom from the lens community is to do lookups in nested maps with the equivalent of:
alterF key1 . traverse . alterF key2
There is a similar idiom for doing inserts into nested maps as well.
Flipping it means any composition of alterF incurs lots of flips.
-Edward
On Jun 19, 2013, at 8:27 AM, Milan Straka
Hi all,
-----Original message----- From: Nikita Volkov
Sent: 19 Jun 2013, 13:47 Hello guys!
A deadline of a discusssion on this has been reached. To review the discussion you can visit the archives. Following is a summarization.
1. Following is an implementation proposed by Schachaf Ben-Kiki, which in a combination with an `INLINABLE` pragma produces very impressive results by making even the primitive operations reimplemented in terms of it perform better:
insert: ~ +5% increase using alterF delete: ~ +10% increase using alterF
I probably did not make myself clear enough -- the insert reimplemented with alterF runs 5% slower (the running time is increased by 5%) and similarly for delete.
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)
2. `alterF` seems to be a mutually accepted title for the function
3. There was one downvote for implementing `alterF` with a changed order of parameters to "key -> lambda", as compared to "lambda -> key" of other modification functions in the library. Others seemed to be neutral about it. The implementation above is in that changed order. After some thinking my vote can be counted as a downvote too on that.
Looking at alterF, I think we should be consistent with the rest of the API and use lambda -> key.
Cheers, Milan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I think consistency with the rest of the Map API is more important than
ease of use with lens/nested compositions. I agree that the current arg
ordering is often inconvenient, but having some functions ordered one way
and others a different way seems a very poor decision.
John L.
On Wed, Jun 19, 2013 at 9:14 PM, Edward A Kmett
Flipping to lambda -> key means that you cannot compose these for nested lookups.
alterF in its current form is a valid lens.
A very common idiom from the lens community is to do lookups in nested maps with the equivalent of:
alterF key1 . traverse . alterF key2
There is a similar idiom for doing inserts into nested maps as well.
Flipping it means any composition of alterF incurs lots of flips.
-Edward
On Jun 19, 2013, at 8:27 AM, Milan Straka
wrote: Hi all,
-----Original message----- From: Nikita Volkov
Sent: 19 Jun 2013, 13:47 Hello guys!
A deadline of a discusssion on this has been reached. To review the discussion you can visit the archives. Following is a summarization.
1. Following is an implementation proposed by Schachaf Ben-Kiki, which in a combination with an `INLINABLE` pragma produces very impressive results by making even the primitive operations reimplemented in terms of it perform better:
insert: ~ +5% increase using alterF delete: ~ +10% increase using alterF
I probably did not make myself clear enough -- the insert reimplemented with alterF runs 5% slower (the running time is increased by 5%) and similarly for delete.
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)
2. `alterF` seems to be a mutually accepted title for the function
3. There was one downvote for implementing `alterF` with a changed order of parameters to "key -> lambda", as compared to "lambda -> key" of other modification functions in the library. Others seemed to be neutral about it. The implementation above is in that changed order. After some thinking my vote can be counted as a downvote too on that.
Looking at alterF, I think we should be consistent with the rest of the API and use lambda -> key.
Cheers, Milan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+1 for the key -> lambda form. Even disregarding lens, compositionality is extremely important. Not to mention which, the key -> lambda form feels much more natural even on its own. You provide an "index" and get back a function that lifts element modifications to map modifications. The only lambda -> key functions I see in the current API are the insertWith family and "alter". I think the parameter order on "alter" is backwards as well (and maybe we can eliminate it in time now that we have alterF? I suspect the current version is fairly rarely used anyway). And insertWith is hardly analogous. Meanwhile, if we look at "member", "lookup", "insert", etc, the key comes first, which is very useful. In general, I expect the key -> lambda version will be much more commonly used, since it matches how one would tend to think of alterF (creating a map transformer, as opposed to applying a transformation, but not yet knowing where to do so). --G On 6/19/13 9:26 PM, John Lato wrote:
I think consistency with the rest of the Map API is more important than ease of use with lens/nested compositions. I agree that the current arg ordering is often inconvenient, but having some functions ordered one way and others a different way seems a very poor decision.
John L.
On Wed, Jun 19, 2013 at 9:14 PM, Edward A Kmett
mailto:ekmett@gmail.com> wrote: Flipping to lambda -> key means that you cannot compose these for nested lookups.
alterF in its current form is a valid lens.
A very common idiom from the lens community is to do lookups in nested maps with the equivalent of:
alterF key1 . traverse . alterF key2
There is a similar idiom for doing inserts into nested maps as well.
Flipping it means any composition of alterF incurs lots of flips.
-Edward
On Jun 19, 2013, at 8:27 AM, Milan Straka
mailto:fox@ucw.cz> wrote: > Hi all, > >> -----Original message----- >> From: Nikita Volkov
mailto:nikita.y.volkov@gmail.com> >> Sent: 19 Jun 2013, 13:47 >> >> Hello guys! >> >> A deadline of a discusssion on this has been reached. To review the discussion you can visit the archives. Following is a summarization. >> >> 1. Following is an implementation proposed by Schachaf Ben-Kiki, which in a combination with an `INLINABLE` pragma produces very impressive results by making even the primitive operations reimplemented in terms of it perform better: >> >> insert: ~ +5% increase using alterF >> delete: ~ +10% increase using alterF > > I probably did not make myself clear enough -- the insert reimplemented > with alterF runs 5% slower (the running time is increased by 5%) and > similarly for delete. > >> 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) >> >> 2. `alterF` seems to be a mutually accepted title for the function >> >> 3. There was one downvote for implementing `alterF` with a changed order of parameters to "key -> lambda", as compared to "lambda -> key" of other modification functions in the library. Others seemed to be neutral about it. The implementation above is in that changed order. After some thinking my vote can be counted as a downvote too on that. > > Looking at alterF, I think we should be consistent with the rest of the > API and use lambda -> key. > > > Cheers, > Milan > > _______________________________________________ > Libraries mailing list > Libraries@haskell.org mailto:Libraries@haskell.org > http://www.haskell.org/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

As I mentioned, I agree that the current ordering is wrong. But there are
also the adjust and update families of functions. I think there's much
more precedent for the lambda -> key order than you imply. But I suppose
since they're all to be deprecated (I think that's part of the proposal?)
we don't need to perpetuate their mistakes.
(FWIW insertWith is one of the functions I would rather change. The
argument order always feels backwards to me.)
On Thu, Jun 20, 2013 at 9:40 AM, Gershom Bazerman
+1 for the key -> lambda form. Even disregarding lens, compositionality is extremely important. Not to mention which, the key -> lambda form feels much more natural even on its own. You provide an "index" and get back a function that lifts element modifications to map modifications.
The only lambda -> key functions I see in the current API are the insertWith family and "alter". I think the parameter order on "alter" is backwards as well (and maybe we can eliminate it in time now that we have alterF? I suspect the current version is fairly rarely used anyway). And insertWith is hardly analogous.
Meanwhile, if we look at "member", "lookup", "insert", etc, the key comes first, which is very useful.
In general, I expect the key -> lambda version will be much more commonly used, since it matches how one would tend to think of alterF (creating a map transformer, as opposed to applying a transformation, but not yet knowing where to do so).
--G
On 6/19/13 9:26 PM, John Lato wrote:
I think consistency with the rest of the Map API is more important than ease of use with lens/nested compositions. I agree that the current arg ordering is often inconvenient, but having some functions ordered one way and others a different way seems a very poor decision.
John L.
On Wed, Jun 19, 2013 at 9:14 PM, Edward A Kmett
wrote: Flipping to lambda -> key means that you cannot compose these for nested lookups.
alterF in its current form is a valid lens.
A very common idiom from the lens community is to do lookups in nested maps with the equivalent of:
alterF key1 . traverse . alterF key2
There is a similar idiom for doing inserts into nested maps as well.
Flipping it means any composition of alterF incurs lots of flips.
-Edward
On Jun 19, 2013, at 8:27 AM, Milan Straka
wrote: Hi all,
-----Original message----- From: Nikita Volkov
Sent: 19 Jun 2013, 13:47 Hello guys!
A deadline of a discusssion on this has been reached. To review the discussion you can visit the archives. Following is a summarization.
1. Following is an implementation proposed by Schachaf Ben-Kiki, which in a combination with an `INLINABLE` pragma produces very impressive results by making even the primitive operations reimplemented in terms of it perform better:
insert: ~ +5% increase using alterF delete: ~ +10% increase using alterF
I probably did not make myself clear enough -- the insert reimplemented with alterF runs 5% slower (the running time is increased by 5%) and similarly for delete.
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)
2. `alterF` seems to be a mutually accepted title for the function
3. There was one downvote for implementing `alterF` with a changed order of parameters to "key -> lambda", as compared to "lambda -> key" of other modification functions in the library. Others seemed to be neutral about it. The implementation above is in that changed order. After some thinking my vote can be counted as a downvote too on that.
Looking at alterF, I think we should be consistent with the rest of the API and use lambda -> key.
Cheers, Milan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing listLibraries@haskell.orghttp://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I think consistency with the rest of the Map API is more important than ease of use with lens/nested compositions. I agree that the current arg ordering is often inconvenient, but having some functions ordered one way and others a different way seems a very poor decision.
It's worth reminding that an important part of this proposal was to begin a deprecation process of all functions that become redundant in presence of `alterF`, and by accident it so happened that they were the only ones introducing the parameter order conflict. Deprecating them we acknowledge the fact that there's something wrong about them and that there's no need to be consistent with that. Here's a quote from original proposal: 2. Change the order of parameters from "lambda -> key" to "key -> lambda". 3. Begin the deprecation process of the following functions: insertWith, insertWithKey, insertLookupWithKey, adjust, adjustWithKey, update, updateWithKey, updateLookupWithKey, alter.
+1 for the key -> lambda form. Even disregarding lens, compositionality is extremely important. Not to mention which, the key -> lambda form feels much more natural even on its own. You provide an "index" and get back a function that lifts element modifications to map modifications.
That's exactly what I had in mind when proposed this. I however am now conflicted about that, since I see the "lambda -> key" order to be compositional too in its own way: you provide a lambda and get a function ready to modify a map at a key in that specific way.

Okay. It's settled about `alterF`, there however seems a disagreement to have risen on the "key-lambda" and deprecation proposals, so I am starting a vote. Following are stats on the vote we have so far. A "key-lambda" proposal For: 2 Edward Kmett, Gershom Bazerman Against: 1 Johan Tibell Deprecate redundant functions For: 1 Nikita Volkov Against: 3 Schachaf Ben-Kiki, Milan Straka, Johan Tibell, I'm asking those who haven't voted on both proposals to vote again. Correction on old or miscounted votes is also welcome. Concerning the deprecation proposal, comments and suggestions are welcome too.

On 20/06/13 10:58, Nikita Volkov wrote:
Okay. It's settled about `alterF` there however seems a disagreement to have risen on the "key-lambda" and deprecation proposals, so I am starting a vote.
Following are stats on the vote we have so far.
*A "key-lambda" proposal*
+1
*Deprecate redundant functions*
3. Begin the deprecation process of the following functions: insertWith, insertWithKey, insertLookupWithKey, adjust, adjustWithKey, update, updateWithKey, updateLookupWithKey, alter.
This list is too long. I am neutral about deprecating alter, adjust and update. But insertWith is used very often, sometimes also partially applied to just the combining function. It would be much more inconvenient to have to use alterF. So -1 to deprecating this whole list. Twan

I'm also -1 on removing the "redundant functions" as they are often only
really "redundant" in the presence of appropriate functors from
transformers and very awkward coding styles or when using lens.
On Thu, Jun 20, 2013 at 4:58 AM, Nikita Volkov
Okay. It's settled about `alterF`http://haskell.1045720.n5.nabble.com/A-single-general-modification-function-..., there however seems a disagreement to have risen on the "key-lambda" and deprecation proposals, so I am starting a vote.
Following are stats on the vote we have so far.
*A "key-lambda" proposal*
For: 2
Edward Kmett, Gershom Bazerman
Against: 1
Johan Tibell
* * *Deprecate redundant functions*
For: 1
Nikita Volkov
Against: 3
Schachaf Ben-Kiki, Milan Straka, Johan Tibell,
I'm asking those who haven't voted on both proposals to vote again. Correction on old or miscounted votes is also welcome. Concerning the deprecation proposal, comments and suggestions are welcome too.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Dear haskellers, Dne 06/19/2013 02:27 PM, Milan Straka napsal(a):
Hi all,
-----Original message----- From: Nikita Volkov
Sent: 19 Jun 2013, 13:47 Hello guys!
A deadline of a discusssion on this has been reached. To review the discussion you can visit the archives. Following is a summarization.
1. Following is an implementation proposed by Schachaf Ben-Kiki, which in a combination with an `INLINABLE` pragma produces very impressive results by making even the primitive operations reimplemented in terms of it perform better:
insert: ~ +5% increase using alterF delete: ~ +10% increase using alterF I probably did not make myself clear enough -- the insert reimplemented with alterF runs 5% slower (the running time is increased by 5%) and similarly for delete.
I was playing with |alterF| to implement |-- If an element equal to `x` is present, return it. If not, add `x` to the cache. cacheLookup :: (Ord a) => a ->State (M.Map a a) a cacheLookup x = state (alterF x f) where f (Just y) = (y,Just y) fNothing = (x,Just x)| and I realized that in the first case |alterF| needlessly reinserts |y| into the map, which introduces unnecessary traversal. So my suggestion for discussion is to define |alterF| as |data Alter a =Keep |Remove |Replace a deriving (Read,Show,Eq,Ord) alterF :: (Functor f,Ord k) => k -> (Maybe a -> f (Alter a)) -> (Map k a -> f (Map k a)) -- ^^^^^| where |Alter| gives the action to be performed on the map. It's just as |Maybe|, but it adds |Keep| to keep the map intact, if one neither wants to replace an element nor to remove it. Another little benefit is that it's more descriptive and makes |alterF| slightly more accessible to users. Like in my case |cacheLookup| becomes more readable: |cacheLookup x = state (alterF x f) where f (Just x') = (x',Replace x') fNothing = (x,Keep)| It probably won't affect performance for the standard functions defined using |alterF|, but in cases like this it could help. Best regards, Petr

On Tue, Apr 30, 2013 at 6:18 AM, Nikita Volkov
Summarizing, my suggestions are:
1. Implement an efficient version of "withItem" for lazy and strict versions of "Map" and "IntMap".
I think this makes sense as the function makes it possible to more efficiently express something (that you previously had to express using a combination of insert and lookup). 2. Change the order of parameters from "lambda -> key" to "key ->
lambda". The "updateLookupWithKey" example implementation shows how this change can be benefitial.
I'm vary of breaking user code if there isn't a large benefit.
3. Begin the deprecation process of the following functions: insertWith, insertWithKey, insertLookupWithKey, adjust, adjustWithKey, update, updateWithKey, updateLookupWithKey, alter.
We discussed using a function like withItem to implement these functions before. While we'd really like to, it was shown to be too slow. In other words, we can't implement these functions in terms of withItem. Also, I don't see the point of removing them (even after a long deprecation cycle). It will just break lots of code with little benefit to users. -- Johan
participants (11)
-
Edward A Kmett
-
Edward Kmett
-
Gershom Bazerman
-
Johan Tibell
-
John Lato
-
kudah
-
Milan Straka
-
Nikita Volkov
-
Petr Pudlák
-
Shachaf Ben-Kiki
-
Twan van Laarhoven