{-# LANGUAGE MultiParamTypeClasses #-} module Data.Monoid.Map ( module Data.Monoid.Reducer , UnionWith(getUnionWith) ) where import Prelude (Ord) import Data.Monoid.Reducer (Reducer, unit, cons, snoc, Monoid, mempty, mappend) import Data.Map -- only needs m to be a semigroup, but Haskell doesn't have a semigroup class newtype UnionWith k m = UnionWith { getUnionWith :: Map k m } instance (Ord k, Monoid m) => Monoid (UnionWith k m) where mempty = UnionWith empty UnionWith a `mappend` UnionWith b = UnionWith (unionWith mappend a b) instance (Ord k, Monoid m) => Reducer (Map k m) (UnionWith k m) where unit = UnionWith