Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread Henning Thielemann

On Tue, 6 Nov 2007 [EMAIL PROTECTED] 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


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread Lennart Augustsson
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
[EMAIL PROTECTED] wrote:

 On Tue, 6 Nov 2007 [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread Dan Piponi
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 [EMAIL PROTECTED] wrote:

 On Tue, 6 Nov 2007 [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread Guido Genzone
Hi,

sorry my english is not the best :(
2007/11/5, gitulyar [EMAIL PROTECTED]:

 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-07 Thread ajb

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 [EMAIL PROTECTED]:


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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-06 Thread ajb

G'day all.

Quoting [EMAIL PROTECTED]:


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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-05 Thread Felipe Lessa
 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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-05 Thread Dan Weston

Brent Yorgey wrote:


On Nov 5, 2007 5:22 PM, gitulyar [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] 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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-05 Thread jerzy . karczmarczuk
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


Re: [Haskell-cafe] Fibbonachi numbers algorithm work TOO slow.

2007-11-05 Thread Dan Weston

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

[EMAIL PROTECTED] 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





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe