Minor containers API changes

Hi everyone, I have several containers API changes propositions. First five are an attempt to unify the API of different structures. The documentation states IntMap is Map replacement and IntSet is Set replacement, but there are several shortcomings: 1) `{Map,Set}.deleteMin empty` return `empty` `{IntMap,IntSet}.deleteMin empty` trigger `error "Cannot delete in empty..."` Solutions: (a) make `{Map,Set}.deleteMin empty` throw error (b) make `{IntMap,IntSet}.deleteMin empty` return empty I vote for (b), because (a) could cause unexpected runtime errors. Additionally, I expect very little programs depend on `{IntMap,IntSet}.deleteMin empty` causing runtime error. 2) `Map.deleteFind{Min,Max}` has type `Map k a -> ((k,a),Map k a)` `IntMap.deleteFind{Min,Max}` has type `IntMap a -> (a, IntMap a)` Solutions: (a) make the Map variant return only values (b) make the IntMap variant return both key and value I vote for (b), because it generalizes the original functionality. 3) `Map.update{Min,Max}` is given a function of type `(a -> Maybe a)` `Map.update{Min,Max}WithKey` is given a function of type `(key -> a -> Maybe a)` `IntMap.update{Min,Max}` is given a function of type `(a -> a)` `IntMap.update{Min,Max}WithKey` is given a function of type `(key -> a -> a)` Solutions: (a) the Map variants would get a function of type `[key -> ] a -> a` (b) the IntMap variants would get a function of type `[key -> ] a -> Maybe a` I vote for (b), because it generalizes the original functionality. 4) The functions `mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a` have no IntMap correspondents. Both `mapKeys` and `mapKeysWith` can be defined by the user without loss of performance. Solutions: (a) deprecate the `mapKeys*` methods from Map (b) add the `mapKeys*` methods to IntMap. I vote for (a). These methods are all trivial compositions and all but all mapKeysMonotonic are defined as such. For mapKeysMonotonic, a trivial composition with the same asymptotic complexity exists. Also, if these were added to IntMap, none of them would have better performance then user-defined methods. 5) `toDescList` exists in Map, but not in IntMap, Set or IntSet. Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet. I have no strong opinion here. The `toDescList` can be trivially expressed as left fold. But it is currently a subject to list fusion. To vote for (a). Several other changes follow: 6) Result of discussion around http://hackage.haskell.org/trac/ghc/ticket/5242 Add `Map.fromSet :: (key -> a) -> Set key -> Map key a` `IntMap.fromSet :: (Int -> a) -> IntSet -> IntMap a` The implementation would exploit same structure of map and set (leave the shape of the original tree/trie, just adding values). Cons: fromSet is a trivial composition: fromSet f = Map.fromDistinctAscList . map (\k -> (k, f k)) . Set.toAscList This can be defined by the user and is asymptotically optimal. Pro: performance. Also the performance of keysSet would improve, if the map can use data constructors of set. I vote for adding these methods. 7) Improve the generality of intersectionWith. Currently the Map and IntMap define intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c But the combining function is not general enough. Consider two IntMaps storing hashable elements as (hash(element), element). When intersecting elements with the same hash, the intersection can be empty. I propose to change the type of these methods to intersectionWith :: Ord k => (a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c (and appropriately for IntMap). Note that the combining function of differenceWith already has type `(a -> b -> Maybe a)`. Discussion period: 2 weeks Cheers, Milan PS: Sorry for the long email.

On Mon, Nov 28, 2011 at 2:28 PM, Milan Straka
1) `{Map,Set}.deleteMin empty` return `empty` `{IntMap,IntSet}.deleteMin empty` trigger `error "Cannot delete in empty..."`
Solutions: (a) make `{Map,Set}.deleteMin empty` throw error (b) make `{IntMap,IntSet}.deleteMin empty` return empty
I vote for (b), because (a) could cause unexpected runtime errors. Additionally, I expect very little programs depend on `{IntMap,IntSet}.deleteMin empty` causing runtime error.
+1 for (b) as well.
2) `Map.deleteFind{Min,Max}` has type `Map k a -> ((k,a),Map k a)` `IntMap.deleteFind{Min,Max}` has type `IntMap a -> (a, IntMap a)`
Solutions: (a) make the Map variant return only values (b) make the IntMap variant return both key and value
I vote for (b), because it generalizes the original functionality.
+1 for (b) as well.
3) `Map.update{Min,Max}` is given a function of type `(a -> Maybe a)` `Map.update{Min,Max}WithKey` is given a function of type `(key -> a -> Maybe a)` `IntMap.update{Min,Max}` is given a function of type `(a -> a)` `IntMap.update{Min,Max}WithKey` is given a function of type `(key -> a -> a)`
Solutions: (a) the Map variants would get a function of type `[key -> ] a -> a` (b) the IntMap variants would get a function of type `[key -> ] a -> Maybe a`
I vote for (b), because it generalizes the original functionality.
+1 for (b) as well.
4) The functions `mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a` have no IntMap correspondents. Both `mapKeys` and `mapKeysWith` can be defined by the user without loss of performance.
Solutions: (a) deprecate the `mapKeys*` methods from Map (b) add the `mapKeys*` methods to IntMap.
I vote for (a). These methods are all trivial compositions and all but all mapKeysMonotonic are defined as such. For mapKeysMonotonic, a trivial composition with the same asymptotic complexity exists. Also, if these were added to IntMap, none of them would have better performance then user-defined methods.
-1 for (a). I'd rather write 'M.mapKeys f m' than 'M.fromList $ map (\(k,x) -> (f k, x)) $ M.toList m'. +1 for (b).
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet.
Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet.
I have no strong opinion here. The `toDescList` can be trivially expressed as left fold. But it is currently a subject to list fusion. To vote for (a).
-1 for (a). +1 for (b).
Several other changes follow:
6) Result of discussion around http://hackage.haskell.org/trac/ghc/ticket/5242 Add `Map.fromSet :: (key -> a) -> Set key -> Map key a` `IntMap.fromSet :: (Int -> a) -> IntSet -> IntMap a` The implementation would exploit same structure of map and set (leave the shape of the original tree/trie, just adding values).
Cons: fromSet is a trivial composition: fromSet f = Map.fromDistinctAscList . map (\k -> (k, f k)) . Set.toAscList This can be defined by the user and is asymptotically optimal. Pro: performance. Also the performance of keysSet would improve, if the map can use data constructors of set.
I vote for adding these methods.
+1
7) Improve the generality of intersectionWith. Currently the Map and IntMap define intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
But the combining function is not general enough. Consider two IntMaps storing hashable elements as (hash(element), element). When intersecting elements with the same hash, the intersection can be empty.
I propose to change the type of these methods to intersectionWith :: Ord k => (a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c (and appropriately for IntMap).
Note that the combining function of differenceWith already has type `(a -> b -> Maybe a)`.
I have no strong opinions on this =). Thanks! -- Felipe.

