Copyright | (c) 2015-2018 Frederick Schneider |
---|---|
License | MIT |
Maintainer | Frederick Schneider <frederick.schneider2011@gmail.com> |
Stability | Provisional |
Safe Haskell | None |
Language | Haskell2010 |
This module defines the internal canonical representation of numbers (CR_), a product of pairs (prime and exponent). It's not meant to be called directly.
- type CanonRep_ = [CanonElement_]
- type CR_ = CanonRep_
- crValidIntegral :: CR_ -> Bool
- crValidIntegralViaUserFunc :: CR_ -> (Integer -> Bool) -> Bool
- crValidRational :: CR_ -> Bool
- crValidRationalViaUserFunc :: CR_ -> (Integer -> Bool) -> Bool
- crExp :: CR_ -> Integer -> Bool -> CR_
- crRoot :: CR_ -> Integer -> CR_
- crMaxRoot :: CR_ -> Integer
- crShow :: CR_ -> String
- ceShow :: CanonElement_ -> String
- crFromInteger :: Integer -> CR_
- crFromI :: Integer -> CR_
- crToInteger :: CR_ -> Integer
- crToI :: CR_ -> Integer
- crCmp :: CR_ -> CR_ -> Ordering
- crMult :: CR_ -> CR_ -> CR_
- crNegate :: CR_ -> CR_
- crAbs :: CR_ -> CR_
- crDivStrict :: CR_ -> CR_ -> CR_
- crSignum :: CR_ -> CR_
- crNumer :: CR_ -> CR_
- crDenom :: CR_ -> CR_
- crSplit :: CR_ -> (CR_, CR_)
- crDivRational :: CR_ -> CR_ -> CR_
- crIntegral :: CR_ -> Bool
- crShowRational :: CR_ -> String
- crToRational :: CR_ -> Rational
- crGCD :: CR_ -> CR_ -> CR_
- crLCM :: CR_ -> CR_ -> CR_
- crNegative :: CR_ -> Bool
- crPositive :: CR_ -> Bool
- crLog :: CR_ -> Rational
- crLogDouble :: CR_ -> Double
- crDiv :: CR_ -> CR_ -> Either String CR_
- crRadical :: CR_ -> CR_
- integerApply :: (Integer -> Integer -> Integer) -> CR_ -> CR_ -> Integer
- crSimpleApply :: (Integer -> Integer -> Integer) -> CR_ -> CR_ -> CR_
- crPrime :: CR_ -> Bool
- crHasSquare :: CR_ -> Bool
- crRecip :: CR_ -> CR_
- crMin :: CR_ -> CR_ -> CR_
- crMax :: CR_ -> CR_ -> CR_
- crValid :: CR_ -> (Integer -> Bool) -> Bool -> Bool
- crMod :: CR_ -> CR_ -> CR_
- crModI :: CR_ -> Integer -> Integer
- crDivisors :: CR_ -> [CR_]
- crNumDivisors :: CR_ -> Integer
- crWhichDivisor :: CR_ -> CR_ -> Integer
- crNthDivisor :: Integer -> CR_ -> CR_
- crDivsPlus :: CR_ -> [(CR_, Integer)]
- crTau :: CR_ -> Integer
- crTotient :: CR_ -> Integer
- crPhi :: CR_ -> Integer
- crN1 :: CanonRep_
- cr0 :: CanonRep_
- cr1 :: CanonRep_
- creN1 :: CanonElement_
- pattern PZero :: forall a a1. (Num a, Num a1, Eq a, Eq a1) => [(a1, a)]
- pattern PZeroBad :: forall t a. (Num a, Eq a) => [(a, t)]
- pattern POne :: forall t. [t]
- pattern PNeg :: forall a a1. (Num a, Num a1, Eq a, Eq a1) => [(a1, a)]
- pattern PNotPos :: forall t a. (Num a, Ord a) => [(a, t)]
- pattern PN1 :: forall a a1. (Num a, Num a1, Eq a, Eq a1) => [(a1, a)]
- pattern PIntNeg :: forall a. (Num a, Ord a) => a
- pattern PIntNPos :: forall a. (Num a, Ord a) => a
- pattern PIntPos :: forall a. (Num a, Ord a) => a
- totient :: Integer -> Integer
- pmI :: Integer -> Integer -> Integer -> Integer
Documentation
crValidIntegral :: CR_ -> Bool Source #
Checks if a CR_ represents an integral number.
crValidIntegralViaUserFunc :: CR_ -> (Integer -> Bool) -> Bool Source #
Checks if a CR_ is Integral and valid per user-supplied criterion.
crValidRational :: CR_ -> Bool Source #
Checks if a CR_ is represents a rational number (inclusive of integral numbers).
crValidRationalViaUserFunc :: CR_ -> (Integer -> Bool) -> Bool Source #
Checks if a CR_ is Rational and valid per user-supplied criterion.
crExp :: CR_ -> Integer -> Bool -> CR_ Source #
Exponentiation. Note: this does allow for negative exponentiation if bool flag is True.
crMaxRoot :: CR_ -> Integer Source #
Takes the maximum root of the number. Generally, the abs value would be passed to the function.
crFromInteger :: Integer -> CR_ Source #
Factor the number to convert it to a canonical rep. This is of course can be extremely expensive.
crToInteger :: CR_ -> Integer Source #
Converts a canon rep back to an Integer.
crDivStrict :: CR_ -> CR_ -> CR_ Source #
Strict division: Generates error if exact division is not possible.
crDenom :: CR_ -> CR_ Source #
Compute denominator. (Grab the primes with negative exponents and then flip the sign of the exponents.)
crDivRational :: CR_ -> CR_ -> CR_ Source #
Division of rationals is equivalent to multiplying with negated exponents.
crIntegral :: CR_ -> Bool Source #
Check if a CR_ represents an integer.
crShowRational :: CR_ -> String Source #
Display a Canonical Rep rationally, as a quotient of its numerator and denominator.
crToRational :: CR_ -> Rational Source #
Convert a CR_ to a Rational number.
crGCD :: CR_ -> CR_ -> CR_ Source #
For the GCD (Greatest Common Divisor), take the lesser of two exponents for each prime encountered.
crLCM :: CR_ -> CR_ -> CR_ Source #
For the LCM (Least Common Multiple), take the max of two exponents for each prime encountered.
crNegative :: CR_ -> Bool Source #
Check if a CR_ is negative.
crPositive :: CR_ -> Bool Source #
Check if a CR_ is positive.
crLog :: CR_ -> Rational Source #
This log function is much more expensive but accurate. You have an "infinity" problem potentially with crLogDouble.
crLogDouble :: CR_ -> Double Source #
Returns log of CR_ as a Double.
crRadical :: CR_ -> CR_ Source #
Compute the Radical of a CR_ (http:/en.wikipedia.orgwiki/Radical_of_an_integer). Its the product of the unique primes in its factorization.
integerApply :: (Integer -> Integer -> Integer) -> CR_ -> CR_ -> Integer Source #
The Op(eration) is intended to be plus or minus.
crSimpleApply :: (Integer -> Integer -> Integer) -> CR_ -> CR_ -> CR_ Source #
Calls integerApply and returns a CR_.
crHasSquare :: CR_ -> Bool Source #
Checks if a number has a squared (or higher) factor.
crRecip :: CR_ -> CR_ Source #
Take the reciprocal by raising a CR to the -1 power (equivalent to multiplying exponents by -1).
crValid :: CR_ -> (Integer -> Bool) -> Bool -> Bool Source #
Canon rep validity check: The 2nd param checks the validity of the base, the 3rd of the exponent. The base pred should be some kind of prime or psuedo-prime test unless you knew for certain the bases are prime. There are two choices for the exp pred: positiveOnly (True) or nonZero (False) (which allows for "rationals").
crModI :: CR_ -> Integer -> Integer Source #
Compute the modulus between a CR_ and Integer and return an Integer.
crDivisors :: CR_ -> [CR_] Source #
Efficiently computes all of the divisors based on the canonical representation.
crNumDivisors :: CR_ -> Integer Source #
Divisor functions -- should be called with integral CRs (no negative exponents).
crWhichDivisor :: CR_ -> CR_ -> Integer Source #
Consider this to be an inverse of the crNthDivisor function.
crNthDivisor :: Integer -> CR_ -> CR_ Source #
Computes the nth divisor. This is zero based. Note: This is deterministic but it's not ordered by the value of the divisor.
crDivsPlus :: CR_ -> [(CR_, Integer)] Source #
Like the crDivisors function, except that it returns pairs of the CR_ and resp. numeric value, instead of just the CR_.
crTau :: CR_ -> Integer Source #
Divisor functions -- should be called with integral CRs (no negative exponents).
crTotient :: CR_ -> Integer Source #
Divisor functions -- should be called with integral CRs (no negative exponents).
crPhi :: CR_ -> Integer Source #
Divisor functions -- should be called with integral CRs (no negative exponents).
pattern PZero :: forall a a1. (Num a, Num a1, Eq a, Eq a1) => [(a1, a)] Source #
Pattern to match the CR_ equivalent of zero
pattern PZeroBad :: forall t a. (Num a, Eq a) => [(a, t)] Source #
Pattern to match a badly formed zero, meaning it's an invalid CR_
pattern PNeg :: forall a a1. (Num a, Num a1, Eq a, Eq a1) => [(a1, a)] Source #
Pattern for a negative CR_
pattern PNotPos :: forall t a. (Num a, Ord a) => [(a, t)] Source #
Pattern to match a non-positive CR_
pattern PN1 :: forall a a1. (Num a, Num a1, Eq a, Eq a1) => [(a1, a)] Source #
Pattern to match the CR_ equivalent of -1