The Fibonacci sequence: Difference between revisions
DonStewart (talk | contribs) |
RossPaterson (talk | contribs) (organization, uniformity, plus a matrix implementation) |
||
Line 1: | Line 1: | ||
Implementing the [http://en.wikipedia.org/wiki/Fibonacci_number | Implementing the [http://en.wikipedia.org/wiki/Fibonacci_number Fibonacci sequence] is considered the "Hello, world!" of Haskell programming. This page collects Haskell implementations of the sequence. | ||
== Naive | == Naive definition == | ||
<haskell> | <haskell> | ||
Line 9: | Line 9: | ||
</haskell> | </haskell> | ||
== | == Linear-time implementations == | ||
One can compute the first ''n'' Fibonacci numbers with ''O(n)'' additions. | |||
If <hask>fibs</hask> is the infinite list of Fibonacci numbers, one can define | |||
<haskell> | <haskell> | ||
fib = | fib n = fibs!!n | ||
</haskell> | </haskell> | ||
== | === Canonical zipWith implementation === | ||
<haskell> | <haskell> | ||
fibs = 0 : 1 : zipWith (+) fibs (tail fibs) | |||
</haskell> | </haskell> | ||
== With | === With scanl === | ||
<haskell> | <haskell> | ||
fibs = fix ((0:) . scanl (+) 1) | |||
</haskell> | </haskell> | ||
== A fairly fast version, using some identities == | === With unfoldr === | ||
<haskell> | |||
fibs = unfoldr (\(f1,f2) -> Just (f1,(f2,f1+f2))) (0,1) | |||
</haskell> | |||
== Log-time implementations == | |||
=== Using 2x2 matrices === | |||
Using [[Prelude_extensions#Matrices|simple matrices]], | |||
<haskell> | |||
fib n = head (apply (Matrix [[1,1], [1,0]] ^ n) [0,1]) | |||
</haskell> | |||
=== A fairly fast version, using some identities === | |||
<haskell> | <haskell> | ||
Line 40: | Line 57: | ||
</haskell> | </haskell> | ||
== Another fast fib == | === Another fast fib === | ||
<haskell> | <haskell> | ||
Line 55: | Line 72: | ||
</haskell> | </haskell> | ||
== Fastest Fib in the West == | === Fastest Fib in the West === | ||
This was contributed by [http://www.haskell.org/pipermail/haskell-cafe/2005-January/008839.html wli] | This was contributed by [http://www.haskell.org/pipermail/haskell-cafe/2005-January/008839.html wli] | ||
(It assumes that the sequence starts with 1.) | |||
<haskell> | <haskell> | ||
import Data.List | import Data.List | ||
fib1 n = snd . foldl fib' (1, 0) . map (toEnum . fromIntegral) $ unfoldl divs n | |||
where | where | ||
unfoldl f x = case f x of | unfoldl f x = case f x of | ||
Line 75: | Line 92: | ||
| 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> | </haskell> | ||
Revision as of 23:02, 9 May 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)
Log-time implementations
Using 2x2 matrices
Using simple matrices,
fib n = head (apply (Matrix [[1,1], [1,0]] ^ n) [0,1])
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))