Fibbonachi numbers algorithm work TOO slow.

Please help me. I'm new in Haskell programming, but wrote some things in Scheme. I make so function: fib 1 = 1 fib 2 = 2 fib n = fib (n-1) + fib (n-2) And when I call "fib 30" it works about 5 seconds. As for me it's really TOO SLOW. Tell me please if I have something missed, maybe some compiler (interpretaitor) options (I use ghc 6.6.1). P.S. As I understand function "fib n" should be calculated one time. For example if I call "fib 30" compiler builds tree in which call function "fib 28" 2 times and so on. But as for lazy calculation principle it should be calculated just ones and then it's value is used for all other calls of this function with the same argument. But it seems that this principle doesn't work in this algorithm. -- View this message in context: http://www.nabble.com/Fibbonachi-numbers-algorithm-work-TOO-slow.-tf4752338.... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Nov 5, 2007 5:22 PM, gitulyar
Please help me. I'm new in Haskell programming, but wrote some things in Scheme. I make so function:
fib 1 = 1 fib 2 = 2 fib n = fib (n-1) + fib (n-2)
And when I call "fib 30" it works about 5 seconds. As for me it's really TOO SLOW.
Tell me please if I have something missed, maybe some compiler (interpretaitor) options (I use ghc 6.6.1).
P.S. As I understand function "fib n" should be calculated one time. For example if I call "fib 30" compiler builds tree in which call function "fib 28" 2 times and so on. But as for lazy calculation principle it should be calculated just ones and then it's value is used for all other calls of this function with the same argument. But it seems that this principle doesn't
work in this algorithm. Lazy evaluation is not the same thing as memoization. This algorithm for calculating fibonacci numbers is just as inefficient in Haskell as it is in any other language. Lazy evaluation has to do with *when* things get executed, not saving the values of function calls to be used in place of other calls with the same arguments. For a more efficient Haskell implementation of fibonacci numbers, try fibs :: [Integer] fibs = 1 : 1 : zipWith (+) fibs (tail fibs) fib n = fibs !! n -Brent

For a more efficient Haskell implementation of fibonacci numbers, try
fibs :: [Integer] fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
fib n = fibs !! n
This is uglier, but just to keep using just plain recursion: fib = fib' 0 1 where fib' a b 0 = a fib' a b n = fib' b (a+b) (n-1) You may want "fib' a b n | a `seq` b `seq` n `seq` False = undefined" for strictness if the compiler isn't smart enough to figure out (sorry, didn't test it). And, *please* correct me if I said something stupid =). See ya, -- Felipe.

Brent Yorgey wrote:
On Nov 5, 2007 5:22 PM, gitulyar
mailto:gitulyar@gmail.com> wrote: Please help me. I'm new in Haskell programming, but wrote some things in Scheme. I make so function:
fib 1 = 1 fib 2 = 2 fib n = fib (n-1) + fib (n-2)
And when I call "fib 30" it works about 5 seconds. As for me it's really TOO SLOW.
Tell me please if I have something missed, maybe some compiler (interpretaitor) options (I use ghc 6.6.1).
P.S. As I understand function "fib n" should be calculated one time. For example if I call "fib 30" compiler builds tree in which call function "fib 28" 2 times and so on. But as for lazy calculation principle it should be calculated just ones and then it's value is used for all other calls of this function with the same argument. But it seems that this principle doesn't
work in this algorithm.
Lazy evaluation is not the same thing as memoization. This algorithm for calculating fibonacci numbers is just as inefficient in Haskell as it is in any other language. Lazy evaluation has to do with *when* things get executed, not saving the values of function calls to be used in place of other calls with the same arguments.
For a more efficient Haskell implementation of fibonacci numbers, try
fibs :: [Integer] fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
fib n = fibs !! n
-Brent
Close, I believe Brent actually meant
fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
In any case, to answer your question more specifically, the memoization of *constants* is essential to the efficient implementation of lazy evaluation, and GHC certainly does it. You can just unroll the loop yourself to see. The following runs as fast as you'd expect: fib00 = 0 fib01 = 1 fib02 = fib00 + fib01 fib03 = fib01 + fib02 fib04 = fib02 + fib03 fib05 = fib03 + fib04 fib06 = fib04 + fib05 fib07 = fib05 + fib06 fib08 = fib06 + fib07 fib09 = fib07 + fib08 fib10 = fib08 + fib09 fib11 = fib09 + fib10 fib12 = fib10 + fib11 fib13 = fib11 + fib12 fib14 = fib12 + fib13 fib15 = fib13 + fib14 fib16 = fib14 + fib15 fib17 = fib15 + fib16 fib18 = fib16 + fib17 fib19 = fib17 + fib18 fib20 = fib18 + fib19 fib21 = fib19 + fib20 fib22 = fib20 + fib21 fib23 = fib21 + fib22 fib24 = fib22 + fib23 fib25 = fib23 + fib24 fib26 = fib24 + fib25 fib27 = fib25 + fib26 fib28 = fib26 + fib27 fib29 = fib27 + fib28 fib30 = fib28 + fib29 main = putStrLn . show $ fib30 The key insight is that by pure syntactic transformation, you can create a graph of fib## that has only (##+1) nodes in it. For a parametrized function fib n, no mere syntactic transformation can be so made. You actually have to evaluate the values (n-1) and (n-2) before you know how to wire the graph, putting it out of reach of a compile-time graph generator.

