The Fibonacci sequence: Difference between revisions
RossPaterson (talk | contribs) (tweak for generality) |
(Added constant-time implementations section) |
||
Line 101: | Line 101: | ||
| p = (f*(f+2*g), f^2 + g^2) | | p = (f*(f+2*g), f^2 + g^2) | ||
| otherwise = (f^2+g^2, g*(2*f-g)) | | otherwise = (f^2+g^2, g*(2*f-g)) | ||
</haskell> | |||
== Constant-time implementations == | |||
The Fibonacci numbers can be computed in constant time using Binet's formula. | |||
However, that only works well within the range of floating-point numbers | |||
available on your platform. | |||
Beyond that, you can use [http://haskell.org/haskellwiki/Applications_and_libraries/Mathematics#Real_and_rational_numbers unlimited-precision floating-point numbers], | |||
but the result will probably not be any better than the [[#Log-time_implementations|log-time implementations]] above. | |||
=== Using Binet's formula === | |||
<haskell> | |||
fib n = round $ phi ** fromIntegral n / sq5 | |||
where | |||
sq5 = sqrt 5 :: Double | |||
phi = (1 + sq5) / 2 | |||
</haskell> | </haskell> | ||
Revision as of 10:20, 6 November 2007
Implementing the Fibonacci sequence is considered the "Hello, world!" of Haskell programming. This page collects Haskell implementations of the sequence.
Naive definition
fib 0 = 0
fib 1 = 1
fib n = fib (n-1) + fib (n-2)
Linear-time implementations
One can compute the first n Fibonacci numbers with O(n) additions.
If fibs
is the infinite list of Fibonacci numbers, one can define
fib n = fibs!!n
Canonical zipWith implementation
fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
With scanl
fibs = fix ((0:) . scanl (+) 1)
With unfoldr
fibs = unfoldr (\(f1,f2) -> Just (f1,(f2,f1+f2))) (0,1)
With iterate
fibs = map fst $ iterate (\(f1,f2) -> (f2,f1+f2)) (0,1)
Log-time implementations
Using 2x2 matrices
The argument of iterate
above is a linear transformation,
so we can represent it as matrix and compute the nth power of this matrix with O(log n) multiplications and additions.
For example, using the simple matrix implementation in Prelude extensions,
fib n = head (apply (Matrix [[0,1], [1,1]] ^ n) [0,1])
This technique works for any linear recurrence.
A fairly fast version, using some identities
fib 0 = 0
fib 1 = 1
fib n | even n = f1 * (f1 + 2 * f2)
| n `mod` 4 == 1 = (2 * f1 + f2) * (2 * f1 - f2) + 2
| otherwise = (2 * f1 + f2) * (2 * f1 - f2) - 2
where k = n `div` 2
f1 = fib k
f2 = fib (k-1)
Another fast fib
fib = fst . fib2
-- | Return (fib n, fib (n + 1))
fib2 0 = (1, 1)
fib2 1 = (1, 2)
fib2 n
| even n = (a*a + b*b, c*c - a*a)
| otherwise = (c*c - a*a, b*b + c*c)
where (a,b) = fib2 (n `div` 2 - 1)
c = a + b
Fastest Fib in the West
This was contributed by wli (It assumes that the sequence starts with 1.)
import Data.List
fib1 n = snd . foldl fib' (1, 0) . map (toEnum . fromIntegral) $ unfoldl divs n
where
unfoldl f x = case f x of
Nothing -> []
Just (u, v) -> unfoldl f v ++ [u]
divs 0 = Nothing
divs k = Just (uncurry (flip (,)) (k `divMod` 2))
fib' (f, g) p
| p = (f*(f+2*g), f^2 + g^2)
| otherwise = (f^2+g^2, g*(2*f-g))
Constant-time implementations
The Fibonacci numbers can be computed in constant time using Binet's formula. However, that only works well within the range of floating-point numbers available on your platform.
Beyond that, you can use unlimited-precision floating-point numbers, but the result will probably not be any better than the log-time implementations above.
Using Binet's formula
fib n = round $ phi ** fromIntegral n / sq5
where
sq5 = sqrt 5 :: Double
phi = (1 + sq5) / 2