On 29 November 2011 03:42, Felipe Almeida Lessa
On Mon, Nov 28, 2011 at 2:28 PM, Milan Straka
wrote: 1) `{Map,Set}.deleteMin empty` return `empty` `{IntMap,IntSet}.deleteMin empty` trigger `error "Cannot delete in empty..."`
Solutions: (a) make `{Map,Set}.deleteMin empty` throw error (b) make `{IntMap,IntSet}.deleteMin empty` return empty
I vote for (b), because (a) could cause unexpected runtime errors. Additionally, I expect very little programs depend on `{IntMap,IntSet}.deleteMin empty` causing runtime error.
+1 for (b) as well.
2) `Map.deleteFind{Min,Max}` has type `Map k a -> ((k,a),Map k a)` `IntMap.deleteFind{Min,Max}` has type `IntMap a -> (a, IntMap a)`
Solutions: (a) make the Map variant return only values (b) make the IntMap variant return both key and value
I vote for (b), because it generalizes the original functionality.
+1 for (b) as well.
3) `Map.update{Min,Max}` is given a function of type `(a -> Maybe a)` `Map.update{Min,Max}WithKey` is given a function of type `(key -> a -> Maybe a)` `IntMap.update{Min,Max}` is given a function of type `(a -> a)` `IntMap.update{Min,Max}WithKey` is given a function of type `(key -> a -> a)`
Solutions: (a) the Map variants would get a function of type `[key -> ] a -> a` (b) the IntMap variants would get a function of type `[key -> ] a -> Maybe a`
I vote for (b), because it generalizes the original functionality.
+1 for (b) as well.
4) The functions `mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a` have no IntMap correspondents. Both `mapKeys` and `mapKeysWith` can be defined by the user without loss of performance.
Solutions: (a) deprecate the `mapKeys*` methods from Map (b) add the `mapKeys*` methods to IntMap.
I vote for (a). These methods are all trivial compositions and all but all mapKeysMonotonic are defined as such. For mapKeysMonotonic, a trivial composition with the same asymptotic complexity exists. Also, if these were added to IntMap, none of them would have better performance then user-defined methods.
-1 for (a). I'd rather write 'M.mapKeys f m' than 'M.fromList $ map (\(k,x) -> (f k, x)) $ M.toList m'.
+1 for (b).
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet.
Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet.
I have no strong opinion here. The `toDescList` can be trivially expressed as left fold. But it is currently a subject to list fusion. To vote for (a).
-1 for (a). +1 for (b).
Several other changes follow:
6) Result of discussion around http://hackage.haskell.org/trac/ghc/ticket/5242 Add `Map.fromSet :: (key -> a) -> Set key -> Map key a` `IntMap.fromSet :: (Int -> a) -> IntSet -> IntMap a` The implementation would exploit same structure of map and set (leave the shape of the original tree/trie, just adding values).
Cons: fromSet is a trivial composition: fromSet f = Map.fromDistinctAscList . map (\k -> (k, f k)) . Set.toAscList This can be defined by the user and is asymptotically optimal. Pro: performance. Also the performance of keysSet would improve, if the map can use data constructors of set.
I vote for adding these methods.
+1
7) Improve the generality of intersectionWith. Currently the Map and IntMap define intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
But the combining function is not general enough. Consider two IntMaps storing hashable elements as (hash(element), element). When intersecting elements with the same hash, the intersection can be empty.
I propose to change the type of these methods to intersectionWith :: Ord k => (a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c (and appropriately for IntMap).
Note that the combining function of differenceWith already has type `(a -> b -> Maybe a)`.
I have no strong opinions on this =).
I (coincidentally! honest!) vote the same as Felipe for all these. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Mon, 28 Nov 2011, Milan Straka wrote:
First five are an attempt to unify the API of different structures. The documentation states IntMap is Map replacement and IntSet is Set replacement, but there are several shortcomings:
1) `{Map,Set}.deleteMin empty` return `empty` `{IntMap,IntSet}.deleteMin empty` trigger `error "Cannot delete in empty..."`
Solutions: (a) make `{Map,Set}.deleteMin empty` throw error (b) make `{IntMap,IntSet}.deleteMin empty` return empty
I vote for (b), because (a) could cause unexpected runtime errors. Additionally, I expect very little programs depend on `{IntMap,IntSet}.deleteMin empty` causing runtime error.
I would like that it is consistent with Map.delete on an empty set. Prelude> Map.delete undefined Map.empty :: Map.Map Char Int fromList [] Looks like a vote for (b).

Hi, I’ll skip on the +1 and only make negative comments, as they are fewer :-) Am Montag, den 28.11.2011, 17:28 +0100 schrieb Milan Straka:
4) The functions `mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a` have no IntMap correspondents. Both `mapKeys` and `mapKeysWith` can be defined by the user without loss of performance.
Solutions: (a) deprecate the `mapKeys*` methods from Map (b) add the `mapKeys*` methods to IntMap.
They seem useful to me to write legible code, therefore I’m in favor of (b). Also, they are used in the wild (random reference): http://darcswatch.nomeata.de/bundles/a3fbac8e4ce65d1426c5d1e0d19a6020f425b5d...
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet.
Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet.
I have no strong opinion here. The `toDescList` can be trivially expressed as left fold. But it is currently a subject to list fusion. To vote for (a).
I have at least one project where I make heavy use of list fusion. In that case I only use toList, but one could imagine a case where I want that order. Therefore, I’m in favor of (b).
6) Result of discussion around http://hackage.haskell.org/trac/ghc/ticket/5242 Add `Map.fromSet :: (key -> a) -> Set key -> Map key a` `IntMap.fromSet :: (Int -> a) -> IntSet -> IntMap a` The implementation would exploit same structure of map and set (leave the shape of the original tree/trie, just adding values).
Cons: fromSet is a trivial composition: fromSet f = Map.fromDistinctAscList . map (\k -> (k, f k)) . Set.toAscList This can be defined by the user and is asymptotically optimal. Pro: performance. Also the performance of keysSet would improve, if the map can use data constructors of set.
I vote for adding these methods.
I very much agree (guess I don’t want to be only negative after all). Greetings and thanks for your work, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