G'day all.
Quoting Dan Weston
In any case, to answer your question more specifically, the memoization of *constants*
I think you meant "CAFs".
You can just unroll the loop yourself to see. The following runs as fast as you'd expect:
fib00 = 0 fib01 = 1 fib02 = fib00 + fib01 [deletia] fib30 = fib28 + fib29
This is why we don't pay programmers by LOC.
For a parametrized function fib n, no mere syntactic transformation can be so made.
That's right, but you can do it by hand. Incidentally, we've been here before. Check out this thread: http://comments.gmane.org/gmane.comp.lang.haskell.cafe/19623 Cheers, Andrew Bromage

Andrew Bromage:
G'day all.
(MIS)Quoting Dan Weston:
fib00 = 0 fib01 = 1 fib02 = fib00 + fib01 [deletia] fib7698760 = fib7698759 + fib7698758
This is why we don't pay programmers by LOC. ... Incidentally, we've been here before. Check out this thread:
http://comments.gmane.org/gmane.comp.lang.haskell.cafe/19623
There is one solution missing there (unless I skipped it) fib n=((1+s)/2)^n-((1-s)/2)^n)/s where s=sqrt 5 If some of you complain that this is real, not integer, please remember that Leonardo of Pisa thought of applying this to rabbits. Well, rabbits are not integers, they eat carrots and have long ears. They are real thing. Hm. Well, sqrt is Floating. Now, floating rabbits are less common. Jerzy Karczmarczuk

I assume you meant
fib n=(((1+s)/2)^n-((1-s)/2)^n)/s where s=sqrt 5
Your solution starts to diverge from reality at n = 76:
fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
Prelude> let n = 76 in fibs !! n - round (fib n) 1 jerzy.karczmarczuk@info.unicaen.fr wrote:
Andrew Bromage:
G'day all. (MIS)Quoting Dan Weston:
fib00 = 0 fib01 = 1 fib02 = fib00 + fib01 [deletia] fib7698760 = fib7698759 + fib7698758
This is why we don't pay programmers by LOC. ... Incidentally, we've been here before. Check out this thread: http://comments.gmane.org/gmane.comp.lang.haskell.cafe/19623
There is one solution missing there (unless I skipped it) fib n=((1+s)/2)^n-((1-s)/2)^n)/s where s=sqrt 5 If some of you complain that this is real, not integer, please remember that Leonardo of Pisa thought of applying this to rabbits. Well, rabbits are not integers, they eat carrots and have long ears. They are real thing. Hm. Well, sqrt is Floating. Now, floating rabbits are less common. Jerzy Karczmarczuk
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

