exact-real-0.12.3: Exact real arithmetic

Safe HaskellNone
LanguageHaskell2010

Data.CReal.Internal

Contents

Description

This module exports a bunch of utilities for working inside the CReal datatype. One should be careful to maintain the CReal invariant when using these functions

Synopsis

The CReal type

newtype CReal (n :: Nat) Source #

The type CReal represents a fast binary Cauchy sequence. This is a Cauchy sequence with the invariant that the pth element divided by 2^p will be within 2^-p of the true value. Internally this sequence is represented as a function from Ints to Integers.

Constructors

CR (Int -> Integer) 
Instances
KnownNat n => Eq (CReal n) Source #

Values of type CReal p are compared for equality at precision p. This may cause values which differ by less than 2^-p to compare as equal.

>>> 0 == (0.1 :: CReal 1)
True
Instance details

Defined in Data.CReal.Internal

Methods

(==) :: CReal n -> CReal n -> Bool #

(/=) :: CReal n -> CReal n -> Bool #

Floating (CReal n) Source # 
Instance details

Defined in Data.CReal.Internal

Methods

pi :: CReal n #

exp :: CReal n -> CReal n #

log :: CReal n -> CReal n #

sqrt :: CReal n -> CReal n #

(**) :: CReal n -> CReal n -> CReal n #

logBase :: CReal n -> CReal n -> CReal n #

sin :: CReal n -> CReal n #

cos :: CReal n -> CReal n #

tan :: CReal n -> CReal n #

asin :: CReal n -> CReal n #

acos :: CReal n -> CReal n #

atan :: CReal n -> CReal n #

sinh :: CReal n -> CReal n #

cosh :: CReal n -> CReal n #

tanh :: CReal n -> CReal n #

asinh :: CReal n -> CReal n #

acosh :: CReal n -> CReal n #

atanh :: CReal n -> CReal n #

log1p :: CReal n -> CReal n #

expm1 :: CReal n -> CReal n #

log1pexp :: CReal n -> CReal n #

log1mexp :: CReal n -> CReal n #

Fractional (CReal n) Source #

Taking the reciprocal of zero will not terminate

Instance details

Defined in Data.CReal.Internal

Methods

(/) :: CReal n -> CReal n -> CReal n #

recip :: CReal n -> CReal n #

fromRational :: Rational -> CReal n #

Num (CReal n) Source #

signum (x :: CReal p) returns the sign of x at precision p. It's important to remember that this may not represent the actual sign of x if the distance between x and zero is less than 2^-p.

This is a little bit of a fudge, but it's probably better than failing to terminate when trying to find the sign of zero. The class still respects the abs-signum law though.

>>> signum (0.1 :: CReal 2)
0.0
>>> signum (0.1 :: CReal 3)
1.0
Instance details

Defined in Data.CReal.Internal

Methods

(+) :: CReal n -> CReal n -> CReal n #

(-) :: CReal n -> CReal n -> CReal n #

(*) :: CReal n -> CReal n -> CReal n #

negate :: CReal n -> CReal n #

abs :: CReal n -> CReal n #

signum :: CReal n -> CReal n #

fromInteger :: Integer -> CReal n #

KnownNat n => Ord (CReal n) Source #

Like equality values of type CReal p are compared at precision p.

Instance details

Defined in Data.CReal.Internal

Methods

compare :: CReal n -> CReal n -> Ordering #

(<) :: CReal n -> CReal n -> Bool #

(<=) :: CReal n -> CReal n -> Bool #

(>) :: CReal n -> CReal n -> Bool #

(>=) :: CReal n -> CReal n -> Bool #

max :: CReal n -> CReal n -> CReal n #

min :: CReal n -> CReal n -> CReal n #

KnownNat n => Read (CReal n) Source #

The instance of Read will read an optionally signed number expressed in decimal scientific notation

Instance details

Defined in Data.CReal.Internal

