Proposal: add traverseWithKey to Data.Map

Hi Haskellers, I propose to add a new function, traverseWithKey, to Data.Map: """ -- | /O(n)/. -- @'traverseWithKey' f s == 'fmap' 'fromList' ('traverse' (\(k, v) -> fmap ((,) k) (f k v)) ('toList' s))@ -- That is, behaves exactly like a regular 'traverse' except that the traversing -- function also has access to the key associated with a value. -- -- > traverseWithKey (\k v -> if k + v < 10 then Just (v + 1) else Nothing) (fromList [(1, 2), (5, 4)]) == Just (fromList [(1, 3), (5, 5)]) -- > traverseWithKey (\k v -> if k + v < 10 then Just (v + 1) else Nothing) (fromList [(5, 5)]) == Nothing traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map k b) """ This is a rather useful function, and if we define it in SATed style and with an INLINE pragma (as in my attached patch), GHC can generate really good code for it at use sites. While the utility of a traversal function like this is clear, we can also use it to define other useful combinators such as mapWithKeyM/mapMWithKey. It can also be used to define efficient right/left with-key-folds on Map that avoid a problem in GHC's strictness analyser. For example, this function: """ c m = M.foldlWithKey (\k v (a, b) -> if k + v > 2 then (a, b) else (b, a)) (0, 1) m """ Generates a loop which allocates a new pair on every iteration. (The situation is the same with foldrWithKey.). If we have traverseWithKey, we can work around it by defining an optimised fold for accumulators that are pairs: """ newtype State2L s1 s2 a = State2L { unState2L :: s1 -> s2 -> (s1, s2) } instance Functor (State2L s1 s2) where fmap _ = State2L . unState2L instance Applicative (State2L s1 s2) where pure _ = State2L (,) mf <*> mx = State2L $ \s1 s2 -> case unState2L mf s1 s2 of (s1, s2) -> unState2L mx s1 s2 -- NB: left side first {-# INLINE foldl2WithKey' #-} foldl2WithKey' :: ((a1, a2) -> k -> v -> (a1, a2)) -> (a1, a2) -> M.Map k v -> (a1, a2) foldl2WithKey' f (a1, a2) kvs = unState2L (traverseWithKey (\k v -> State2L $ \a1 a2 -> f (a1, a2) k v) kvs) a1 a2 """ The loop resulting from foldl2WithKey' does not allocate any pairs when compiled with current GHCs. Of course, traverseWithKey is also sufficiently general that it can implement many functions already exported from Data.Map (with varying degrees of efficiency), such as find{Max,Min}, mapWithKey, fold{r,l}WithKey, withAccumWithKey and mapAccumL. There is precedence for the "traverseWithKey" name: 1. "unordered-containers" has a function with exactly this name and compatible type, used for HashMaps [1] 2. The "keys" package defines a type class TraversableWithKey with a compatible type [2] This is an API addition so breakage from the change should be low. Overall this should be a low risk addition to the interface which adds a lot of flexibility. What do you think? Deadline: 2 weeks (i.e. 28th March) Patch is attached, assuming it doesn't get stripped by the mailing list manager. Cheers, Max [1] http://hackage.haskell.org/packages/archive/unordered-containers/0.1.1.0/doc... [2] http://hackage.haskell.org/packages/archive/keys/0.1.0/doc/html/src/Data-Key...

