In the last post we saw that, for example, -3 is a square mod any prime . This means we have or we can say we have a multiple of expressed as a sum of two squares if we write . Similarly for primes we have .
In some lecture notes ( http://math.bu.edu/people/kost/teaching/MA341/ - Lecture 6 - Sums of Squares ) I found a very nice proof that shows if we can write then we can "descend" to a smaller pair with the same property. By iterating this - since you can only get smaller so many times before you reach 1 - we eventually reach . In fact this proof constitues an algorithm and I have it implemented.
Another key fact about these forms is the uniqueness of representation: Euler showed how to factor a number given two distinct representations . This can be found in ( https://archive.org/stream/NumberTheoryItsHistory/Ore-NumberTheoryItsHistory page 61 ). The consequence of this factoring algorithm is that any representation of a prime must be unique.
I was able to adapt both of these algorithms to the form . This proves that all primes are represented, and in a unique way by this form.
Let be two distinct primitive representations of a number, by primitive I mean that and otherwise we would already have a factorization. Hence
Now , so by inverting the sign of assume this means . Using the gcd we can resolve and into parts:
with all coprime to each other. Now
leads to the factorization
Let , we wish to find for some smaller until
If we are done and have a representation using this form.
If then we can simply "divide by 3": implies so put and divide out the 3 to get: .
This is the really interesting case, by congruence considerations . Pick and with .
With the identity in mind note
Here is a bit of code that implements this
{-# LANGUAGE BangPatterns, NoMonomorphismRestriction #-} import Prelude hiding ((/)) import System.Environment --import System.Random import Debug.Trace x / y = if not test then error ("doesnt divide " ++ show (x,y)) else x `div` y where test = x `mod` y == 0 factorialm _ 0 = 1 factorialm !m !n = (n * factorialm m (n - 1)) `mod` m --f :: Integer -> {- forall prime p, p = 4k + 1, exists n. n^2 = -1 mod p -} f !p = if not test then error "fail" else u where test = (u^2 + 1) `mod` p == 0 u = factorialm p ((p - 1) / 2) {- f' p = do n <- randomRIO (2, p - 1) let k = (p - 1) / 4 let g = (n^k) `mod` p if (g^2 + 1) `mod` p == 0 then return g else f' p -} pow p n 0 !r = r pow p n 1 !r = n * r pow p n k !r = pow p n (k - 1) ((n * r)`mod`p) f3' p = do n <- [ 2 .. p - 1 ] let k = (p - 1) / 3 let g = (2*pow p n k 1 + 1) `mod` p if (g^2 + 3) `mod` p == 0 then return g else [] -- f3' p g !p = (f p, 1) h !p !(a, b) = case () of _ | d == 1 -> if not test then error "really fail" else (a, b) _ | even d -> if even a then h p (a / 2, b / 2) else h p ((a + b) / 2, (a - b) / 2) _ | odd d -> let (u, v) = (q a, q b) in h p ((a * u + b * v) / d, (a * v - b * u) / d) where d = (a^2 + b^2) / p test = a^2 + b^2 == p q !a = let a' = a `mod` d in if 2 * a' > d then a' - d else a' h3 !p !(a, b) = {- trace (show [a,b,d, q a, q b]) $ -} case () of _ | d == 1 -> if not test then error "really fail" else (a, b) _ | (d`mod`3) == 0 -> h3 p (b, a/3) _ | otherwise -> let (u, v) = (q a, q b) in h3 p ((a * u + 3 * b * v) / d, (a * v - b * u) / d) where d = (a^2 + 3*b^2) / p test = a^2 + 3*b^2 == p q !a = let a' = a `mod` d in if 2 * a' > d then a' - d else a' {- *Main> :l n [1 of 1] Compiling Main ( n.hs, interpreted ) Ok, modules loaded: Main. *Main> h3 10687 (7307, 1) (98,19) *Main> 98^2 + 3*19^2 10687 *Main> 3*3562210+1 10686631 *Main> head $ f3' (3*3562210+1) 10239214 *Main> h3 (3*3562210+1) (10239214, 1) (2078,1457) *Main> 2078^2 + 3*1457^2 10686631 *Main> -}
The reason for all of this (besides being able to resolve primes into sum of squares forms) is that I want to prove something about
supposing . This theorem comes from Weil - Number theory through history.
In this case any prime divisor of divides and hence is of this form - therefore is a product of these forms and so we must have and therefore
by the following calculation
? f(x,y,u,v) = [x*u+3*y*v, x*v - y*u] %1 = (x,y,u,v)->[x*u+3*y*v,x*v-y*u] ? f(h,k,h,k) %2 = [h^2 + 3*k^2, 0] ? f(h^2 + 3*k^2,0,h,k) %3 = [h^3 + 3*k^2*h, k*h^2 + 3*k^3]
we can infact choose to make
All of this was completely elementary and did not make use of any irrational or imaginary numbers. The same results can be proved much quicker using algebraic number fields - they are of course what lurks behind all the mathematics here.