[Haskell-cafe] overlapping instance error -- need help using instance Monoid (Sum a) where a is a map of "money" values

Thomas Hartman tphyahoo at gmail.com
Sun Jan 20 00:56:17 EST 2008


The code below compiles as given, however if I uncomment the tSM
function I get the overlapping instance error mentioned in the subject
line.

Can someone give me advice on how to do what I want to do?

basically I want to add, for example, (USD,1) and (USD,2) and (Euro,3)
and get result

fromList [(USD,3), (Euro,3)]

the datatypes below are more verbose but the above is the basic idea

thanks!

thomas.

*****

module TransactionRows {- ( mkTransactionRows,TransactionRows ) -} where
import Data.Monoid
import Data.List
import qualified Data.Map as M

data Currency a = Currency a
  deriving ( Show, Eq, Ord )
data Money c a = Money ( M.Map c a )
  deriving Show
instance (Num a, Ord c)=> Monoid ( Sum (Money c a) ) where
  mempty = Sum ( Money M.empty )
  Sum ( Money m1 ) `mappend` Sum ( Money m2 ) = Sum (Money m1
`plusmoney` Money m2)

plusmoney (Money m1s) (Money m2s) = Money msum
  where msum = foldl' f m1s (M.toList m2s)
        f m (k,v) = M.insertWith (+) k v m

mkMoney1 :: Currency String -> Float -> Money (Currency String) Float
mkMoney1 c a = Money $ M.singleton c a

--sumMoney :: [Money (Currency String) Float] -> Money (Currency String) Float
sumMoney ms = getSum $ mconcat $ map Sum ms

-- if I uncomment this, get Overlapping instances for Monoid error
--tSM = sumMoney [mkMoney1 (Currency "usd") 1 :: Money (Currency String) Float]


More information about the Haskell-Cafe mailing list