[Haskell-cafe] speeding up fibonacci with memoizing

Stefan O'Rear stefanor at cox.net
Mon Feb 19 03:32:13 EST 2007


On Mon, Feb 19, 2007 at 08:47:39AM +0100, Mikael Johansson wrote:
> On Sun, 18 Feb 2007, Yitzchak Gale wrote:
> >Besides memoizing, you might want to use the fact
> >that:
> >
> >fib (2*k) == (fib (k+1))^2 - (fib (k-1))^2
> >fib (2*k-1) == (fib k)^2 + (fib (k-1))^2
> >
> 
> Or, you know, go straight to the closed form for the fibonacci numbers! :)

That's fine in the blessed realm of arithmatic rewrite rules, but
here we need bitstrings, and computing large powers of irrational numbers
is not exactly fast.

Phi is definable in finite fields (modular exponentiation yay!) but modular-ation
seems ... problematic.

I have a gut feeling the p-adic rationals might help, but insufficient knowledge
to formulate code.

The GMP fibbonacci implementation is of my quasilinear recurrence family, not
closed form.

And lest we forget the obvious - by far the fastest way to implement fib in GHC Haskell:

{-# OPTIONS_GHC -O2 -cpp -fglasgow-exts #-}
module 
#ifdef fibimpl
Main(main)
#else
Fibs
#endif
where
import System.Environment
import Array
import List(unfoldr)

#ifdef __GLASGOW_HASKELL__
import System.IO.Unsafe
import Foreign.Marshal.Alloc
import Foreign.Storable
import GHC.Exts
import Foreign.C.Types
#endif

-- same as before

#ifdef __GLASGOW_HASKELL__
foreign import ccall "gmp.h __gmpz_fib_ui" _gfib :: Ptr Int -> CULong -> IO ()
foreign import ccall "gmp.h __gmpz_init" _ginit :: Ptr Int -> IO ()

gmpfib :: Int -> Integer
gmpfib n = unsafePerformIO $ allocaBytes 12 $ \p -> do
    _ginit p
    _gfib p (fromIntegral n)
    I# sz <- peekElemOff p 1
    I# pt <- peekElemOff p 2
    return (J# sz (unsafeCoerce# (pt -# 8#)))
#endif

-- same as before 

stefan at stefans:~/fibbench$ ./h gs 100000000
12.84user 0.24system 0:13.08elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+21082minor)pagefaults 0swaps
stefan at stefans:~/fibbench$ ./h gmp 100000000
9.12user 0.42system 0:09.58elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+35855minor)pagefaults 0swaps
stefan at stefans:~/fibbench$


More information about the Haskell-Cafe mailing list