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

John Ky john at gocatch.com
Sun May 11 06:11:52 UTC 2014


Hmmm - I lie, it isn't equivalent.  Only works if the HashMap value is a
monoid over the left operation.  In which case isn't it better not to
define the monoid for HashMap at all?

On 11 May 2014 15:31, 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/>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140511/a56716b9/attachment.html>


More information about the Haskell-Cafe mailing list