I agree entirely with Joachim Breitner: +1 in general, but I'm opposed to removing/deprecating functions which (a) allow for list fusion, (b) allow for other significant optimizations, or (c) which clearly express the intent behind common idioms. On 11/28/11 3:24 PM, Joachim Breitner wrote:
Hi,
I’ll skip on the +1 and only make negative comments, as they are fewer :-)
Am Montag, den 28.11.2011, 17:28 +0100 schrieb Milan Straka:
4) The functions `mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a` have no IntMap correspondents. Both `mapKeys` and `mapKeysWith` can be defined by the user without loss of performance.
Solutions: (a) deprecate the `mapKeys*` methods from Map (b) add the `mapKeys*` methods to IntMap.
They seem useful to me to write legible code, therefore I’m in favor of (b). Also, they are used in the wild (random reference): http://darcswatch.nomeata.de/bundles/a3fbac8e4ce65d1426c5d1e0d19a6020f425b5d...
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet.
Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet.
I have no strong opinion here. The `toDescList` can be trivially expressed as left fold. But it is currently a subject to list fusion. To vote for (a).
I have at least one project where I make heavy use of list fusion. In that case I only use toList, but one could imagine a case where I want that order. Therefore, I’m in favor of (b).
6) Result of discussion around http://hackage.haskell.org/trac/ghc/ticket/5242 Add `Map.fromSet :: (key -> a) -> Set key -> Map key a` `IntMap.fromSet :: (Int -> a) -> IntSet -> IntMap a` The implementation would exploit same structure of map and set (leave the shape of the original tree/trie, just adding values).
Cons: fromSet is a trivial composition: fromSet f = Map.fromDistinctAscList . map (\k -> (k, f k)) . Set.toAscList This can be defined by the user and is asymptotically optimal. Pro: performance. Also the performance of keysSet would improve, if the map can use data constructors of set.
I vote for adding these methods.
I very much agree (guess I don’t want to be only negative after all).
-- Live well, ~wren

[ sorry, somehow gmail forgot about my default reply-to-all config ]
4) The functions `mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a` have no IntMap correspondents. Both `mapKeys` and `mapKeysWith` can be defined by the user without loss of performance.
Solutions: (a) deprecate the `mapKeys*` methods from Map (b) add the `mapKeys*` methods to IntMap.
I vote for (a). These methods are all trivial compositions and all but all mapKeysMonotonic are defined as such. For mapKeysMonotonic, a trivial composition with the same asymptotic complexity exists. Also, if these were added to IntMap, none of them would have better performance then user-defined methods.
I've used mapKeys a bit, but if the performance is really the same as 'Map.fromList . map first f . Map.toList' then I guess it's not super necessary. On the other hand, I would just immediately add the above composition to my own Map utils module, and why should we go removing stuff if it's just going to cause people to add copies to their private libraries?
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet.
Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet.
I have no strong opinion here. The `toDescList` can be trivially expressed as left fold. But it is currently a subject to list fusion. To vote for (a).
I actually added toDescList so I do have an opinion. I couldn't figure out any way it could be expressed as a left fold (or maybe that left fold function didn't exist back then). Without this function there's no way to (efficiently) iterate over a map backwards, which is pretty essential for an ordered collection! In any case, it's asymmetrical to have toAscList but no toDescList. +1 on everything else!

Hi,
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet.
Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet.
I have no strong opinion here. The `toDescList` can be trivially expressed as left fold. But it is currently a subject to list fusion. To vote for (a).
I actually added toDescList so I do have an opinion. I couldn't figure out any way it could be expressed as a left fold (or maybe that left fold function didn't exist back then). Without this function there's no way to (efficiently) iterate over a map backwards, which is pretty essential for an ordered collection!
The left folds are pretty new in the library (the commit log states 13 Jul 2011), so it definitely was not possible at that time. Cheers, Milan

