What about something like

data AddMult a b = AddMult a b

class Monoid a where
  operation :: a -> a -> a
  identity  :: a

instance (Monoid a, Monoid b) => Monoid (AddMult a b) where
  operation  (AddMult a1 m1)
             (AddMult a2 m2)
           =  AddMult (operation a1 a2)
                      (operation m1 m2)
  identity =  AddMult identity identity

class Commutative a where
  -- Nothing, this is a programmer proof obligation

class Monoid a => Group a where
  inverse :: a -> a

class (Commutative a, Group a) => AbelianGroup a where

class (AbelianGroup a, AbelianGroup b) => Field a b where

instance AbelianGroup a => Field a a where


George Pollard wrote:
Is there a good way of doing this? My running example is Monoid:

class Monoid a where
        operation :: a -> a -> a
        identity :: a

With the obvious examples on Num:

instance (Num a) => Monoid a where
        operation = (+)
        identity = 1

instance (Num a) => Monoid a where
        operation = (*)
        identity = 0

Of course, this won't work. I could introduce a newtype wrapper:

newtype (Num a) => MulNum a = MulNum a
newtype (Num a) => AddNum a = AddNum a

instance (Num a) => Monoid (MulNum a) where
        operation (MulNum x) (MulNum y) = MulNum (x * y)
        identity = MulNum 1

instance (Num a) => Monoid (AddNum a) where ... -- etc

However, when it comes to defining (e.g.) a Field class you have two
Abelian groups over the same type, which won't work straight off:

class Field a where ...
instance (AbelianGroup a, AbelianGroup a) => Field a where ...

Could try using the newtypes again:
instance (AbelianGroup (x a), AbelianGroup (y a) => Field a where ...

... but this requires undecidable instances. I'm not even sure if it
will do what I want. (For one thing it would also require an indication
of which group distributes over the other, and this may restore
decidability.)

I'm beginning to think that the best way to do things would be to drop
the newtype wrappers and include instead an additional parameter of a
type-level Nat to allow multiple definitions per type. Is this a good
way to do things?

Has anyone else done something similar? I've taken a look at the Numeric
Prelude but it seems to be doing things a bit differently. (e.g. there
aren't constraints on Ring that require Monoid, etc)

- George



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to