exact-real-0.4.0.0: Exact real arithmetic

Safe HaskellNone
LanguageHaskell2010

Data.CReal.Internal

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

Documentation

newtype CReal n Source

The type CReal represents a fast binary Cauchy sequence. This is a Cauchy sequence with the invariant that the pth element 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

Methods

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

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

Floating (CReal n) Source 

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

Fractional (CReal n) Source

Taking the reciprocal of zero will not terminate

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

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.

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 => 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"

Methods

showsPrec :: Int -> CReal n -> ShowS

show :: CReal n -> String

showList :: [CReal n] -> ShowS

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

expBounded :: CReal n -> CReal n Source

The input to expBounded must be in the range (-1..1)

logBounded :: CReal n -> CReal n Source

The input must be in [1..2]

atanBounded :: CReal n -> CReal n Source

The input to atanBounded must be in [-1..1]

sinBounded :: CReal n -> CReal n Source

The input to sinBounded must be in (-1..1)

cosBounded :: CReal n -> CReal n Source

The input to cosBounded must be in (-1..1)

shiftL :: CReal n -> Int -> CReal n 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 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

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

powerSeries q f x atPrecision p will evaluate the power series with coefficients q at precision f p at x

f should be a function such that the CReal invariant is maintained

See any of the trig functions for an example

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 -> 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.

log10 :: Integer -> Int Source

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

isqrt :: Integer -> Integer Source

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

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.