exact-real-0.8.0.2: Exact real arithmetic

Safe HaskellNone
LanguageHaskell2010

Data.CReal

Description

This module exports everything you need to use exact real numbers

Synopsis

Documentation

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

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 => Read (CReal n) Source

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

KnownNat n => Real (CReal n) Source

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

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

KnownNat n => RealFrac (CReal n) Source 

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"

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