[Haskell-cafe] Monoids and newtypes

Ketil Malde ketil at malde.org
Thu Jan 22 10:11:26 EST 2009


One wart that was briefly mentioned during the Great Monoid Naming
Thread of 2009 is the need to wrap types in newtypes to provide multiple
instances of the same class with different semantics -- the archetypical
example being Integer as a monoid over addition as well as
multiplication. 

I was just wondering if not phantom types might serve here as an
alternative way to go about that.  Here's a small example illustrating
it: 

----------------------------------------
{-# LANGUAGE EmptyDataDecls  #-}
{-# LANGUAGE FlexibleInstances  #-}

module Monoids where
import Data.Monoid

data Foo a = Foo Integer deriving (Show, Eq)

data Additive
data Multiplicative

instance Monoid (Foo Additive) where
    mappend (Foo x) (Foo y) = Foo (x+y)
    mempty = Foo 0

instance Monoid (Foo Multiplicative) where
    mappend (Foo x) (Foo y) = Foo (x*y)
    mempty = Foo 1

instance Num (Foo a) where
    fromInteger x = Foo x
    Foo x + Foo y = Foo (x+y)
    Foo x * Foo y = Foo (x*y)
    signum (Foo x) = Foo (signum x)
----------------------------------------

Loading this into ghci, you get:
*Monoids> mconcat [1,2]

<interactive>:1:0:
    Ambiguous type variable `t' in the constraints:
      `Monoid t' arising from a use of `mconcat' at <interactive>:1:0-12
      `Num t' arising from the literal `2' at <interactive>:1:11
    Probable fix: add a type signature that fixes these type variable(s)
*Monoids> mconcat [1,2::Foo Additive]
Foo 3
*Monoids> mconcat [1,2::Foo Multiplicative]
Foo 2

(This can of course be prettified a bit by omitting the constructor
from the Show instance).  

Any thought about this, pro/contra the newtype method?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants


More information about the Haskell-Cafe mailing list