Fibonacci numbers generator in Haskell

Fibonacci numbers implementations in Haskell one of the classical examples. An example I found is the following: fibs :: [Int] fibs = 0 : 1 : [ a + b | (a, b) <- zip fibs (tail fibs)] To get the k-th number you do the following: Result = fibs !! k It is elegant but creates a list of all Fibonacci numbers less than k-th, and the code is not very readable :). I wrote my own Fibonacci numbers generator: fib :: Int -> [Int] fib 0 = [0,0] fib 1 = [1,0] fib n = [sum prevFib, head prevFib] where a = fib (n - 1) To get the k-th number you do the following: result = head (fib k) It does not generate full list of Fibonacci numbers, but keeps only 2 previous numbers, and has only one recursive call. Because the list always has only 2 elements using the functions head and sum is a bit overkill. Can we do better? _________________________________________________________________ Are you using the latest version of MSN Messenger? Download MSN Messenger 7.5 today! http://join.msn.com/messenger/overview

Here's some code I wrote a while back for computing the nth Fibonacci number. It has O(log n) time complexity rather than O(n). It isn't the most elegant example, but it should be one of the fastest approaches.
import Data.Bits (shiftR, xor, (.|.), (.&.)) import Data.Word (Word32)
fibo :: Word32 -> Integer fibo n = loop (highestBitMask n) 1 0 where loop :: Word32 -> Integer -> Integer -> Integer loop i a b | i == 0 = b | n .&. i /= 0 = (loop (shiftR i 1) $! a*(2*b + a)) $! a*a + b*b | otherwise = (loop (shiftR i 1) $! a*a + b*b) $! b*(2*a - b)
highestBitMask :: Word32 -> Word32 highestBitMask x = case (x .|. shiftR x 1) of x -> case (x .|. shiftR x 2) of x -> case (x .|. shiftR x 4) of x -> case (x .|. shiftR x 8) of x -> case (x .|. shiftR x 16) of x -> (x `xor` (shiftR x 1))
Cheers,
Spencer Janssen
On 6/15/06, Vladimir Portnykh
Fibonacci numbers implementations in Haskell one of the classical examples. An example I found is the following:
fibs :: [Int] fibs = 0 : 1 : [ a + b | (a, b) <- zip fibs (tail fibs)]
To get the k-th number you do the following: Result = fibs !! k
It is elegant but creates a list of all Fibonacci numbers less than k-th, and the code is not very readable :).
I wrote my own Fibonacci numbers generator:
fib :: Int -> [Int] fib 0 = [0,0] fib 1 = [1,0] fib n = [sum prevFib, head prevFib] where a = fib (n - 1)
To get the k-th number you do the following:
result = head (fib k)
It does not generate full list of Fibonacci numbers, but keeps only 2 previous numbers, and has only one recursive call. Because the list always has only 2 elements using the functions head and sum is a bit overkill.
Can we do better?
_________________________________________________________________ Are you using the latest version of MSN Messenger? Download MSN Messenger 7.5 today! http://join.msn.com/messenger/overview
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, 15 Jun 2006, Vladimir Portnykh wrote:
Fibonacci numbers implementations in Haskell one of the classical examples. An example I found is the following:
fibs :: [Int] fibs = 0 : 1 : [ a + b | (a, b) <- zip fibs (tail fibs)]
To get the k-th number you do the following: Result = fibs !! k
It is elegant but creates a list of all Fibonacci numbers less than k-th, and the code is not very readable :).
The garbage collector will free storage for values that are no longer needed. So if the garbage collector is hard working there will be no more than 2 previous values stored per computation of a new value.
I wrote my own Fibonacci numbers generator:
fib :: Int -> [Int] fib 0 = [0,0] fib 1 = [1,0] fib n = [sum prevFib, head prevFib] where a = fib (n - 1)
To get the k-th number you do the following:
result = head (fib k)
It does not generate full list of Fibonacci numbers, but keeps only 2 previous numbers, and has only one recursive call. Because the list always has only 2 elements using the functions head and sum is a bit overkill.
If you want to do it that way, better use pairs of numbers instead of lists. Lists can have any number of elements, pairs have exactly two members. So the latter is more type safe.

