Computing with decadic numbers

[This is the ninth, and, I think, final in a series of posts on the decadic numbers (previous posts: A curiosity, An invitation to a funny number system, What does "close to" mean?, The decadic metric, Infinite decadic numbers, More fun with infinite decadic numbers, A self-square number, u-tube).]

In a previous post, we found a decadic number

u = \dots 57423423230896109004106619977392256259918212890625

with the curious property that it is its own square, even though it is obviously not zero or one. We then derived a more efficient algorithm for generating the digits of u. Here’s some Haskell code (explained in the previous post) which implements the more efficient algorithm, which I include here just so that this post will be a valid literate Haskell file in its entirety.

> {-# LANGUAGE TypeSynonymInstances
>            , FlexibleInstances
>   #-}
> 
> module Decadic2 where
> 
> import Control.Monad.State
> 
> -- State for incrementally constructing u_n.
> -- Invariant: curT = 10^n; un^2 = pn*curT + un
> data UState = UState { pn     :: Integer
>                      , un     :: Integer
>                      , curT   :: Integer
>                      }
>   deriving Show
> 
> -- u_1 = 5;  5^2 = 25 = 2*10 + 5
> initUState = UState 2 5 10
> 
> uStep :: State UState Int
> uStep = do
>   u <- gets un
>   p <- gets pn
>   t <- gets curT
> 
>   let d   = p `mod` 10      -- next digit
>       u'  = d * t + u       -- prepend the next digit to u
>       p'  = (p + 2*d*u + d*d*t) `div` 10   -- see above proof
> 
>   put (UState p' u' (10*t)) -- record the new values
> 
>   return $ fromInteger d    -- return the new digit
> 
> type Decadic = [Int]
> 
> u :: Decadic
> u = 5 : evalState (sequence $ repeat uStep) initUState

To round things out, I’d like to show off some of the cool things we can do with this. First, as we know, it’s possible to do arithmetic with decadic numbers. So let’s implement it!

Addition of decadic numbers is done just like addition of the usual decimal numbers: we add corresponding places (i.e., line up the numbers one under the other and then add in columns).

> plus :: Decadic -> Decadic -> Decadic

First, we have special cases for zero, represented by the empty list of digits: in those cases we just return the other number unchanged.

> plus [] n2 = n2
> plus n1 [] = n1

Next, to add a decadic number whose first digit is x to a decadic number whose first digit is y, we just add x and y and then continue adding recursively.

> plus (x:xs) (y:ys) = (x+y) : plus xs ys

Of course, we’re not done: this doesn’t do any carrying. Instead of modifying our plus function to do carrying, we just write a function normalize which makes sure every place in a decadic number is between 0 and 9; it will come in handy for more than just addition.

> normalize :: Decadic -> Decadic

The normalize function simply calls a recursive helper function normalize' which keeps track of the current "carry". The starting carry, of course, is zero.

> normalize = normalize' 0

To normalize zero (the empty list) when the current carry is zero, just return the empty list.

>   where normalize' 0 [] = []

With a nonzero carry and the empty list, we simply extend the list with a special zero digit and continue normalizing.

>         normalize' carry [] = normalize' carry [0]

In the general case, we add the current carry to the next digit x, and compute the quotient and remainder when dividing this sum by ten. The remainder is the next digit d, and the quotient is the new carry which gets passed along recursively.

>         normalize' carry (x:xs) = d : normalize' carry' xs
>           where (carry', d) = (carry + x) `divMod` 10

And now for multiplication, which is based on the observation that zero times anything is zero, and in the general case

(a + 10b)(c + 10d) = ac + 10(a \cdot d + b \cdot (c + 10d)).

> mul :: Decadic -> Decadic -> Decadic
> mul [] _ = []
> mul _ [] = []
> mul (x:xs) (y:ys) = x*y : (map (x*) ys + (xs * (y:ys)))

Finally, we declare Decadic to be an instance of the Num class, which allows us to use decadic numbers in the same ways that we can use other numeric types:

> instance Num Decadic where

To add or multiply decadic numbers, use the plus and mul functions and then normalize.

>   n1 + n2 = normalize (plus n1 n2)
>   n1 * n2 = normalize (mul n1 n2)

To negate a decadic number, subtract the last digit from 10 and the rest of the digits from 9.

>   negate [] = []
>   negate (x:xs) = normalize $ (10-x) : negate' xs
>     where negate' []     = repeat 9
>           negate' (x:xs) = (9-x) : negate' xs

Finally, to convert an integer into a decadic number, put the integer into a list of one element and normalize.

>   fromInteger = normalize . (:[]) . fromInteger

So, let’s try it! We’ll want a way to display decadic numbers:

> showDecadic :: Decadic -> IO ()
> showDecadic d = putStrLn . dots $ digits
>   where d'   = take 31 d
>         dots | length d' <= 30 = id
>              | otherwise       = ("..." ++)
>         digits =  concat . reverse . map show . take 30 $ d'

Normal decimal integers can also be used as decadic numbers:

*Decadic2> showDecadic 7
7

Here’s u:

*Decadic2> showDecadic u
...106619977392256259918212890625

And here’s u^2; it had better be the same as u!

*Decadic2> showDecadic (u^2)
...106619977392256259918212890625

Well, looks like it’s the same for the first 30 digits at least! We can also compute 1-u. Remember, if u^2 = u then (1-u)^2 = 1 - 2u + u^2 = 1 - 2u + u = 1 - u, so 1-u should be another self-square number. Remember how we thought there might be a self-square number ending in 6? Well, this is it!

*Decadic2> showDecadic (1-u)
...893380022607743740081787109376
*Decadic2> showDecadic ((1-u)^2)
...893380022607743740081787109376

Finally, we can check that u (1 - u) = u - u^2 = u - u = 0:

*Decadic2> showDecadic (u * (1-u))
...000000000000000000000000000000

If you recall, this is in some sense the fundamental reason why the decadic numbers act so funny, because it has zero divisors: pairs of numbers (like u and 1-u), neither of which is zero, whose product is nonetheless zero.

Now, if you remember, from even further back, what got us into this whole decadic mess in the first place:

image

In that first post, I said

I managed to extend this pattern for a few more digits before I got bored. Does it continue forever or does it eventually stop? Is there any deeper mathematical explanation lurking behind this supposed “curiosity”? What’s so special about f(x) = 2x^2 - 1? Do patterns like this exist for other functions?

Well, by this point I hope it’s clear that there is indeed a deeper mathematical explanation lurking! The equation

x = 2x^2 - 1

admits the solutions x = 1 and x = -1/2, but does it admit any other decadic solutions? Notice that given (x - a)(x - b) = 0, which has x = a and x = b as solutions, then u a + (1-u)b (and (1-u)a + ub) are also solutions:

(ua + (1-u)b - a)(ua + (1-u)b - b) = ((u-1)a + (1-u)b)(ua + ub) = 0.

So in this case we get

\displaystyle u - (1-u)/2 = \frac{3u - 1}{2}

as a solution (the other solution is not a decadic integer).

To implement it, we need a way to halve decadic numbers (I’ll let you work out what’s going on here):

> halve :: Decadic -> Decadic
> halve [] = []
> halve t@(s:_)
>   | odd s     = error "foo"
>   | otherwise = halve' t
>   where
>     halve' [] = []
>     halve' [x] = [x `div` 2]
>     halve' (x:x':xs) = (x `div` 2 + adj) : halve' (x':xs)
>       where adj | odd x'    = 5
>                 | otherwise = 0

And now we can define

> q = halve (3*u - 1)
*Decadic2> showDecadic q
...159929966088384389877319335937
*Decadic2> showDecadic (2*q^2 - 1)
...159929966088384389877319335937

Woohoo! This clearly shows that the pattern does, in fact, continue forever. It also shows us that f(x) = 2x^2 - 1 is not particularly special: any quadratic function that factors as (x - a)(x - b), at the very least, will lead to a pattern like this, and probably lots of other equations do too.

If you’re interested in reading more, here’s where I got some of my information. For example, you can read about how there is another number v = \dots 04103263499879186432, defined by starting with 2 and iteratively raising to the fifth power (just as we defined u by starting with 5 and successively squaring), such that v^5 = v. It even seems that the author of that page, Gérard Michon, has recently added a discussion of this very problem, prompted by my blog posts! Isn’t the internet great?

About Brent

Associate Professor of Computer Science at Hendrix College. Functional programmer, mathematician, teacher, pianist, follower of Jesus.
This entry was posted in arithmetic, programming and tagged , , . Bookmark the permalink.

2 Responses to Computing with decadic numbers

  1. Anonymous Rex says:

    Hi, great series of posts!

    Fyi, I think your negate function gets un-normalized if the first digit is 0.

Comments are closed.