On Wed, Mar 14, 2012 at 4:28 PM, Max Bolingbroke
This is an API addition so breakage from the change should be low. Overall this should be a low risk addition to the interface which adds a lot of flexibility. What do you think?
Deadline: 2 weeks (i.e. 28th March)
+1
Patch is attached, assuming it doesn't get stripped by the mailing list manager.
Could you please open a pull request on GitHub for the change (at least if it's accepted), it makes it easier for us to track it and not forget about it. -- Johan

+1
This will let me get rid of the horrible traverseWithKey implementation I
have for Data.Map in my 'keys' package!
-Edward
On Wed, Mar 14, 2012 at 8:29 PM, Conrad Parker
On 15 March 2012 07:28, Max Bolingbroke
wrote: Hi Haskellers,
I propose to add a new function, traverseWithKey, to Data.Map:
+1
Conrad.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 14 March 2012 23:28, Max Bolingbroke
Hi Haskellers,
I propose to add a new function, traverseWithKey, to Data.Map:
+1 A few minor comments below.
""" -- | /O(n)/. -- @'traverseWithKey' f s == 'fmap' 'fromList' ('traverse' (\(k, v) -> fmap ((,) k) (f k v)) ('toList' s))@
Since we're assuming that the users already knows Applicative, I believe the following formulation would be easier to read: fromList <$> traverse (\(k, v) -> (,) k <$> f k v) (toList m) I agree with the use of '==' rather than '=' since the above definition has an Ord constraint on the key, but this function does not. You could get that by using fromDistinctAscList but that would defeat the purpose of giving an easy to understand definition.
-- That is, behaves exactly like a regular 'traverse' except that the traversing -- function also has access to the key associated with a value. -- -- > traverseWithKey (\k v -> if k + v < 10 then Just (v + 1) else Nothing) (fromList [(1, 2), (5, 4)]) == Just (fromList [(1, 3), (5, 5)]) -- > traverseWithKey (\k v -> if k + v < 10 then Just (v + 1) else Nothing) (fromList [(5, 5)]) == Nothing traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map k b) """
I think this example could be a bit confusing because both key and value have the same type. I suggest the following example: traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (3, 'e')]) == Just (fromList [(1,'b'),(3,'f')])
This is a rather useful function, and if we define it in SATed style and with an INLINE pragma (as in my attached patch), GHC can generate really good code for it at use sites.
I think we're moving away from INLINE in favour of INLIN[E]ABLE. In this case it seems fine since it's just building a closure + tailcalling which probably would get optimised away. Still, would using INLINEABLE have a drawback in this case?

On Thu, Mar 15, 2012 at 8:47 AM, Thomas Schilling
This is a rather useful function, and if we define it in SATed style and with an INLINE pragma (as in my attached patch), GHC can generate really good code for it at use sites.
I think we're moving away from INLINE in favour of INLIN[E]ABLE. In this case it seems fine since it's just building a closure + tailcalling which probably would get optimised away. Still, would using INLINEABLE have a drawback in this case?
We've moved to INLINABLE for non-higher order functions with type class constraints. GHC does a great job with those (specializing them at the call site.) For HOF that call the higher order argument e.g. O(n) times, INLINE still works better. It removes both allocation of the closure and O(n) indirect calls. -- Johan

Hi,
This is a rather useful function, and if we define it in SATed style and with an INLINE pragma (as in my attached patch), GHC can generate really good code for it at use sites.
I think we're moving away from INLINE in favour of INLIN[E]ABLE. In this case it seems fine since it's just building a closure + tailcalling which probably would get optimised away. Still, would using INLINEABLE have a drawback in this case?
Reasonably small high order functions are marked INLINE, for example all folds, and I would consider traverseWithKey to be reasonably small. This allows to inline all calls to f in traverseWithKey, which can be a huge win (for example, if f only uses primops). Cheers, Milan

On 15 March 2012 15:47, Thomas Schilling
A few minor comments below.
Thanks for your documentation suggestions. I will certainly incorporate them into the final patch.
I think we're moving away from INLINE in favour of INLIN[E]ABLE. In this case it seems fine since it's just building a closure + tailcalling which probably would get optimised away. Still, would using INLINEABLE have a drawback in this case?
To my mind, INLINEABLE really serves a different purpose than INLINE: it doesn't really force GHC to inline something, just expose the unfolding. We still need to force INLINE for SATed functions in order to achieve actual function specialisation. I think the other replies to the list elaborate on this point. Cheers, Max

On 14 March 2012 23:28, Max Bolingbroke
I propose to add a new function, traverseWithKey, to Data.Map:
This proposal has passed (with no opposing votes), with the following provisos: * The function should be added to IntMap as well * The documentation could be improved I've submitted a pull request incorporating both those changes to the upstream at https://github.com/haskell/containers/pull/10 Thanks Max

LGTM
On 30 March 2012 14:59, Max Bolingbroke
On 14 March 2012 23:28, Max Bolingbroke
wrote: I propose to add a new function, traverseWithKey, to Data.Map:
This proposal has passed (with no opposing votes), with the following provisos: * The function should be added to IntMap as well * The documentation could be improved
I've submitted a pull request incorporating both those changes to the upstream at https://github.com/haskell/containers/pull/10
Thanks
Max
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Push the envelope. Watch it bend.
participants (6)
-
Conrad Parker
-
Edward Kmett
-
Johan Tibell
-
Max Bolingbroke
-
Milan Straka
-
Thomas Schilling