From: qikink
Subject: Fibonacci Recursion, What??
Date: 
Message-ID: <1190182829.086646.130040@i38g2000prf.googlegroups.com>
So I'm going through a textbook, and I type in the cute little
recursive fibonacci program, but of course its dead slow above 30. I
know one way to improve fibonacci programs, and recursive programs in
general is to have it save the value each time it calculates a
fibonacci number. In other words, only calculate fib(5) once, then use
that value each time it comes up. So I go on my merry way, trying to
program this in lisp, which I'm still not very adept at, and come up
with this:
<code>
(setf fibber1 #'(lambda (x)
  (if (zerop x) 1 (if (equal x 1) 1 (if t
					 (let ((a (+ (funcall fibber1 (- x 1)) (funcall fibber1 (- x 2))))
(b x))
					   (setf fibber1 fibber2)

					  (if (> x limit) (setf fibber2 #'(lambda (x)(if (equal x (eval
b)) (eval a) (funcall fibber1 x)))) nil)
					  (if (> x limit) (setq limit x))
					  a
					  )
				       )
                    )
  )
)
)

(setf fibber2 #'(lambda (x)
  (if (zerop x) 1 (if (equal x 1) 1 (if t
					 (let ((a (+ (funcall fibber1 (- x 1)) (funcall fibber1 (- x 2))))
(b x))
					   (setf fibber1 fibber2)

					  (if (> x limit) (setf fibber2 #'(lambda (x)(if (equal x (eval
b)) (eval a) (funcall fibber1 x)))) nil)
					  (if (> x limit) (setq limit x))
					  a
					  )
				       )
                   )
   )
)
)
(setq limit 2)
</code>
(sorry for length)
And when I type (funcall  fibber1 500), quick as a flash I get the
right answer. There is one issue, fibber1 and fibber2 are now totallly
useless, and give a program stack overflow, but I can just redefine
them again and they work once more. So i just wrap up a function fib
with the code to call fibber one and redefine fibber1 and 2, and
everything is happy. So my question is, HOW DOES IT EVEN WORK? I
reallly have no idea how it spits out answers. I'm using emacs
inferior-lisp mode to communicate with GNU CLISP, if that matters. Any
help is appreciated.

