| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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
- data CReal (n :: Nat) = CR !(MVar Cache) (Int -> Integer)
- data Cache
- atPrecision :: CReal n -> Int -> Integer
- crealPrecision :: KnownNat n => CReal n -> Int
- plusInteger :: CReal n -> Integer -> CReal n
- mulBounded :: CReal n -> CReal n -> CReal n
- (.*.) :: CReal n -> CReal n -> CReal n
- mulBoundedL :: CReal n -> CReal n -> CReal n
- (.*) :: CReal n -> CReal n -> CReal n
- (*.) :: CReal n -> CReal n -> CReal n
- recipBounded :: CReal n -> CReal n
- shiftL :: CReal n -> Int -> CReal n
- shiftR :: CReal n -> Int -> CReal n
- square :: CReal n -> CReal n
- squareBounded :: CReal n -> CReal n
- expBounded :: CReal n -> CReal n
- expPosNeg :: CReal n -> (CReal n, CReal n)
- logBounded :: CReal n -> CReal n
- atanBounded :: CReal n -> CReal n
- sinBounded :: CReal n -> CReal n
- cosBounded :: CReal n -> CReal n
- crMemoize :: (Int -> Integer) -> CReal n
- powerSeries :: [Rational] -> (Int -> Int) -> CReal n -> CReal n
- alternateSign :: Num a => [a] -> [a]
- (/.) :: Integer -> Integer -> Integer
- (/^) :: Integer -> Int -> Integer
- log2 :: Integer -> Int
- log10 :: Integer -> Int
- isqrt :: Integer -> Integer
- showAtPrecision :: Int -> CReal n -> String
- decimalDigitsAtPrecision :: Int -> Int
- rationalToDecimal :: Int -> Rational -> String
The CReal type
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 Methods toRational :: CReal n -> Rational # | |
| KnownNat n => RealFloat (CReal n) Source # | Several of the functions in this class ( 
 | 
| Defined in Data.CReal.Internal Methods 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  | 
| 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 | |
Memoization
The Cache type represents a way to memoize a CReal. It holds the largest
 precision the number has been evaluated that, as well as the value. Rounding
 it down gives the value for lower numbers.
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` 1010240
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
Additive
plusInteger :: CReal n -> Integer -> CReal n infixl 6 Source #
x `plusInteger` n is equal to x + fromInteger n, but more efficient
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]
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]
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
squareBounded :: CReal n -> CReal n Source #
A more efficient square with the restrictuion that the value must be in
 the closed range [-1..1]
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]
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  will evaluate the power series with
 coefficients atPrecision pq 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 2182.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.
(/^) :: Integer -> Int -> Integer infixl 7 Source #
n /^ p is equivalent to n '/.' (2^p), but faster, and it works for
 negative values of p.
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