Why isn't Data.Map not an instance of Monoid :-)
Adrian Hey
ahey at iee.org
Mon May 7 07:35:22 EDT 2007
Lauri Alanko wrote:
> On Mon, May 07, 2007 at 10:23:24AM +0100, Adrian Hey wrote:
>> instance (Ord k) => Monoid (Map k v) where
>> mempty = empty
>> mappend = union
>> mconcat = unions
>>
>> This worries me because there is no obviously correct choice for the
>> semantics of union for maps (as in which maps associated values get
>> dropped).
>
> Right. I think that the real fundamental MMap type should be
something like:
>
> instance (Ord k, Monoid v) => Monoid (MMap k v) where
> mempty = empty
> mappend = unionWith mappend
Ross Paterson has suggested the same thing so I'll go with that, unless
Jean-Philippe has some objection (I think Data.Map and Data.Map.AVL
should be the same in this regard).
This still breaks the Coolections module though, but I guess it's
fixable.
> and with a lookup operation
>
> lookup :: (Ord k, Monoid v) => k -> MMap k v -> v
>
> which returns mempty when the key was not found in the map, _or_ if a
> mempty value was somehow stored in the map. The distinction is purely
> an implementation detail and shouldn't be visible.
>
> Then it is easy to see that the current Data.Map is just a wrapper to
> the above interface specialized to a left-biased monoid on Maybe. So
> Data.Map isn't as general as it should be, but at least it's
> _consistently_ non-general. There's not much point in generalizing the
> monoid instance of the map as long as there is still an implicit Maybe
> in the values.
Actually at the moment lookup is..
lookup :: (Monad m,Ord k) => k -> Map k a -> m a
Maybe we should have something like.
lookupMaybe :: Ord k => k -> Map k a -> Maybe a
lookupMonad :: (Monad m,Ord k) => k -> Map k a -> m a
lookupMonoid :: (Ord k, Monoid a) => k -> Map k a -> a
Hmm..
> I'm not really advocating changing the Data.Map interface: Data.Map is
> intentionally specialized and optimized for pragmatic
> purposes. Abstract algebraic generalizations belong to Edison.
Or Jean-Philippes collections classes
Regards
--
Adrian Hey
More information about the Libraries
mailing list