Minor containers API changes

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Mon Nov 28 21:49:54 CET 2011


On 29 November 2011 03:42, Felipe Almeida Lessa <felipe.lessa at gmail.com> wrote:
> On Mon, Nov 28, 2011 at 2:28 PM, Milan Straka <fox at ucw.cz> 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 at gmail.com
IvanMiljenovic.wordpress.com



More information about the Libraries mailing list