The left folds are pretty new in the library (the commit log states 13 Jul 2011), so it definitely was not possible at that time.
Ahh, nice. Ok, I guess toDescList is no longer necessary. I still like it though, because it's exactly the way I want to iterate over a map (i.e., as a [(k, a)]). If it disappeared I would just add it back to my util library. Were I a new user, I'd look at toAscList and wonder where toDescList went. That you can left fold with (:) and make one may not be obvious to a beginner (it wasn't to me, back in the day). On the other hand it's better to teach people about general forms and composition than use specializations all the time. But still, I have a mild preference for keeping it. You know, something else I've noticed is that Data.Map is by far my most common haddock destination. So I think there's something to the idea that there are too many functions to memorize, even for frequent users, and we should emphasize combining forms over specific functions.

On 11/28/11 3:54 PM, Evan Laforge wrote:
You know, something else I've noticed is that Data.Map is by far my most common haddock destination. So I think there's something to the idea that there are too many functions to memorize, even for frequent users, and we should emphasize combining forms over specific functions.
Agreed. I think the factorization used in the bytestring-trie library gives a nice balance of (a) simplicity for the basic functions you really need, and (b) the whole kitchen sink if you really want it. In particular, the breakdown is to have two or three modules: Data.Foo: - Just the basics and the super-general combinators Data.Foo.Internal: - The real guts, if you feel like exposing them Data.Foo.Convenience: - Everything else that has crept into the API over the years - Not deprecated, but perhaps... lightly discouraged The "basics" in the Data.Foo module include both the primitives (like `empty`) and also extremely specialized versions of the super-general combinators (like `insert`, `lookup`, or `delete`). This is the place for beginners to look. The Convenience module is just giving common names for various specializations of the super-general combinators. While there are no optimization benefits or anything, it can be helpful to have this shared vocabulary for the various intermediate points between the super-general combinators and the basic operations. It also serves as a backward compatibility layer for people who don't want to have to change all their code to just using the basics. However, this sort of refactoring should be considered in a separate proposal. -- Live well, ~wren

Evan Laforge
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet. Without this function there's no way to (efficiently) iterate over a map backwards, which is pretty essential for an ordered collection!
How about using the Down/Dual/Desc/Converse/Opposite/Reverse newtype discussed in another recent thread, and providing for Data.Map: reverse :: Map k a -> Map (Reverse k) a reverse Tip = Tip reverse (Bin n k a l r) = Bin n (Reverse k) a (reverse r) (reverse l) (Arguably we also need reverse' :: Map (Reverse k) a -> Map k a. Hmm...) Only problem right now is that Map is spine-strict, so the above is O(n). Would this fuse with to(Asc)List? Cheers, /Liyang

On Wed, Nov 30, 2011 at 4:54 AM, Liyang HU
Evan Laforge
writes: 5) `toDescList` exists in Map, but not in IntMap, Set or IntSet. Without this function there's no way to (efficiently) iterate over a map backwards, which is pretty essential for an ordered collection!
How about using the Down/Dual/Desc/Converse/Opposite/Reverse newtype discussed in another recent thread, and providing for Data.Map:
reverse :: Map k a -> Map (Reverse k) a reverse Tip = Tip reverse (Bin n k a l r) = Bin n (Reverse k) a (reverse r) (reverse l)
(Arguably we also need reverse' :: Map (Reverse k) a -> Map k a. Hmm...)
reverse' :: Map (Reverse k) a -> Map k a reverse' = unsafeCoerce . reverse Sorry, couldn't resist =). Cheers, -- Felipe.

On 11/30/11 7:51 AM, Felipe Almeida Lessa wrote:
On Wed, Nov 30, 2011 at 4:54 AM, Liyang HU
wrote: How about using the Down/Dual/Desc/Converse/Opposite/Reverse newtype discussed in another recent thread, and providing for Data.Map:
reverse :: Map k a -> Map (Reverse k) a reverse Tip = Tip reverse (Bin n k a l r) = Bin n (Reverse k) a (reverse r) (reverse l)
(Arguably we also need reverse' :: Map (Reverse k) a -> Map k a. Hmm...)
reverse' :: Map (Reverse k) a -> Map k a reverse' = unsafeCoerce . reverse
Sorry, couldn't resist =).
As an addendum to the mapKeysAntitonic proposal, we should add the functorial rewrite rules which account for mono-/antitonicity. {-# RULES "mapKeysAntitonic id" mapKeysAntitonic id = id "mapKeysAntitonic f . mapKeysAntitonic g" mapKeysAntitonic f . mapKeysAntitonic g = mapKeysMonotonic (f . g) "mapKeysAntitonic f / mapKeysAntitonic g" forall x. mapKeysAntitonic f (mapKeysAntitonic g x) = mapKeysMonotonic (f . g) x -- And if these aren't already declared: "mapKeysMonotonic id" mapKeysMonotonic id = id "mapKeysMonotonic f . mapKeysMonotonic g" mapKeysMonotonic f . mapKeysMonotonic g = mapKeysMonotonic (f . g) "mapKeysMonotonic f / mapKeysMonotonic g" forall x. mapKeysMonotonic f (mapKeysMonotonic g x) = mapKeysMonotonic (f . g) x #-} From there, it should be easy for GHC to do reversal fusion: mapKeysAntitonic Reverse . mapKeysAntitonic unReverse === mapKeysMonotonic (Reverse . unReverse) === mapKeysMonotonic id === id mapKeysAntitonic unReverse . mapKeysAntitonic Reverse === mapKeysMonotonic (unReverse . Reverse) === mapKeysMonotonic id === id Or, more generally, fusion of any pair of inverse antitonic functions. Though for things other than newtypes it may require stating a rule that the functions are indeed inverses. This way, not only can we avoid unsafeCoerce (which can impede optimizations), but we get some optimizations to boot! -- Live well, ~wren

On 12/2/11 12:28 PM, wren ng thornton wrote:
On 11/30/11 7:51 AM, Felipe Almeida Lessa wrote:
On Wed, Nov 30, 2011 at 4:54 AM, Liyang HU
wrote: How about using the Down/Dual/Desc/Converse/Opposite/Reverse newtype discussed in another recent thread, and providing for Data.Map:
reverse :: Map k a -> Map (Reverse k) a reverse Tip = Tip reverse (Bin n k a l r) = Bin n (Reverse k) a (reverse r) (reverse l)
(Arguably we also need reverse' :: Map (Reverse k) a -> Map k a. Hmm...)
reverse' :: Map (Reverse k) a -> Map k a reverse' = unsafeCoerce . reverse
Sorry, couldn't resist =).
As an addendum to the mapKeysAntitonic proposal, we should add the functorial rewrite rules which account for mono-/antitonicity.
{-# RULES "mapKeysAntitonic id" mapKeysAntitonic id = id
"mapKeysAntitonic f . mapKeysAntitonic g" mapKeysAntitonic f . mapKeysAntitonic g = mapKeysMonotonic (f . g)
Whoops, forgot the other two fusions: "mapKeysAntitonic f . mapKeysMonotonic g" mapKeysAntitonic f . mapKeysMonotonic g = mapKeysAntitonic (f . g) "mapKeysMonotonic f . mapKeysAntitonic g" mapKeysMonotonic f . mapKeysAntitonic g = mapKeysAntitonic (f . g) I know older GHC had an eta problem that led to the need for separate "f.g" and "f/g" forms of rules. I'm not sure whether that's still an issue or not though. -- Live well, ~wren

Hi, Am Mittwoch, den 30.11.2011, 10:51 -0200 schrieb Felipe Almeida Lessa:
How about using the Down/Dual/Desc/Converse/Opposite/Reverse newtype discussed in another recent thread, and providing for Data.Map:
reverse :: Map k a -> Map (Reverse k) a reverse Tip = Tip reverse (Bin n k a l r) = Bin n (Reverse k) a (reverse r) (reverse l)
(Arguably we also need reverse' :: Map (Reverse k) a -> Map k a. Hmm...)
reverse' :: Map (Reverse k) a -> Map k a reverse' = unsafeCoerce . reverse
Sorry, couldn't resist =).
have used unsafeCoerce to change the type inside a container to a "type" alias in real code, but your post makes me wonder: Under what circumstances is that safe? Is that documented somehow? Can a tool or the compiler decide for us whether it is safe? Thanks, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

The semantics of unsafeCoerce are a bit informal, since it doesn't
exist as far as the standard is concerned. The docs are here:
http://hackage.haskell.org/packages/archive/base/4.4.1.0/doc/html/Unsafe-Coe...
for GHC: http://hackage.haskell.org/packages/archive/ghc-prim/0.2.0.0/doc/html/GHC-Pr...
With regard to your question about tools and compilers, well,
unsafeCoerce is kind of for the situtations where your automated tools
fail to prove safety, so I don't think there's a good general
solution.
On Sat, Dec 3, 2011 at 7:39 PM, Joachim Breitner
Hi,
Am Mittwoch, den 30.11.2011, 10:51 -0200 schrieb Felipe Almeida Lessa:
How about using the Down/Dual/Desc/Converse/Opposite/Reverse newtype discussed in another recent thread, and providing for Data.Map:
reverse :: Map k a -> Map (Reverse k) a reverse Tip = Tip reverse (Bin n k a l r) = Bin n (Reverse k) a (reverse r) (reverse l)
(Arguably we also need reverse' :: Map (Reverse k) a -> Map k a. Hmm...)
reverse' :: Map (Reverse k) a -> Map k a reverse' = unsafeCoerce . reverse
Sorry, couldn't resist =).
have used unsafeCoerce to change the type inside a container to a "type" alias in real code, but your post makes me wonder: Under what circumstances is that safe? Is that documented somehow? Can a tool or the compiler decide for us whether it is safe?
Thanks, Joachim
-- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sat, Dec 3, 2011 at 5:39 PM, Joachim Breitner
have used unsafeCoerce to change the type inside a container to a "type" alias in real code, but your post makes me wonder: Under what circumstances is that safe? Is that documented somehow? Can a tool or the compiler decide for us whether it is safe?
AFAIK, newtypes are safe, and for everything else you're on your own. =) Cheers, -- Felipe.

On 12/3/11 9:07 PM, Felipe Almeida Lessa wrote:
On Sat, Dec 3, 2011 at 5:39 PM, Joachim Breitner
wrote: have used unsafeCoerce to change the type inside a container to a "type" alias in real code, but your post makes me wonder: Under what circumstances is that safe? Is that documented somehow? Can a tool or the compiler decide for us whether it is safe?
AFAIK, newtypes are safe, and for everything else you're on your own. =)
N.B., newtypes are safe in the sense of congruent rewriting; i.e., if X is a newtype of Y, then we can rewrite X to Y (or Y to X) in any subterm of the type term (just like if X = Y or X ~ Y). It's not just at the top-level of the type term. -- Live well, ~wren

Hi, Am Sonntag, den 04.12.2011, 00:50 -0500 schrieb wren ng thornton:
On 12/3/11 9:07 PM, Felipe Almeida Lessa wrote:
On Sat, Dec 3, 2011 at 5:39 PM, Joachim Breitner
wrote: have used unsafeCoerce to change the type inside a container to a "type" alias in real code, but your post makes me wonder: Under what circumstances is that safe? Is that documented somehow? Can a tool or the compiler decide for us whether it is safe?
AFAIK, newtypes are safe, and for everything else you're on your own. =)
N.B., newtypes are safe in the sense of congruent rewriting; i.e., if X is a newtype of Y, then we can rewrite X to Y (or Y to X) in any subterm of the type term (just like if X = Y or X ~ Y). It's not just at the top-level of the type term.
that is what I would expect at first glance, but at least some type features break this behavior: $ cat brokenNewtype.hs {-# LANGUAGE TypeFamilies #-} import Unsafe.Coerce newtype Int' = Int' Int type family Break a type instance Break Int = Int type instance Break Int' = Int -> IO Int list :: [Break Int] list = [1..10] list' :: [Break Int'] list' = unsafeCoerce list main = do print list head list' 1 >>= print $ ghc --make brokenNewtype.hs [1 of 1] Compiling Main ( brokenNewtype.hs, brokenNewtype.o ) Linking brokenNewtype ... $ ./brokenNewtype [1,2,3,4,5,6,7,8,9,10] brokenNewtype: internal error: stg_ap_v_ret (GHC version 7.0.4 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Abgebrochen So the question remains: Under which circumstances is newtypes coercing within a type term using unsafeCoerce safe? And I find this not a purely academic question: If I have a huge data structure of “[Tagged SomePhantomType Int]” and I need to run some library function on it that only provides me with an operation of type “[Int] -> [Int]”, I do not want to re-create the list twice even when I _know_ the representation is the same. Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

On Sun, Dec 04, 2011 at 11:17:25AM +0100, Joachim Breitner wrote:
Hi,
Am Sonntag, den 04.12.2011, 00:50 -0500 schrieb wren ng thornton:
On 12/3/11 9:07 PM, Felipe Almeida Lessa wrote:
On Sat, Dec 3, 2011 at 5:39 PM, Joachim Breitner
wrote: have used unsafeCoerce to change the type inside a container to a "type" alias in real code, but your post makes me wonder: Under what circumstances is that safe? Is that documented somehow? Can a tool or the compiler decide for us whether it is safe?
AFAIK, newtypes are safe, and for everything else you're on your own. =)
N.B., newtypes are safe in the sense of congruent rewriting; i.e., if X is a newtype of Y, then we can rewrite X to Y (or Y to X) in any subterm of the type term (just like if X = Y or X ~ Y). It's not just at the top-level of the type term.
that is what I would expect at first glance, but at least some type features break this behavior:
So the question remains: Under which circumstances is newtypes coercing within a type term using unsafeCoerce safe?
Intuitively, it is safe to do newtype coercing as long as the newtype is treated "parametrically" by the context, i.e. it never appears as the argument to a type family. In principle this analysis could be done in an automated way; actually, the fact that GHC *doesn't* do this analysis means that GeneralizedNewtypeDeriving is unsound in the presence of type families; see http://hackage.haskell.org/trac/ghc/ticket/1496. For one approach to solving this see "Generative type abstraction and type-level computation" (POPL 2011) by Weirich, Vytiniotis, Peyton-Jones, and Zdancewic. It isn't implemented yet, but once it (or something like it) is, it may not be too hard to expose the ability to explicitly do congruent newtype coercing to the user. -Brent

On Sun, Dec 4, 2011 at 15:04, Brent Yorgey
On Sun, Dec 04, 2011 at 11:17:25AM +0100, Joachim Breitner wrote:
Hi,
Am Sonntag, den 04.12.2011, 00:50 -0500 schrieb wren ng thornton:
On 12/3/11 9:07 PM, Felipe Almeida Lessa wrote:
On Sat, Dec 3, 2011 at 5:39 PM, Joachim Breitner
wrote: have used unsafeCoerce to change the type inside a container to a "type" alias in real code, but your post makes me wonder: Under what circumstances is that safe? Is that documented somehow? Can a tool or the compiler decide for us whether it is safe?
AFAIK, newtypes are safe, and for everything else you're on your own. =)
N.B., newtypes are safe in the sense of congruent rewriting; i.e., if X is a newtype of Y, then we can rewrite X to Y (or Y to X) in any subterm of the type term (just like if X = Y or X ~ Y). It's not just at the top-level of the type term.
that is what I would expect at first glance, but at least some type features break this behavior:
So the question remains: Under which circumstances is newtypes coercing within a type term using unsafeCoerce safe?
Intuitively, it is safe to do newtype coercing as long as the newtype is treated "parametrically" by the context, i.e. it never appears as the argument to a type family. In principle this analysis could be done in an automated way; actually, the fact that GHC *doesn't* do this analysis means that GeneralizedNewtypeDeriving is unsound in the presence of type families; see http://hackage.haskell.org/trac/ghc/ticket/1496.
It's not just type families though, right? I mean, a (Map A) cannot be coerced to a (Map B), even if B is a newtype over A, since they might have different Ord instances, and thus a different map structure. Erik

On Sun, Dec 4, 2011 at 3:30 PM, Erik Hesselink
It's not just type families though, right? I mean, a (Map A) cannot be coerced to a (Map B), even if B is a newtype over A, since they might have different Ord instances, and thus a different map structure.
It depends on what you call "safe". The bug Brent Yorgey was referring to allows you to get sefaults and the like. The bug you're describing violates some invariants, but these invariants are not expressed in the type system and won't make a hard crash of your program. Cheers, -- Felipe.

On 12/04/2011 12:40 PM, Felipe Almeida Lessa wrote:
On Sun, Dec 4, 2011 at 3:30 PM, Erik Hesselink
wrote: It's not just type families though, right? I mean, a (Map A) cannot be coerced to a (Map B), even if B is a newtype over A, since they might have different Ord instances, and thus a different map structure.
It depends on what you call "safe". The bug Brent Yorgey was referring to allows you to get sefaults and the like. The bug you're describing violates some invariants, but these invariants are not expressed in the type system and won't make a hard crash of your program.
This problem could be addressed by the hypothetical safe-coercion operator requiring any relevant constructors to be in scope. (Alas, then it would have to be magical syntax.) -Isaac

On Sun, Dec 4, 2011 at 18:40, Felipe Almeida Lessa
On Sun, Dec 4, 2011 at 3:30 PM, Erik Hesselink
wrote: It's not just type families though, right? I mean, a (Map A) cannot be coerced to a (Map B), even if B is a newtype over A, since they might have different Ord instances, and thus a different map structure.
It depends on what you call "safe". The bug Brent Yorgey was referring to allows you to get sefaults and the like. The bug you're describing violates some invariants, but these invariants are not expressed in the type system and won't make a hard crash of your program.
Ah, you are right of course. The Ord case is the same as having a hidden constructor, and a partial construction function which verifies some invariant. As you mention, the type family case is substantially different. Erik

On 12/4/11 5:17 AM, Joachim Breitner wrote:
N.B., newtypes are safe in the sense of congruent rewriting; i.e., if X is a newtype of Y, then we can rewrite X to Y (or Y to X) in any subterm of the type term (just like if X = Y or X ~ Y). It's not just at the top-level of the type term.
that is what I would expect at first glance, but at least some type features break this behavior:
Ah, yes, type families can break the behavior because they're functions at the type level, and therefore non-parametric since they can do type-case analysis on their arguments. Associated types also break the newtype congruence for the same reason, they're functions at the type level and can perform type-case analysis on their arguments and so are therefore non-parametric. The congruences I meant were for proper type constructors (i.e., the primitives like (->) and (,) as well as parametric datatypes). Since these are all parametric, they can't distinguish whether their type-arguments are newtypes or original types, and therefore they cannot change their representation based on that. It's the use of non-parametricity to change the representation which causes TF/AT to break. Other than the non-parametricity of TF/AT, the only other issue I can think of is to do with type classes. In terms of unsafeCoerce, it's sound to replace a type class' argument by a newtype (or if it's already a newtype, then replace by the original type)--- because the representations for both the instance dictionary and the values of the type are still the same. However, just because you have an instance of Foo X doesn't mean you have an instance of Foo Y, so that could mess things up if you can confuse the compiler into accepting a program which will ultimately need access to an instance that doesn't exist. And even if you have both instances, you may screw up the semantics of functions which rely on the semantics of the particular instance at hand. This is Erik Hesselink's example about coercing Map X to Map Y. Doing so is sound in the sense that the program will not crash due to corrupted memory etc. However, doing so will not preserve the semantics of the functions operating on Map, so it may not be sound in the way you would like. As always, you must be clear about whether you want to preserve the representation or the semantics, because you can't always do both. -- Live well, ~wren

On Sun, Dec 4, 2011 at 3:52 AM, Edward Z. Yang
Excerpts from Felipe Almeida Lessa's message of Wed Nov 30 07:51:20 -0500 2011:
reverse' :: Map (Reverse k) a -> Map k a reverse' = unsafeCoerce . reverse
Sorry, couldn't resist =).
I might be confused, but doesn't this break internal invariants in Map?
Which ones? The Ord instance of 'Reverse (Reverse k)'s should be the same as that of 'k', right? Other than that, what invariants could be broken? Cheers, -- Felipe.

Excerpts from Felipe Almeida Lessa's message of Sun Dec 04 08:06:36 -0500 2011:
Which ones? The Ord instance of 'Reverse (Reverse k)'s should be the same as that of 'k', right? Other than that, what invariants could be broken?
Yes, Reverse (Reverse k)) should be functionally equal to k, but that's not what reverse' was doing, was it? ;-) Edward

On Sun, Dec 4, 2011 at 3:37 PM, Edward Z. Yang
Excerpts from Felipe Almeida Lessa's message of Sun Dec 04 08:06:36 -0500 2011:
Which ones? The Ord instance of 'Reverse (Reverse k)'s should be the same as that of 'k', right? Other than that, what invariants could be broken?
Yes, Reverse (Reverse k)) should be functionally equal to k, but that's not what reverse' was doing, was it? ;-)
It seems I may have missed something then. It gets a map with keys of type 'Reverse k', uses 'reverse' to get 'Reverse (Reverse k)' and then unsafeCoerces to 'k'. Doesn't it? =) Cheers, -- Felipe.

Excerpts from Felipe Almeida Lessa's message of Sun Dec 04 12:41:54 -0500 2011:
It seems I may have missed something then. It gets a map with keys of type 'Reverse k', uses 'reverse' to get 'Reverse (Reverse k)' and then unsafeCoerces to 'k'. Doesn't it? =)
Ah yes, I seem to have misunderstood the code. Carry on. 8)

On 11/30/11 1:54 AM, Liyang HU wrote:
Evan Laforge
writes: 5) `toDescList` exists in Map, but not in IntMap, Set or IntSet. Without this function there's no way to (efficiently) iterate over a map backwards, which is pretty essential for an ordered collection!
How about using the Down/Dual/Desc/Converse/Opposite/Reverse newtype discussed in another recent thread, and providing for Data.Map:
reverse :: Map k a -> Map (Reverse k) a reverse Tip = Tip reverse (Bin n k a l r) = Bin n (Reverse k) a (reverse r) (reverse l)
(Arguably we also need reverse' :: Map (Reverse k) a -> Map k a. Hmm...)
That'd be a nice function once the Ord-reversing newtype is included, but I worry about API explosion. As you mention, we'd want both reverse and unreverse. However, this does suggest a very valuable extension to the API. Namely, we have mapKeysMonotonic but we lack the dual version: mapKeysAntitonic :: (k1 -> k1) -> Map k1 a -> Map k2 a mapKeysAntitonic f Tip = Tip mapKeysAntitonic f (Bin n k a l r) = Bin n (f k) a (mapKeysAntitonic f r) (mapKeysAntitonic f l) With that function users could just define (or use inline), -- assuming newtype Reverse a = Reverse { unReverse :: a } reverse :: Map k a -> Map (Reverse k) a reverse = mapKeysAntitonic Reverse unreverse :: Map (Reverse k) a -> Map k a unreverse = mapKeysAntitonic unReverse But this way we only add one function to the API, and that function is very general since it can be used with any antitone function. I'm surprise we've never noticed the lack of mapKeysAntitonic before! -- Live well, ~wren

I strongly support all these changes (and agree with Milan's chocie of options), having run into many of the inconsistencies in my own code and had to write impedence matchers.
7) Improve the generality of intersectionWith. Currently the Map and IntMap define intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
But the combining function is not general enough. Consider two IntMaps storing hashable elements as (hash(element), element). When intersecting elements with the same hash, the intersection can be empty.
I propose to change the type of these methods to intersectionWith :: Ord k => (a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c (and appropriately for IntMap).
Note that the combining function of differenceWith already has type `(a -> b -> Maybe a)`.
The absence of intersection with this signature has been a particular annoyance. -Jan-Willem Maessen

Hello, This is off-topic but I'm curious. Why the container package does not provide a type-class to unify APIs? Are there any technical/historical reasons? --Kazu
Hi everyone,
I have several containers API changes propositions.
First five are an attempt to unify the API of different structures. The documentation states IntMap is Map replacement and IntSet is Set replacement, but there are several shortcomings:
1) `{Map,Set}.deleteMin empty` return `empty` `{IntMap,IntSet}.deleteMin empty` trigger `error "Cannot delete in empty..."`
Solutions: (a) make `{Map,Set}.deleteMin empty` throw error (b) make `{IntMap,IntSet}.deleteMin empty` return empty
I vote for (b), because (a) could cause unexpected runtime errors. Additionally, I expect very little programs depend on `{IntMap,IntSet}.deleteMin empty` causing runtime error.
2) `Map.deleteFind{Min,Max}` has type `Map k a -> ((k,a),Map k a)` `IntMap.deleteFind{Min,Max}` has type `IntMap a -> (a, IntMap a)`
Solutions: (a) make the Map variant return only values (b) make the IntMap variant return both key and value
I vote for (b), because it generalizes the original functionality.
3) `Map.update{Min,Max}` is given a function of type `(a -> Maybe a)` `Map.update{Min,Max}WithKey` is given a function of type `(key -> a -> Maybe a)` `IntMap.update{Min,Max}` is given a function of type `(a -> a)` `IntMap.update{Min,Max}WithKey` is given a function of type `(key -> a -> a)`
Solutions: (a) the Map variants would get a function of type `[key -> ] a -> a` (b) the IntMap variants would get a function of type `[key -> ] a -> Maybe a`
I vote for (b), because it generalizes the original functionality.
4) The functions `mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a` have no IntMap correspondents. Both `mapKeys` and `mapKeysWith` can be defined by the user without loss of performance.
Solutions: (a) deprecate the `mapKeys*` methods from Map (b) add the `mapKeys*` methods to IntMap.
I vote for (a). These methods are all trivial compositions and all but all mapKeysMonotonic are defined as such. For mapKeysMonotonic, a trivial composition with the same asymptotic complexity exists. Also, if these were added to IntMap, none of them would have better performance then user-defined methods.
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet.
Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet.
I have no strong opinion here. The `toDescList` can be trivially expressed as left fold. But it is currently a subject to list fusion. To vote for (a).
Several other changes follow:
6) Result of discussion around http://hackage.haskell.org/trac/ghc/ticket/5242 Add `Map.fromSet :: (key -> a) -> Set key -> Map key a` `IntMap.fromSet :: (Int -> a) -> IntSet -> IntMap a` The implementation would exploit same structure of map and set (leave the shape of the original tree/trie, just adding values).
Cons: fromSet is a trivial composition: fromSet f = Map.fromDistinctAscList . map (\k -> (k, f k)) . Set.toAscList This can be defined by the user and is asymptotically optimal. Pro: performance. Also the performance of keysSet would improve, if the map can use data constructors of set.
I vote for adding these methods.
7) Improve the generality of intersectionWith. Currently the Map and IntMap define intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
But the combining function is not general enough. Consider two IntMaps storing hashable elements as (hash(element), element). When intersecting elements with the same hash, the intersection can be empty.
I propose to change the type of these methods to intersectionWith :: Ord k => (a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> Maybe c) -> Map k a -> Map k b -> Map k c (and appropriately for IntMap).
Note that the combining function of differenceWith already has type `(a -> b -> Maybe a)`.
Discussion period: 2 weeks
Cheers, Milan
PS: Sorry for the long email.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 29 November 2011 12:29, Kazu Yamamoto
Hello,
This is off-topic but I'm curious.
Why the container package does not provide a type-class to unify APIs? Are there any technical/historical reasons?
Various people have tried, but they're typically unweildy, and in some cases difficult to express without using extensions. There's also tension between "this should be a class method" vs "this should be a function that uses the class" (large classes are annoying, but having a function as a class method allows for more potential implementation-specific optimisations). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Ivan,
Why the container package does not provide a type-class to unify APIs? Are there any technical/historical reasons?
Various people have tried, but they're typically unweildy, and in some cases difficult to express without using extensions. There's also tension between "this should be a class method" vs "this should be a function that uses the class" (large classes are annoying, but having a function as a class method allows for more potential implementation-specific optimisations).
Thank you for your explanation! --Kazu

