
Hi, I currently have a newtype definition of a typed Data.Map. newtype G = G Data.Map String Values I have done this because for my specific use-case, I can define G as a monoid and get some nice benefits. However, I find myself often just re-declaring functions of Data.Map and wrap/unwrap them in my Constructor G, such as singleton :: String -> Value -> G singleton s v = G $ (Data.Map.singleton s v) I think I do not need to limit the scope of G's functionality, I basically want everything from Data.Map + Bonus , like my Monoid. Also I want G to be a specific Data.Map, there is never any other case where it's not a Map String Values. However, if I have type G2 = Data.Map String Values I cannot instance Monoid. So, I am very sure that I'm not the first person ever doing this. Is there a language extension providing what I want? Or is what i want "bad"? Am I just missing a higher-order base function which does what I want? best regards & thanks Leonhard

Hello Leonardh, a couple of ideas: On Fri, Nov 15, 2019 at 11:36:03AM +0000, Leonhard Applis wrote:
I currently have a newtype definition of a typed Data.Map.
newtype G = G Data.Map String Values
[...]
However, if I have
type G2 = Data.Map String Values
`Map k v` is already an instance of `Monoid` (when `v` is an instance of `Ord`), are you sure you need to write another one? If the answer is "yes", you can write a small helper: withG :: (M.Map String a -> M.Map String a) -> G a -> G a withG mf (G m) = G $ mf m or use GeneralizedNewtypeDeriving to ease some pain: {-# Language GeneralizedNewtypeDeriving #-} module Prova where import Data.Map as M import GHC.Exts newtype G a = G { unwrapG :: M.Map String a } deriving (Eq, Show, Functor, Foldable)
participants (2)
-
Francesco Ariis
-
Leonhard Applis