A ring is a set R with two binary operations, addition and multiplication, satisfying certain rules. Specifically:
R is a commutative group with respect to addition
- Addition is associative: a+(b+c) = (a+b)+c
- There is an additive identity, 0, such that a+0 = 0+a = a
- There is an additive inverse, -a, such that a+(-a) = (-a)+a = 0
- Addition is commutative: a+b = b+a
- Multiplication is associative: a*(b*c) = (a*b)*c
- Often, there will be a multiplicative identity, 1, such that 1*a = a*1 = a
- Quite often, multiplication will be commutative
- a*(b+c) = a*b + a*c
- (a+b)*c = a*c + b*c
- The integers. These are really the prototype for the concept. However the integers are actually quite a special ring, having many properties that other rings can fail to have. Part of understanding rings is understanding which properties of the integers don't hold for all rings. Mathematicians use the abbreviation Z for the integers (from the German Zahlen, meaning numbers)
- The rational numbers (Q), real numbers (R), and complex numbers (C).
- For fixed n, the set of n*n matrices. For example, the set of 2*2 matrices.
- The set of polynomials in x
- The natural numbers N (the positive integers). They're not a ring because we don't have additive inverses (the negative integers).
- Vectors with the cross product as multiplication. The problem is that the cross product isn't associative.
{-# OPTIONS_GHC -fglasgow-exts #-}
module Rings where
newtype Matrix r = M [[r]] deriving (Eq,Show)
instance Num r => Num (Matrix r) where
M [[a,b],[c,d]] + M [[a',b'],[c',d']] = M [[a+a',b+b'],[c+c',d+d']]
negate (M [[a,b],[c,d]]) = M [[-a,-b],[-c,-d]]
M [[a,b],[c,d]] * M [[e,f],[g,h]] = M [[a*e+b*g, a*f+b*h] ,[c*e+d*g, c*f+d*h]]
fromInteger n = M [[fromInteger n, 0],[0, fromInteger n]]
It wouldn't have been much harder to handle the n*n case rather than just the 2*2 case, but I thought the code was clearer this way.
Let's quickly test it:
> M [[1,2],[3,4]] - M [[1,0],[0,1]]
M [[0,2],[3,3]]
> M [[2,0],[0,3]] * M [[1,2],[3,4]]
M [[2,4],[9,12]]
Notice that in Haskell, the Num type class is what you use when you want to define a ring. It provides the (+), (-), and (*) operators that you need. We also need a way to say what the 0 and 1 are in our ring. This is what the fromInteger function is for. If we wanted, we could have just defined fromInteger 0 and fromInteger 1, and left the other cases unmatched, like so:
fromInteger 0 = M [[0,0],[0,0]]
fromInteger 1 = M [[1,0],[0,1]]
As far as defining a ring goes, this would have been fine. But once someone knows what fromInteger 1 is, they can use the ring laws to work out fromInteger n as follows:
fromInteger n | n >= 0 = sum $ replicate n $ fromInteger 1
| otherwise = negate $ fromInteger $ negate n
So we might as well save them the trouble and just do it for them.
Note that because Haskell will do fromInteger calls implicitly for us, we can write things like this:
> 2 * M [[1,2],[3,4]]
M [[2,4],[6,8]]
A couple of things to point out about the ring of 2*2 matrices:
- Multiplication is not commutative
- There are zero divisors - we can find matrices a/=0, b/=0 such that a*b==0
Okay, next, polynomials in x:
newtype UPoly a = UP [a] deriving (Eq)
-- the list [a_0, a_1, ..., a_n] represents the polynomial a_0 + a_1 x + ... + a_n x^n
x = UP [0,1] :: UPoly Integer
instance (Show a, Num a) => Show (UPoly a) where
show (UP []) = "0"
show (UP as) = let powers = reverse $ filter ( (/=0) . fst ) $ zip as [0..]
c:cs = concatMap showTerm powers
in if c == '+' then cs else c:cs
where showTerm (a,i) = showCoeff a ++ showPower a i
showCoeff a | a == 1 = "+"
| a == -1 = "-"
| otherwise = let cs = show a
in if head cs == '-' then cs else '+':cs
showPower a i | i == 0 = if a `elem` [1,-1] then "1" else ""
| i == 1 = "x"
| i > 1 = "x^" ++ show i
instance Num a => Num (UPoly a) where
UP as + UP bs = toUPoly $ as <+> bs
negate (UP as) = UP $ map negate as
UP as * UP bs = toUPoly $ as <*> bs
fromInteger 0 = UP []
fromInteger a = UP [fromInteger a]
toUPoly as = UP (reverse (dropWhile (== 0) (reverse as)))
(a:as) <+> (b:bs) = (a+b) : (as <+> bs)
as <+> [] = as
[] <+> bs = bs
[] <*> _ = []
_ <*> [] = []
(a:as) <*> (b:bs) = [a*b] <+> (0 : map (a*) bs) <+> (0 : map (*b) as) <+> (0 : 0 : as <*> bs)
Quick test:
> (x+1)^3
x^3+3x^2+3x+1
Unlike the matrices, this ring of polynomials over the integers (which mathematicians write as Z[x]) is quite a nicely behaved ring. Multiplication is commutative, and there are no zero divisors.
There are many other important rings. Let's look at one more: the integers modulo n (for fixed n) - also known as "clock arithmetic", and denoted Zn by mathematicians. Here I'm going to use some phantom type trickery, so the following code may not compile in all environments:
class IntegerAsType a whereWhen using this code, I need to make sure that the interpreter knows which type I am working in:
value :: a -> Integer
data T12
instance IntegerAsType T12 where value _ = 12
data T10
instance IntegerAsType T10 where value _ = 10
newtype Zn n = Zn Integer deriving (Eq)
instance Show (Zn n) where
show (Zn x) = show x
instance IntegerAsType n => Num (Zn n) where
Zn x + Zn y = Zn $ (x+y) `mod` value (undefined :: n)
negate (Zn 0) = 0
negate (Zn x) = Zn $ value (undefined :: n) - x
Zn x * Zn y = Zn $ (x*y) `mod` value (undefined :: n)
fromInteger n = Zn $ n `mod` value (undefined :: n)
Zn is a commutative ring. However, when n is composite (not a prime), then it has zero divisors.
> 2*9 :: Zn T12
6
> 2*9 :: Zn T10
8
So there you have it, a few examples of the concept of ring.
At the beginning, I said that the Num type class didn't quite succeed at capturing the concept of ring. That's because it has a couple of other functions that we've been ignoring up to now - abs and signum. This is the little blot in Haskell's copybook. abs and signum don't have anything to do with rings. They don't make sense for most of the rings we've discussed. In fact they're only really relevant to rings which can be embedded into the complex numbers. I'm hoping that in the next version of Haskell, this little wrinkle will be ironed out.
Next time: fields