Proposal: Remove Semigroup and Monoid instances for Data.Map, Data.IntMap, Data.HashMap

David Feuer david.feuer at gmail.com
Wed Feb 14 14:47:47 UTC 2018


We can use rewrite rules to recognize and optimize unionWith in one or
more special cases:

unionWith f = plainUnionWith f
{-# NOINLINE [1] unionWith #-}

bottom1, bottom2 :: a
bottom1 = undefined
{-# NOINLINE bottom1 #-}
bottom2 = undefined
{-# NOINLINE bottom2 #-}

unionWithMagic :: a -> (a -> a -> a) -> Map k a -> Map k a -> Map k a
unionWithMagic _ f = plainUnionWith f
{-# INLINE [1] unionWithMagic #-}

RULES:
unionWith f ===> unionWithMagic (f bottom1 bottom2) f
unionWithMagic bottom1 f ===> union

On Wed, Feb 14, 2018 at 5:16 AM, Akio Takano <tkn.akio at gmail.com> wrote:
> Hi Oleg,
>
> On 14 February 2018 at 09:48, Oleg Grenrus <oleg.grenrus at iki.fi> wrote:
>> I agree with Oliver, was just writing the very same.
>>
>>
>> `Map.map First = Map.map coerce = coerce`
>>
>> i.e. mapping First is _zero-cost_, thanks to the fact `v` in `Map k v`
>> has represenational role.
>
> Yes, I agree that mapping First is zero-cost. I'm saying that
> `unionWith (<>)` over the First monoid costs more than `union`, due to
> allocation of extra thunks.
>
> - Akio
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries


More information about the Libraries mailing list