fixedprec-0.2.2.2: A fixed-precision real number type

Safe HaskellSafe
LanguageHaskell98

Data.Number.FixedPrec

Contents

Description

A reasonably efficient implementation of arbitrary-but-fixed precision real numbers. This is inspired by, and partly based on, Data.Number.Fixed and Data.Number.CReal, but more efficient.

Synopsis

Type-level integers for precision

class Precision e Source #

A type class for type-level integers, capturing a precision parameter. Precision is measured in decimal digits.

Minimal complete definition

digits

Instances
Precision P2000 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P2000 -> Int

Precision P1000 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P1000 -> Int

Precision P100 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P100 -> Int

Precision P10 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P10 -> Int

Precision P1 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P1 -> Int

Precision P0 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P0 -> Int

Precision e => Precision (PPlus1000 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus1000 e -> Int

Precision e => Precision (PPlus100 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus100 e -> Int

Precision e => Precision (PPlus10 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus10 e -> Int

Precision e => Precision (PPlus3 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus3 e -> Int

Precision e => Precision (PPlus1 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus1 e -> Int

data P0 Source #

Precision of 0 digits.

Instances
Precision P0 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P0 -> Int

data P1 Source #

Precision of 1 digit.

Instances
Precision P1 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P1 -> Int

data P10 Source #

Precision of 10 digits.

Instances
Precision P10 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P10 -> Int

data P100 Source #

Precision of 100 digits.

Instances
Precision P100 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P100 -> Int

data P1000 Source #

Precision of 1000 digits.

Instances
Precision P1000 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P1000 -> Int

data P2000 Source #

Precision of 2000 digits.

Instances
Precision P2000 Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: P2000 -> Int

data PPlus1 e Source #

Add 1 digit to the given precision.

Instances
Precision e => Precision (PPlus1 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus1 e -> Int

data PPlus3 e Source #

Add 3 digits to the given precision.

Instances
Precision e => Precision (PPlus3 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus3 e -> Int

data PPlus10 e Source #

Add 10 digits to the given precision.

Instances
Precision e => Precision (PPlus10 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus10 e -> Int

data PPlus100 e Source #

Add 100 digits to the given precision.

Instances
Precision e => Precision (PPlus100 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus100 e -> Int

data PPlus1000 e Source #

Add 1000 digits to the given precision.

Instances
Precision e => Precision (PPlus1000 e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

digits :: PPlus1000 e -> Int

Fixed-precision numbers

data FixedPrec e Source #

The type of fixed-precision numbers.

Instances
Eq (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

(==) :: FixedPrec e -> FixedPrec e -> Bool #

(/=) :: FixedPrec e -> FixedPrec e -> Bool #

Precision e => Floating (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Precision e => Fractional (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Precision e => Num (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Ord (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Precision e => Real (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Precision e => RealFrac (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

properFraction :: Integral b => FixedPrec e -> (b, FixedPrec e) #

truncate :: Integral b => FixedPrec e -> b #

round :: Integral b => FixedPrec e -> b #

ceiling :: Integral b => FixedPrec e -> b #

floor :: Integral b => FixedPrec e -> b #

Precision e => Show (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Precision e => Random (FixedPrec e) Source # 
Instance details

Defined in Data.Number.FixedPrec

Methods

randomR :: RandomGen g => (FixedPrec e, FixedPrec e) -> g -> (FixedPrec e, g) #

random :: RandomGen g => g -> (FixedPrec e, g) #

randomRs :: RandomGen g => (FixedPrec e, FixedPrec e) -> g -> [FixedPrec e] #

randoms :: RandomGen g => g -> [FixedPrec e] #

randomRIO :: (FixedPrec e, FixedPrec e) -> IO (FixedPrec e) #

randomIO :: IO (FixedPrec e) #

getprec :: Precision e => FixedPrec e -> Int Source #

Get the precision of a fixed-precision number, in decimal digits.

Static and dynamic casts

cast :: (Precision e, Precision f) => FixedPrec e -> FixedPrec f Source #

Cast from any FixedPrec type to another.

upcast :: Precision e => FixedPrec e -> FixedPrec (PPlus3 e) Source #

Cast to a fixed-point type with three additional digits of accuracy.

downcast :: Precision e => FixedPrec (PPlus3 e) -> FixedPrec e Source #

Cast to a fixed-point type with three fewer digits of accuracy.

with_added_digits :: forall a f. Precision f => Int -> (forall e. Precision e => FixedPrec e -> a) -> FixedPrec f -> a Source #

The function with_added_digits d f x evaluates f(x), adding d digits of accuracy to x during the computation.

Other operations

fractional :: Precision e => FixedPrec e -> FixedPrec e Source #

Return the positive fractional part of a fixed-precision number. The result is always in [0,1), regardless of the sign of the input.

solve_quadratic :: Precision e => FixedPrec e -> FixedPrec e -> Maybe (FixedPrec e, FixedPrec e) Source #

Solve the quadratic equation x^2 + bx + c = 0 with maximal possible precision, using a numerically stable method. Return the pair (x1, x2) of solutions with x1 <= x2, or Nothing if no solution exists.

This is far more precise, and probably more efficient, than naively using the quadratic formula.

log_double :: (Floating a, Real a) => a -> Double Source #

A version of the natural logarithm that returns a Double. The logarithm of just about any value can fit into a Double; so if not a lot of precision is required in the mantissa, this function is often faster than log.