On Mon, Nov 28, 2011 at 5:29 PM, Kazu Yamamoto
Hello,
This is off-topic but I'm curious.
Why the container package does not provide a type-class to unify APIs? Are there any technical/historical reasons?
Mostly technical I would say. I hope we should be able to do this right now when we have constraint kinds [1] i.e. we can do something like: class Map m where type C :: Constraints insert :: C => k -> v -> Map k v -> Map k v instance Map HashMap where type C = Ord insert = ... 1. http://blog.omega-prime.co.uk/?p=127 -- Johan

On 29 November 2011 14:09, Johan Tibell
On Mon, Nov 28, 2011 at 5:29 PM, Kazu Yamamoto
wrote: Hello,
This is off-topic but I'm curious.
Why the container package does not provide a type-class to unify APIs? Are there any technical/historical reasons?
Mostly technical I would say. I hope we should be able to do this right now when we have constraint kinds [1] i.e. we can do something like:
class Map m where type C :: Constraints insert :: C => k -> v -> Map k v -> Map k v
instance Map HashMap where type C = Ord insert = ...
Definitely: this kind of thing was what stopped me when I tried to do something similar last year. There's still the tension of whether to put particular functions as class methods or not though (e.g. just look at these proposals about whether to include certain functions). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Hi, Am Dienstag, den 29.11.2011, 14:20 +1100 schrieb Ivan Lazar Miljenovic:
There's still the tension of whether to put particular functions as class methods or not though (e.g. just look at these proposals about whether to include certain functions).
I’d expect that in a lot of uses, the type is known at compile time. In that case, the general of a function that is not part of the class can be replaced by an optimized function using RULES, can’t it? But this is not perfect, because non-inlined code that is itself still polymorphic would not benefit from that. Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

