Oh no, not another Haskell way of calculating Fibonacci numbers! Well, yes but done perhaps slightly differently.
This post brings together
The Golden Ratio (Phi)
“…two quantities are in the golden ratio if their ratio is the same as the ratio of their sum to the larger of the two quantities.”
This ratio appears often mathematics and in nature, perhaps almost as pervasive as pi. And there is the Golden Rectangle, a 2-D extension of the Golden Ratio, often used in art because of its intrinsically appealing properties.
Fibonacci Numbers
0, 1, 1, 2, 3, 5, 8, 13, 21, 34, 55, 89, 144,… ‘Nuff said.
Continued Fractions
Are like this, fractions where the denominator is also a fraction and so on…
The idea in this post is to create a Haskell representation of fractions but in particular have that representation handle continued fractions. Once we can do that then we can create a continued fraction for the Golden Ratio, which is this:
and then, if the continued fraction above is ‘flattened’ into a list of intermediate fractions, the denominators of those intermediate fractions are the terms of the Fibonacci series! Which I think is quite stunning.
For details see section 11 in this link: “The Convergents of Phi’s CF are Ratios of Fibonacci Numbers!”
A Little Bit of Haskell
A fraction is a numerator ‘over’ a denominator and we’ll also consider a whole number to be a fraction with an implicit denominator of 1.
Furthermore, if we are to have continued fractions then the denominator must, optionally, be a fraction too. Here’s a couple of type synonyms and an algebraic data type to express these ideas.
1 2 3 4 5 |
-- type Numerator = Integer type Denominator = Integer data Fraction = Numbr Numerator | F Numerator Fraction |
This will allow us to create a simple fraction like, for example, Numbr 4 which is 4/1 or using the F type constructor F 7 (Numbr 8). A continued fraction could be something like F 7 (F 6 (F 11 (Numbr 23))) which could be have been continued indefinitely, which is quite cool!
Next we need a sensible way of showing fractions – we do this by making Fraction an instance of the Show type class like this
1 2 3 4 5 6 7 8 9 10 |
-- instance Show Fraction where show (Numbr n) = show n ++ "/1" show (F n 0) = show n ++ "/0" show (F n (Numbr d)) | n == 0 = show 0 | d == 1 = show n ++ "/1" | (n > 0 && d < 0) || (n < 0 && d < 0 ) = show (-n) ++ "/" ++ show (-d) | otherwise = show n ++ "/" ++ show d show (F n f@(F _ _)) = show n ++ "/" ++ show f |
This is fairly simple pattern matching on the show function. The final pattern is slightly more complex as it handles the condition where a fraction may have another fraction as its denominator and so it calls show again recursively.
If we make Fraction an instance of the Num typeclass then we can, with suitable definitions, use operators +, -, * on Fractions. And, if we make Fraction an instance of Haskell’s Fractional typeclass we can use the division, /, operator. I think the code is fairly self explanatory so I’ll add it all here and then describe some of the more important parts.
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 |
-- -- module Fractions where import Data.Ratio type Numerator = Integer type Denominator = Integer {- So a fraction can be a simple 3 or 3/4 or 3 / (4 / (...)) a recursive, continued, fraction: -} data Fraction = Numbr Numerator | F Numerator Fraction instance Show Fraction where show (Numbr n) = show n ++ "/1" show (F n 0) = show n ++ "/0" show (F n (Numbr d)) | n == 0 = show 0 | d == 1 = show n ++ "/1" | (n > 0 && d < 0) || (n < 0 && d < 0 ) = show (-n) ++ "/" ++ show (-d) | otherwise = show n ++ "/" ++ show d show (F n f@(F _ _)) = show n ++ "/" ++ show f -- Make Fraction into a Number so that +, * etc can be used. instance Num Fraction where (+) = add (*) = mul (-) = sub abs (Numbr n) = Numbr (abs n) abs f@(F n d) = F (abs n1) (abs d1) where F n1 d1 = simplify f signum (Numbr n) = Numbr (signum n) signum f@(F n d) | n1 == 0 = Numbr 0 | n1 > 0 && d1 < 0 = Numbr (-1) | n1 < 0 && d1 > 0 = Numbr (-1) | otherwise = Numbr 1 where F n1 d1 = simplify f fromInteger = Numbr -- Allows the '/' operator to be used with Fraction instance Fractional Fraction where fromRational x = F (numerator x) (Numbr (denominator x)) (/) = divid -- Notion of equality between Fractions instance Eq Fraction where (==) f g = res where fr = reduce f gr = reduce g res = num fr == num gr && denom fr == denom gr -- And ordering instance Ord Fraction where (<=) f g = signum (f - g ) == -1 -- Fraction specific definitions of basic arithmetic ops. These are referenced -- in the previous typeclass definitions. mul :: Fraction -> Fraction -> Fraction mul f f1 = mul1 (simplify f) (simplify f1) where mul1 (Numbr p) (Numbr q) = Numbr (p * q) mul1 (Numbr p) (F p1 (Numbr q1)) = F (p * p1) (Numbr q1) mul1 (F p1 (Numbr q1)) (Numbr p) = F (p * p1) (Numbr q1) mul1 (F p (Numbr q)) (F p1 (Numbr q1)) = F (p * p1) (Numbr (q * q1)) add :: Fraction -> Fraction -> Fraction add f f1 = add1 (simplify f) (simplify f1) where add1 (Numbr p) (Numbr q) = Numbr (p + q) add1 (Numbr p) (F p1 (Numbr q1)) = F (q1 * p + p1) (Numbr q1) add1 (F p1 (Numbr q1)) (Numbr p) = F (q1 * p + p1) (Numbr q1) add1 (F p (Numbr q)) (F p1 (Numbr q1)) = F (p * q1 + q * p1) (Numbr (q * q1)) sub :: Fraction -> Fraction -> Fraction sub f f1 = sub1 (simplify f) (simplify f1) where sub1 (Numbr p) (Numbr q) = Numbr (p - q) sub1 (Numbr p) (F p1 (Numbr q1)) = F (q1 * p - p1) (Numbr q1) sub1 (F p1 (Numbr q1)) (Numbr p) = F (q1 * p - p1) (Numbr q1) sub1 (F p (Numbr q)) (F p1 (Numbr q1)) = F (p * q1 - q * p1) (Numbr (q * q1)) divid :: Fraction -> Fraction -> Fraction divid f f1 = divid1 (simplify f) (simplify f1) where divid1 (Numbr p) (Numbr q) = F p (Numbr q) divid1 (Numbr p) (F p1 (Numbr q1)) = F (p * q1) (Numbr p1) divid1 (F p1 (Numbr q1)) (Numbr p) = F p1 (Numbr (q1 * p) ) divid1 (F p (Numbr q)) (F p1 (Numbr q1)) = F (p * q1) (Numbr (q * p1)) -- This works by taking a possibly nested fraction, flattening -- it into a list and then folds (/) over the list to simplify the -- fraction simplify :: Fraction -> Fraction simplify f = foldr (/) lastFraction remainingFractions where flat = flatten f lastFraction = last flat remainingFractions = takeWhile (/= lastFraction) flat -- Remove common divisors -- eg reduce 6/10 -> 3/5, reduce 3/5 -> 3/5 reduce :: Fraction -> Fraction reduce (Numbr n) = Numbr n reduce f@(F n (Numbr d)) | gDiv == 1 = f | otherwise = F (n `div` gDiv) (Numbr (d `div` gDiv)) where gDiv = gcd n d reduce (F n f) = F n (reduce f) -- Take a possibly recursive fraction and reduce it to a list of fractions flatten :: Fraction -> [Fraction] flatten f@(F _ (Numbr _) ) = [f] flatten (Numbr n) = [F n (Numbr 1)] flatten (F n f) = Numbr n : flatten f -- Simple pattern matching to get the numerator from a Fraction num :: Fraction -> Integer num (Numbr n) = n num (F n _) = n -- and the denominator denom :: Fraction -> Integer denom (Numbr _) = 1 denom (F _ (Numbr n)) = n denom (F _ f@(F _ _)) = denom f -- Takes a Fraction, simplifies it by a "flatten and foldr" technique, -- removes common divisors and finally resolves the fraction as a Float. evalFrac :: Fraction -> Float evalFrac f = fromIntegral n / fromIntegral d where F n (Numbr d) = reduce . simplify $ f -- The 'a' coefficients The 'b' coefficients Depth contFrac :: (Integer -> Fraction) -> (Integer -> Numerator) -> Integer -> Fraction contFrac fa fb = rf 0 where rf n t | n > t = 0 | otherwise = fa n + F (fb n) (rf (n + 1) t) root2 :: Integer -> Fraction root2 = contFrac fa fb where fa 0 = 1 fa _ = 2 fb _ = 1 root5 :: Integer -> Fraction root5 = contFrac fa fb where fa 0 = 2 fa _ = 4 fb _ = 1 phi :: Integer -> Fraction phi = contFrac fa fb where fa _ = 1 fb _ = 1 |
The functions mul, add, sub and divid are all fairly simple and are really how you would expect multiplication, addition, subtraction and division of fractions to be done and they work on continued fractions by calling simplify before applying the operation.
The function contFrac is the core of what we are doing and it’s really quite a simple recursive function. It take two ‘generator’ functions that supply the a and b values in this image:
and the depth parameter determines how many times it recurses. So with a pair of suitable generator functions many (maybe all) continued fractions can be generated. For example the square root of 2 is
and so we have
1 2 3 4 5 6 7 |
-- -- root2 :: Integer -> Fraction root2 = contFrac fa fb where fa 0 = 1 fa _ = 2 fb _ = 1 |
Trying this out in GHCi to a depth of 5 we get
1 2 |
λ-> evalFrac . root2 $ 5 1.4137931 |
To a depth of 10 we get
1 2 |
λ-> evalFrac . root2 $ 10 1.4142137 |
We can also get the terms for each value of depth like this
1 2 3 4 |
λ-> roots = [evalFrac . root2 $ n | n <- [0..20]] *Fractions λ-> roots [Infinity,1.0,1.5,1.4,1.4166666,1.4137931,1.4142857,1.4142011,1.4142157,1.4142132,1.4142137,1.4142135,1.4142135,1.4142135,1.4142135,1.4142135,1.4142135,1.4142135,1.4142135,1.4142135,1.4142135] |
Or, in fraction form:
1 2 3 4 |
λ-> roots = [root2 $ n | n <- [0..20]] *Fractions λ-> roots [1/0,1/1,3/2,7/5,17/12,41/29,99/70,239/169,577/408,1393/985,3363/2378,8119/5741,19601/13860,47321/33461,114243/80782,275807/195025,665857/470832,1607521/1136689,3880899/2744210,9369319/6625109,22619537/15994428] |
The continued fraction for phi is really simple – the ‘a‘ s and ‘b‘ s are all 1.
1 2 3 4 |
phi :: Integer -> Fraction phi = contFrac fa fb where fa _ = 1 fb _ = 1 |
Calculating to a depth of 100 we have
1 2 3 |
-- λ-> evalFrac . phi $ 100 1.6180339 |
which is quite accurate!
Getting the terms out we have…
1 2 3 4 5 6 7 8 |
-- -- λ-> phis = [phi n | n <- [0..30]] *Fractions λ-> phis [1/0,1/1,2/1,3/2,5/3,8/5,13/8,21/13,34/21,55/34,89/55,144/89,233/144,377/233,610/377,987/610,1597/987,2584/1597,4181/2584, 6765/4181,10946/6765,17711/10946,28657/17711,46368/28657,75025/46368,121393/75025,196418/121393,317811/196418,514229/317811, 832040/514229,1346269/832040] |
If we now map denom (or num) over phis we get the terms of the Fibonacci series! 🙂
1 2 |
λ-> map denom phis [0,1,1,2,3,5,8,13,21,34,55,89,144,233,377,610,987,1597,2584,4181,6765,10946,17711,28657,46368,75025,121393,196418,317811,514229,832040] |
or slightly larger…
λ-> map denom phis
[0,1,1,2,3,5,8,13,21,34,55,89,144,233,377,610,987,1597,2584,4181,6765,10946,17711,28657,46368,75025,121393,196418,317811,514229,832040]
which was the purpose of this post.
Concluding Notes
What I’ve written here has only touched the surface of continued fractions. I hope that future posts will
- explore an alternative to foldr when resolving a continued fraction.
- create a parser that will generate continued fractions from standard notation for continued fractions
- extend the type beyond fractions using integers to fractions with complex numbers
This website is a mine of wonderfully explained ideas about fractions and is well worth a look. It explains in a clear and detailed way many properties of continued fractions.
You can find this Haskell code in GitHub.
Thanks for reading…!