G'day all. Quoting jerzy.karczmarczuk@info.unicaen.fr:
There is one solution missing there (unless I skipped it) fib n=((1+s)/2)^n-((1-s)/2)^n)/s where s=sqrt 5 If some of you complain that this is real, not integer, please remember that Leonardo of Pisa thought of applying this to rabbits. Well, rabbits are not integers, they eat carrots and have long ears. They are real thing.
As noted, floating-point arithmetic diverges from integer arithmetic fairly quickly in this case. Of course, we can avoid this by doing computations in the field extension Q[sqrt 5]: data QS5 = QS5 Rational Rational infixl 7 <*>,> infixl 6 <->,<+> conjugate :: QS5 -> QS5 conjugate (QS5 a1 a2) = QS5 a1 (negate a2) (<+>),(<->),(<*>),(>) :: QS5 -> QS5 -> QS5 (QS5 a1 a2) <+> (QS5 b1 b2) = QS5 (a1+b1) (a2+b2) (QS5 a1 a2) <-> (QS5 b1 b2) = QS5 (a1-b1) (a2-b2) (QS5 a1 a2) <*> (QS5 b1 b2) = QS5 (a1*b1 + 5*a2*b2) (a1*b2 + a2*b1) a@(QS5 a1 a2) > b@(QS5 b1 b2) = let QS5 c1 c2 = a <*> conjugate b s = (b1*b1 - 5*b2*b2) in QS5 (c1 / s) (c2 / s) qpow :: QS5 -> Integer -> QS5 qpow q n | n < 3 = case n of 0 -> QS5 1 0 1 -> q 2 -> q <*> q | even n = let q' = qpow q (n `div` 2) in q' <*> q' | otherwise = let q' = qpow q (n `div` 2) in q' <*> q' <*> q fib ::Integer -> Integer fib n = let (QS5 fn _) = (qpow phi n <-> qpow phi' n) > s5 in numerator fn where phi = QS5 (1%2) (1%2) phi' = QS5 (1%2) (negate 1%2) s5 = QS5 0 1 However, this is still an O(log n) algorithm, because that's the complexity of raising-to-the-power-of. And it's slower than the simpler integer-only algorithms. It might be amusing to see if this could be transformed into one of the simpler algorithms, though. Cheers, Andrew Bromage

[I changed the subject, so (hopefully) rare people who just follow the thread may miss it, but I couldn't look at the name of Fibonacci with two errors in it anymore...] Andrew Bromage rebukes me once more that the fl. point solution diverges from the integer one [as if I didn't know that...], and proposes to make this calculation in an algebraic extension field. OK. His program has just 20 lines. It seems that we are slowly streaming to the generation of all possible and impossible Fibonacci generators, which - as everybody knows - is absolutely essential for the future of Humanity. So, I have another contribution. I hope that the complexity is linear, but I don't want to check. The generation function of Fibonaccis: SUM_{n=0}^infty f_n*x^n, where x is a formal variable, is equal to x/(1-x-x^2). Thus, it suffices to represent this rational expression as formal power series in x. Let's write a small *lazy* package which manipulates such power series, implemented as lists: u_0 + u_1*x + u_2*x^2 + ... ==> [u_0, u_1, u_2,...]. I have written such a package some 12 years ago, then Doug McIlroy wrote independently a Functional Pearl paper about series... Here you are just a fragment of it, without transcendental functions (nor sqrt), without reversal, composition, or other thinks the series lovers appreciate. -- ******************* -- The 'x' variable is a series with coeff_1=1, remaining: zero. So: zeros = 0 : zeros x = 0:1:zeros -- Good to have something to multiply series by scalars. infixr 7 *> c *> s = map (c*) s -- Num instance. Only interesting line is the multiplication, co-recursive. instance (Num a) => Num [a] where fromInteger n = fromInteger n : zeros (+) = zipWith (+) (-) = zipWith (-) (u0:uq)*v@(v0:vq) = u0*v0 : u0*>vq + v*uq -- The division. Reconstructed from the multiplication. Also co-recursive. instance (Fractional a) => Fractional [a] where fromRational c = fromRational c : zeros (u0:uq) / v@(v0:vq) = let w0 = u0/v0 in w0:(uq - w0*>vq)/v -- and now the solution: fibs = x/(1-x-x*x) -- ********************** If you complain that you don't want floating point numbers, just add the signature :: [Rational] (and import Ratio before). Everything becomes fraction with denominator 1. Now Fritz Ruehr can take the Haskell Wiki page and reconstruct from it a new instance of the 'Evolution of Haskell Programmer', based on the most useless Fibonacci algorithms. BTW, for your general culture: you *should* know that Fibonacci numbers have been invented by an Indian mathematician and grammarian Pangala, famous for his book Chandas Shastra. Not too much is known about him. WP says: "In Indian literary tradition, Pingala is identified as the younger brother of Panini..." [who was a great grammarian from 4BC, and who - as some think also invented a specific version of Italian hot sandwiches. This brings us nearer to Leonardo Pisano]. Jerzy Karczmarczuk

G'day all. Quoting jerzy.karczmarczuk@info.unicaen.fr:
Andrew Bromage rebukes me once more that the fl. point solution diverges from the integer one [as if I didn't know that...],
Sorry if it came across as that. I just meant it as a segue into a way to make the algorithm practical. I do note that nobody has tried it with continued fractions yet. Cheers, Andrew Bromage

Andrew Bromage:
I do note that nobody has tried it with continued fractions yet.
Now, it depends... If we take the PHI expansion as a CF: 1,1,1,1,1,... then the convergents constitue the (rations of) Fibonaccis, but it goes through the standard recurrence, so it is not so fancy. But we can take a decent representation of the Rabbit Number, in binary: 0.101101011011010110101101101011...., and then develop it in CF, which will give [0; 1, 2, 2, 4, 8, 32, 256, ...], then we find that those numbers are powers of Fibonaccis, 8=2^3, 32=2^5, 256=2^8, the next is 2^13, etc. It suffices to take the binary logarithm and the problem is solved. This is an industrial-strength, serious algorithm, involving lazy Rabbit Sequences, infinite Continued Fractions and Binary Logarithms, so everybody sees that it will for sure contribute to the Progress of the Western Civilization. I leave the homework for some Haskell newbies who want to become famous. Anyway, if somebody finds in his/her library The Fibonacci Quarterly, there is therein most probably much more about this fascinating subject, essential for our comprehension of the Universe, and of Phyllotaxis in particular. Jerzy Karczmarczuk

On Wed, Nov 07, 2007 at 10:30:30AM +0100, jerzy.karczmarczuk@info.unicaen.fr wrote:
[I changed the subject, so (hopefully) rare people who just follow the thread may miss it, but I couldn't look at the name of Fibonacci with two errors in it anymore...]
People with real e-mail clients will still see it in the thread because you still have In-reply-to and References set up correctly. Changing the topic in mid-thread isn't hazardous to us. Stefan

Stefan O'Rear wrote:
On Wed, Nov 07, 2007 at 10:30:30AM +0100, jerzy.karczmarczuk@info.unicaen.fr wrote:
[I changed the subject, so (hopefully) rare people who just follow the thread may miss it, but I couldn't look at the name of Fibonacci with two errors in it anymore...]
People with real e-mail clients will still see it in the thread because you still have In-reply-to and References set up correctly. Changing the topic in mid-thread isn't hazardous to us.
In addition, if you take an arbitrary message in "FP design", hit "reply", erase all quoting, and change the subject line to "About Fibonacci again...", then In-Reply-To and References are still set up correctly so that real e-mail clients still put it under the tree structure of "FP design", so hopefully people with real e-mail clients will miss it.

A fscinating dialog between 3 persons, almost like Adams' trilogy in 4 volumes! Albert Y. C. Lai writes:
Stefan O'Rear wrote:
jerzy.karczmarczuk@info.unicaen.fr wrote:
[I changed the subject, so (hopefully) rare people who just follow the thread may miss it...
People with real e-mail clients will still see it...
In addition, if you take an arbitrary message in "FP design", hit "reply", ... hopefully people with real e-mail clients will miss it.
Since I have no idea what a "real" mail client is, you will not frighten me! My mail client is apparently complex. Jerzy Karczmarczuk

Am Freitag, 9. November 2007 02:25 schrieb jerzy.karczmarczuk@info.unicaen.fr:
Since I have no idea what a "real" mail client is, you will not frighten me! My mail client is apparently complex.
As long as it's not purely imaginary...
Jerzy Karczmarczuk
Cheers, Daniel

On Fri, 2007-11-09 at 02:38 +0100, Daniel Fischer wrote:
Am Freitag, 9. November 2007 02:25 schrieb jerzy.karczmarczuk@info.unicaen.fr:
Since I have no idea what a "real" mail client is, you will not frighten me! My mail client is apparently complex.
As long as it's not purely imaginary...
This is becoming surreal. -- Bill Wood

When discussing the complexity of fib don't forget that integer
operations for bignums are no longer constant time.
-- Lennart
On Nov 7, 2007 6:55 AM, Henning Thielemann
On Tue, 6 Nov 2007 ajb@spamcop.net wrote:
However, this is still an O(log n) algorithm, because that's the complexity of raising-to-the-power-of. And it's slower than the simpler integer-only algorithms.
You mean computing the matrix power of
/1 1\ \0 1/
? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

There are some nice formulae for the Fibonacci numbers that relate f_m
to values f_n where n is around m/2. This leads to a tolerably fast
recursive algorithm.
Here's a complete implementation:
fib 0 = 0
fib 1 = 1
fib 2 = 1
fib m | even m = let n = m `div` 2 in fib n*(fib (n-1)+fib (n+1))
| otherwise = let n = (m-1) `div` 2 in fib n^2+fib (n+1)^2
Combine that with the NaturalTree structure here:
http://www.haskell.org/haskellwiki/Memoization and it seems to run
faster than Mathematica's built in Fibonacci function taking about 3
seconds to compute fib (10^7) on my PC.
--
Dan
On 11/7/07, Henning Thielemann
On Tue, 6 Nov 2007 ajb@spamcop.net wrote:
However, this is still an O(log n) algorithm, because that's the complexity of raising-to-the-power-of. And it's slower than the simpler integer-only algorithms.
You mean computing the matrix power of
/1 1\ \0 1/
? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

G'day all. I wrote:
However, this is still an O(log n) algorithm, because that's the complexity of raising-to-the-power-of. And it's slower than the simpler integer-only algorithms.
Quoting Henning Thielemann
You mean computing the matrix power of
/1 1\ \0 1/
?
I mean all of the most efficient ones. The Gosper-Salamin algorithm is the matrix power algorithm in disguise, more or less. Cheers, Andrew Bromage

Hi,
sorry my english is not the best :(
2007/11/5, gitulyar
Please help me. I'm new in Haskell programming, but wrote some things in Scheme. I make so function:
fib 1 = 1 fib 2 = 2 fib n = fib (n-1) + fib (n-2)
And when I call "fib 30" it works about 5 seconds. As for me it's really TOO SLOW.
Because the scheme is Inefficient If you define fib like this: dfib 0 = (1,1) dfib n = let (a,b) = dfib (n-1) in (b, b+a) -- dfib n = (fib n, fib (n+1)) this explote lazy evaluation fib n = fst (dfib n) With this definition the lazy evaluation calculate only one fib 1, one fib 2......etc.
Tell me please if I have something missed, maybe some compiler (interpretaitor) options (I use ghc 6.6.1).
The scheme is bad, no ghci.
P.S. As I understand function "fib n" should be calculated one time. For example if I call "fib 30" compiler builds tree in which call function "fib 28" 2 times and so on. But as for lazy calculation principle it should be calculated just ones and then it's value is used for all other calls of this function with the same argument. But it seems that this principle doesn't work in this algorithm.
If you have this: mult:Int->Int mult x = x + x + x ------------------------------------------------------------------- mult (fib 20) = <Definition> (fib 20) + (fib 20) + (fib 20) = < By lazy evaluation, this is equal..> x + x + x where x = fib 20 ------------------------------------------------------------------- In this case fib 20 calculate only the first call, no three times. But fib 20 fib 20 = < Definition> fib 19 + fib 18 Then the calulate of fib 19 and fib 18 individualy
participants (14)
-
ajb@spamcop.net
-
Albert Y. C. Lai
-
Bill Wood
-
Brent Yorgey
-
Dan Piponi
-
Dan Weston
-
Daniel Fischer
-
Felipe Lessa
-
gitulyar
-
Guido Genzone
-
Henning Thielemann
-
jerzy.karczmarczuk@info.unicaen.fr
-
Lennart Augustsson
-
Stefan O'Rear