HERA-0.2

Data.Number.Real

Synopsis

Documentation

show x will output as much decimalas as a standard IEEE 754 double if possible.

(==) and (/=) should not be used as x == y will diverge if two reals should be equal.

data CReal Source

Real number is represented as a chain of dyadic intervals which are neither necessarily nested nor bounded away from 0.

On n-th stage computations are performed with precision of n bits.

data PBool Source

Partial booleans

Constructors

PTrue

equivalent to True

PFalse

equivalent to False

Indeterminate

neither True nor False.

Instances

limSource

Arguments

:: (Nat -> CReal)

Sequence

-> (Nat -> CReal)

Error bounds

-> CReal 

A basic general limit which takes as arguments a sequence of reals and a sequence of error bounds.

limRecSource

Arguments

:: CReal

initial value

-> (CReal -> Nat -> (CReal, CReal))

a function which produces a pair, (next element, error estimate) from previous one and location

-> CReal 

Similar to lim, but can sometimes be more convenient for some sequences

limRatSource

Arguments

:: (Nat -> Dyadic)

Sequence of dyadics

-> (Nat -> Dyadic)

Sequence of (dyadic) error bounds

-> CReal 

Limit of a sequence of rationals.

infSumSource

Arguments

:: (Nat -> CReal)

Sequence of reals

-> (Nat -> CReal)

Sequence of series remainders

-> CReal 

Computes an infinite sum of a series

infSumRec :: CReal -> (CReal -> Nat -> (CReal, CReal)) -> CRealSource

Similar to infSum but can sometimes be more convenient Second argument is a_0

approx :: CReal -> Nat -> Either (Dyadic, Word) DyadicSource

approx x n tries to compute a dyadic approximation to x so than |x - d| <= 10^(-n) If it succeeds it returns Right d where d is a dyadic rational, otherwise it returns Left (d, n) where d is a dyadic rational and n is the number of accurate decimal places

Approx succeeds if result can be computed with precision less than the square of the number of required bits of precision.

pCompare :: CReal -> CReal -> Nat -> POrderingSource

pCompare x y returns a function Nat -> POrdering which when applied to some n computes approximates with precision n and then compares the resulting intervals

(<.) :: CReal -> CReal -> Nat -> PBoolSource

x <. y is a function Nat -> PBool which, when applied to some n , computes the approximation with precision n and then compares the intervals. If intervals are disjoint then result is either PTrue or PFalse, otherwise result is Indeterminate.

(>.) :: CReal -> CReal -> Nat -> PBoolSource

Similar to (<.)

fromInt :: Int -> CRealSource

fromInt should be preferred over fromIntegral where applicable

fromWord :: Word -> CRealSource

fromWord should be preferred over fromIntegral where applicable

toString :: Nat -> CReal -> StringSource

toString computes the result with specified precision.

toStringDec :: Nat -> CReal -> StringSource

toStringDec tries to compute the result to the number of specified significand digits