[containers] Proposal: Change to the Data.Map Monoid

Julian Bean jules at jellybean.co.uk
Fri Oct 9 07:37:14 UTC 2015


Apologies for digging out an 18 month old post, but it shows some context.

In fact this proposal was made in 2012, resurrected in 2013, and re-made in 2014. Each time it has been defeated because it would break too much code to change it now.

Would there be any downside to providing a package with a newtyped Map with all operations ported over? The newtype already exists in semigroups as UnionWith (Map k) v; what is missing is the entire Map API.

Now that we have Data.Coerce (which we didn’t have at least the first time this was discussed) I believe I’m right in saying that you can basically patch the API over as:

module Data.MonoidMap.Strict where {
import qualified Data.Map.Strict as MS
import Data.Semigroup.Union

type Map k v = UnionWith (MS.Map k) v

— I don’t know if we need to use {-# INLINE #-} here or fully saturate singleton to get inlining to work
singleton :: k -> a -> Map k a
singleton = coerce MS.singleton

insert :: Ord k => k -> a -> Map k a -> Map k a
insert = coerce MS.insert
….
}

which is entirely mechanical (and can presumably be automated). Do the same for Lazy of course. And also for HashMap.

Add the correct Monoid instance (presumably using Semigroup since we have that as a dependency anyway). We can export also

fromMap :: Data.Map.Strict.Map k v -> Data.MonoidMap.Strict.Map k v
fromMap = coerce

and the reverse.

then legacy code is entirely unharmed, but new code which wishes to use the “correct” instance of Monoid has a package to import to use it, and it is relatively easy to co-exist with existing code using the old type, with an O(1) conversion function.

To be clear - this isn’t a library proposal, because it’s a proposal for a new package which will depend on containers and semigroups. However it is a suggestion of how we can solve the problem of Map having the wrong Monoid instance and not have to live with the problems forever. Who knows, one day in the future semigroups might be in base.

Jules


On 19 May 2014, at 01:05, Nick Partridge <nkpart at gmail.com> wrote:

> Hi, 
> 
> Currently the Monoid instance for Data.Map is implemented using union/unions, which are left biased. On key collision, it discards values from the right hand side of `mappend` - https://github.com/ghc/packages-containers/blob/bae098fb0a3994bc2b0ec3313004b40cd097ed8d/Data/Map/Base.hs#L341-L344
> 
> If you compare this with the Monoid for Maybe, it's like we're defaulting to First as the monoid instance for maps.
> 
> A more useful instance, however very much a breaking change, would be to make the instance depend on a Monoid (or better yet, a Semigroup) for the values in the map:
> 
> instance Monoid v => Monoid (Map k v) where
>     mappend = unionWith mappend
> 
> This lets us build up maps with values in a useful Monoid, and mappend them with gusto. 
> 
> Thoughts?
> 
> - Nick Partridge
> 
> Discussion period: 2 weeks.
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20151009/018b73af/attachment.html>


More information about the Libraries mailing list