
Ross Paterson writes:
Such features would be useful, but are unlikely to be available for Haskell'. If we concede that, is it still desirable to make these changes to the class hierarchy?
I've collected some notes on these issues at
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ StandardClasses Coincidentally, I spent some time last week thinking about a replacement for the Num class. I think I managed to come up with something that's more flexible than Num, but still mostly comprehensible. ----
class Monoid a where zero :: a (+) :: a -> a -> a
Laws: identity : zero + a == a == a + zero associativity : a + (b + c) == (a + b) + c Motivation: Common superclass for Group and Semiring.
class Monoid a => Group a where negate :: a -> a (-) :: a -> a -> a
a - b = a + negate b negate a = zero - a
Laws: negate (negate a) == a a + negate a == zero == negate a + a Motivation: Money, dimensional quantities, vectors. An Abelian group is just a group where (+) is commutative. If there's a need, we can declare a subclass. For non-Abelian groups, it's important to note that (-) provides right subtraction.
class Monoid a => Semiring a where one :: a (*) :: a -> a -> a
Laws: identity : one * a == a == a * one associativity : a * (b * c) == (a * b) * c zero annihilation : zero * a == zero == a * zero Motivation: Natural numbers support addition and multiplication, but not negation. Unexpectedly, instances of MonadPlus and ArrowPlus can also be considered Semirings, with (>>) and (>>>) being the multiplication. Since Semiring is a subclass of Monoid, we get the (+,0) instance for free. The following wrapper implements the (*,1) monoid.
newtype Prod a = Prod { unProd :: a }
instance (Semiring a) => Monoid (Prod a) where zero = Prod one Prod a + Prod b = Prod (a * b)
class (Semiring a, Group a) => Ring a where fromInteger :: Integer -> a
Placing 'fromInteger' here is similar to Num in spirit, but perhaps undesirable. I'm not sure what the contract is for fromInteger. Perhaps something like, fromInteger 0 = zero fromInteger 1 = one fromInteger n | n < 0 = negate (fromInteger (negate n)) fromInteger n = one + fromInteger (n-1) Which, actually, could also be a default definition. The original Num class is essentially a Ring with abs, signum, show, and (==).
class (Ring a, Eq a, Show a) => Num a where abs :: a -> a signum :: a -> a
These are probably best put in a NormedRing class or something. ---- I don't have enough math to judge the classes like Integral, Real, RealFrac, etc, but Fractional is fairly straightforward.
class Ring a => DivisionRing a where recip :: a -> a (/) :: a -> a -> a fromRational :: Rational -> a
a / b = a * recip b recip a = one / a
Laws: recip (recip a) == a, unless a == zero a * recip a == one == recip a * a, unless a == zero Motivation: A division ring is essentially a field that doesn't require multiplication to commute, which allows us to include quaternions and other non-commuting division algebras. Again, (/) represents right division. ---- These show up a lot, but don't have standard classes.
class (Group g) => GroupAction g a | a -> g where add :: g -> a -> a
Laws: add (a + b) c == add a (add b c) add zero c == c Motivation: Vectors act on points, durations act on times, groups act on themselves (another wrapper can provide that, if need be).
class (GroupAction g a) => SymmetricGroupAction g a | a -> g where diff :: a -> a -> g
Laws: diff a b == negate (diff b a) diff (add a b) b == a Motivation: I'm not sure whether this is the correct class name, but it's certainly a useful operation when applicable.
class (Ring r, Group a) => Module r a | a -> r where mult :: r -> a -> a
Laws: mult (a * b) c == mult a (mult b c) mult one c == c Motivation: Scalar multiplication is fairly common. A module is essentially a vector space over a ring, instead of a field. It's fairly trivial to write an adapter to produce a GroupAction instance for any Module. ---- For illustration, here's an example with vectors and points:
data Pt a = Pt a a deriving (Eq, Show) data Vec a = Vec a a deriving (Eq, Show)
instance (Ring a) => Monoid (Vec a) where zero = Vec 0 0 Vec x y + Vec x' y' = Vec (x + x') (y + y')
instance (Ring a) => Group (Vec a) where Vec x y - Vec x' y' = Vec (x - x') (y - y')
instance (Ring a) => Module a (Vec a) where mult a (Vec x y) = Vec (a * x) (a * y)
instance (Ring a) => GroupAction (Vec a) (Pt a) where add (Vec dx dy) (Pt x y) = Pt (dx + x) (dy + y)
instance (Ring a) => SymmetricGroupAction (Vec a) (Pt a) where diff (Pt x y) (Pt x' y') = Vec (x - x') (y - y')
midpoint p1 p2 = add (mult 0.5 (diff p1 p2)) p2
The type of midpoint is something like
(DivisionRing a, Module a b, SymmetricGroupAction b c) => c -> c -> c
--
David Menendez