canon-0.1.0.0: Massive Number Arithmetic

Copyright(c) 2015-2018 Frederick Schneider
LicenseMIT
MaintainerFrederick Schneider <frederick.schneider2011@gmail.com>
StabilityProvisional
Safe HaskellNone
LanguageHaskell2010

Math.NumberTheory.Canon.Internals

Description

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.

Synopsis

Documentation

type CanonRep_ = [CanonElement_] Source #

Canonical representation: list of canon elements

type CR_ = CanonRep_ Source #

Shorthand for canonical representation

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.

crRoot :: CR_ -> Integer -> CR_ Source #

Attempt to compute a particular root of a CR_.

crMaxRoot :: CR_ -> Integer Source #

Takes the maximum root of the number. Generally, the abs value would be passed to the function.

crShow :: CR_ -> String Source #

Display a canonical representation.

ceShow :: CanonElement_ -> String Source #

Display a Canon Element (as either p^e or p).

crFromInteger :: Integer -> CR_ Source #

Factor the number to convert it to a canonical rep. This is of course can be extremely expensive.

crFromI :: Integer -> CR_ Source #

Shorthand for crFromInteger function

crToInteger :: CR_ -> Integer Source #

Converts a canon rep back to an Integer.

crToI :: CR_ -> Integer Source #

Alias to crToInteger.

crCmp :: CR_ -> CR_ -> Ordering Source #

CR_ Compare Function

crMult :: CR_ -> CR_ -> CR_ Source #

Multiply two crs by summing the exponents for each prime.

crNegate :: CR_ -> CR_ Source #

Negate a CR_.

crAbs :: CR_ -> CR_ Source #

Take the Absolute Value of a CR_.

crDivStrict :: CR_ -> CR_ -> CR_ Source #

Strict division: Generates error if exact division is not possible.

crSignum :: CR_ -> CR_ Source #

Compute the signum and return as CR_.

crNumer :: CR_ -> CR_ Source #

Compute numerator (by filtering on positive exponents).

crDenom :: CR_ -> CR_ Source #

Compute denominator. (Grab the primes with negative exponents and then flip the sign of the exponents.)

crSplit :: CR_ -> (CR_, CR_) Source #

Split a CR_ into its Numerator and Denominator.

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.

crDiv :: CR_ -> CR_ -> Either String CR_ Source #

Attempt to take the quotient.

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

crPrime :: CR_ -> Bool Source #

Check if a number is a prime.

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

crMin :: CR_ -> CR_ -> CR_ Source #

Min function

crMax :: CR_ -> CR_ -> CR_ Source #

Max functon

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").

crMod :: CR_ -> CR_ -> CR_ Source #

Compute modulus with all CR_ parameters. This wraps crModI.

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

crN1 :: CanonRep_ Source #

Canon rep for -1

cr0 :: CanonRep_ Source #

Canon rep for 0

cr1 :: CanonRep_ Source #

Canon rep for 1

creN1 :: CanonElement_ Source #

Canonical values for a few special numbers

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 POne :: forall t. [t] Source #

Pattern to match the CR_ equivalent of 1

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

pattern PIntNeg :: forall a. (Num a, Ord a) => a Source #

Pattern to match a negative number

pattern PIntNPos :: forall a. (Num a, Ord a) => a Source #

Pattern to match a non-positive number

pattern PIntPos :: forall a. (Num a, Ord a) => a Source #

Pattern to match a positive number

totient :: Integer -> Integer Source #

Compute totient: Logic from deprecated arithmoi function used here.

pmI :: Integer -> Integer -> Integer -> Integer Source #

powerModInteger adapted here from deprecated arithmoi function.