[Haskell-cafe] fastest Fibonacci numbers in the West

William Lee Irwin III wli at holomorphy.com
Thu Jan 27 00:08:33 EST 2005


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.

mlton seems to enjoy substantially better speed despite equivalent
algorithms; it may be enlightening to determine the causes of this,
at least for those concerned about performance and the inner workings
of the Haskell runtime system(s). In general, I am not usually very
concerned about performance, nor am I in this case. But it's something
of a mindless microbenchmark or similar.

The things I'd normally think of to speed this up would be getting
some primitives to find the highest bit of an integer (floor . lg)
and to test a given bit of an integer (something vaguely like
fromEnum . fromIntegral . (`mod` 2) . (/2^k)), both in some lightweight
O(1) with low-hidden-constant manner. This doesn't appear to be a factor
in the testing I did, as they're largely 1:1 translations of each other.
Still, such things would be useful in various other algorithms, of far
greater importance than this one.

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.

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.


-- wli
-------------- next part --------------
module Main where
import System.Environment
import Data.List

fib 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))

main = getArgs >>= mapM_ (print . fib . read)
-------------- next part --------------
fun	  unfold 0 = []
	| unfold n = let val ((q:int), (r:int)) = (n div 2, n mod 2)
		     in (unfold q) @ [if r = 1 then true else false]
		     end

fun crunch (p, (f, g)) = if p then (f*(f+2*g), f*f+g*g) else (f*f+g*g, g*(2*f-g))

fun myfib n = #2 (foldl crunch (1, 0) (unfold n))

val n = valOf(Int.fromString(hd(CommandLine.arguments())))
  handle Option =>
    (print ("usage: tailfib n\n");
    OS.Process.exit(OS.Process.failure))

val _ = print (IntInf.toString (myfib n) ^ "\n")


More information about the Haskell-Cafe mailing list