G'day all.
Quoting Vladimir Portnykh
I wrote my own Fibonacci numbers generator:
fib :: Int -> [Int] fib 0 = [0,0] fib 1 = [1,0] fib n = [sum prevFib, head prevFib] where a = fib (n - 1)
To get the k-th number you do the following:
result = head (fib k)
[...]
Can we do better?
Sure we can. We can use a more efficient algorithm: fib :: Integer -> Integer fib k | k < 0 = error "fib" | otherwise = fst (fib' k) fib' :: Integer -> (Integer,Integer) fib' 0 = (0,1) fib' k | k `mod` 2 == 0 = let (a,b) = fib' (k `div` 2 - 1) c = a + b c2 = c*c in (c2 - a*a, c2 + b*b) | otherwise = let (a,b) = fib' ((k-1) `div` 2) c = a+b a2 = a*a in (b*b + a2, c*c - a2) Cheers, Andrew Bromage

How about the closed form ;)
-- fib x returns the x'th number in the fib sequence
fib :: Integer -> Integer
fib x = let phi = ( 1 + sqrt 5 ) / 2
in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) )
Seems pretty quick to me, even with sqrt and arbitrarily large numbers.
On 6/15/06 9:33 AM, "Vladimir Portnykh"
Fibonacci numbers implementations in Haskell one of the classical examples. An example I found is the following:
fibs :: [Int] fibs = 0 : 1 : [ a + b | (a, b) <- zip fibs (tail fibs)]
To get the k-th number you do the following: Result = fibs !! k
It is elegant but creates a list of all Fibonacci numbers less than k-th, and the code is not very readable :).
I wrote my own Fibonacci numbers generator:
fib :: Int -> [Int] fib 0 = [0,0] fib 1 = [1,0] fib n = [sum prevFib, head prevFib] where a = fib (n - 1)
To get the k-th number you do the following:
result = head (fib k)
It does not generate full list of Fibonacci numbers, but keeps only 2 previous numbers, and has only one recursive call. Because the list always has only 2 elements using the functions head and sum is a bit overkill.
Can we do better?
_________________________________________________________________ Are you using the latest version of MSN Messenger? Download MSN Messenger 7.5 today! http://join.msn.com/messenger/overview
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Mathew Mills
-- fib x returns the x'th number in the fib sequence fib :: Integer -> Integer fib x = let phi = ( 1 + sqrt 5 ) / 2 phi' = ( 1 - sqrt 5 ) / 2 in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) )
-- Seems pretty quick to me, even with sqrt and arbitrarily large numbers.
You don't actually need the part with phi'^x. Since |phi'| < 1, phi'^x gets small fast as x increases. In fact |phi'^x| is always smaller than 1/2, so -phi'^x in the expression above can be replaced by +0.5. Unfortunately with arbitrarily large numbers it gets the answer wrong. "Arbitrarily large" in this case is smaller than 100.
fib 100 354224848179261800448
The correct answer is 354224848179261915075 The relative error is very small, so it is a good approximation.

G'day all.
Quoting Mathew Mills
How about the closed form ;)
-- fib x returns the x'th number in the fib sequence
fib :: Integer -> Integer
fib x = let phi = ( 1 + sqrt 5 ) / 2
in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) )
Seems pretty quick to me, even with sqrt and arbitrarily large numbers.
I called my version "fib" and your version "fib2". I get: *Fib> [ i | i <- [30..100], fib i == fib2 i ] [32,35,43,46,51,71] Yes, the closed form is faster. But if, as part of the rules, one is allowed to give wrong answers, it's not difficult to write a function that's even faster than this. Cheers, Andrew Bromage