KnownNat n => Real (CReal n) Source #

toRational returns the CReal n evaluated at a precision of 2^-n

Instance details

Defined in Data.CReal.Internal

Methods

toRational :: CReal n -> Rational #

KnownNat n => RealFloat (CReal n) Source #

Several of the functions in this class (floatDigits, floatRange, exponent, significand) only make sense for floats represented by a mantissa and exponent. These are bound to error.

atan2 y x atPrecision p performs the comparison to determine the quadrant at precision p. This can cause atan2 to be slightly slower than atan

Instance details

Defined in Data.CReal.Internal

KnownNat n => RealFrac (CReal n) Source # 
Instance details

Defined in Data.CReal.Internal

Methods

properFraction :: Integral b => CReal n -> (b, CReal n) #

truncate :: Integral b => CReal n -> b #

round :: Integral b => CReal n -> b #

ceiling :: Integral b => CReal n -> b #

floor :: Integral b => CReal n -> b #

KnownNat n => Show (CReal n) Source #

A CReal with precision p is shown as a decimal number d such that d is within 2^-p of the true value.

>>> show (47176870 :: CReal 0)
"47176870"
>>> show (pi :: CReal 230)
"3.1415926535897932384626433832795028841971693993751058209749445923078164"
Instance details

Defined in Data.CReal.Internal

Methods

showsPrec :: Int -> CReal n -> ShowS #

show :: CReal n -> String #

showList :: [CReal n] -> ShowS #

KnownNat n => Random (CReal n) Source #

The Random instance for 'CReal' p will return random number with at least p digits of precision, every digit after that is zero.

Instance details

Defined in Data.CReal.Internal

Methods

randomR :: RandomGen g => (CReal n, CReal n) -> g -> (CReal n, g) #

random :: RandomGen g => g -> (CReal n, g) #

randomRs :: RandomGen g => (CReal n, CReal n) -> g -> [CReal n] #

randoms :: RandomGen g => g -> [CReal n] #

randomRIO :: (CReal n, CReal n) -> IO (CReal n) #

randomIO :: IO (CReal n) #

Converge [CReal n] Source #

The overlapping instance for CReal n has a slightly different behavior. The instance for Eq will cause converge to return a value when the list converges to within 2^-n (due to the Eq instance for CReal n) despite the precision the value is requested at by the surrounding computation. This instance will return a value approximated to the correct precision.

It's important to note when the error function reaches zero this function behaves like converge as it's not possible to determine the precision at which the error function should be evaluated at.

Find where log x = π using Newton's method

>>> let initialGuess = 1
>>> let improve x = x - x * (log x - pi)
>>> let Just y = converge (iterate improve initialGuess)
>>> showAtPrecision 10 y
"23.1406"
>>> showAtPrecision 50 y
"23.1406926327792686"
Instance details

Defined in Data.CReal.Converge

Associated Types

type Element [CReal n] :: Type Source #

Methods

converge :: [CReal n] -> Maybe (Element [CReal n]) Source #

convergeErr :: (Element [CReal n] -> Element [CReal n]) -> [CReal n] -> Maybe (Element [CReal n]) Source #

type Element [CReal n] Source # 
Instance details

Defined in Data.CReal.Converge

type Element [CReal n] = CReal n

Simple utilities

atPrecision :: CReal n -> Int -> Integer Source #

x `atPrecision` p returns the numerator of the pth element in the Cauchy sequence represented by x. The denominator is 2^p.

>>> 10 `atPrecision` 10
10240

crealPrecision :: KnownNat n => CReal n -> Int Source #

crealPrecision x returns the type level parameter representing x's default precision.

>>> crealPrecision (1 :: CReal 10)
10

More efficient variants of common functions

Multiplicative

mulBounded :: CReal n -> CReal n -> CReal n infixl 7 Source #

A more efficient multiply with the restriction that both values must be in the closed range [-1..1]

