[Haskell-cafe] fastest Fibonacci numbers in the West

Daniel Fischer daniel.is.fischer at web.de
Thu Jan 27 09:26:39 EST 2005


Am Donnerstag, 27. Januar 2005 06:08 schrieb William Lee Irwin III:
> Inspired by a discussion on freenode #haskell, I tried to write the
> fastest Fibonacci number function possible, i.e. given a natural
> number input n to compute F_n.
>
>
> For the moment, mlton-generated binaries crash computing fib (10^8-1),
> and there is a 6:1 speed difference for fib (10^7-1) between the two,
> where mlton-generated binaries take just under 1 minute, and ghc-
> generated binaries take just under 6 minutes.

Obviously, your machine is significantly faster than mine.
On mine, fib (10^6) takes a little under two minutes, fib (10^7-1) I ^C-ed 
after twenty.

I think ,more readable than
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))

would be
unfoldl f x = case f x of
                         Nothing -> []
                         Just (q,r) -> unfoldl f q ++ [r]
divs 0 = Nothing
divs k = Just (n `quotRem` 2)
-- this has no influence on performance, since it's optimized anyway.
>
> Anyway, thoughts on how to improve all this from the programmer's
> point of view, or otherwise explaining what's going on or ameliorating
> whatever effect is at work here would be appreciated.
>

I thought, I'd do it in the ring of integers in Q(sqrt(5)), code attached,
this was a whiff faster for n = 700000 on my machine, a whiff slower 
for n = 10^6 -- any idea how that may come?
>
> -- wli
Daniel
-------------- next part --------------
module Main where

import System.Environment

infix 8 :+

data Surd5 = !Integer :+ !Integer
                deriving (Eq, Show, Read)

instance Num Surd5 where
   (a :+ b) + (c :+ d) = (a+c) :+ (b+d)
   (a :+ b) - (c :+ d) = (a-c) :+ (b-d)
   (a :+ b) * (c :+ d) = (a*c+b*d) :+ (a*d+(c+d)*b)
   negate (a :+ b) = (-a) :+ (-b)
   signum (a :+ b) = case signum a of
                        0 -> signum b :+ 0
			1 -> case signum b of
			        (-1) -> signum ((2*a-b)^2-5*b^2) :+ 0
				_    -> 1 :+ 0
			_ -> case signum b of
			        1 -> signum (5*b^2-(2*a-b)^2) :+ 0
				_ -> (-1) :+ 0
   abs s = signum s * s
   fromInteger n = n :+ 0

fib :: Integral a => a -> Integer
fib n = let (a:+b) = (0:+1)^n in b

main :: IO ()
main = getArgs >>= mapM_ (print . fib . read)


More information about the Haskell-Cafe mailing list