I guess I don't get any points for an approximate solution, ay?
Is there anything that can be done (easily) to reduce the rounding errors?
On 6/15/06 11:23 PM, "ajb@spamcop.net"
G'day all.
Quoting Mathew Mills
: How about the closed form ;)
-- fib x returns the x'th number in the fib sequence
fib :: Integer -> Integer
fib x = let phi = ( 1 + sqrt 5 ) / 2
in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) )
Seems pretty quick to me, even with sqrt and arbitrarily large numbers.
I called my version "fib" and your version "fib2". I get:
*Fib> [ i | i <- [30..100], fib i == fib2 i ] [32,35,43,46,51,71]
Yes, the closed form is faster. But if, as part of the rules, one is allowed to give wrong answers, it's not difficult to write a function that's even faster than this.
Cheers, Andrew Bromage _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Mathew Mills wrote:
I guess I don't get any points for an approximate solution, ay?
Is there anything that can be done (easily) to reduce the rounding errors?
http://www.google.com/search?q=haskell+exact+real+arithmetic

Chris Kuklewicz wrote:
Mathew Mills wrote:
I guess I don't get any points for an approximate solution, ay?
Is there anything that can be done (easily) to reduce the rounding errors?
http://www.google.com/search?q=haskell+exact+real+arithmetic
Using Era.hs (with the patch at http://www.haskell.org/hawiki/ExactRealArithmetic) and add spaces around 1%n to 1 % n (since I have -fglasgow-exts turned on and %n looks like a linear implicit thingie). Now this works:
fib x = let phi,phi' :: CR phi = (1 + sqrt 5) /2 phi' = (1 - sqrt 5)/2 in truncate ( recip (sqrt 5) * (phi^x -phi'^x))
*Era> fib 100 354224848179261915075 which is the (allegedly) correct answer. -- Chris

Mathew Mills
Is there anything that can be done (easily) to reduce the rounding errors?
The hint that I gave before is one easy way.
fib :: Integer -> Integer fib x = let phi = ( 1 + sqrt 5 ) / 2 in truncate( ( 1 / sqrt 5 ) * ( phi ^ x + 0.5) )
You run out of precision eventually. IEEE Double's give you about 15 decimal digits, so the results become approximate for x > 75.

Doug Quale
Mathew Mills
writes: Is there anything that can be done (easily) to reduce the rounding errors?
The hint that I gave before is one easy way.
fib :: Integer -> Integer fib x = let phi = ( 1 + sqrt 5 ) / 2 in truncate( ( 1 / sqrt 5 ) * ( phi ^ x + 0.5) )
You run out of precision eventually. IEEE Double's give you about 15 decimal digits, so the results become approximate for x > 75.
Sorry, I suffered brain lock. The correct expression is parenthesized differently:
fib n = truncate(phi^n/sqrt 5 + 0.5) where phi = (1 + sqrt 5)/2

On 2006-06-15 at 17:33BST "Vladimir Portnykh" wrote:
Fibonacci numbers implementations in Haskell one of the classical examples. An example I found is the following:
fibs :: [Int] fibs = 0 : 1 : [ a + b | (a, b) <- zip fibs (tail fibs)]
Can we do better?
Well, you've had various variously sensible responses, so here's one with /worse/ space performance (but a degree of cuteness): module Main where import InfiniteMap fib = memo fib' where fib' fib 0 = 0 fib' fib 1 = 1 fib' fib n = fib (n-1) + fib (n-2) memo f = f memf where memf n = locate n m m = build $ f memf --- module InfiniteMap where data IM t = Node {entry:: t, if_even::IM t, if_odd:: IM t} build f = Node (f 0) (build $ f . (*2)) (build $ f . (+1) . (*2)) locate 0 (Node e _ _) = e locate n (Node _ e o) | even n = locate (n`div`2) e | otherwise = locate ((n-1)`div`2) o -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk
participants (9)
-
ajb@spamcop.net
-
Chris Kuklewicz
-
Doug Quale
-
Henning Thielemann
-
Jon Fairbairn
-
Mathew Mills
-
Ronny Wichers Schreur
-
Spencer Janssen
-
Vladimir Portnykh