(.*.) :: CReal n -> CReal n -> CReal n infixl 7 Source #

Alias for mulBoundedL

mulBoundedL :: CReal n -> CReal n -> CReal n infixl 7 Source #

A more efficient multiply with the restriction that the first argument must be in the closed range [-1..1]

(.*) :: CReal n -> CReal n -> CReal n infixl 7 Source #

Alias for mulBoundedL

(*.) :: CReal n -> CReal n -> CReal n infixl 7 Source #

Alias for flip mulBoundedL

recipBounded :: CReal n -> CReal n Source #

A more efficient recip with the restriction that the input must have absolute value greater than or equal to 1

shiftL :: CReal n -> Int -> CReal n infixl 8 Source #

x `shiftL` n is equal to x multiplied by 2^n

n can be negative or zero

This can be faster than doing the multiplication

shiftR :: CReal n -> Int -> CReal n infixl 8 Source #

x `shiftR` n is equal to x divided by 2^n

n can be negative or zero

This can be faster than doing the division

square :: CReal n -> CReal n Source #

Return the square of the input, more efficient than (*)

Exponential

expBounded :: CReal n -> CReal n Source #

A more efficient exp with the restriction that the input must be in the closed range [-1..1]

expPosNeg :: CReal n -> (CReal n, CReal n) Source #

expPosNeg x returns @(exp x, exp (-x))#

logBounded :: CReal n -> CReal n Source #

A more efficient log with the restriction that the input must be in the closed range [2/3..2]

Trigonometric

atanBounded :: CReal n -> CReal n Source #

A more efficient atan with the restriction that the input must be in the closed range [-1..1]

sinBounded :: CReal n -> CReal n Source #

A more efficient sin with the restriction that the input must be in the closed range [-1..1]

cosBounded :: CReal n -> CReal n Source #

A more efficient cos with the restriction that the input must be in the closed range [-1..1]

Utilities for operating inside CReals

crMemoize :: (Int -> Integer) -> CReal n Source #

crMemoize takes a fast binary Cauchy sequence and returns a CReal represented by that sequence which will memoize the values at each precision. This is essential for getting good performance.

powerSeries :: [Rational] -> (Int -> Int) -> CReal n -> CReal n Source #

powerSeries q f x atPrecision p will evaluate the power series with coefficients q up to the coefficient at index f p at value x

f should be a function such that the CReal invariant is maintained. This means that if the power series y = a[0] + a[1] + a[2] + ... is evaluated at precision p then the sum of every a[n] for n > f p must be less than 2^-p.

This is used by all the bounded transcendental functions.

>>> let (!) x = product [2..x]
>>> powerSeries [1 % (n!) | n <- [0..]] (max 5) 1 :: CReal 218
2.718281828459045235360287471352662497757247093699959574966967627724

alternateSign :: Num a => [a] -> [a] Source #

Apply negate to every other element, starting with the second

>>> alternateSign [1..5]
[1,-2,3,-4,5]

Integer operations

(/.) :: Integer -> Integer -> Integer infixl 7 Source #

Division rounding to the nearest integer and rounding half integers to the nearest even integer.

log2 :: Integer -> Int Source #

log2 x returns the base 2 logarithm of x rounded towards zero.

The input must be positive

log10 :: Integer -> Int Source #

log10 x returns the base 10 logarithm of x rounded towards zero.

The input must be positive

isqrt :: Integer -> Integer Source #

isqrt x returns the square root of x rounded towards zero.

The input must not be negative

Utilities for converting CReals to Strings

showAtPrecision :: Int -> CReal n -> String Source #

Return a string representing a decimal number within 2^-p of the value represented by the given CReal p.

decimalDigitsAtPrecision :: Int -> Int Source #

How many decimal digits are required to represent a number to within 2^-p

rationalToDecimal :: Int -> Rational -> String Source #

rationalToDecimal p x returns a string representing x at p decimal places.