On 30 November 2011 08:28, Joachim Breitner
Hi,
Am Dienstag, den 29.11.2011, 14:20 +1100 schrieb Ivan Lazar Miljenovic:
There's still the tension of whether to put particular functions as class methods or not though (e.g. just look at these proposals about whether to include certain functions).
I’d expect that in a lot of uses, the type is known at compile time. In that case, the general of a function that is not part of the class can be replaced by an optimized function using RULES, can’t it?
I've seen that be used before but to me it seems rather hacky (and rather GHC-specific).
But this is not perfect, because non-inlined code that is itself still polymorphic would not benefit from that.
Right, so any form of other derived generic code would also not be optimised. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Another issue is that containers tries to remain with a public API that is very close to Haskell 98/2011 for portability.
Sent from my iPad
On Nov 28, 2011, at 10:09 PM, Johan Tibell
On Mon, Nov 28, 2011 at 5:29 PM, Kazu Yamamoto
wrote: Hello,
This is off-topic but I'm curious.
Why the container package does not provide a type-class to unify APIs? Are there any technical/historical reasons?
Mostly technical I would say. I hope we should be able to do this right now when we have constraint kinds [1] i.e. we can do something like:
class Map m where type C :: Constraints insert :: C => k -> v -> Map k v -> Map k v
instance Map HashMap where type C = Ord insert = ...
1. http://blog.omega-prime.co.uk/?p=127
-- Johan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Milan Straka
1) `{Map,Set}.deleteMin empty` return `empty` `{IntMap,IntSet}.deleteMin empty` trigger `error "Cannot delete in empty..."`
Solutions: (a) make `{Map,Set}.deleteMin empty` throw error (b) make `{IntMap,IntSet}.deleteMin empty` return empty
+1 for (b)
2) `Map.deleteFind{Min,Max}` has type `Map k a -> ((k,a),Map k a)` `IntMap.deleteFind{Min,Max}` has type `IntMap a -> (a, IntMap a)`
Solutions: (a) make the Map variant return only values (b) make the IntMap variant return both key and value
+1 for (b)
3) `Map.update{Min,Max}` is given a function of type `(a -> Maybe a)` `Map.update{Min,Max}WithKey` is given a function of type `(key -> a -> Maybe a)` `IntMap.update{Min,Max}` is given a function of type `(a -> a)` `IntMap.update{Min,Max}WithKey` is given a function of type `(key -> a -> a)`
Solutions: (a) the Map variants would get a function of type `[key -> ] a - a` (b) the IntMap variants would get a function of type `[key -> ] a -> Maybe a`
I vote for (b), because it generalizes the original functionality.
+1 for (b)
4) The functions `mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a` `mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a` have no IntMap correspondents. Both `mapKeys` and `mapKeysWith` can be defined by the user without loss of performance.
Solutions: (a) deprecate the `mapKeys*` methods from Map (b) add the `mapKeys*` methods to IntMap.
I vote for (a). These methods are all trivial compositions and all but all mapKeysMonotonic are defined as such. For mapKeysMonotonic, a trivial composition with the same asymptotic complexity exists. Also, if these were added to IntMap, none of them would have better performance then user-defined methods.
+1 for (b) Same asymptotic complexity is fine in theory but not necessarily in practice. OTOH, API uniformity between Map and IntMap (and HashMap) would be nice, such that the only difference would be in the class constraints. (When Johan adds Data.Map.Class &c., we should rename Map to OrdMap...)
5) `toDescList` exists in Map, but not in IntMap, Set or IntSet.
Solutions: (a) deprecate `Map.toDescList` (b) add `toDescList` to IntMap. In this case, we should consider adding it also to Set and IntSet.
I'm inclined towards (a), because if you're going down the route of offering Desc versions of toList, why not fromDescList* too? In fact, deprecate Map.toAscList too, and rename it to Map.toList.
6) Result of discussion around http://hackage.haskell.org/trac/ghc/ticket/5242 Add `Map.fromSet :: (key -> a) -> Set key -> Map key a` `IntMap.fromSet :: (Int -> a) -> IntSet -> IntMap a` The implementation would exploit same structure of map and set (leave the shape of the original tree/trie, just adding values).
Opting out due to conflict of interests.
7) Improve the generality of intersectionWith.
+1 Cheers, /Liyang
participants (17)
-
Ben Millwood
-
Brent Yorgey
-
Edward Kmett
-
Edward Z. Yang
-
Erik Hesselink
-
Evan Laforge
-
Felipe Almeida Lessa
-
Henning Thielemann
-
Isaac Dupree
-
Ivan Lazar Miljenovic
-
Jan-Willem Maessen
-
Joachim Breitner
-
Johan Tibell
-
Kazu Yamamoto
-
Liyang HU
-
Milan Straka
-
wren ng thornton