constructible-0.1.0.1: Exact computation with constructible real numbers

PortabilityNon-portable (GHC extensions)
Stabilityexperimental
MaintainerAnders Kaseorg <andersk@mit.edu>
Safe HaskellNone

Data.Real.Constructible

Description

The constructible reals, Construct, are the subset of the real numbers that can be represented exactly using field operations (addition, subtraction, multiplication, division) and positive square roots. They support exact computations, equality comparisons, and ordering.

>>> [((1 + sqrt 5)/2)^n - ((1 - sqrt 5)/2)^n :: Construct | n <- [1..10]]
[sqrt 5,sqrt 5,2*sqrt 5,3*sqrt 5,5*sqrt 5,8*sqrt 5,13*sqrt 5,21*sqrt 5,34*sqrt 5,55*sqrt 5]
>>> let f (a, b, t, p) = ((a + b)/2, sqrt (a*b), t - p*((a - b)/2)^2, 2*p)
>>> let (a, b, t, p) = f . f . f . f $ (1, 1/sqrt 2, 1/4, 1 :: Construct)
>>> floor $ ((a + b)^2/(4*t))*10**40
31415926535897932384626433832795028841971
>>> let qf (p, q) = ((p + sqrt (p^2 - 4*q))/2, (p - sqrt (p^2 - 4*q))/2 :: Construct)
>>> let [(v, w), (x, _), (y, _), (z, _)] = map qf [(-1, -4), (v, -1), (w, -1), (x, y)]
>>> z/2
-1/16 + 1/16*sqrt 17 + 1/8*sqrt (17/2 - 1/2*sqrt 17) + 1/4*sqrt (17/4 + 3/4*sqrt 17 - (3/4 + 1/4*sqrt 17)*sqrt (17/2 - 1/2*sqrt 17))

Constructible complex numbers may be built from constructible reals using Complex from the complex-generic library.

>>> (z/2 :+ sqrt (1 - (z/2)^2))^17
1 :+ 0

Synopsis

Documentation

data Construct Source

The type of constructible real numbers.

Instances

Enum Construct 
Eq Construct 
Floating Construct

This partial Floating instance only supports sqrt and ** where the exponent is a dyadic rational. Passing a negative number to sqrt will throw the ConstructSqrtNegative exception. All other operations will throw the Unconstructible exception.

Fractional Construct 
Num Construct 
Ord Construct 
Read Construct 
Real Construct

This Real instance only supports toRational on numbers that are in fact rational. toRational on an irrational number will throw the ConstructIrrational exception.

RealFrac Construct 
Show Construct 
Floating (Complex Construct) 
Fractional (Complex Construct) 
Num (Complex Construct) 
ComplexRect (Complex Construct) Construct 
ComplexPolar (Complex Construct) Construct 

deconstruct :: Construct -> Either Rational (Construct, Construct, Construct)Source

Deconstruct a rational constructible number as a Rational, or an irrational constructible number as a triple (a, b, r) of simpler constructible numbers representing a + b*sqrt r (with b /= 0 and r > 0). Recursively calling deconstruct on all triples will yield a finite tree that terminates in Rational leaves.

Note that two constructible numbers that compare as equal may deconstruct in different ways.

fromConstruct :: Floating a => Construct -> aSource

Evaluate a floating-point approximation for a constructible number.

To improve numerical stability, addition of numbers with different signs is avoided using quadratic conjugation.

>>> fromConstruct $ sum (map sqrt [7, 14, 39, 70, 72, 76, 85]) - sum (map sqrt [13, 16, 46, 55, 67, 73, 79])
1.8837969820815017e-19

data ConstructException Source

The type of exceptions thrown by impossible Construct operations.

Constructors

ConstructIrrational

toRational was given an irrational constructible number.

ConstructSqrtNegative

sqrt was given a negative constructible number.

Unconstructible String

** was given an exponent that is not a dyadic rational, or a transcendental function was called.