[Haskell-cafe] Canned routines for the first say thousand digits of pi, e, sqrt 2, etc?

Olaf Klinke olf at aatal-apotheke.de
Fri Dec 18 12:31:33 UTC 2015


As it happens, I am just studying a presentation [1] Martin Escardo gave to students at the University of Birmingham. It contains Haskell code for exact real number computation. Among other things, there is a function that computes a signed digit representation of pi/32. It computes several thousand digits in a few seconds. 
I did not try it yet, but many irrational numbers are fixed points of simple arithmetical expressions. For example, the golden ratio is the fixed point of \x -> 1+1/x. Infinite streams of digits should be a type where such a fixed point is computable. Or you could use a sufficiently precise rational approximation and convert that do decimal in the usual way. 

import Data.Ratio
import Data.List (iterate)

-- one step of Heron's algorithm for sqrt(a)
heron :: (Fractional a) => a -> a -> a
heron a x = (x+a/x)/2

-- infinite stream of approximations to sqrt(a)
approx :: (Fractional a) => a -> [a]
approx a = iterate (heron a) 1

-- Find an interval with rational end-points 
-- for a signed-digit real number
type SDReal = [Int] -- use digits [-1,0,1]
interval :: Int -> SDReal -> (Rational,Rational)
interval precision x = let
  f = foldr (\d g -> (a d).g) id (take precision x))
  a d = \x -> ((fromIntegral d)+x)/2
  in (f(-1),f(1))

Cheers, 
Olaf

[1] www.cs.bham.ac.uk/~mhe/.talks/phdopen2013/realreals.lhs


More information about the Haskell-Cafe mailing list