From: Alex Mizrahi
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f0d3b3$0$90263$14726298@news.sunsite.dk>
(message (Hello 'qikink)
(you :wrote  :on '(Wed, 19 Sep 2007 06:20:29 -0000))
(

 q> have it save the value each time it calculates a
 q> fibonacci number. In other words, only calculate fib(5) once, then use
 q> that value each time it comes up.

 yup, and in lisp we can abstract it to some separate layer.
we call it memoizing, see here: http://www.tfeb.org/lisp/hax.html#MEMOIZE

so instead of

(defun fib (n)
  (if (<= n 1)
      1
      (+ (fib (- n 1))
           (fib (- n 2)))))

you just write:

(def-memoized-function fib (n)
  (if (<= n 1)
      1
       (+ (fib (- n 1))
            (fib (- n 2)))))

and you got speedup. -- it automatically creates a table where it stores 
results, and does load/store automatically. magic, isn't it?

but actually memoiziation ain't best way to calculate fibs -- when you'll 
calculate sufficiently large fib, it will just consume all available 
memory..

so this is tradeoff. if you need just one fib -- calculate it in a loop.
e.g. tail-recursive:

(defun fib-trec (n)
  "Tail-recursive Fibonacci number function"
  (labels ((calc-fib (n a b)
                     (if (= n 0)
                       a
                       (calc-fib (- n 1) b (+ a b)))))
    (calc-fib n 0 1)))

 q> everything is happy. So my question is, HOW DOES IT EVEN WORK?

you could easily be a winner in an obfuscated Lisp contest. why don't you 
format code as others do?
is it a joke? do you know about cond?
what is a point of "(if t" in

 (if (zerop x) 1 (if (equal x 1) 1 (if t

for me it looks like a weird unrolled cond

(cond
  ((zerop x) 1)
  ((equal x 1) 1)
  (t ...

but what were you thinking about?

 q>  I reallly have no idea how it spits out answers. I'm using emacs

Emacs should help you formatting code.

)
(With-best-regards '(Alex Mizrahi) :aka 'killer_storm)
"Hanging In The Balance Of Deceit And Blasphemy") 
From: Alan Crowe
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <86sl5aj04k.fsf@cawtech.freeserve.co.uk>
"Alex Mizrahi" <········@users.sourceforge.net> writes:

> (message (Hello 'qikink)
> (you :wrote  :on '(Wed, 19 Sep 2007 06:20:29 -0000))
> (
> 
>  q> have it save the value each time it calculates a
>  q> fibonacci number. In other words, only calculate fib(5) once, then use
>  q> that value each time it comes up.
> 
>  yup, and in lisp we can abstract it to some separate layer.
> we call it memoizing, see here: http://www.tfeb.org/lisp/hax.html#MEMOIZE
> 
> so instead of
> 
> (defun fib (n)
>   (if (<= n 1)
>       1
>       (+ (fib (- n 1))
>            (fib (- n 2)))))
> 
> you just write:
> 
> (def-memoized-function fib (n)
>   (if (<= n 1)
>       1
>        (+ (fib (- n 1))
>             (fib (- n 2)))))
> 
> and you got speedup. -- it automatically creates a table where it stores 
> results, and does load/store automatically. magic, isn't it?
> 

How bad is it to abuse defmethod like this:

CL-USER> (defmethod fib ((n (eql 0))) 1)
#<STANDARD-METHOD FIB ((EQL 0)) {486206CD}>

CL-USER> (defmethod fib ((n (eql 1))) 1)
#<STANDARD-METHOD FIB ((EQL 1)) {4871255D}>

CL-USER> (defmethod fib (n)
           (let ((answer (+ (fib (- n 1))
                            (fib (- n 2)))))
             (defmethod fib ((x (eql n))) answer)
             answer))
#<STANDARD-METHOD FIB (T) {488E12B5}>

CL-USER> (fib 2)
2

CL-USER> (fib 10)
89

CL-USER> (fib 100)
573147844013817084101

I wonder if Manny's code

http://project-apollo.net/mos/mos061.html

uses defmethod like that :-)

Alan Crowe
Edinburgh
Scotland
From: qikink
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <1190242121.372310.86880@v29g2000prd.googlegroups.com>
> you could easily be a winner in an obfuscated Lisp contest. why don't you
> format code as others do?
> is it a joke? do you know about cond?
> what is a point of "(if t" in
>
>  (if (zerop x) 1 (if (equal x 1) 1 (if t
>

yeah, now that I think about it, I really don't know why thats there.
The original plan here, before I had even this small understanding of
what I'm doing, was to add on (if (= x {8,9,10... w/e} ) to the
beginning of the function. Only, I couldn't really figure that out. So
the above code is what I did, which I still don't understand, but
there you are. Its obfuscated to where the coder himself doesn't know
how it works. woot.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f1f10f$0$7493$4c368faf@roadrunner.com>
Alex Mizrahi wrote:
[snip]
> 
> (def-memoized-function fib (n)
>   (if (<= n 1)
>       1
>        (+ (fib (- n 1))
>             (fib (- n 2)))))
> 
> and you got speedup. -- it automatically creates a table where it stores 


I was looking browsing through 
http://mathworld.wolfram.com/FibonacciNumber.html

The formulas (55) and (66) suggest recursive version which should be 
reasonably fast. (This time I wrote a version that satisfies F_1=1 F_2=1 
and F_{n+1} = F_{n} + F_{n-1} and even works for negative n, i.e., 
F_{-1}=1 F_{-2}=-1 F_{-3}=2 ..., hope I am not clubbed this time).

I guess this will benefit from storing a table of computed values too.


(defun fib (n)
   (if (> 0 n)
     (let* ( (sign (- 1 (* 2 (mod (- n 1) 2)))))
       (return-from fib (* sign (fib (* -1 n))))))
   (if (> 2 n) (return-from fib n)
     (if (= n 2) (return-from fib 1)))
   (if (= (mod n 2) 0)
     (progn
       (setf n (/ n 2))
       (let*  ((fib1 (fib (+ n 1))) (fib2 (fib (- n 1))))
	(return-from fib (- (* fib1 fib1) (* fib2 fib2))))))
     (progn
       (setf n (/ (+ n 1) 2))
       (let*  ((fib1  (fib  n) ) (fib2 (fib (- n  1))))
	(return-from fib (+ (* fib1 fib1) (* fib2 fib2))))))


clisp session:
[1]> (load "l3.lisp")
;; Loading file l3.lisp ...
;; Loaded file l3.lisp
T
[2]> (fib -3)
2
[3]> (fib -2)
-1
[4]> (fib -1)
1
[5]> (fib 0)
0
[6]> (fib 1)
1
[7]> (fib 2)
1
[8]> (fib 3)
2
[9]> (fib 200)
280571172992510140037611932413038677189525
[10]>
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f1fbd3$0$18906$4c368faf@roadrunner.com>
J. I. Gyasu wrote:

> 
> The formulas (55) and (66) suggest recursive version which should be 
> reasonably fast.
Its (55) and (56).
From: Thomas A. Russ
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <ymi8x716our.fsf@blackcat.isi.edu>
"J. I. Gyasu" <·········@nospam> writes:
> I guess this will benefit from storing a table of computed values too.
> 
> 
> (defun fib (n)
>    (if (> 0 n)
>      (let* ( (sign (- 1 (* 2 (mod (- n 1) 2)))))
>        (return-from fib (* sign (fib (* -1 n))))))
>    (if (> 2 n) (return-from fib n)
>      (if (= n 2) (return-from fib 1)))
>    (if (= (mod n 2) 0)
>      (progn
>        (setf n (/ n 2))
>        (let*  ((fib1 (fib (+ n 1))) (fib2 (fib (- n 1))))
> 	(return-from fib (- (* fib1 fib1) (* fib2 fib2))))))
>      (progn
>        (setf n (/ (+ n 1) 2))
>        (let*  ((fib1  (fib  n) ) (fib2 (fib (- n  1))))
> 	(return-from fib (+ (* fib1 fib1) (* fib2 fib2))))))

This set of if clauses would greatly benefit from using the
multiple-branch test construct COND, and also eliminating the
RETURN-FROM statements for the final values.  Lisp forms return the
final value automatically.  It will have a more Lisp-like style:

 (defun fib (n)
   (cond ((< n 0)
	  (let* ((sign (- 1 (* 2 (mod (- n 1) 2)))))
	    (* sign (fib (* -1 n)))))
	 ((< n 2)
	  n)
	 ((= n 2)
	  1)
	 ((= (mod n 2) 0)
	  (setf n (/ n 2))
	  (let*  ((fib1 (fib (+ n 1))) 
		  (fib2 (fib (- n 1))))
	    (- (* fib1 fib1) (* fib2 fib2))))
	 (t 
	  (setf n (/ (+ n 1) 2))
	  (let*  ((fib1  (fib  n))
		  (fib2 (fib (- n  1))))
	    (+ (* fib1 fib1) (* fib2 fib2))))))


I also suspect that clever use of the multiple return values from either
MOD or REM would allow the last two clauses to be collapsed, but I don't
have time right now to work out whether that is true or not.

-- 
Thomas A. Russ,  USC/Information Sciences Institute
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092101112216807-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-20 16:53:00 -0400, ···@sevak.isi.edu (Thomas A. Russ) said:

>  (defun fib (n)
>    (cond ((< n 0)
> 	  (let* ((sign (- 1 (* 2 (mod (- n 1) 2)))))
> 	    (* sign (fib (* -1 n)))))
> 	 ((< n 2)
> 	  n)
> 	 ((= n 2)
> 	  1)
> 	 ((= (mod n 2) 0)
> 	  (setf n (/ n 2))
> 	  (let*  ((fib1 (fib (+ n 1)))
> 		  (fib2 (fib (- n 1))))
> 	    (- (* fib1 fib1) (* fib2 fib2))))
> 	 (t
> 	  (setf n (/ (+ n 1) 2))
> 	  (let*  ((fib1  (fib  n))
> 		  (fib2 (fib (- n  1))))
> 	    (+ (* fib1 fib1) (* fib2 fib2))))))
> 
> 
> I also suspect that clever use of the multiple return values from either
> MOD or REM would allow the last two clauses to be collapsed, but I don't
> have time right now to work out whether that is true or not.

the mod is just being used to determine whether n is even, so:

(defun fib (n)
  (cond ((not (and (integerp n) (>= n 0)))
	 (error "fibonacci numbers are only defined for integers 0 and greater"))
	((< n 2) n)
	((= n 2) 1)
	(t (let* ((even? (evenp n))
		  (k (/ (+ n (if even? 0 1)) 2))
		  (fib1 (fib (if even? (1+ k) k)))
		  (fib2 (fib (1- k))))
	     (funcall (if even? #'- #'+) (* fib1 fib1) (* fib2 fib2))))))
From: Carlo Capocasa
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <fcss6q$1k1$1@registered.motzarella.org>
(defun fibo(n)
  (let ((phi1 (/ (+ (sqrt 5) 1) 2)) (phi2 (/ (- (sqrt 5) 1) 2)))
  (round (/ (- (expt phi1 n) (expt (- 0 phi2) n)) (sqrt 5)))))

Carlo
From: Carlo Capocasa
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <fcssl2$2nl$1@registered.motzarella.org>
Correction:

(defun fibo(n)
  (let ((phi1 (/ (+ (sqrt 5) 1) 2)) (phi2 (/ (- (sqrt 5) 1) 2)))
  (prog1(round
    (/ (- (expt phi1 n) (expt (- 0 phi2) n)) (sqrt 5))))))

Carlo
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f1fb5b$0$18906$4c368faf@roadrunner.com>
Carlo Capocasa wrote:
> Correction:
> 
> (defun fibo(n)
>   (let ((phi1 (/ (+ (sqrt 5) 1) 2)) (phi2 (/ (- (sqrt 5) 1) 2)))
>   (prog1(round
>     (/ (- (expt phi1 n) (expt (- 0 phi2) n)) (sqrt 5))))))
> 
> Carlo

fib defined as in my previous post.

[15]> (= (fibo 30) (fibo 30))
T
[16]> (= (fibo 100) (fib 100))
NIL
[17]> (fibo 500)
*** - floating point overflow
The following restarts are available:
ABORT          :R1      ABORT
Break 1 [18]> abort
[19]> (fib 500)
139423224561697880139724382870407283950070256587697307264108962948325571622863290691557658876222521294125
[20]>
From: Carlo Capocasa
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <fct39i$h6r$1@registered.motzarella.org>
> [16]> (= (fibo 100) (fib 100))
> NIL

Good point.
From: KT
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <1190491052.772336.156530@22g2000hsm.googlegroups.com>
Can you get it faster than this?
 ;;;; fibonacci.lisp

(defun %fibonacci-iter (n)
  (check-type n (integer 0 *))
  (labels ((mul (a b)
           (vector (+ (* (svref a 0) (svref b 0))
                      (* (svref a 2) (svref b 1)))
                   (+ (* (svref a 0) (svref b 1))
                      (* (svref a 1) (svref b 3)))
                   (+ (* (svref a 0) (svref b 2))
                      (* (svref a 2) (svref b 3)))
                   (+ (* (svref a 2) (svref b 1))
                      (* (svref a 3) (svref b 3)))))
         (mexpt (a k)
           (let ((x #(1 0 0 1)))
             (loop :until (= k 0)
                   :do (if (evenp k)
                           (setf a (mul a a)
                                 k (/ k 2))
                           (setf x (mul x a)
                                 k (1- k))))
             x)))
    (if (= 0 n) 1
        (let ((m (mexpt #(0 1 1 1) (1- n))))
          (+ (svref m 2) (svref m 3))))))

(defun fibonacci (n)
  (check-type n (integer 0 *))
  (cond ((= 0 n) 0)
        ((= 1 n) 1)
        ((= 2 n) 1)
        (t (%fibonacci-iter (- n 1)))))

;;; eof

(time (fibonacci 10000))
Evaluation took:
  0.003 seconds of real time
  0.004 seconds of user run time
  0.0 seconds of system run time
  0 calls to %EVAL
  0 page faults and
  36,352 bytes consed.
33644764876431783266621612005107543310302148460680063906564769974680081442166662
36815559551363373402558206533268083615937373479048386526826304089246305643188735
45443695598274916066020998841839338646527313000888302692356736131351175792974378
54413752130520504347701602264758318906527890855154366159582987279682987510631200
57542878345321551510387081829896979161312785626503319548714021428753269818796204
69360978799003509623022910263681314931952756302278376284415403605844025721143349
61180023091208287046088923962328835461505776583271252546093591128203925285393434
62090424524892940390170623388899108584106518317336043747073790855263176432573399
37128719375877468974799263058370657428301616374089691784263786242128352581128205
16370298089332099905707920064367426202389783111470054074998459250360633560933883
83192338678305613643535189213327973290813373264265263398976392272340788292817795
35805709936910491754708089318410561463223382174656373212482263830921032977016480
54726243842374862411453093812206564914032751086643394517512161526545361333111314
04243685480510676584349352383695965342807176877532834823434555736671973139274627
36291082106792807847180353291311767789246590899386354593278945237776744061922403
37638674004021330343297496902028328145933418826817683893072003634795623117103101
29195316979460763273758925353077255237594378843450406771555577905645044301664011
94625809722167297586150269684431469520346149322911059706762432685159928347098912
84706740862008587135016260312071903172086094081298321581077282076353186624611278
24553720853236530577595643007251774431505153960090516860322034916322264088524885
24331580515348496224348482993809050704834824493274537326245677558790891871908036
62058009594743150052402532709746995318770724376825907419939632265984147498193609
28522394503970716544315642132815768890805878318340491743455627052022356484649519
61124602683139709750693826487066132645076650746115126775227486215986425307112984
41182622661057163515069260029861704945425047491378115154139941550671256271197133
25276363193960690289565028826860836224108205056243070179497617112123306607331005
9947366875
From: Vesa Karvonen
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <fd3uvj$n1e$1@oravannahka.helsinki.fi>
KT <······@gmail.com> wrote:
> Can you get it faster than this?
>  ;;;; fibonacci.lisp
[...]

Try this one:

<---->
type 'a m = {11 : 'a, 12 : 'a, 22 : 'a}
type m = IntInf.int m

fun isOdd i = 0 <> Int.rem (i, 2)

fun mul (l : m, r : m) =
    {11 = #11 l * #11 r + #12 l * #12 r,
     12 = #11 l * #12 r + #12 l * #22 r,
     22 = #12 l * #12 r + #22 l * #22 r}

fun pow (g, n) =
    if isOdd n then
       mul (g, pow (g, n-1))
    else if n = 0 then
       {11 = 1, 12 = 0, 22 = 1}
    else let
          val g = pow (g, Int.quot (n, 2))
       in
          mul (g, g)
       end

val fib =
 fn 0 => 0
  | 1 => 1
  | n => #11 (pow ({11 = 1, 12 = 1, 22 = 0}, n-1))

val () =
    (print (IntInf.toString (fib (valOf (Int.fromString (hd (CommandLine.arguments ()))))))
   ; print "\n")
<---->

Get MLton (http://mlton.org/Download), save the above code as fib.sml,
compile with

  mlton fib.sml

and run as

  time ./fib 10000

-Vesa Karvonen
From: Vesa Karvonen
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <fd41c0$otq$1@oravannahka.helsinki.fi>
Vesa Karvonen <·············@cs.helsinki.fi> wrote:
> KT <······@gmail.com> wrote:
> > Can you get it faster than this?
> >  ;;;; fibonacci.lisp
> [...]

> Try this one:
[...]

Here is a slightly faster one:

<---->
type 'a m = {11 : 'a, 12 : 'a, 22 : 'a}
type m = IntInf.int m

fun mul (l : m, r : m) =
    case #12 l * #12 r
     of x => {11 = #11 l * #11 r + x,
              12 = #11 l * #12 r + #12 l * #22 r,
              22 =             x + #22 l * #22 r}

fun pow (g, n) =
    if 0w0 <> n mod 0w2 then
       mul (g, pow (g, n - 0w1))
    else if 0w0 = n then
       {11 = 1, 12 = 0, 22 = 1}
    else
       case pow (g, n div 0w2)
        of g => mul (g, g)

val fib =
 fn 0 => 0 | 1 => 1 | 2 => 1
  | n => if n < 0 then raise Domain else
         case pow ({11 = 1, 12 = 1, 22 = 0}, Word.fromInt n - 0w2)
          of g => #11 g + #12 g

val () =
    (print (IntInf.toString (fib (valOf (Int.fromString (hd (CommandLine.arguments ()))))))
   ; print "\n")
<---->

The previous instructions apply.

-Vesa Karvonen
From: Rainer Joswig
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <joswig-D222BB.23313822092007@news-europe.giganews.com>
In article <············@oravannahka.helsinki.fi>,
 Vesa Karvonen <·············@cs.helsinki.fi> wrote:

> Vesa Karvonen <·············@cs.helsinki.fi> wrote:
> > KT <······@gmail.com> wrote:
> > > Can you get it faster than this?
> > >  ;;;; fibonacci.lisp
> > [...]
> 
> > Try this one:
> [...]
> 
> Here is a slightly faster one:
> 
> <---->
> type 'a m = {11 : 'a, 12 : 'a, 22 : 'a}
> type m = IntInf.int m
> 
> fun mul (l : m, r : m) =
>     case #12 l * #12 r
>      of x => {11 = #11 l * #11 r + x,
>               12 = #11 l * #12 r + #12 l * #22 r,
>               22 =             x + #22 l * #22 r}
> 
> fun pow (g, n) =
>     if 0w0 <> n mod 0w2 then
>        mul (g, pow (g, n - 0w1))
>     else if 0w0 = n then
>        {11 = 1, 12 = 0, 22 = 1}
>     else
>        case pow (g, n div 0w2)
>         of g => mul (g, g)
> 
> val fib =
>  fn 0 => 0 | 1 => 1 | 2 => 1
>   | n => if n < 0 then raise Domain else
>          case pow ({11 = 1, 12 = 1, 22 = 0}, Word.fromInt n - 0w2)
>           of g => #11 g + #12 g
> 
> val () =
>     (print (IntInf.toString (fib (valOf (Int.fromString (hd (CommandLine.arguments ()))))))
>    ; print "\n")
> <---->
> 
> The previous instructions apply.
> 
> -Vesa Karvonen

Now rewrite it Lisp, that would be more interesting.

-- 
http://lispm.dyndns.org
From: Vesa Karvonen
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <fd447q$r95$1@oravannahka.helsinki.fi>
Rainer Joswig <······@lisp.de> wrote:
[...]
> Now rewrite it Lisp, that would be more interesting.

I leave that exercise to the common lispers. ;-)

-Vesa Karvonen
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092301032416807-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-22 12:24:56 -0400, KT <······@gmail.com> said:

> Can anyone get better than this?


The version I posted a couple of days ago:

(defun fib (n)
  (cond ((not (and (integerp n) (>= n 0)))
	 (error "fibonacci numbers are only defined for integers 0 and greater"))
	((< n 2) n)
	((= n 2) 1)
	(t (let* ((even? (evenp n))
		  (k (/ (+ n (if even? 0 1)) 2))
		  (fib1 (fib (if even? (1+ k) k)))
		  (fib2 (fib (1- k))))
	     (funcall (if even? #'- #'+) (* fib1 fib1) (* fib2 fib2))))))


which is simply a rewrite of T. Russ's rewrite of somebody else's 
version is much faster (which is what you mean by "better," right? or 
did you mean "more obfuscated?")

Here are the timing results, where fibonacci" is yours "fib" is mine:

CL-USER> (time (dotimes (n 1) (fibonacci (expt 10 6))))
Evaluation took:
  12.347 seconds of real time
  12.184681 seconds of user run time
  0.047269 seconds of system run time
  0 calls to %EVAL
  0 page faults and
  6,173,936 bytes consed.
NIL
CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
Evaluation took:
  2.018 seconds of real time
  1.973404 seconds of user run time
  0.019084 seconds of system run time
  [Run times include 0.029 seconds GC run time.]
  0 calls to %EVAL
  0 page faults and
  13,960,424 bytes consed.
NIL


Both are dog slow compared to mzscheme for example, which does (fib 
(expt 10 6)) in 190 milliseconds, or 10 times as fast as my common lisp 
version under sbcl and 60 times as fast as yours. Really this is just a 
benchmark of the bignum library that the implementation uses, and 
mzscheme clearly uses a good one.
From: George Neuner
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <jbcdf31ugsommo1kvaln35p2mb1afu3rct@4ax.com>
On Sun, 23 Sep 2007 01:03:24 -0400, Raffael Cavallaro
<················@pas-d'espam-s'il-vous-plait-mac.com> wrote:

>On 2007-09-22 12:24:56 -0400, KT <······@gmail.com> said:
>
>> Can anyone get better than this?
>
>
>The version I posted a couple of days ago:
>
>(defun fib (n)
>  (cond ((not (and (integerp n) (>= n 0)))
>	 (error "fibonacci numbers are only defined for integers 0 and greater"))
>	((< n 2) n)
>	((= n 2) 1)
>	(t (let* ((even? (evenp n))
>		  (k (/ (+ n (if even? 0 1)) 2))
>		  (fib1 (fib (if even? (1+ k) k)))
>		  (fib2 (fib (1- k))))
>	     (funcall (if even? #'- #'+) (* fib1 fib1) (* fib2 fib2))))))
>
>
>which is simply a rewrite of T. Russ's rewrite of somebody else's 
>version is much faster (which is what you mean by "better," right? or 
>did you mean "more obfuscated?")
>
>Here are the timing results, where fibonacci" is yours "fib" is mine:
>
>CL-USER> (time (dotimes (n 1) (fibonacci (expt 10 6))))
>Evaluation took:
>  12.347 seconds of real time
>  12.184681 seconds of user run time
>  0.047269 seconds of system run time
>  0 calls to %EVAL
>  0 page faults and
>  6,173,936 bytes consed.
>NIL
>CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
>Evaluation took:
>  2.018 seconds of real time
>  1.973404 seconds of user run time
>  0.019084 seconds of system run time
>  [Run times include 0.029 seconds GC run time.]
>  0 calls to %EVAL
>  0 page faults and
>  13,960,424 bytes consed.
>NIL
>
>
>Both are dog slow compared to mzscheme for example, which does (fib 
>(expt 10 6)) in 190 milliseconds, or 10 times as fast as my common lisp 
>version under sbcl and 60 times as fast as yours. Really this is just a 
>benchmark of the bignum library that the implementation uses, and 
>mzscheme clearly uses a good one.

Printing the result frequently takes far longer than calculating it.
It would be interesting to see a break down of the results.

Also, it's impossible to compare results without knowing the hardware
the program ran on.

George
--
for email reply remove "/" from address
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092317401416807-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-23 14:39:09 -0400, George Neuner <·········@comcast.net> said:

> Printing the result frequently takes far longer than calculating it.
> It would be interesting to see a break down of the results.

All the times I posted were for computation alone, without printing (I 
think you knew this - just clarifying).

If we print the result we end up with a mixed bignum and terminal i/o 
benchmark, not a pure bignum benchmark which is what fib is intended to 
be.

But here are timings with and without printing the result:

           no-print     with-print    print time
sbcl
fib          2.0 sec      4.5 sec      2.5 sec
fibonacci   12.4 sec     14.8 sec      2.4 sec

mzc (fib)    0.2 sec      0.6 sec      0.4 sec

all times rounded to the nearest 1/10 second.

So it appears that mzscheme has a faster printer as well.


Lest anyone think that mzscheme is universally blazingly fast, it 
produces floating point code that is far slower than that produced by 
sbcl.

> 
> Also, it's impossible to compare results without knowing the hardware
> the program ran on.

The timings I gave for the two lisp versions and the mzscheme version 
were all run on a 2.4 GHz core 2 duo mac book pro with 4GB of RAM under 
Mac OS X.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f6c394$0$4979$4c368faf@roadrunner.com>
Guess, it is the same algorithm

(defun pow-mat (n l)
   (if (= n 1)  l
     (let* ( (a (first l)) (b (nth 1 l)) (c (nth 2 l)) (d (nth 3 l)))
       (if (evenp n)
	(let* ((n1 (/ n 2))
	       (a1 (+ (* a a) (* b c))) (b1 (+ (* a b) (* b d)))
	       (c1 (+ (* a c) (* c d))) (d1 (+ (* c b) (* d d)))
	       (l1 (list a1 b1 c1 d1)))
	  (pow-mat n1 l1))
	(let* ((n1 (- n 1))
	       (l1 (pow-mat n1 l))
	       (a1 (first l1)) (b1 (nth 1 l1)) (c1 (nth 2 l1)) (d1 (nth 3 l1))
	       (a2 (+ (* a a1) (* b c1))) (b2 (+ (* a b1) (* b d1)))
	       (c2 (+ (* c a1) (* d c1))) (d2 (+ (* c b1) (* d d1))))
	  (list a2 b2 c2 d2))))))

(defun fib-2 (n)
   (if (> 0 n)
     (if (evenp n)
       (- (fib-2 (- n)))
       (fib-2 (- n)))
     (if (> 2 n)
       n
       (first (pow-mat (- n 1) '(1 1 1 0))))))

On my comp:
(time (fib-2 10000))
Evaluation took:
   0.002 seconds of real time
   0.004 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   89,392 bytes consed.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f6edfb$0$15339$4c368faf@roadrunner.com>
Actually noting that the (1,2)th and (2,1)th entries of the nth power of 
the matrix are always the same can lead to even greater speedups.

(defun pow-fib (n)
   (if (= n 1) (list 1 1 0)
       (if (evenp n)
	(let* ((n1 (/ n 2))
	       (l (pow-fib n1))
	       (a (first l))
	       (b (nth 1 l))
	       (d (nth 2 l))
	       (a1 (+ (* a a) (* b b)))
	       (b1 (+ (* a b) (* b d)))
	       (d1 (+ (* b b) (* d d))))
	  (list a1 b1 d1))
	(let* ((n1 (1- n))
	      (l1 (pow-fib n1))
	      (a (first l1))
	      (b (nth 1 l1)))
	      (list (+ a b) a b)))))

(defun fib-3 (n)
   (if (> 0 n)
     (if (evenp n)
       (- (fib-2 (- n)))
       (fib-2 (- n)))
     (if (> 2 n)
       n
       (first (pow-fib (1- n) )))))


(time (fib-3 10000))
Evaluation took:
   0.001 seconds of real time
   0.0 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   24,192 bytes consed.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46F71FFC.5030802@nospam>
J. I. Gyasu wrote:
> Actually noting that the (1,2)th and (2,1)th entries of the nth power of 
> the matrix are always the same can lead to even greater speedups.
> 

+ the observation that (2,2)th element of the matrix is always the 
difference of (1,1)th entry and (1,2)th entry we are led to this simpler 
and faster version of the previous code:

(defun pow-fib-4 (n)
   (if (= n 1) (list 1 1)
       (if (evenp n)
	(let* ((l (pow-fib-4 (/ n 2))) (a (first l)) (b (nth 1 l)))
	  (list (+ (* a a) (* b b)) (+ (* 2 a b) (- (* b b)))))
	(let* ((l1 (pow-fib-4 (1- n))) (a (first l1)) (b (nth 1 l1)))
	      (list (+ a b) a)))))

(defun fib-4 (n)
   (if (> 0 n)
     (if (evenp n) (- (fib-4 (- n))) (fib-4 (- n)))
     (if (> 2 n) n (first (pow-fib-4 (1- n) )))))

CL-USER> (time (fib-4 10000))
Evaluation took:
   0.0 seconds of real time
   0.0 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   19,776 bytes consed.

CL-USER> (time (fib-4 100000))
Evaluation took:
   0.04 seconds of real time
   0.040002 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   144,912 bytes consed
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f72266$0$19621$4c368faf@roadrunner.com>
J. I. Gyasu wrote:
> Actually noting that the (1,2)th and (2,1)th entries of the nth power of 
> the matrix are always the same can lead to even greater speedups.

+ the observation that (2,2)th element of the matrix is always the 
difference of (1,1)th entry and (1,2)th entry we are led to this simpler 
and faster version of the previous code:

(defun pow-fib-4 (n)
   (if (= n 1) (list 1 1)
       (if (evenp n)
     (let* ((l (pow-fib-4 (/ n 2))) (a (first l)) (b (nth 1 l)))
       (list (+ (* a a) (* b b)) (+ (* 2 a b) (- (* b b)))))
     (let* ((l1 (pow-fib-4 (1- n))) (a (first l1)) (b (nth 1 l1)))
           (list (+ a b) a)))))

(defun fib-4 (n)
   (if (> 0 n)
     (if (evenp n) (- (fib-4 (- n))) (fib-4 (- n)))
     (if (> 2 n) n (first (pow-fib-4 (1- n) )))))


CL-USER> (time (fib-4 10000))
Evaluation took:
   0.0 seconds of real time
   0.0 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   19,776 bytes consed.

That is fast :)

CL-USER> (time (fib-4 100000))
Evaluation took:
   0.04 seconds of real time
   0.040002 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   144,912 bytes consed
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092323054875249-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-23 22:35:19 -0400, "J. I. Gyasu" <·········@nospam> said:

> + the observation that (2,2)th element of the matrix is always the 
> difference of (1,1)th entry and (1,2)th entry we are led to this 
> simpler and faster version of the previous code:

It's now almost as fast my rewrite of Thomas Russ's rewrite of your 
version that I posted a couple of days ago. fib-4 is your most recent 
version and fib is mine from a couple of days ago:

CL-USER> (time (dotimes (n 1) (fib-4 (expt 10 6))))
Evaluation took:
  2.498 seconds of real time
  2.48296 seconds of user run time
  0.006428 seconds of system run time
  0 calls to %EVAL
  0 page faults and
  1,464,544 bytes consed.
NIL
CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
Evaluation took:
  2.011 seconds of real time
  1.977596 seconds of user run time
  0.021692 seconds of system run time
  [Run times include 0.037 seconds GC run time.]
  0 calls to %EVAL
  0 page faults and
  13,959,632 bytes consed.
NIL

mzscheme is still 10 times as fast as both at under 0.2 seconds.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46F72C88.3090408@nospam>
Raffael Cavallaro wrote:
> CL-USER> (time (dotimes (n 1) (fib-4 (expt 10 6))))
...
>  1,464,544 bytes consed.

What does this measure : 1,464,544 bytes consed.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f72cca$0$9581$4c368faf@roadrunner.com>
Raffael Cavallaro wrote:
> CL-USER> (time (dotimes (n 1) (fib-4 (expt 10 6))))
> Evaluation took:
>  2.498 seconds of real time
>  2.48296 seconds of user run time
>  0.006428 seconds of system run time
>  0 calls to %EVAL
>  0 page faults and
>  1,464,544 bytes consed.


What does this measure: >  1,464,544 bytes consed.
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092400480450073-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-23 23:19:33 -0400, "J. I. Gyasu" <·········@nospam> said:

> What does this measure: >  1,464,544 bytes consed.

The total amount of memory allocated during the computation.
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092401061843658-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-24 00:48:04 -0400, Raffael Cavallaro 
<················@pas-d'espam-s'il-vous-plait-mac.com> said:

> On 2007-09-23 23:19:33 -0400, "J. I. Gyasu" <·········@nospam> said:
> 
>> What does this measure: >  1,464,544 bytes consed.
> 
> The total amount of memory allocated during the computation.

Just to be completely clear, fib (mine) allocates 13 million bytes, 
fib-4 (yours) allocates 1.4 million bytes. Both of these figures are 
temporary churn though - the gc reclaims all of it.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f74622$0$18959$4c368faf@roadrunner.com>
Raffael Cavallaro wrote:
> On 2007-09-23 22:35:19 -0400, "J. I. Gyasu" <·········@nospam> said:
> It's now almost as fast my rewrite of Thomas Russ's rewrite of your 
> version that I posted a couple of days ago. fib-4 is your most recent 
> version and fib is mine from a couple of days ago:
> 

I tried to mimic your style (learn from the masters :) ) and rewrote the 
code.
The timings improved!

(defun pow-fib-5 (n)
   (if (= n 1) (list 1 1)
       (let* ((even? (evenp n)) (fb (pow-fib-5 (if even? (/ n 2) (1- n))))
	(a (first fb)) (b (nth 1 fb)))
	(if even?
	  (let ((bsq (* b b))) (list (+ (* a a) bsq) (- (* 2 a b) bsq)))
	  (list (+ a b) a)))))

(defun fib-5 (n)
   (if (> 0 n)
     (if (evenp n) (- (fib-5 (- n))) (fib-5 (- n)))
     (if (> 2 n) n (first (pow-fib-5 (1- n) )))))



CL-USER> (time (dotimes (n 1) (fib-5 (expt 10 6))))
Evaluation took:
   2.884 seconds of real time
   2.88418 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   1,123,704 bytes consed.
NIL
CL-USER> (defun fib (n)
  (cond ((not (and (integerp n) (>= n 0)))
      (error "fibonacci numbers are only defined for integers 0 and 
greater"))
     ((< n 2) n)
     ((= n 2) 1)
     (t (let* ((even? (evenp n))
           (k (/ (+ n (if even? 0 1)) 2))
           (fib1 (fib (if even? (1+ k) k)))
           (fib2 (fib (1- k))))
          (funcall (if even? #'- #'+) (* fib1 fib1) (* fib2 fib2))))))
FIB
CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
Evaluation took:
   2.984 seconds of real time
   2.984187 seconds of user run time
   0.0 seconds of system run time
   [Run times include 0.024 seconds GC run time.]
   0 calls to %EVAL
   0 page faults and
   13,961,440 bytes consed.
NIL
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <200709240146248930-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-24 01:07:41 -0400, "J. I. Gyasu" <·········@nospam> said:

> I tried to mimic your style (learn from the masters :) ) and rewrote the code.
> The timings improved!
> 
> (defun pow-fib-5 (n)
>    (if (= n 1) (list 1 1)
>        (let* ((even? (evenp n)) (fb (pow-fib-5 (if even? (/ n 2) (1- n))))
> 	(a (first fb)) (b (nth 1 fb)))
> 	(if even?
> 	  (let ((bsq (* b b))) (list (+ (* a a) bsq) (- (* 2 a b) bsq)))
> 	  (list (+ a b) a)))))
> 
> (defun fib-5 (n)
>    (if (> 0 n)
>      (if (evenp n) (- (fib-5 (- n))) (fib-5 (- n)))
>      (if (> 2 n) n (first (pow-fib-5 (1- n) )))))
> 
> 
> 
> CL-USER> (time (dotimes (n 1) (fib-5 (expt 10 6))))
> Evaluation took:
>    2.884 seconds of real time
>    2.88418 seconds of user run time
>    0.0 seconds of system run time
>    0 calls to %EVAL
>    0 page faults and
>    1,123,704 bytes consed.

Nice - you've gotten the time down and the consing as well.

Here's a version of the same algorithm based on a scheme implementation 
I saw once (I think someone on c.l.s. emailed it to me a few years 
back):

(defun fib (x)
  (if (< x 1) 0
      (let ((n (1- x)))
	(labels ((fib-aux (number)
		   (case number
		     ((0) (values 1 0))
		     ((1) (values 0 1))
		     (otherwise (let ((k (floor number 2)))
				  (multiple-value-bind (a b) (fib-aux k)
				    (let* ((aa (* a a))
					   (bb (* b b))
					   (ab2 (* 2 a b))
					   (ab2bb (+ ab2 bb)))
				      (if (= number (* 2 k))
					  (values (+ aa bb) ab2bb)
					  (values ab2bb (+ ab2bb aa bb))))))))))
	  (if (<= n 1) 1
	      (let ((k (floor n 2)))
		(multiple-value-bind (a b) (fib-aux k)
		  (let ((ab (+ a b)))
		    (if (= n (* 2 k))
			(+ (* ab ab) (* b b))
			(+ (* ab ab) (* 2 b ab)))))))))))

CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
Evaluation took:
  1.406 seconds of real time
  1.396959 seconds of user run time
  0.00571 seconds of system run time
  0 calls to %EVAL
  0 page faults and
  899,968 bytes consed.

This version is a bit longer than those you posted (and that T. Russ 
and I rewrote a bit), but it is a bit faster and conses a bit less. You 
might take note of the use of common lisp's ability to return multiple 
values where you've been explicitly constructing a list.
From: Thomas A. Russ
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <ymihclk56w9.fsf@blackcat.isi.edu>
Raffael Cavallaro <················@pas-d'espam-s'il-vous-plait-mac.com> writes:

> Here's a version of the same algorithm based on a scheme implementation
> I saw once (I think someone on c.l.s. emailed it to me a few years back):
> 
> (defun fib (x)
>   (if (< x 1) 0
>       (let ((n (1- x)))
> 	(labels ((fib-aux (number)
> 		   (case number
> 		     ((0) (values 1 0))
> 		     ((1) (values 0 1))
> 		     (otherwise (let ((k (floor number 2)))
> 				  (multiple-value-bind (a b) (fib-aux k)
> 				    (let* ((aa (* a a))
> 					   (bb (* b b))
> 					   (ab2 (* 2 a b))
> 					   (ab2bb (+ ab2 bb)))
> 				      (if (= number (* 2 k))
> 					  (values (+ aa bb) ab2bb)
> 					  (values ab2bb (+ ab2bb aa bb))))))))))
> 	  (if (<= n 1) 1
*> 	      (let ((k (floor n 2)))
> 		(multiple-value-bind (a b) (fib-aux k)
> 		  (let ((ab (+ a b)))
*> 		    (if (= n (* 2 k))
> 			(+ (* ab ab) (* b b))
> 			(+ (* ab ab) (* 2 b ab)))))))))))

What about using the multiple values returned by FLOOR to avoid the
multiplication by 2 in the inner test?

 	      (multiple-value-bind (k r) (floor n 2)
 		(multiple-value-bind (a b) (fib-aux k)
 		  (let ((ab (+ a b)))
 		    (if (= r 0)
 			(+ (* ab ab) (* b b))
 			(+ (* ab ab) (* 2 b ab))))))

and likwise in the FIX-AUX function?


-- 
Thomas A. Russ,  USC/Information Sciences Institute
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092500471716807-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-24 13:07:34 -0400, ···@sevak.isi.edu (Thomas A. Russ) said:

> What about using the multiple values returned by FLOOR to avoid the
> multiplication by 2 in the inner test?

sadly it seems to blow out the control stack in an enless recursion on 
fib-aux under both openmcl and sbcl :(
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092500572975249-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-25 00:47:17 -0400, Raffael Cavallaro 
<················@pas-d'espam-s'il-vous-plait-mac.com> said:

> On 2007-09-24 13:07:34 -0400, ···@sevak.isi.edu (Thomas A. Russ) said:
> 
>> What about using the multiple values returned by FLOOR to avoid the
>> multiplication by 2 in the inner test?
> 
> sadly it seems to blow out the control stack in an enless recursion on 
> fib-aux under both openmcl and sbcl :(

of course, here again this is really just a test to see if the number 
is even, so we could substitute evenp for the multiplication. It makes 
our intent clearer, but it runs in exactly the same time and conses the 
almost exactly the same:

(defun fib (x)
  (if (< x 1) 0
      (let ((n (1- x)))
	(labels ((fib-aux (number)
		   (case number
		     ((0) (values 1 0))
		     ((1) (values 0 1))
		     (otherwise (let ((k (floor number 2)))
				  (multiple-value-bind (a b) (fib-aux k)
				    (let* ((aa (* a a))
					   (bb (* b b))
					   (ab2 (* 2 a b))
					   (ab2bb (+ ab2 bb)))
				      (if (evenp number)
					  (values (+ aa bb) ab2bb)
					  (values ab2bb (+ ab2bb aa bb))))))))))
	  (if (<= n 1) 1
	      (let ((k (floor n 2)))
		(multiple-value-bind (a b) (fib-aux k)
		  (let ((ab (+ a b)))
		    (if (evenp n)
			(+ (* ab ab) (* b b))
			(+ (* ab ab) (* 2 b ab)))))))))))

CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
Evaluation took:
  1.404 seconds of real time
  1.397153 seconds of user run time
  0.003321 seconds of system run time
  0 calls to %EVAL
  0 page faults and
  899,208 bytes consed.
NIL
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f8b0ab$0$17137$4c368faf@roadrunner.com>
Surprisingly, adding one extra condition leads to substantial 
improvement in timings.

Look the the formula for Fib(4n) here 
http://en.wikipedia.org/wiki/Fibonacci_number

I modified your code to add one extra condition:

(defun fib-8 (n)
   (if (> 0 n)
     (if (evenp n) (- (fib-8 (- n))) (fib-8 (- n)))
     (if (> 2 n) n
       (cond
	((= n 2) 1)
	((= n 3) 2)
	((= n 4) 3)
	((= (mod n 4) 0)
	 (let* ((k (/ n 4)) (f1 (fib-8 k)) (f2 (fib-8 (1+ k))) (f1sq (* f1 f1)) 
(f2sq (* f2 f2)) (f12 (* f1 f2)) )
	   (- (* (* 4 f12) (+ f2sq (* 2 f1sq))) (* (* 3 f1sq) (+ f1sq (* 2 
f2sq))))))
	(t (let* ((even? (evenp n))
           (k (/ (+ n (if even? 0 1)) 2))
           (fib1 (fib-8 (if even? (1+ k) k)))
           (fib2 (fib-8 (1- k))))
          (funcall (if even? #'- #'+) (* fib1 fib1) (* fib2 fib2))))))))


(defun fib (n)
  (cond ((not (and (integerp n) (>= n 0)))
      (error "fibonacci numbers are only defined for integers 0 and 
greater"))
     ((< n 2) n)
     ((= n 2) 1)
     (t (let* ((even? (evenp n))
           (k (/ (+ n (if even? 0 1)) 2))
           (fib1 (fib (if even? (1+ k) k)))
           (fib2 (fib (1- k))))
          (funcall (if even? #'- #'+) (* fib1 fib1) (* fib2 fib2))))))

CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
Evaluation took:
   3.099 seconds of real time
   3.092193 seconds of user run time
   0.008 seconds of system run time
   [Run times include 0.04 seconds GC run time.]
   0 calls to %EVAL
   0 page faults and
   13,944,840 bytes consed.


CL-USER> (time (dotimes (n 1) (fib-8 (expt 10 6))))
Evaluation took:
   2.322 seconds of real time
   2.316144 seconds of user run time
   0.004 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   1,822,408 bytes consed.
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092509570050073-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-25 02:54:24 -0400, "J. I. Gyasu" <·········@nospam> said:

> (defun fib-8 (n)
>    (if (> 0 n)
>      (if (evenp n) (- (fib-8 (- n))) (fib-8 (- n)))
>      (if (> 2 n) n
>        (cond
> 	((= n 2) 1)
> 	((= n 3) 2)
> 	((= n 4) 3)
> 	((= (mod n 4) 0)
> 	 (let* ((k (/ n 4)) (f1 (fib-8 k)) (f2 (fib-8 (1+ k))) (f1sq (* f1 
> f1)) (f2sq (* f2 f2)) (f12 (* f1 f2)) )
> 	   (- (* (* 4 f12) (+ f2sq (* 2 f1sq))) (* (* 3 f1sq) (+ f1sq (* 2 f2sq))))))
> 	(t (let* ((even? (evenp n))
>            (k (/ (+ n (if even? 0 1)) 2))
>            (fib1 (fib-8 (if even? (1+ k) k)))
>            (fib2 (fib-8 (1- k))))
>           (funcall (if even? #'- #'+) (* fib1 fib1) (* fib2 fib2))))))))

couple of things:
1. this is still a bit slower than and conses twice as much as the the 
fib-aux version I recently posted.
2. your fib-8 requires that fib be defined for negative integers, which 
is wrong - it won't catch erroneous inputs.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f9c32a$0$28818$4c368faf@roadrunner.com>
Raffael Cavallaro wrote:

> 1. this is still a bit slower than and conses twice as much as the the 
> fib-aux version I recently posted.
> 2. your fib-8 requires that fib be defined for negative integers, which 
> is wrong - it won't catch erroneous inputs.
> 

Given the definition:
  F(0)=0 F(1)=1, F(n+1)=F(n)+F(n-1),
the fibonacci series can be extended in both directions. For example, 
F(-1) must satisfy F(-1)+F(0)=F(1) ==> F(-1) = 1 etc.
For any n>0, we have.
F(-n) = (-1)^{n+1} F(n)
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092609340350073-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-25 22:25:32 -0400, "J. I. Gyasu" <·········@nospam> said:

> Given the definition:
>   F(0)=0 F(1)=1, F(n+1)=F(n)+F(n-1),
> the fibonacci series can be extended in both directions. For example, 
> F(-1) must satisfy F(-1)+F(0)=F(1) ==> F(-1) = 1 etc.
> For any n>0, we have.
> F(-n) = (-1)^{n+1} F(n)

But this is an *extension* of the definition of fibonacci numbers, one 
that violates the accepted definition. This extension violates the 
property that terms give the total number of pairs in a population of 
idealized rabbits descendend from a single original breeding pair for 
generation n as put forward by Leonardo of Pisa a.k.a. Fibonacci, the 
man for whom this sequence is named - you can't have *negative* 
generations or negative rabbits. Using such a function requires that 
you accept erroneous input for *fibonacci* numbers, which are only 
defined for integers 0 or greater.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f9cc1a$0$17128$4c368faf@roadrunner.com>
Using the interplay between lucas and fibonacci numbers leads to a 
pretty fast method (see for instance : 
http://mathforum.org/library/drmath/view/52677.html and 
http://mathworld.wolfram.com/LucasNumber.html )
So here is another method

(defun lucas-fib (n b)
   (if (= 0 b)
     ;calculate lucas numbers
     (case n
       ( (0) 2)
       ( (1) 1)
       (otherwise
	(if (evenp n)
	  (let* ( (k (/ n 2)) (l (lucas-fib k 0)) )
	    (+ (* l l) (if (evenp k) -2 2)))
	  (let* ( (k (1- n)) (l (lucas-fib k 0)) (f (lucas-fib k 1)) )
	    (/ (+ (* 5 f) l) 2)))))
     ;calculate fibonacci numbers
     (case n
       ( (0) 0)
       ( (1) 1)
       (otherwise
	(if (evenp n)
	  (let* ( (k (/ n 2)) (l (lucas-fib k 0)) (f (lucas-fib k 1)))
	    (* f l))
	  (let* ((k (1- n)) (l (lucas-fib k 0)) (f (lucas-fib k 1)))
	    (/ (+ f l) 2)))))))

(defun fib-10 (n)
   (lucas-fib n 1))

CL-USER> (time (dotimes (n 1) (fib-10 (expt 10 6))))
Evaluation took:
   1.298 seconds of real time
   1.300081 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   728,416 bytes consed

(defun fib (x)
  (if (< x 1) 0
      (let ((n (1- x)))
     (labels ((fib-aux (number)
            (case number
              ((0) (values 1 0))
              ((1) (values 0 1))
              (otherwise (let ((k (floor number 2)))
                   (multiple-value-bind (a b) (fib-aux k)
                     (let* ((aa (* a a))
                        (bb (* b b))
                        (ab2 (* 2 a b))
                        (ab2bb (+ ab2 bb)))
                       (if (evenp number)
                       (values (+ aa bb) ab2bb)
                       (values ab2bb (+ ab2bb aa bb))))))))))
       (if (<= n 1) 1
           (let ((k (floor n 2)))
         (multiple-value-bind (a b) (fib-aux k)
           (let ((ab (+ a b)))
             (if (evenp n)
             (+ (* ab ab) (* b b))
             (+ (* ab ab) (* 2 b ab)))))))))))

CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
Evaluation took:
   2.147 seconds of real time
   2.148134 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   906,544 bytes consed.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46f9d176$0$28866$4c368faf@roadrunner.com>
J. I. Gyasu wrote:

> 
> (defun fib-10 (n)
>   (lucas-fib n 1))
> 

The above works only if n>=0, and unfortunately goes into an infinite 
loop when n<0 so in general fib-10 should be

(defun fib-10 (n)
   (if (>= n 0) (lucas-fib n 1)
     (if (evenp n) (- (fib-10 (- n))) (fib-10 (- n)))))

or

(defun fib-10 (n)
   (if (>= n 0) (lucas-fib n 1)
     (error "fibonacci numbers are only defined for integers 0 and 
greater")))
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <200709261002058930-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-25 23:03:40 -0400, "J. I. Gyasu" <·········@nospam> said:

> Using the interplay between lucas and fibonacci numbers leads to a 
> pretty fast method (see for instance : 
> http://mathforum.org/library/drmath/view/52677.html and 
> http://mathworld.wolfram.com/LucasNumber.html )

Yes, this last one of yours is the fastest so far and doesn't cons much 
either.  BTW, it can be rewritten as below using an &optional arg for b:

(defun fib-lucas (n &optional (b 1))
  (if (= 0 b)  ;calculate lucas numbers
      (case n
	((0) 2)
	((1) 1)
	(otherwise
	 (if (evenp n)
	     (let* ((k (/ n 2)) (l (fib-lucas k 0)) )
	       (+ (* l l) (if (evenp k) -2 2)))
	     (let* ((k (1- n)) (l (fib-lucas k 0)) (f (fib-lucas k 1)) )
	       (/ (+ (* 5 f) l) 2)))))
      (case n  ;calculate fibonacci numbers
	((0) 0)
	((1) 1)
	(otherwise
	 (if (evenp n)
	     (let* ((k (/ n 2)) (l (fib-lucas k 0)) (f (fib-lucas k 1)))
	       (* f l))
	     (let* ((k (1- n)) (l (fib-lucas k 0)) (f (fib-lucas k 1)))
	       (/ (+ f l) 2)))))))


CL-USER> (time (dotimes (n 1) (fib-lucas (expt 10 6))))
Evaluation took:
  0.84 seconds of real time
  0.831465 seconds of user run time
  0.003285 seconds of system run time
  0 calls to %EVAL
  0 page faults and
  725,616 bytes consed.
NIL
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46fc8a77$0$9602$4c368faf@roadrunner.com>
Raffael Cavallaro wrote:
> Yes, this last one of yours is the fastest so far and doesn't cons much 
> either.  BTW, it can be rewritten as below using an &optional arg for b:
> 

fib-11 is an almost iterative version of fib-lucas (I use recursion to 
find the steps needed in the iteration), I expected it to be faster than 
fib-lucas.

(defun steps (n)
   (if (= 1 n) nil
     (let* ( (even? (evenp n)) (v (if even? t nil))
                   (k (if even? (/ n 2) (1- n))) )
       (append (steps k) (list v )))))

  (defun fib-11 (n)
   (if (>= n 2)
     (let* ( (seq (steps n)) (f 1) (l 1) (p nil) )
       (progn
     (dolist (v seq)
       (if v (psetq f (* f l) l (+ (* l l) (if p -2 2)) p t )
         (psetq f (/ (+ f l) 2)  l (/ (+ (* 5 f) l) 2) p nil)))
     f))
     (if (>= n 0) n  (error "invalid input"))))



In clisp:
Timing of fib-lucas

[2]> (time (dotimes (n 1) (fib-lucas (expt 10 6))))
Real time: 0.289031 sec.
Run time: 0.288018 sec.
Space: 688712 Bytes
GC: 1, GC time: 0.004 sec.
NIL

Timings of fib-11

[5]> (time (dotimes (n 1) (fib-11 (expt 10 6))))
Real time: 0.201916 sec.
Run time: 0.200012 sec.
Space: 532376 Bytes
NIL

fib-11 is slightly faster.

Back to the usual:

CL-USER> (time (dotimes (n 1) (fib-lucas (expt 10 6))))
Evaluation took:
   1.23 seconds of real time
   1.228077 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   729,480 bytes consed.

CL-USER> (time (dotimes (n 1) (fib-11 (expt 10 6))))
Evaluation took:
   1.835 seconds of real time
   1.836115 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   528,272 bytes consed.


fib-lucas is significantly faster.
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007093023294516807-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-28 01:00:28 -0400, "J. I. Gyasu" <·········@gmail.com> said:

> fib-11 is an almost iterative version of fib-lucas (I use recursion to 
> find the steps needed in the iteration), I expected it to be faster 
> than fib-lucas.

Actually it's a bit faster than fib-aux, the same speed as Brad 
Lucier's version, but still takes almost 50% more time than fib-lucas 
which is still the speed leader. Fib-steps (a.k.a., fib-11) does cons a 
bit less though:

CL-USER> (time (dotimes (n 1) (fib-steps (expt 10 6))))
Evaluation took:
  1.258 seconds of real time
  1.242817 seconds of user run time
  0.004368 seconds of system run time
  0 calls to %EVAL
  0 page faults and
  528,936 bytes consed.
NIL

CL-USER> (time (dotimes (n 1) (fib-lucas (expt 10 6))))
Evaluation took:
  0.842 seconds of real time
  0.830631 seconds of user run time
  0.001846 seconds of system run time
  0 calls to %EVAL
  0 page faults and
  721,808 bytes consed.
NIL
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <470079ae$0$26374$4c368faf@roadrunner.com>
Raffael Cavallaro wrote:
> On 2007-09-28 01:00:28 -0400, "J. I. Gyasu" <·········@gmail.com> said:
>  
> Actually it's a bit faster than fib-aux, the same speed as Brad Lucier's 
> version, but still takes almost 50% more time than fib-lucas which is 
> still the speed leader. Fib-steps (a.k.a., fib-11) does cons a bit less 
> though:
> 


On my machine, under gnu clisp fib-11 ran a bit faster than fib-lucas 
but under sbcl fib-lucas ran much faster than fib-11 (things ran much 
faster under gnu clisp in general).

I am a bit surprised, (ignoring the steps part which runs very fast) the 
number of additions and multiplications in fib-lucas and fib-11 should 
be nearly the same, yet under sbcl there is this huge difference in 
performance. Why would the recursive code be that much faster than the 
iterative version in sbcl?
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007100113064175249-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-10-01 00:37:57 -0400, "J. I. Gyasu" <·········@gmail.com> said:

> On my machine, under gnu clisp fib-11 ran a bit faster than fib-lucas 
> but under sbcl fib-lucas ran much faster than fib-11 (things ran much 
> faster under gnu clisp in general).

Again, benchmarks like this are measuring the performance of the 
implementation's bignum library more than anything else. SBCL's is not 
the best since mzscheme (for example) routinely does almost 10x better.


> 
> I am a bit surprised, (ignoring the steps part which runs very fast) 
> the number of additions and multiplications in fib-lucas and fib-11 
> should be nearly the same, yet under sbcl there is this huge difference 
> in performance. Why would the recursive code be that much faster than 
> the iterative version in sbcl?

That would be a question for one of the sbcl maintainers who frequent 
this group - Juho?

For a first idea you could look at the output of disassemble.
From: Juho Snellman
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <slrnfg2kmn.sso.jsnell@sbz-30.cs.Helsinki.FI>
Raffael Cavallaro <················@pas-d'espam-s'il-vous-plait-mac.com> wrote:
> On 2007-10-01 00:37:57 -0400, "J. I. Gyasu" <·········@gmail.com> said:
>> I am a bit surprised, (ignoring the steps part which runs very fast) 
>> the number of additions and multiplications in fib-lucas and fib-11 
>> should be nearly the same, yet under sbcl there is this huge difference 
>> in performance. Why would the recursive code be that much faster than 
>> the iterative version in sbcl?
>
> That would be a question for one of the sbcl maintainers who frequent 
> this group - Juho?

I won't pretend to understand your code, so I'll just take at face
value that they are indeed executing roughly the same amounts of
multiplications (additions are going to be completely irrelevant:
addition is O(N) on the length of the operands, naive multiplication
is O(N^2) -> the runtime will be dominated by multiplications).

So the probable explanation is then that the distribution of the
lengths of the multiplication operands is different for the two
variants. SBCL only includes a naive multiplier, so when the numbers
get huge it's going to slow down more relative to clisp or Lisps that
use gmp for bignums. IIRC the break-even point that gmp used for
switching from a Karatsuba multiplier [ O(N^1.6) ] to an FFT
multiplier [ O(N log N) ] was something like 100K bits. You're
probably going way over that limit here. So if one of the versions is
doing more operations on really large numbers, it'll cause a larger
slowdown on SBCL than on the competition.

At least that's the only explanation that I can come up with off the
cuff. Since you two seem to understand the actul code, you can
probably figure ot whether the explanation actually makes sense :-)

> For a first idea you could look at the output of disassemble.

Not very likely to be of use. Replacing all calls to * with calls to
(defun foo (x y) (print (list (integer-length x) (integer-length y)))
(* x y)) and running the two variants might be more illuminating.

-- 
Juho Snellman
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092601394016807-raffaelcavallaro@pasdespamsilvousplaitmaccom>
Finally, here's a version by Bradley Lucier, translated by Nicholas 
Neuss from scheme into common lisp, and only slightly modified by yours 
truly to handle bogus inputs. It runs faster than any of the other 
versions posted here so far, and only conses a bit more, but then, it 
returns two values at every recursive call, fib(n) and fib(n + 1):

(defun fib (n) 
  "Returns f_n f_{n+1}."
  (cond ((not (and (integerp n) (>= n 0)))
	 (error "fibonacci numbers are only defined for integers 0 and greater"))
	((zerop n) (values 0 1))
	((= n 1) (values 1 1))
	((= n 2) (values 1 2)) 
	(t (let ((m (floor n 2))) 
	     (multiple-value-bind (f_m f_m+1) (fib m) 
	       (let ((f_m^2   (* f_m f_m)) 
		     (f_m+1^2 (* f_m+1 f_m+1))) 
		 (if (evenp n) 
		     (values (- (* 2 f_m+1^2) 
				(* 3 f_m^2) 
				(if (oddp m) -2 2)) 
			     (+ f_m^2 f_m+1^2)) 
		     (values (+ f_m^2 f_m+1^2) 
			     (- (* 3 f_m+1^2) 
				(* 2 f_m^2) 
				(if (oddp m) -2 2))))))))))

btw, Brad's original scheme version:

(define (fib n) 
  ;; returns f_n f_{n+1} 
  (case n 
    ((1) (values 1 1)) 
    ((2) (values 1 2)) 
    (else 
     (let ((m (quotient n 2))) 
       (call-with-values 
	   (lambda () (fib m)) 
	 (lambda (f_m f_m+1) 
	   (let ((f_m^2   (* f_m f_m)) 
		 (f_m+1^2 (* f_m+1 f_m+1))) 
	     (if (even? n) 
		 (values (- (* 2 f_m+1^2) 
			    (* 3 f_m^2) 
			    (if (odd? m) 
				-2 
				2)) 
			 (+ f_m^2 f_m+1^2)) 
		 (values (+ f_m^2 f_m+1^2) 
			 (- (* 3 f_m+1^2) 
			    (* 2 f_m^2) 
			    (if (odd? m) 
				-2 
				2)))))))))))

computes the 1 millionth fibonacci number (and the million-and-first) 
in 0.14 seconds under mzscheme compared to the sbcl common lisp time of 
1.25 seconds, so mzscheme is still almost 10 times as fast here.
From: J. I. Gyasu
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <46fa4ede$0$19643$4c368faf@roadrunner.com>
Raffael Cavallaro wrote:
> Finally, here's a version by Bradley Lucier, translated by Nicholas 
> Neuss from scheme into common lisp, and only slightly modified by yours 
> truly to handle bogus inputs. It runs faster than any of the other 
> versions posted here so far, and only conses a bit more,

Results will vary from computer to computer but this is the output from 
my machine:

CL-USER>
(defun fib (n)  "Returns f_n f_{n+1}."
  (cond ((not (and (integerp n) (>= n 0)))
      (error "fibonacci numbers are only defined for integers 0 and 
greater"))
     ((zerop n) (values 0 1))
     ((= n 1) (values 1 1))
     ((= n 2) (values 1 2))     (t (let ((m (floor n 2))) 
(multiple-value-bind (f_m f_m+1) (fib m)            (let ((f_m2   (* f_m 
f_m))              (f_m+12 (* f_m+1 f_m+1)))          (if (evenp n) 
          (values (- (* 2 f_m+12)                 (* 3 f_m2) 
      (if (oddp m) -2 2))                  (+ f_m2 f_m+12)) 
  (values (+ f_m2 f_m+12)                  (- (* 3 f_m+12) 
    (* 2 f_m2)                 (if (oddp m) -2 2))))))))))
FIB
CL-USER> (time (dotimes (n 1) (fib (expt 10 6))))
Evaluation took:
   1.827 seconds of real time
   1.828115 seconds of user run time
   0.0 seconds of system run time
   0 calls to %EVAL
   0 page faults and
   1,208,896 bytes consed.
NIL
CL-USER> (defun lucas-fib (n b)
   (if (= 0 b)
     ;calculate lucas numbers
     (case n
       ( (0) 2)
       ( (1) 1)
       (otherwise
     (if (evenp n)
       (let* ( (k (/ n 2)) (l (lucas-fib k 0)) )
         (+ (* l l) (if (evenp k) -2 2)))
       (let* ( (k (1- n)) (l (lucas-fib k 0)) (f (lucas-fib k 1)) )
         (/ (+ (* 5 f) l) 2)))))
     ;calculate fibonacci numbers
     (case n
       ( (0) 0)
       ( (1) 1)
       (otherwise
     (if (evenp n)
       (let* ( (k (/ n 2)) (l (lucas-fib k 0)) (f (lucas-fib k 1)))
         (* f l))
       (let* ((k (1- n)) (l (lucas-fib k 0)) (f (lucas-fib k 1)))
         (/ (+ f l) 2)))))))

(defun fib-10 (n)
   (lucas-fib n 1))
FIB-10
CL-USER> (time (dotimes (n 1) (fib-10 (expt 10 6))))
Evaluation took:
   1.25 seconds of real time
   1.244077 seconds of user run time
   0.008001 seconds of system run time
   [Run times include 0.024 seconds GC run time.]
   0 calls to %EVAL
   0 page faults and
   719,680 bytes consed.
From: Nicolas Neuss
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <87bqbpes19.fsf@ma-patru.mathematik.uni-karlsruhe.de>
Raffael Cavallaro <················@pas-d'espam-s'il-vous-plait-mac.com>
writes:

> Finally, here's a version by Bradley Lucier, translated by Nicholas Neuss
                                                             Nicolas
Ha, I did not remember that any more.

> from scheme into common lisp, and only slightly modified by yours truly to
> handle bogus inputs. It runs faster than any of the other versions posted
> here so far, and only conses a bit more, but then, it returns two values at
> every recursive call, fib(n) and fib(n + 1):
>
> (defun fib (n) "Returns f_n f_{n+1}."
>  (cond ((not (and (integerp n) (>= n 0)))
> 	 (error "fibonacci numbers are only defined for integers 0 and greater"))
> 	((zerop n) (values 0 1))
> 	((= n 1) (values 1 1))
> 	((= n 2) (values 1 2)) 	(t (let ((m (floor n 2)))
> (multiple-value-bind (f_m f_m+1) (fib m) 	       (let ((f_m^2   (*
> f_m f_m)) 		     (f_m+1^2 (* f_m+1 f_m+1)))
> (if (evenp n) 		     (values (- (* 2 f_m+1^2)
> (* 3 f_m^2) 				(if (oddp m) -2 2))
> (+ f_m^2 f_m+1^2)) 		     (values (+ f_m^2 f_m+1^2)
> (- (* 3 f_m+1^2) 				(* 2 f_m^2)
> (if (oddp m) -2 2))))))))))

but I found it between my files (better formatted):

(defun fast-fib-pair (n)
  "Returns f_n f_{n+1}."
  (cond
    ((= n 1) (values 1 1))
    ((= n 2) (values 1 2))
    (t (let ((m (floor n 2)))
         (multiple-value-bind (f_m f_m+1)
             (fast-fib-pair m)
           (let ((f_m^2   (* f_m f_m))
                 (f_m+1^2 (* f_m+1 f_m+1)))
             (if (evenp n)
                 (values (- (* 2 f_m+1^2)
                            (* 3 f_m^2)
                            (if (oddp m) -2 2))
                         (+ f_m^2 f_m+1^2))
                 (values (+ f_m^2 f_m+1^2)
                         (- (* 3 f_m+1^2)
                            (* 2 f_m^2)
                            (if (oddp m) -2 2))))))))))

> computes the 1 millionth fibonacci number (and the million-and-first) in
> 0.14 seconds under mzscheme compared to the sbcl common lisp time of 1.25
> seconds, so mzscheme is still almost 10 times as fast here.

This test only measures only bignum performance.  Try CLISP instead:

(time (progn (fast-fib-pair 1000000) nil))
Real time: 0.135602f0 sec.
Run time: 0.136008f0 sec.
Space: 1216456 Bytes


Nicolas
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092609085175249-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-26 04:42:58 -0400, Nicolas Neuss 
<········@mathematik.uni-karlsruhe.de> said:

> This test only measures only bignum performance.  Try CLISP instead:

right - that was my point halfway back up the thread - we're mostly 
measuring the implementation's bignum library here.
From: Thomas A. Russ
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <ymi4phi5t5i.fsf@blackcat.isi.edu>
Raffael Cavallaro <················@pas-d'espam-s'il-vous-plait-mac.com> writes:

> On 2007-09-24 13:07:34 -0400, ···@sevak.isi.edu (Thomas A. Russ) said:
> 
> > What about using the multiple values returned by FLOOR to avoid the
> > multiplication by 2 in the inner test?
> 
> sadly it seems to blow out the control stack in an enless recursion on
> fib-aux under both openmcl and sbcl :(

Hmmm.  Interestingly enough, my first attempt achieved the same result
in ACL 6.2, but then I made a silly copy & paste mistake.  With fixed
code, like that below:

(defun fib (x)
  (if (< x 1) 0
    (let ((n (1- x)))
      (labels ((fib-aux (number)
			(case number
			  ((0) (values 1 0))
			  ((1) (values 0 1))
			  (otherwise (multiple-value-bind (k r)(floor number 2)
				       (multiple-value-bind (a b) (fib-aux k)
					 (let* ((aa (* a a))
						(bb (* b b))
						(ab2 (* 2 a b))
						(ab2bb (+ ab2 bb)))
					   (if (= r 0)
					       (values (+ aa bb) ab2bb)
					     (values ab2bb (+ ab2bb aa bb))))))))))
	(if (<= n 1) 1
	  (multiple-value-bind (k r) (floor n 2)
	    (multiple-value-bind (a b) (fib-aux k)
	      (let ((ab (+ a b)))
		(if (= r 0)
		    (+ (* ab ab) (* b b))
		  (+ (* ab ab) (* 2 b ab)))))))))))


I got reasonable results:

 (time (fib 1000))
; cpu time (non-gc) 0 msec user, 0 msec system
; cpu time (gc)     0 msec user, 0 msec system
; cpu time (total)  0 msec user, 0 msec system
; real time  0 msec
; space allocation:
;  1 cons cell, 1,392 other bytes, 0 static bytes

43466557686937456435688527675040625802564660517371780402481729089536555417949051890403879840079255169295922593080322634775209689623239873322471161642996440906533187938298969649928516003704476137795166849228875




-- 
Thomas A. Russ,  USC/Information Sciences Institute
From: Raffael Cavallaro
Subject: Re: Fibonacci Recursion, What??
Date: 
Message-ID: <2007092609360343658-raffaelcavallaro@pasdespamsilvousplaitmaccom>
On 2007-09-25 17:31:21 -0400, ···@sevak.isi.edu (Thomas A. Russ) said:

> Interestingly enough, my first attempt achieved the same result
> in ACL 6.2, but then I made a silly copy & paste mistake.

I must have made the same silly mistake :(

Thanks for the fix!