ireal-0.1: Real numbers and intervals with not so inefficient exact arithmetic.

Safe HaskellNone
LanguageHaskell98

Data.Number.IReal

Contents

Description

This module provides the type IReal, the values of which are real numbers and intervals, with potentially unbounded precision arithmetic and elementary functions.

IReal is an instance of the standard numeric classes, so we can interact in ghci as follows:

>>> exp 0.5 + pi * sqrt ( 2 + sin 1) ? 50
6.94439823755032768935865535478209938180612180886848

The right operand to the operator ? indicates the number of decimals to display in the result. Using ? is the default way to print values; the Show instance is not recommended to use, since the redundant rounding policy implies that we cannot guarantee to generate equal string representations for equal values.

For simple expressions like the above, one can request a thousand decimals with more or less instantaneous result; also ten thousand decimals is easy (less than a second on a typical laptop).

Here is an example with interval arguments:

>>> exp (0.5 +- 0.001) + pi * sqrt ( 2 + sin (1 +- 0.003)) ? 30
6.94[| 1236147625 .. 7554488225 |]

The result is displayed in a non-standard but hopefully easily interpreted notation. We will not get the requested 30 decimals here; interval upper and lower bounds are displayed with at most 10 distinguishing digits. The result of an interval computation is conservative; it includes all possible values of the expression for inputs in the given intervals. As always in interval arithmetic, results may be unduly pessimistic because of the dependency problem.

As a third example, consider

>>> log (2 +- 1e-50) ? 30
0.693147180559945309417232121458

The result is obviously an interval, not a number, but displayed with 30 decimals it looks just like a real number. Conversely, a real number is an infinite object and we can only ever compute an approximation to it. So a finitely printed IReal value can always be thought of as denoting an interval; there is an error margin of one unit in the last displayed digit. These remarks give a first intuition for why it may be fruitful to merge real numbers and intervals into one type.

IReal is also an instance of Eq and Ord; these are, however, non-total for computability reasons; evaluation of e.g. sin pi == 0 at type IReal will not terminate.

At the github site https://github.com/sydow/ireal.git one can find a QuickCheck testsuite (in directory tests), a paper with documentation (in directory doc) and a number of small applications (in directory applications).

Synopsis

The type of real numbers and intervals

data IReal Source

A real number/interval is a function from required precision to an integer interval; for numbers the interval is thin (has radius 1).

Instances

Enum IReal 
Eq IReal

Equality test for overlapping values is non-terminating.

Floating IReal 
Fractional IReal

Division by zero is non-terminating.

Num IReal 
Ord IReal 
Real IReal 
RealFloat IReal 
RealFrac IReal 
Show IReal

IReal is an instance of Show but it should be avoided; see introduction. Use x ? n to print x with n decimals.

Powers IReal 
VarPrec IReal

prec n x is an interval of width 10^(-n) containing x.

Scalable IReal 
Arbitrary IReal 

Printing IReals

(?) :: IReal -> Int -> IO () infix 3 Source

Prints an IReal with given number of decimals. Rounding error is up to one unit in the last position.

(??) :: IReal -> Int -> IO () infix 3 Source

Prints an IReal in scientific notation with given number of digits. Rounding error is up to one unit in the last position.

Total comparison operators

(<!) :: IReal -> IReal -> Precision -> Bool infix 3 Source

Total, approximate inequality test. If x <! y atDecimals d returns True, then x is definitely smaller than y, If it returns False, x may still be smaller than y, but their difference is then at most 10^(-d).

(>!) :: IReal -> IReal -> Precision -> Bool infix 3 Source

x >! y is the same as y <! x.

(=?=) :: IReal -> IReal -> Precision -> Bool infix 3 Source

Total, approximate equality test. If x =?= y atDecimals d returns False, then x and y are definitely not equal. If it returns True, then the absolute value of their difference is less than 10^(-d) (but they may be non-equal).

atDecimals :: (Int -> a) -> Int -> a infix 1 Source

Operator allowing function expecting binary precision to be applied to decimal ditto.

Intervals

Constructing interval values

(+-) :: Rational -> Rational -> IReal infix 6 Source

Constructs an interval from midpoint and radius.

(-+-) :: IReal -> IReal -> IReal infix 6 Source

Constructs an interval from end points (which can be given in any order).

hull :: [IReal] -> IReal Source

Convex hull of a list of intervals.

intersection :: IReal -> IReal -> Maybe IReal Source

Intersection of intervals; empty intersection gives Nothing

Selectors

lower :: IReal -> IReal Source

Returns left end point of argument.

upper :: IReal -> IReal Source

Returns right end point of argument.

mid :: IReal -> IReal Source

Returns midpoint of argument.

rad :: IReal -> IReal Source

Returns radius of argument.

containedIn :: IReal -> IReal -> Precision -> Bool Source

Tests whether first arg is contained in second, using total tests of given precision.

Balanced folds

foldb :: (a -> a -> a) -> a -> [a] -> a Source

Balanced fold, minimizing depth of call tree. Assumes associative operator. Often much more efficient than foldl/foldr when type a is IReal and the list is long.

foldb1 :: (a -> a -> a) -> [a] -> a Source

Balanced fold for associative operator over non-empty list.

bsum :: Num a => [a] -> a Source

Balanced sum, reorganized for (much) better efficiency when type a is IReal and the list is long.

foldb' :: (a -> a -> a) -> a -> [a] -> a Source

isumN' :: Integer -> [IReal] -> IReal Source

1st arg should be length of 2nd arg.

QuickCheck support

Generators

uniformNum :: (Integer, Integer) -> Gen IReal Source

Generates real numbers uniformly distributed over the given interval.

uniformIval :: (Integer, Integer) -> Gen IReal Source

Generates real intervals of varying width, with midpoints uniformly distributed over given interval.

exprGen :: Floating a => Gen a -> Gen a Source

Generates random expressions built from values generated by argument generator, arithmetic operators and applications of Floating functions.

Properties

propIsRealNum :: IReal -> Property Source

Basic test that the argument is a proper real number (is thin and satisfies Cauchy criterion).

propIsRealIval :: IReal -> Property Source

Basic test that argument is a proper interval (the end points are proper numbers, with left end smaller than right end).

Auxiliary functions and type classes

force :: Int -> IReal -> IReal Source

Forces evaluation of second argument to given number of decimals; returns second argument.

dec2bits :: Int -> Int Source

Converts precisions from decimal to binary.

lg2 :: Integer -> Int Source

Base 2 logarithm of argument, rounded downwards.

class Num a => Powers a where Source

Common functions collected to allow for instances which handle dependency problems for intervals, and for automatic differentiation.

Minimal complete definition

Nothing

Methods

sq :: a -> a Source

pow :: a -> Int -> a Source

class Scalable a where Source

Scaling. scale x n computes x * 2^n using bit shifts.

Methods

scale :: a -> Int -> a Source

Instances

Scalable Double 
Scalable Integer

Correctly rounded result for negative n. Rounds upwards when decimal part of unrounded result is .5

Scalable IntegerInterval 
Scalable IReal 
(Integral a, Bits a) => Scalable (Ratio a) 

class VarPrec a where Source

Minimal complete definition

precB

Methods

prec :: Int -> a -> a Source

precB :: Int -> a -> a Source

Instances

VarPrec Double 
VarPrec IReal

prec n x is an interval of width 10^(-n) containing x.

VarPrec a => VarPrec [a]