series. Reply

S.D.Mechveliani mechvel@math.botik.ru
Wed, 15 Aug 2001 12:45:30 +0400


Luis Pablo Michelena <lmichele@multi.com.uy> writes
on the subject `series' 

> where to find a haskell program that calculates the number e, that is 
> the list of infinite digits? 
> [..]
> what i am looking for is something like the ertostenes sifts, that 
> prints every prime number until it run out of memory ...


In what way the Heratosphenes sieve for prime numbers may relate to 
finding approximations of number  e ?

As to finding the infinite list of digits for  e = lim (1 + 1/n)^n,
                                                   n -> infinity 

here the program is suggested for finding  (eAppr n) :: Rational  
such that  
                    |e - (eAppr n)| < 1/2^(n-3) :

  import Ratio
  eAppr :: Integer -> Rational
  eAppr n = appr 0 (1%1) (0%1)
    where
    appr k member res =           --- member = 1/(k!),
      if                          --- res = sum [1/i! | i <- [0..k]]
         k==n  then  res
      else      appr (k+1) (member/(fromInteger (k+1))) (res+member)


Several decimal digits can be obtained, then, like this:
 
        fromRational (eAppr 6)  :: Double  --> 2.716666666666667       
        fromRational (eAppr 20) :: Double  --> 2.718281828459045

Explanation. According to Calculus, we have
 
     e = lim (eApp n),   where  eAppr n = sum [1/k! | k <- [0..n]] 
         n -> infinity
and                      |e - (eAppr n)|  < 3/n!  <= 1/2^(n-3).  

Therefore,  eAppr(n+3)  differs from  e  in less than  1/2^n.

I believe, this fact will help us to find first true  k  digits of  e
for any given  k.  
 
If people would not give other good solution and if you ask me to 
complete this task, then I'll try to do this.

Regards,

-----------------
Serge Mechveliani
mechvel@botik.ru