[Haskell-cafe] Fibonacci numbers generator in Haskell

Spencer Janssen spencerjanssen at gmail.com
Thu Jun 15 12:51:18 EDT 2006


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 <vportnykh at hotmail.com> 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 :).
>
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list