[Haskell-cafe] Custome monoid mappend on HashMap and HashSet values

Dom De Re domdere at domdere.com
Sun May 11 22:45:16 UTC 2014


Hey John,

Its a bit tedious to rewrite the library for an entire type when you
newtype it.

Typically I would newtype it, write the custom instance for it, but I would
still use the main type everywhere where i am not using the custom instance.

This would reduce your code to:



newtype MyHashMap k v = MyHashMap {toHashMap :: (M.HashMap k v)}

instance (Eq k, Hashable k, Monoid v) => Monoid (MyHashMap k v) where
  mempty = empty
  mappend (MyHashMap a) (MyHashMap b) = MyHashMap (M.unionWith mappend a b)

empty :: MyHashMap k v
empty = MyHashMap M.empty


It has the following main benefit:

HashMap is a common data structure that a lot of users are familiar with a
single "goto" source for the docs (
http://hackage.haskell.org/package/unordered-containers), when users or
collaborators look at the type and they see HashMap in there they either
know exactly how it behaves already or they know where to go to find a
complete definition, without having to also look at what implicit local
instances are in scope (like in Scala).

If the code inside a function isnt using your overridden monoid instance
then you may as well give them a function that works with the more widely
spread type, rather than getting them to needlessly wrap it into your type.

Even if you are then you still may as well use the plain (Lazy/Strict)
HashMap type in the signature of your function so again people are more
familiar with the value thats going in, and explicitly wrap and unwrap the
values in the body of your function.  This way again when someone reads
your code they know whats going in and whats coming out and they can see
that the monoid instance is being overwritten. e.g (I might be missing some
constraints):

unionWithAppendAll :: (Eq k, Hashable k) => [M.HashMap k v] -> M.HashMap k v

unionWithAppendAll x = toHashMap (fold myhashmaps) -- unwrap it aftr yo
have used your monoid instance

    where

        -- wrap your values

        myhashmaps :: [MyHashMap k v]

        myhashmaps = fmap MyHashMap x



-- I wrote it that way to try and make what is going on more clear, but it
can be written more concisely as:

unionWithAppendAll :: (Eq k, Hashable k) => [M.HashMap k v] -> M.HashMap k v

unionWithAppendAll = toHashMap . foldMap MyHashMap



where fold and foldMap are described here:
http://hackage.haskell.org/package/base-4.3.1.0/docs/Data-Foldable.html#v:fold
If you were writing a library that might be shared, this allows you to not
expose MyHashMap in your interface if you dont believe that the MyHashMap
Monoid instance has any use for anyone else besides your specific purpose
in your particular library.  It can even simplify your module for your
collaborators.



Thanks,

Dom.


On Sun, May 11, 2014 at 3:31 PM, John Ky <john at gocatch.com> wrote:

>
> Thanks Alexander and Tran,
>
> So I went through the whole process of defining newtype, but it was quite
> a long process.  My code below.
>
> Surely it would make more sense if the HashMap monoid were defined in
> terms of the monoid of its value type?
>
> In that case you could choose the monoid for the value to take the left
> value, which would be the equivalent of the current behaviour.
>
> Cheers,
>
> -John
>
> import qualified  Control.Applicative as A
> import            Data.Hashable
> import qualified  Data.HashMap.Lazy as M
> import            Data.Monoid
>
> newtype HashMap k v = HashMap (M.HashMap k v)
>
> instance (Eq k, Hashable k, Monoid v) => Monoid (HashMap k v) where
>   mempty = empty
>   mappend (HashMap a) (HashMap b) = HashMap (M.unionWith mappend a b)
>
> empty :: HashMap k v
> empty = HashMap M.empty
>
> singleton :: Hashable k => k -> v -> HashMap k v
> singleton k v = HashMap (M.singleton k v)
>
> null :: HashMap k v -> Bool
> null (HashMap m) = M.null m
>
> size :: HashMap k v -> Int
> size (HashMap m) = M.size $ m
>
> member :: (Eq k, Hashable k) => k -> HashMap k a -> Bool
> member k (HashMap m) = M.member k m
>
> lookup :: (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
> lookup k (HashMap m) = M.lookup k m
>
> lookupDefault :: (Eq k, Hashable k) => v -> k -> HashMap k v -> v
> lookupDefault v k (HashMap m) = M.lookupDefault v k m
>
> (!) :: (Eq k, Hashable k) => HashMap k v -> k -> v
> (!) (HashMap m) k = (M.!) m k
>
> insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v
> insert k v (HashMap m) = HashMap (M.insert k v m)
>
> insertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v
> -> HashMap k v
> insertWith f k v (HashMap m) = HashMap (M.insertWith f k v m)
>
> delete :: (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
> delete k (HashMap m) = HashMap $ M.delete k m
>
> adjust :: (Eq k, Hashable k) => (v -> v) -> k -> HashMap k v -> HashMap k v
> adjust f k (HashMap m) = HashMap $ M.adjust f k m
>
> union :: (Eq k, Hashable k) => HashMap k v -> HashMap k v -> HashMap k v
> union (HashMap a) (HashMap b) = HashMap (M.union a b)
>
> unionWith :: (Eq k, Hashable k) => (v -> v -> v) -> HashMap k v -> HashMap
> k v -> HashMap k v
> unionWith f (HashMap a) (HashMap b) = HashMap (M.unionWith f a b)
>
> unions :: (Eq k, Hashable k) => [HashMap k v] -> HashMap k v
> unions ms = HashMap (M.unions [un m | m <- ms])
>   where un (HashMap m) = m
>
> map  :: (v1 -> v2) -> HashMap k v1 -> HashMap k v2
> map f (HashMap m) = HashMap (M.map f m)
>
> --mapWithKey :: (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2
> --mapWithKey f (HashMap m) = HashMap (M.mapWithKey f m)
>
> traverseWithKey :: A.Applicative f => (k -> v1 -> f v2) -> HashMap k v1 ->
> f (HashMap k v2)
> traverseWithKey f (HashMap m) = HashMap `fmap` (M.traverseWithKey f m)
>
> difference :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap
> k v
> difference (HashMap a) (HashMap b) = HashMap (M.difference a b)
>
> intersection :: (Eq k, Hashable k) => HashMap k v -> HashMap k w ->
> HashMap k v
> intersection (HashMap a) (HashMap b) = HashMap (M.intersection a b)
>
> intersectionWith :: (Eq k, Hashable k) => (v1 -> v2 -> v3) -> HashMap k v1
> -> HashMap k v2 -> HashMap k v3
> intersectionWith f (HashMap a) (HashMap b) = HashMap (M.intersectionWith f
> a b)
>
> foldl' :: (a -> v -> a) -> a -> HashMap k v -> a
> foldl' f v (HashMap m) = M.foldl' f v m
>
> foldlWithKey' :: (a -> k -> v -> a) -> a -> HashMap k v -> a
> foldlWithKey' f v (HashMap m) = M.foldlWithKey' f v m
>
> foldr :: (v -> a -> a) -> a -> HashMap k v -> a
> foldr f v (HashMap m) = M.foldr f v m
>
> foldrWithKey :: (k -> v -> a -> a) -> a -> HashMap k v -> a
> foldrWithKey f v (HashMap m) = M.foldrWithKey f v m
>
> filter :: (v -> Bool) -> HashMap k v -> HashMap k v
> filter f (HashMap m) = HashMap (M.filter f m)
>
> filterWithKey :: (k -> v -> Bool) -> HashMap k v -> HashMap k v
> filterWithKey f (HashMap m) = HashMap (M.filterWithKey f m)
>
> keys :: HashMap k v -> [k]
> keys (HashMap m) = M.keys m
>
> elems :: HashMap k v -> [v]
> elems (HashMap m) = M.elems m
>
> toList :: HashMap k v -> [(k, v)]
> toList (HashMap m) = M.toList m
>
> fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v
> fromList kvs = HashMap (M.fromList kvs)
>
> fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap
> k v
> fromListWith f kvs = HashMap (M.fromListWith f kvs)
>
>
>
>
>
> On 10 May 2014 16:07, Alexander V Vershilov <alexander.vershilov at gmail.com
> > wrote:
>
>> Hi, John.
>>
>> You can always use newtype wrapper if you need to overload existing
>> method behavior:
>>
>> newtype MyHashMap a b = MyHashMap { unMy :: HashMap a b}
>>
>> instance Monoid (MyHasMap a b) where
>>   mempty = MyHasMap mempty
>>   mappend a b = your_overloaded_function
>>
>> Then just wrap and unwrap your data to do a custom mappend, also you can
>> write a wrapper function, in case if you'll restrict types then it may work
>> only for the types you need:
>>
>> (<~>) :: HashMap Int (HashMap Int Int) -> HashMap Int (HashMap Int Int)
>> -> HashMap Int (HashMap Int Int)
>> a <~> b = unMy $ (<>) `on` MyHashMap a b
>>
>> --
>> Alexander
>>
>
>
>  <http://www.gocatch.com/>
>   Sydney, Australia
>
>   <https://www.facebook.com/goCatch>  <https://twitter.com/gocatchapp> <http://www.linkedin.com/company/goCatch>
>    <https://itunes.apple.com/au/app/gocatch/id444439909?mt=8> <https://play.google.com/store/apps/details?id=com.gocatchapp.goCatch&hl=en>
>  <http://www.windowsphone.com/en-au/store/app/gocatch/d76b0eb5-bad6-429f-b99e-0ce85d953f93>
>   <http://appworld.blackberry.com/webstore/content/31917887/>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140512/c1772780/attachment-0001.html>


More information about the Haskell-Cafe mailing list