Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module exports everything you need to use exact real numbers
Synopsis
- data CReal (n :: Nat)
- atPrecision :: CReal n -> Int -> Integer
- crealPrecision :: KnownNat n => CReal n -> Int
Documentation
data 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, as well as an MVar
to hold the highest
precision cached value.
Instances
KnownNat n => Eq (CReal n) Source # | Values of type
|
Floating (CReal n) Source # | |
Fractional (CReal n) Source # | Taking the reciprocal of zero will not terminate |
Num (CReal n) Source # |
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.
|
KnownNat n => Ord (CReal n) Source # | Like equality values of type |
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 # |
|
Defined in Data.CReal.Internal toRational :: CReal n -> Rational # | |
KnownNat n => RealFloat (CReal n) Source # | Several of the functions in this class (
|
Defined in Data.CReal.Internal floatRadix :: CReal n -> Integer # floatDigits :: CReal n -> Int # floatRange :: CReal n -> (Int, Int) # decodeFloat :: CReal n -> (Integer, Int) # encodeFloat :: Integer -> Int -> CReal n # significand :: CReal n -> CReal n # scaleFloat :: Int -> CReal n -> CReal n # isInfinite :: CReal n -> Bool # isDenormalized :: CReal n -> Bool # isNegativeZero :: CReal n -> Bool # | |
KnownNat n => RealFrac (CReal n) Source # | |
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.
|
KnownNat n => Random (CReal n) Source # | The |
Defined in Data.CReal.Internal | |
Converge [CReal n] Source # | The overlapping instance for It's important to note when the error function reaches zero this function
behaves like Find where log x = π using Newton's method
|
type Element [CReal n] Source # | |
Defined in Data.CReal.Converge |