Why does this simplification make my function slower? - performance

The following function computes the Fibonacci series by tail recursive and squaring:
(defun fib1 (n &optional (a 1) (b 0) (p 0) (q 1))
(cond ((zerop n) b)
((evenp n)
(fib1 (/ n 2)
a
b
(+ (* p p) (* q q))
(+ (* q q) (* 2 p q))))
(t
(fib1 (1- n)
(+ (* b q) (* a (+ p q)))
(+ (* b p) (* a q))
p
q))))
Basically it reduces every odd input to a even one, and reduces every even input by half. For example,
F(21)
= F(21 1 0 0 1)
= F(20 1 1 0 1)
= F(10 1 1 1 1)
= F(5 1 1 2 3)
= F(4 8 5 2 3)
= F(2 8 5 13 21)
= F(1 8 5 610 987)
= F(0 17711 10946 610 987)
= 10946
When I saw this I thought it might be better to combine the even and odd cases (since odd minus one = even), so I wrote
(defun fib2 (n &optional (a 1) (b 0) (p 0) (q 1))
(if (zerop n) b
(fib2 (ash n -1)
(if (evenp n) a (+ (* b q) (* a (+ p q))))
(if (evenp n) b (+ (* b p) (* a q)))
(+ (* p p) (* q q))
(+ (* q q) (* 2 p q)))))
and hoping this will make it faster, as the equations above now becomes
F(21)
= F(21 1 0 0 1)
= F(10 1 1 1 1)
= F(5 1 1 2 3)
= F(2 8 5 13 21)
= F(1 8 5 610 987)
= F(0 17711 10946 1346269 2178309)
= 10946
However, it turned out to be much slower (takes about 50% more time in e.g. Clozure CL, CLisp and Lispworks) when I check the time needed for Fib(1000000) by the following code (Ignore the progn, I just don't want my screen filled with numbers.)
(time (progn (fib1 1000000)()))
(time (progn (fib2 1000000)()))
I can only see fib2 may do more evenp than fib1, so why is it that much slower?
EDIT: I think n.m. get it right, and I edited the second group of formulae. E.g. in the example of F(21) above, fib2 actually computes F(31) and F(32) in p and q, which is never used. So in F(1000000), fib2 computes F(1048575) and F(1048576).
Lazy evaluation rocks, that's a very good point. I guess in Common Lisp only some macro like "and" and "or" are evaluated lazily?
The following modified fib2 (defined for n>0) actually runs faster:
(defun fib2 (n &optional (a 1) (b 0) (p 0) (q 1))
(if (= n 1) (+ (* b p) (* a q))
(fib2 (ash n -1)
(if (evenp n) a (+ (* b q) (* a (+ p q))))
(if (evenp n) b (+ (* b p) (* a q)))
(+ (* p p) (* q q))
(+ (* q q) (* 2 p q)))))

Insert printing of the intermediate results. Pay attention to p and q towards the end of the computation.
You will notice that fib2 computes much larger values for p and q at the last step. These two values account for all the performance difference.
The ironic thing is that these expensive values are unused. This is why Haskell doesn't suffer from this performance problem: the unused values are not actually computed.

If nothing else, fib2 has more conditionals (while computing the arguments). That may well change how the code flow is done. Conditionals imply jumps, implies pipeline stalls.
It would probably be instructive to look at the generated code (try (disassemble #'fib1) and (disassemble #'fib2) and see if there's any blatant differences). It might also be worth to change the optimization settings, there's usually a fair few optimizations that are not done unless you request heavy optimization for speed.

Related

First power of 2 that has leading decimal digits of 12 in Common Lisp

In the webpage of Rosetta Code (http://rosettacode.org/wiki/First_power_of_2_that_has_leading_decimal_digits_of_12#C) there is the following challenge: Find the first power of 2 that has leading decimal digits of 12.
I have written several versions in Common Lisp, but I fail miserably in terms of performance compared to what other languages report.
The following code is one of the many versions that I have tried.
(defun log10 (x) (/ (log x) (log 10)))
(defun first-digits (n l)
(let* ((len-n (1+ (floor (log10 n))))
(tens (expt 10 (- len-n l))) )
(truncate n tens) ))
(defun p (rem n)
(do* ((len-rem (1+ (floor (log10 rem))))
(i 0 (1+ i))
(k 1 (* 2 k)) )
((= n 0) (1- i))
(when (= rem (first-digits k len-rem))
(decf n) )))
The performance is really poor, but I refuse to admit that Common Lisp is slower than any competitors. Any idea of how to achieve the run time of a few seconds reported by C#, C++, etc.?
Here is an answer which is now substantially equivalent to yours (based on the idea in this maths SE answer, but a little more general and a little more optimized. In particular:
it lets you specify both the number you want to raise to a power;
it lets you specify the base you want to work in (so not just 10);
it knows that (log x b) is the log of x in base b;
it computes the log you need just once;
it reorganizes some of the float operations to avoid overflows (at some point your version will call (expt 10 n) with a big enough n thay you'll get a floating point overflow.
I think (in fact I'm reasonably sure) that the remaining thing that is making it slow is float consing. It ought to be possible to prevail upon a compiler to avoid this, and I spent a small amount of time trying but to no avail.
Anyway, here it is.
(defun p (L n &key (b 2) (base 10.0d0))
;; nth occurence of power of b with leading digits L in base:
;; returns power (p below)
(let ((k-1 (floor (log L base))) ;(digits of L in base) - 1
(logb (log (float b 1.0d0) base))) ;log of b in base
(do* ((p 0 (1+ p)) ;power
(d 1 (floor (expt base (+ (rem (* p logb) 1) k-1)))) ;digits
(c (if (= L 1) 1 0) ;count of hits
(if (= L d) (1+ c) c)))
((= c n) p))))
Below is an earlier, useless answer: I've left it for posterity.
Note that the first part what's below deals with only the two-leading-digit case because I didn't bother looking at the original rosetta code thing: see the end for a generalisation.
First of all to pull out the first two decimal digits of something, you want to start by divide it by a suitable power of 10 that the result is a two digit number. That means taking logs, but you can cheat: if you know the number of bits, b, in the number then the number is 2^b + change (assuming it's a positive integer), and knowing the number of bits is very very quick. And then if 10^x = 2^y then x = y/(log_2 10) where log_2 is log base 2. And this is a constant.
So you can write this function after fiddling around with pen and paper for a bit:
(defun leading-two-digits (n)
(truncate (truncate n (expt 10 (1- (truncate (integer-length n)
(load-time-value (log 10 2))))))
10))
Note the use of load-time-value to compute the (log 10 2) just once. And note also that this relies on either having correct integer arithmetic or at least a function which will tell you what the number of bits in a number would be if you did have.
So now
> (leading-two-decimal-digits 59468049869823987435)
5
9
OK, looks good (extensive testing...).
So now you just need to start from 1 and successively multiply by the base, looking for the leading two digits being what you care about. As a hack if the base is 2 you can just left shift: my original function assumed the base was 2 and always left shifted, this one has a configurable base but still special-cases 2, which I suspect may no longer help at all.
(defun nth-ld-power (n &key (b 2) (leading 1) (second 2))
;; iterate is tfeb.github.io/tfeb-lisp-hax/, also should be in
;; Quicklisp
(iterate looking ((v 1) ;value
(p 0) ;power (so we can report it)
(c 0)) ;hit count
(multiple-value-bind (d1 d2) (leading-two-decimal-digits v)
(if (and (= d1 leading) (= d2 second))
(let ((c+ (1+ c)))
(if (= c+ n)
(values v p)
(looking (if (= b 2) (ash v 1) (* v b)) (1+ p) c+)))
(looking (if (= b 2) (ash v 1) (* v b)) (1+ p) c)))))
Again you would want to deal with the multiple-leading-digits case by passing a list of leading digits, but.
OK, so now:
> (time (nth-ld-power 2))
Timing the evaluation of (nth-ld-power 2)
User time = 0.000
System time = 0.000
Elapsed time = 0.000
Allocation = 2848 bytes
0 Page faults
GC time = 0.000
1208925819614629174706176
80
> (time (nth-ld-power 10))
Timing the evaluation of (nth-ld-power 10)
User time = 0.000
System time = 0.000
Elapsed time = 0.000
Allocation = 40704 bytes
0 Page faults
GC time = 0.000
124330809102446660538845562036705210025114037699336929360115994223289874253133343883264
286
OK, this is too quick to measure, let's make it do some real work:
> (time (nth-ld-power 1000))
Timing the evaluation of (nth-ld-power 1000)
User time = 3.264
System time = 0.039
Elapsed time = 3.384
Allocation = 845193424 bytes
517 Page faults
GC time = 0.020
12[...long number truncated here ...]
28745
So that's at least reasonable performance, I think. These figures were for LispWorks on a 2013 macbook. Obviously you can rewrite it without Tim's iterate, but I like it.
Here is a generalisation to the n-digit case.
(defun leading-decimal-digits (n m)
;; Return M leading digits from N: no sanity check
(iterate peel ((q (truncate n (expt 10 (- (truncate (integer-length n)
(load-time-value (log 10 2)))
(- m 1)))))
(digits '()))
(multiple-value-bind (qq d) (truncate q 10)
(cond
((zerop qq)
(cons d digits))
((< qq 10)
(list* qq d digits))
(t
(peel qq (cons d digits)))))))
(defun nth-power-with-leading-decimal-digits (n b leading)
;; Find the N'th occurrence of a power of B whose leading digits are
;; LEADING (a list of digits). Return the value of B^P and P, the
;; power.
(let ((nleading (length leading)))
(iterate looking ((v 1) ;value
(p 0) ;power (so we can report it)
(c 0)) ;hit count
(if (equal (leading-decimal-digits v nleading) leading)
(let ((c+ (1+ c)))
(if (= c+ n)
(values v p)
(looking (if (= b 2) (ash v 1) (* v b)) (1+ p) c+)))
(looking (if (= b 2) (ash v 1) (* v b)) (1+ p) c)))))
So:
> (nth-power-with-leading-decimal-digits 2 2 '(1 2 8))
12855504354071922204335696738729300820177623950262342682411008
203
> (nth-power-with-leading-decimal-digits 2 3 '(2 7 8))
278954761343915929031866324148580803686773879062609352173281933430969939572023921519256921927359964084535215107090906022143908601839272147120823008337941481521208646465304746378648054338849857759629806700446921838039313884792762356955010344065298744426691826196079923777796821513452648753573059469525738664313409324728161550430310432705576201607066435772343529511415605105251217669677767280155388600975280964482318641251059803074701681895639266095014303466041595626938522373004626313927779288797843485898785327074755040298312905780373591994824646107875196292150692772609024142420597241695173176699988995274347532223981851419958515807471788303361043192244700492703668505222371093498892685289816397935636213340656919509760640657215827785179171568543835684943671352357398679232652259639784388841436515656182938820127024910154405205830179436914341715546500034485031465189386918271898229029201
1860
2^203 is the second occurrence of a power of 2 beginning with 128, and 3^1860 is the second occurrence of a power of 3 beginning 278. The second one took 0.017 seconds.

Finding primes up to a certain number in Racket

I'm learning Racket (with the HtDP course) and it's my first shot at a program in a functional language.
I've tried to design a function that finds all primes under a certain input n using (what I think is) a functional approach to the problem, but the program can get really slow (86 seconds for 100.000, while my Python, C and C++ quickly-written solutions take just a couple of seconds).
The following is the code:
;; Natural Natural -> Boolean
;; Helper function to avoid writing the handful (= 0 (modulo na nb))
(define (divisible na nb) (= 0 (modulo na nb)))
;; Natural ListOfNatural -> Boolean
;; n is the number to check, lop is ALL the prime numbers less than n
(define (is-prime? n lop)
(cond [(empty? lop) true]
[(divisible n (first lop)) false]
[ else (is-prime? n (rest lop))]))
;; Natural -> ListOfNatural
(define (find-primes n)
(if (= n 2)
(list 2)
(local [(define LOP (find-primes (sub1 n)))]
(if (is-prime? n LOP)
(append LOP (list n))
LOP))))
(time (find-primes 100000))
I'm using the divisible function instead of just plowing the rest in because I really like to have separated functions when they could be of use in another part of the program. I also should probably define is-prime? inside of find-primes, since no one will ever call is-prime? on a number while also giving all the prime numbers less than that number.
Any pointers on how to improve this?
Here are some ideas for improving the performance, the procedure now returns in under two seconds for n = 100000.
(define (is-prime? n lop)
(define sqrtn (sqrt n))
(if (not (or (= (modulo n 6) 1) (= (modulo n 6) 5)))
false
(let loop ([lop lop])
(cond [(or (empty? lop) (< sqrtn (first lop))) true]
[(zero? (modulo n (first lop))) false]
[else (loop (rest lop))]))))
(define (find-primes n)
(cond [(<= n 1) '()]
[(= n 2) '(2)]
[(= n 3) '(2 3)]
[else
(let loop ([lop '(2 3)] [i 5])
(cond [(> i n) lop]
[(is-prime? i lop) (loop (append lop (list i)) (+ i 2))]
[else (loop lop (+ i 2))]))]))
Some of the optimizations are language-related, others are algorithmic:
The recursion was converted to be in tail position. In this way, the recursive call is the last thing we do at each step, with nothing else to do after it - and the compiler can optimize it to be as efficient as a loop in other programming languages.
The loop in find-primes was modified for only iterating over odd numbers. Note that we go from 3 to n instead of going from n to 2.
divisible was inlined and (sqrt n) is calculated only once.
is-prime? only checks up until sqrt(n), it makes no sense to look for primes after that. This is the most important optimization, instead of being O(n) the algorithm is now O(sqrt(n)).
Following #law-of-fives's advice, is-prime? now skips the check when n is not congruent to 1 or 5 modulo 6.
Also, normally I'd recommend to build the list using cons instead of append, but in this case we need the prime numbers list to be constructed in ascending order for the most important optimization in is-prime? to work.
Here's Óscar López's code, tweaked to build the list in the top-down manner:
(define (is-prime? n lop)
(define sqrtn (sqrt n))
(let loop ([lop lop])
(cond [(or (empty? lop) (< sqrtn (mcar lop))) true]
[(zero? (modulo n (mcar lop))) false]
[else (loop (mcdr lop))])))
(define (find-primes n)
(let* ([a (mcons 3 '())]
[b (mcons 2 a)])
(let loop ([p a] [i 5] [d 2] ; d = diff +2 +4 +2 ...
[c 2]) ; c = count of primes found
(cond [(> i n) c]
[(is-prime? i (mcdr a))
(set-mcdr! p (mcons i '()))
(loop (mcdr p) (+ i d) (- 6 d) (+ c 1))]
[else (loop p (+ i d) (- 6 d) c )]))))
Runs at about ~n1.25..1.32, empirically; compared to the original's ~n1.8..1.9, in the measured range, inside DrRacket (append is the culprit of that bad behaviour). The "under two seconds" for 100K turns into under 0.05 seconds; two seconds gets you well above 1M (one million):
; (time (length (find-primes 100000))) ; with cons times in milliseconds
; 10K 156 ; 20K 437 ; 40K 1607 ; 80K 5241 ; 100K 7753 .... n^1.8-1.9-1.7 OP's
; 10K 62 ; 20K 109 ; 40K 421 ; 80K 1217 ; 100K 2293 .... n^1.8-1.9 Óscar's
; mcons:
(time (find-primes 2000000))
; 100K 47 ; 200K 172 ; 1M 1186 ; 2M 2839 ; 3M 4851 ; 4M 7036 .... n^1.25-1.32 this
; 9592 17984 78498 148933 216816 283146
It's still just a trial division though... :) The sieve of Eratosthenes will be much faster yet.
edit: As for set-cdr!, it is easy to emulate any lazy algorithm with it... Otherwise, we could use extendable arrays (lists of...), for the amortized O(1) snoc/append1 operation (that's lots and lots of coding); or maintain the list of primes split in two (three, actually; see the code below), building the second portion in reverse with cons, and appending it in reverse to the first portion only every so often (specifically, judging the need by the next prime's square):
; times: ; 2M 1934 ; 3M 3260 ; 4M 4665 ; 6M 8081 .... n^1.30
;; find primes up to and including n, n > 2
(define (find-primes n)
(let loop ( [k 5] [q 9] ; next candidate; square of (car LOP2)
[LOP1 (list 2)] ; primes to test by
[LOP2 (list 3)] ; more primes
[LOP3 (list )] ) ; even more primes, in reverse
(cond [ (> k n)
(append LOP1 LOP2 (reverse LOP3)) ]
[ (= k q)
(if (null? (cdr LOP2))
(loop k q LOP1 (append LOP2 (reverse LOP3)) (list))
(loop (+ k 2)
(* (cadr LOP2) (cadr LOP2)) ; next prime's square
(append LOP1 (list (car LOP2)))
(cdr LOP2) LOP3 )) ]
[ (is-prime? k (cdr LOP1))
(loop (+ k 2) q LOP1 LOP2 (cons k LOP3)) ]
[ else
(loop (+ k 2) q LOP1 LOP2 LOP3 ) ])))
;; n is the number to check, lop is list of prime numbers to check it by
(define (is-prime? n lop)
(cond [ (null? lop) #t ]
[ (divisible n (car lop)) #f ]
[ else (is-prime? n (cdr lop)) ]))
edit2: The easiest and simplest fix though, closest to your code, was to decouple the primes calculations of the resulting list, and of the list to check divisibility by. In your
(local [(define LOP (find-primes (sub1 n)))]
(if (is-prime? n LOP)
LOP is used as the list of primes to check by, and it is reused as part of the result list in
(append LOP (list n))
LOP))))
immediately afterwards. Breaking this entanglement enables us to stop the generation of testing primes list at the sqrt of the upper limit, and thus it gives us:
;times: ; 1M-1076 2M-2621 3M-4664 4M-6693
; n^1.28 ^1.33 n^1.32
(define (find-primes n)
(cond
((<= n 4) (list 2 3))
(else
(let* ([LOP (find-primes (inexact->exact (floor (sqrt n))))]
[lp (last LOP)])
(local ([define (primes k ps)
(if (<= k lp)
(append LOP ps)
(primes (- k 2) (if (is-prime? k LOP)
(cons k ps)
ps)))])
(primes (if (> (modulo n 2) 0) n (- n 1)) '()))))))
It too uses the same is-prime? code as in the question, unaltered, as does the second variant above.
It is slower than the 2nd variant. The algorithmic reason for this is clear — it tests all numbers from sqrt(n) to n by the same list of primes, all smaller or equal to the sqrt(n) — but in testing a given prime p < n it is enough to use only those primes that are not greater than sqrt(p), not sqrt(n). But it is the closest to your original code.
For comparison, in Haskell-like syntax, under strict evaluation,
isPrime n lop = null [() | p <- lop, rem n p == 0]
-- OP:
findprimes 2 = [2]
findprimes n = lop ++ [n | isPrime n lop]
where lop = findprimes (n-1)
= lop ++ [n | n <- [q+1..n], isPrime n lop]
where lop = findprimes q ; q = (n-1)
-- 3rd:
findprimes n | n < 5 = [2,3]
findprimes n = lop ++ [n | n <- [q+1..n], isPrime n lop]
where lop = findprimes q ;
q = floor $ sqrt $ fromIntegral n
-- 2nd:
findprimes n = g 5 9 [2] [3] []
where
g k q a b c
| k > n = a ++ b ++ reverse c
| k == q, [h] <- b = g k q a (h:reverse c) []
| k == q, (h:p:ps) <- b = g (k+2) (p*p) (a++[h]) (p:ps) c
| isPrime k a = g (k+2) q a b (k:c)
| otherwise = g (k+2) q a b c
The b and c together (which is to say, LOP2 and LOP3 in the Scheme code) actually constitute a pure functional queue a-la Okasaki, from which sequential primes are taken and appended at the end of the maintained primes prefix a (i.e. LOP1) now and again, on each consecutive prime's square being passed, for a to be used in the primality testing by isPrime.
Because of the rarity of this appending, its computational inefficiency has no impact on the time complexity of the code overall.

cosine function calculating scheme

Im making a scheme program that calculates
cos(x) = 1-(x^2/2!)+(x^4/4!)-(x^6/6!).......
whats the most efficient way to finish the program and how would you do the alternating addition and subtraction, thats what I used the modulo for but doesnt work for 0 and 1 (first 2 terms). x is the intial value of x and num is the number of terms
(define cosine-taylor
(lambda (x num)
(do ((i 0 (+ i 1)))
((= i num))
(if(= 0 (modulo i 2))
(+ x (/ (pow-tr2 x (* i 2)) (factorial (* 2 i))))
(- x (/ (pow-tr2 x (* i 2)) (factorial (* 2 i))))
))
x))
Your questions:
whats the most efficient way to finish the program? Assuming you want use the Taylor series expansion and simply sum up the terms n times, then your iterative approach is fine. I've refined it below; but your algorithm is fine. Others have pointed out possible loss of precision issues; see below for my approach.
how would you do the alternating addition and subtraction? Use another 'argument/local-variable' of odd?, a boolean, and have it alternate by using not. When odd? subtract when not odd? add.
(define (cosine-taylor x n)
(let computing ((result 1) (i 1) (odd? #t))
(if (> i n)
result
(computing ((if odd? - +) result (/ (expt x (* 2 i)) (factorial (* 2 i))))
(+ i 1)
(not odd?)))))
> (cos 1)
0.5403023058681398
> (cosine-taylor 1.0 100)
0.5403023058681397
Not bad?
The above is the Scheme-ish way of performing a 'do' loop. You should easily be able to see the correspondence to a do with three locals for i, result and odd?.
Regarding loss of numeric precision - if you really want to solve the precision problem, then convert x to an 'exact' number and do all computation using exact numbers. By doing that, you get a natural, Scheme-ly algorithm with 'perfect' precision.
> (cosine-taylor (exact 1.0) 100)
3982370694189213112257449588574354368421083585745317294214591570720658797345712348245607951726273112140707569917666955767676493702079041143086577901788489963764057368985531760218072253884896510810027045608931163026924711871107650567429563045077012372870953594171353825520131544591426035218450395194640007965562952702049286379961461862576998942257714483441812954797016455243/7370634274437294425723020690955000582197532501749282834530304049012705139844891055329946579551258167328758991952519989067828437291987262664130155373390933935639839787577227263900906438728247155340669759254710591512748889975965372460537609742126858908788049134631584753833888148637105832358427110829870831048811117978541096960000000000000000000000000000000000000000000000000
> (inexact (cosine-taylor (exact 1.0) 100))
0.5403023058681398
we should calculate the terms in iterative fashion to prevent the loss of precision from dividing very large numbers:
(define (cosine-taylor-term x)
(let ((t 1.0) (k 0))
(lambda (msg)
(case msg
((peek) t)
((pull)
(let ((p t))
(set! k (+ k 2))
(set! t (* (- t) (/ x (- k 1)) (/ x k)))
p))))))
Then it should be easy to build a function to produce an n-th term, or to sum the terms up until a term is smaller than a pre-set precision value:
(define t (cosine-taylor-term (atan 1)))
;Value: t
(reduce + 0 (map (lambda(x)(t 'pull)) '(1 2 3 4 5)))
;Value: .7071068056832942
(cos (atan 1))
;Value: .7071067811865476
(t 'peek)
;Value: -2.4611369504941985e-8
A few suggestions:
reduce your input modulo 2pi - most polynomial expansions converge very slowly with large numbers
Keep track of your factorials rather than computing them from scratch each time (once you have 4!, you get 5! by multiplying by 5, etc)
Similarly, all your powers are powers of x^2. Compute x^2 just once, then multiply the "x power so far" by this number (x2), rather than taking x to the n'th power
Here is some python code that implements this - it converges with very few terms (and you can control the precision with the while(abs(delta)>precision): statement)
from math import *
def myCos(x):
precision = 1e-5 # pick whatever you need
xr = (x+pi/2) % (2*pi)
if xr > pi:
sign = -1
else:
sign = 1
xr = (xr % pi) - pi/2
x2 = xr * xr
xp = 1
f = 1
c = 0
ans = 1
temp = 0
delta = 1
while(abs(delta) > precision):
c += 1
f *= c
c += 1
f *= c
xp *= x2
temp = xp / f
c += 1
f *= c
c += 1
f *= c
xp *= x2
delta = xp/f - temp
ans += delta
return sign * ans
Other than that I can't help you much as I am not familiar with scheme...
For your general enjoyment, here is a stream implementation. The stream returns an infinite sequence of taylor terms based on the provided func. The func is called with the current index.
(define (stream-taylor func)
(stream-map func (stream-from 0)))
(define (stream-cosine x)
(stream-taylor (lambda (n)
(if (zero? n)
1
(let ((odd? (= 1 (modulo n 2))))
;; Use `exact` if desired...
;; and see #WillNess above; save 'last'; use for next; avoid expt/factorial
((if odd? - +) (/ (expt x (* 2 n)) (factorial (* 2 n)))))))))
> (stream-fold + 0 (stream-take 10 (stream-cosine 1.0)))
0.5403023058681397
Here's the most streamlined function I could come up with.
It takes advantage of the fact that the every term is multiplied by (-x^2) and divided by (i+1)*(i+2) to come up with the text term.
It also takes advantage of the fact that we are computing factorials of 2, 4, 6. etc. So it increments the position counter by 2 and compares it with 2*N to stop iteration.
(define (cosine-taylor x num)
(let ((mult (* x x -1))
(twice-num (* 2 num)))
(define (helper iter prev-term prev-out)
(if (= iter twice-num)
(+ prev-term prev-out)
(helper (+ iter 2)
(/ (* prev-term mult) (+ iter 1) (+ iter 2))
(+ prev-term prev-out))))
(helper 0 1 0)))
Tested at repl.it.
Here are some answers:
(cosine-taylor 1.0 2)
=> 0.5416666666666666
(cosine-taylor 1.0 4)
=> 0.5403025793650793
(cosine-taylor 1.0 6)
=> 0.5403023058795627
(cosine-taylor 1.0 8)
=> 0.5403023058681398
(cosine-taylor 1.0 10)
=> 0.5403023058681397
(cosine-taylor 1.0 20)
=> 0.5403023058681397

multiplicative inverse of modulo m in scheme

I've written the code for multiplicative inverse of modulo m. It works for most of the initial cases but not for some. The code is below:
(define (inverse x m)
(let loop ((x (modulo x m)) (a 1))
(cond ((zero? x) #f) ((= x 1) a)
(else (let ((q (- (quotient m x))))
(loop (+ m (* q x)) (modulo (* q a) m)))))))
For example it gives correct values for (inverse 5 11) -> 9 (inverse 9 11) -> 5 (inverse 7 11 ) - > 8 (inverse 8 12) -> #f but when i give (inverse 5 12) it produces #f while it should have been 5. Can you see where the bug is?
Thanks for any help.
The algorithm you quoted is Algorithm 9.4.4 from the book Prime Numbers by Richard Crandall and Carl Pomerance. In the text of the book they state that the algorithm works for both prime and composite moduli, but in the errata to their book they correctly state that the algorithm works always for prime moduli and mostly, but not always, for composite moduli. Hence the failure that you found.
Like you, I used Algorithm 9.4.4 and was mystified at some of my results until I discovered the problem.
Here's the modular inverse function that I use now, which works with both prime and composite moduli, as long as its two arguments are coprime to one another. It is essentially the extended Euclidean algorithm that #OscarLopez uses, but with some redundant calculations stripped out. If you like, you can change the function to return #f instead of throwing an error.
(define (inverse x m)
(let loop ((x x) (b m) (a 0) (u 1))
(if (zero? x)
(if (= b 1) (modulo a m)
(error 'inverse "must be coprime"))
(let* ((q (quotient b x)))
(loop (modulo b x) x u (- a (* u q)))))))
Does it have to be precisely that algorithm? if not, try this one, taken from wikibooks:
(define (egcd a b)
(if (zero? a)
(values b 0 1)
(let-values (((g y x) (egcd (modulo b a) a)))
(values g (- x (* (quotient b a) y)) y))))
(define (modinv a m)
(let-values (((g x y) (egcd a m)))
(if (not (= g 1))
#f
(modulo x m))))
It works as expected:
(modinv 5 11) ; 9
(modinv 9 11) ; 5
(modinv 7 11) ; 8
(modinv 8 12) ; #f
(modinv 5 12) ; 5
I think this is the Haskell code on that page translated directly into Scheme:
(define (inverse p q)
(cond ((= p 0) #f)
((= p 1) 1)
(else
(let ((recurse (inverse (mod q p) p)))
(and recurse
(let ((n (- p recurse)))
(div (+ (* n q) 1) p)))))))
It looks like you're trying to convert it from recursive to tail-recursive, which is why things don't match up so well.
These two functions below can help you as well.
Theory
Here’s how we find the multiplicative inverse d. We want e*d = 1(mod n), which means that ed + nk = 1 for some integer k. So we’ll write a procedure that solves the general equation ax + by = 1, where a and b are given, x and y are variables, and all of these values are integers. We’ll use this procedure to solve ed + nk = 1 for d and k. Then we can throw away k and simply return d.
>
(define (ax+by=1 a b)
(if (= b 0)
(cons 1 0)
(let* ((q (quotient a b))
(r (remainder a b))
(e (ax+by=1 b r))
(s (car e))
(t (cdr e)))
(cons t (- s (* q t))))))
This function is a general solution to an equation in form of ax+by=1 where a and b is given.The inverse-mod function simply uses this solution and returns the inverse.
(define inverse-mod (lambda (a m)
(if (not (= 1 (gcd a m)))
(display "**Error** No inverse exists.")
(if (> 0(car (ax+by=1 a m)))
(+ (car (ax+by=1 a m)) m)
(car (ax+by=1 a m))))))
Some test cases are :
(inverse-mod 5 11) ; -> 9 5*9 = 45 = 1 (mod 11)
(inverse-mod 9 11) ; -> 5
(inverse-mod 7 11) ; -> 8 7*8 = 56 = 1 (mod 11)
(inverse-mod 5 12) ; -> 5 5*5 = 25 = 1 (mod 12)
(inverse-mod 8 12) ; -> error no inverse exists

Fermat factorization method limit

I am trying to implement Fermat's factorization (Algorithm C in The Art of Computer Programming, Vol. 2). Unfortunately in my edition (ISBN 81-7758-335-2), this algorithm is printed incorrectly. what should be the condition on factor-inner loop below? I am running the loop till y <= n [passed in as limit].
(if (< limit y) 0 (factor-inner x (+ y 2) (- r y) limit))
Is there anyway to avoid this condition altogether, as it will double the speed of loop?
(define (factor n)
(let ((square-root (inexact->exact (floor (sqrt n)))))
(factor-inner (+ (* 2 square-root) 1)
1
(- (* square-root square-root) n)
n)))
(define (factor-inner x y r limit)
(if (= r 0)
(/ (- x y) 2)
(begin
(display x) (display " ") (display y) (display " ") (display r) (newline)
;;(sleep-current-thread 1)
(if (< r 0)
(factor-inner (+ x 2) y (+ r x) limit)
(if (< limit y)
0
(factor-inner x (+ y 2) (- r y) limit))))))
The (< limit y) check is not necessary because, worst-case, the algorithm will eventually find this solution:
x = N + 2
y = N
It will then return 1.
Looking through Algorithm C, it looks like the issue is with the recursion step, which effectively skips step C4 whenever r < 0, because x is not incremented and r is only decremented by y.
Using the notation of a, b and r from the 1998 edition of Vol. 2 (ISBN 0-201-89684-2), a Scheme version would be as follows:
(define (factor n)
(let ((x (inexact->exact (floor (sqrt n)))))
(factor-inner (+ (* x 2) 1)
1
(- (* x x) n))))
(define (factor-inner a b r)
(cond ((= r 0) (/ (- a b) 2))
((< 0 r) (factor-inner a (+ b 2) (- r b)))
(else (factor-inner (+ a 2) (+ b 2) (- r (- a b))))))
EDIT to add: Basically, we are doing a trick that repeatedly checks whether
r <- ((a - b) / 2)*((a + b - 2)/2) - N
is 0, and we're doing it by simply tracking how r changes when we increment a or b. If we were to set b to b+2 in the expression for r above, it's equivalent to reducing r by the old value of b, which is why both are done in parallel in step C4 of the algorithm. I encourage you to expand out the algebraic expression above and convince yourself that this is true.
As long as r > 0, you want to keep decreasing it to find the right value of b, so you keep repeating step C4. However, if you overshoot, and r < 0, you need to increase it. You do this by increasing a, because increasing a by 2 is equivalent to decreasing r by the old value of a, as in step C3. You will always have a > b, so increasing r by a in step C3 automatically makes r positive again, so you just proceed directly on to step C4.
It's also easy to prove that a > b. We start with a manifestly greater than b, and if we ever increase b to the point where b = a - 2, we have
N = (a - (a - 2))/2 * ((a + (a - 2) - 2)/2 = 1 * (a - 2)
This means that N is prime, as the largest factor it has that is less than sqrt(N) is 1, and the algorithm has terminated.

Resources