canon-0.1.1.4: Arithmetic for Psychedelically Large Numbers

Copyright(c) 2015-2019 Frederick Schneider
LicenseMIT
MaintainerFrederick Schneider <fws.nyc@gmail.com>
StabilityProvisional
Safe HaskellNone
LanguageHaskell2010

Math.NumberTheory.Canon

Description

A Canon is exponentation-based representation for arbitrarily massive numbers, including prime towers and hyper-expressions.

Synopsis

Documentation

data Canon Source #

This is a GADT representing either a Bare (Integer), some variation of a Can(onical) form or a HX (Hyper eXpression) consisting of a level and list of Canons (see CanonValueType)

Instances
Enum Canon Source # 
Instance details

Defined in Math.NumberTheory.Canon

Eq Canon Source #

Instances for Canon

Instance details

Defined in Math.NumberTheory.Canon

Methods

(==) :: Canon -> Canon -> Bool #

(/=) :: Canon -> Canon -> Bool #

Fractional Canon Source # 
Instance details

Defined in Math.NumberTheory.Canon

Integral Canon Source # 
Instance details

Defined in Math.NumberTheory.Canon

Num Canon Source # 
Instance details

Defined in Math.NumberTheory.Canon

Ord Canon Source # 
Instance details

Defined in Math.NumberTheory.Canon

Methods

compare :: Canon -> Canon -> Ordering #

(<) :: Canon -> Canon -> Bool #

(<=) :: Canon -> Canon -> Bool #

(>) :: Canon -> Canon -> Bool #

(>=) :: Canon -> Canon -> Bool #

max :: Canon -> Canon -> Canon #

min :: Canon -> Canon -> Canon #

Real Canon Source # 
Instance details

Defined in Math.NumberTheory.Canon

Methods

toRational :: Canon -> Rational #

Show Canon Source # 
Instance details

Defined in Math.NumberTheory.Canon

Methods

showsPrec :: Int -> Canon -> ShowS #

show :: Canon -> String #

showList :: [Canon] -> ShowS #

CanonConv Canon Source #

Instance of CanonConv class

Instance details

Defined in Math.NumberTheory.Canon

makeCanon :: Integer -> Canon Source #

Create a Canon from an Integer. This may involve expensive factorization.

makeCanon' :: Integer -> (Canon, Bool) Source #

Create a Canon from an Integer. Returns the Canon and flag indicating full factorization or not.

data BareStatus Source #

BareStatus: A "Bare Simp" number means a prime number, +/-1 or 0. The code must set the flag properly. A "Bare NSim" number is an Integer that has not been checked (to see if it can be factored).

Constructors

Simp 
NSim 

data CanonValueType Source #

CanonValueType: 3 possibilities for this GADT (integral, non-integral rational, irrational). Imaginary/complex numbers are not supported

Constructors

IntC 
NirC 
IrrC 

cShowFull :: Canon -> String Source #

Various show functions: cShowFull - fully expand large primes and composites in Canon expression. Unf in name means don't factor unless it's too big too display AsCode in name means you can copy and paste the results and execute them.

cShowFullAsCode :: Canon -> String Source #

Various show functions: cShowFull - fully expand large primes and composites in Canon expression. Unf in name means don't factor unless it's too big too display AsCode in name means you can copy and paste the results and execute them.

cShowAsCode :: Canon -> String Source #

Various show functions: cShowFull - fully expand large primes and composites in Canon expression. Unf in name means don't factor unless it's too big too display AsCode in name means you can copy and paste the results and execute them.

cShowAsCodeUnf :: Canon -> String Source #

Various show functions: cShowFull - fully expand large primes and composites in Canon expression. Unf in name means don't factor unless it's too big too display AsCode in name means you can copy and paste the results and execute them.

cShowUnf :: Canon -> String Source #

Various show functions: cShowFull - fully expand large primes and composites in Canon expression. Unf in name means don't factor unless it's too big too display AsCode in name means you can copy and paste the results and execute them.

cMult :: Canon -> Canon -> CycloMap -> (Canon, CycloMap) Source #

Multiply Function: Generally speaking, this will be much cheaper than addition/subtraction which requires factoring. You are usually just merging lists of prime, exponent pairs and adding exponents where common primes are found. This notion is the crux of the library.

Note: This can be used instead of the * operator if you want to maintain a CycloMap for performance reasons.

cDiv :: Canon -> Canon -> CycloMap -> (Canon, CycloMap) Source #

Div function : Multiply by the reciprocal.

cAdd :: Canon -> Canon -> CycloMap -> (Canon, CycloMap) Source #

Addition and subtraction is generally much more expensive because it requires refactorization. There is logic to look for algebraic forms which can greatly reduce simplify factorization. Note: This can be used instead of the +/- operators if you want to maintain a CycloMap for performance reasons.

cSubtract :: Canon -> Canon -> CycloMap -> (Canon, CycloMap) Source #

Addition and subtraction is generally much more expensive because it requires refactorization. There is logic to look for algebraic forms which can greatly reduce simplify factorization. Note: This can be used instead of the +/- operators if you want to maintain a CycloMap for performance reasons.

cExp :: Canon -> Canon -> Bool -> CycloMap -> (Canon, CycloMap) Source #

Exponentiation: This does allow for negative exponentiation if the Bool flag is True. Note: This can be used instead of the exponentiation operator if you want to maintain a CycloMap for performance reasons.

cReciprocal :: Canon -> Canon Source #

Compute reciprocal (by negating exponents or equivalent).

(>^) :: Canon -> Canon -> Canon infixr 9 Source #

Root operator

(<^) :: Canon -> Canon -> Canon infixr 9 Source #

Special exponentiation operator for Canon (One MUST use this instead of the standard exp. operator: ^)

cMod :: Canon -> Canon -> Canon Source #

Modulus function

cOdd :: Canon -> Bool Source #

Check if a Canon is integral and odd/even, respectively. Note: Return False for both if the Canon is not integral. See CanonValueType for possible cases.

cEven :: Canon -> Bool Source #

Check if a Canon is integral and odd/even, respectively. Note: Return False for both if the Canon is not integral. See CanonValueType for possible cases.

cPhi :: Canon -> CycloMap -> (Canon, CycloMap) Source #

Totient function(s)

cNegative :: Canon -> Bool Source #

Function to check if a Canon is negative cNegative c | trace ("cNegative: (l=" ++ show c ++ "))") False = undefined

cPositive :: Canon -> Bool Source #

Function to check if a Canon is positive

cIntegral :: Canon -> Bool Source #

Check if Canon is Integral

cRational :: Canon -> Bool Source #

Check if Canon is Rational

cIrrational :: Canon -> Bool Source #

Check if Canon is Irrational

cPrime :: Canon -> Bool Source #

Check if Canon is prime

cSimplified :: Canon -> Bool Source #

Check if Canon is simplified, meaning completely factored

cSplit :: Canon -> (Canon, Canon) Source #

Split a Canon into the numerator and denominator.

cNumerator :: Canon -> Canon Source #

Return the numerator

cDenominator :: Canon -> Canon Source #

Return the denominator

cCanonical :: Canon -> Bool Source #

Checks if the Canon is Canonical, a more complex expression.

cBare :: Canon -> Bool Source #

Checks if the Canon just a Bare Integer.

cBareStatus :: Canon -> BareStatus Source #

Returns the status for Bare numbers.

cValueType :: Canon -> CanonValueType Source #

Return the CanonValueType (Integral, etc).

cDelve :: Canon -> [Int] -> Canon Source #

Take a Canon and a list of indexes and delve into the Canon. This operates on the internal hyper lists.

cIsPrimeTower :: Canon -> Bool Source #

Check if Canon is a prime tower

cPrimeTowerLevel :: Canon -> Canon Source #

This is used for tetration, etc. It defaults to zero for non-integral reps.

cSuperLog :: Canon -> (SuperPairC, Int) Source #

This is the super log function. Similar to the iterated log function. A level and mantissa is returned along with the number's sign.

cSuperLogCmp :: SuperPairC -> SuperPairC -> Ordering Source #

Compare the level and the "mantissa"

cTetration :: Canon -> Canon -> Canon Source #

Tetration Function - Level 4

cPentation :: Canon -> Canon -> Canon Source #

Pentation Function - Level 5

cHexation :: Canon -> Canon -> Canon Source #

Hexation Function - Level 6

cHeptation :: Canon -> Canon -> Canon Source #

Heptation Function - Level 7

cOctation :: Canon -> Canon -> Canon Source #

Octation Function -- Level 8

cNonation :: Canon -> Canon -> Canon Source #

Nonation Function -- Level 9

cTetrationL :: Canon -> [Canon] -> CycloMap -> (Canon, CycloMap) Source #

Tetration List Function

cPentationL :: Canon -> [Canon] -> CycloMap -> (Canon, CycloMap) Source #

Pentation List Function

cHexationL :: Canon -> [Canon] -> CycloMap -> (Canon, CycloMap) Source #

Hexation List Function

cHeptationL :: Canon -> [Canon] -> CycloMap -> (Canon, CycloMap) Source #

Heptation List Function

cOctationL :: Canon -> [Canon] -> CycloMap -> (Canon, CycloMap) Source #

Octation List Function

cNonationL :: Canon -> [Canon] -> CycloMap -> (Canon, CycloMap) Source #

Nonation List Function

(<^>) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(<<^>>) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(<<<^>>>) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(<<<<^>>>>) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(<<<<<^>>>>>) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(|<^>|) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(<^^>) :: Canon -> [Canon] -> Canon infixr 9 Source #

Tetration list operator

(<<^^>>) :: Canon -> [Canon] -> Canon infixr 9 Source #

Pentation list operator

(<<<^^>>>) :: Canon -> [Canon] -> Canon infixr 9 Source #

Hexation list operator

(<<<<^^>>>>) :: Canon -> [Canon] -> Canon infixr 9 Source #

Heptation list operator

(<<<<<^^>>>>>) :: Canon -> [Canon] -> Canon infixr 9 Source #

Octation list operator

(|<^^>|) :: Canon -> [Canon] -> Canon infixr 9 Source #

Nonation list operator

(~^~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~<^>~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~<<^>>~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~<<<^>>>~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~<<<<^>>>>~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~|^|~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~|<^>|~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~|<<^>>|~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~|<<<^>>>|~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~|<<<<^>>>>|~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~^~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~<^>~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~<<^>>~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~<<<^>>>~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~<<<<^>>>>~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~|^|~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~|<^>|~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~|<<^>>|~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~|<<<^>>>|~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~|<<<<^>>>>|~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~^~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~<^>~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~<<^>>~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~<<<^>>>~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~<<<<^>>>>~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~|^|~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~|<^>|~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~|<<^>>|~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~|<<<^>>>|~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~|<<<<^>>>>|~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~^~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~<^>~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~<<^>>~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~<<<^>>>~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~<<<<^>>>>~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~|^|~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~|<^>|~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~|<<^>>|~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~|<<<^>>>|~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~|<<<<^>>>>|~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

(~~~~~^~~~~~) :: Canon -> Canon -> Canon infixr 9 Source #

Defined specialty hyper operators range from level 4 / tetration (<^>) to level 50 (~~~~~^~~~~~). See source or .odp file for the operator naming convention.

cAddOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cMultOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cExpOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cTetrOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cPentOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cHexOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cHeptOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cOctOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cNonOpLevel :: Canon Source #

Variable reps ranging from 1 to 9 in the hyperoperation hierarchy

cGetHyperList :: Canon -> [Canon] Source #

Return the list of canons from a hyper expression

cGetHyperOp :: Canon -> Canon Source #

Return the level of hyperoperation from a hyper expression.

maxHyperOpDispLevel :: Integer Source #

Internal value that corresponds with ~~~~~^~~~~~ (level 50 hyperoperation)

maxHyperOpDelveLevel :: Canon Source #

Max hyper operaton level when converting to canonical form (for the sake of combining and reducing terms)

cFactorSum :: Canon -> Bool -> Canon Source #

cFactor : Factor simple terms from a sum. If the flag is true, only factor by the gcd if the gcd is a hyper expression

cConvertToSum :: Canon -> (Canon, Bool) Source #

Convert a hyperexpression to a sum if possible. Useful in comparison. Will expand polynomials to a limited degree.

cMaxExpoToExpand :: Canon Source #

Maximum exponent (of a polynomial) to distribute into a sum of terms.

cFactorHorizon :: Canon -> Canon Source #

This is good for polynomial-like expressions like: (1 + 3<^>4 + 3<^>5) <^ 3 - 1, where there's a mixture of "canonical" and hE exponents.

cApplyHy :: Canon -> [Canon] -> Bool -> Canon Source #

wrapper to create apply a hyperoperation to a list

cHyperOp :: Canon -> [Canon] -> CycloMap -> (Canon, CycloMap) Source #

Generalized Hyperoperation Function

cHyperExpr :: Canon -> Bool Source #

Check if Canon is a hyperexpression

cHyperExprAny :: Canon -> Bool Source #

Check if Canon has a hyperexpression anywhere in its definition

cMaxHyperOp :: Canon -> Canon Source #

Find the maximum hyperoperation embedded in a Canon.

cMinHyperOp :: Canon -> Canon Source #

Find the minimum hyperoperation embedded in a Canon. (If it's not a hyper expression, return zero.)

cMaxHyperOpForQC :: Canon -> Canon Source #

Used when checking if one can quasi-canonize a hyper expression (should be compared against the cutoff)

cHyperSum :: Canon -> Bool Source #

Check if Canon is a positive sum (or negative one times a positive sum). Internally, all level 1 expressions are positive.

cHyperProd :: Canon -> Bool Source #

Check if Canon is a product (and specificlly not a negative sum)

cHyperExpo :: Canon -> Bool Source #

Check if Canon is an exponential expression

cHyperSumAny :: Canon -> Bool Source #

Check if Canon has a hypersum embedded in the expression

cHyperize :: Canon -> Canon Source #

cHyperize will take a Canon in quasi-canonized form and try to clean it up in a tidier expression

>>> cShowUnf $ cHyperize $  7 <^ ( 1 + 2 * (49 <^> 7))
7 * 49 <^> 8

cQuasiCanonize :: Canon -> Canon Source #

This is akin to canonical form except you may have sums in the bases. It converts expression up to a hyperoperational cutoff.

cQuasiCanonized :: Canon -> Bool Source #

This checks if the (hyper)expression is in quasi-canonical form.

cCleanup :: Canon -> Canon Source #

Try to make expression more elegant by creating exponential tails and then hyperizing them

cGetAddends :: Canon -> [Canon] Source #

If the Canon is a product, return the factors. Otherwise, return the Canon itself.

cGetFactors :: Canon -> [Canon] Source #

If the Canon is a sum, return the addends. Otherwise, return the Canon itself.

cCleanupAsNumDenPair :: Canon -> (Canon, Canon) Source #

Split the hyperoperation into a cleaned-up numerator and denominator pair (if denom is 1). This still represents an integral value. e.g. 3 ^ 7 / 3 ^ 4

type CanonElement = (Canon, Canon) Source #

This element is a base, exponent pair. The base is an integer and is generally prime or 0, -1. The exponent is also a Canon (allowing for arbitrary nesting) A Canon conceptually consists of a list of these elements. The first member of the pair will be a Canon raised to the first power. By doing this, we allow for further generality in the definition of a Canon.

cGetBase :: CanonElement -> Canon Source #

Return the base b from a CanonElement (equivalent to b^e).

cGetExponent :: CanonElement -> Canon Source #

Return the exponent e from a CanonElement (equivalent to b^e).

type SuperPairC = (Canon, Double) Source #

Used when computing "Super Log"

cGetBases :: Canon -> [Canon] Source #

Return the list of bases from a Canon (conceptually of the form [b^e]).

cGetBasesDeep :: Canon -> [Canon] Source #

This is similar to cGetBases except that it will do trial factoring of any hyper sums. i So, for obvious reasons, this is not a complete factorization.

cGetExponents :: Canon -> [Canon] Source #

Return the list of exponents from a Canon (conceptually of the form [b^e]).

cGetElements :: Canon -> [CanonElement] Source #

Return the list of CanonElements from a Canon (conceptually of the form [b^e]).

cNumDivisors :: Canon -> Canon Source #

Note: Divisor count function(s) should be called with integral Canons. Restricted to positive divisors. Returns Either String Canon

cTau :: Canon -> Canon Source #

Note: Divisor count function(s) should be called with integral Canons. Restricted to positive divisors. Returns Either String Canon

cDivisors :: Canon -> Either String [Canon] Source #

Efficiently compute all of the divisors based on the canonical representation. Returns either an error message or a list of Canons.

cNthDivisor :: Canon -> Canon -> Either String Canon Source #

Compute the nth divisor of a Canon. It operates on the absolute value of the Canon and is zero based. Note: This is deterministic but it's not ordered by the value of the divisor.

cWhichDivisor :: Canon -> Canon -> Either String Canon Source #

Consider this to be the inverse of the cNthDivisor function. This function ignores signs but both parameters must be integral.

cRelativelyPrime :: Canon -> Canon -> Maybe Bool Source #

This will determine if two arbitary expressions are relatively prime or not (if possible). Goes deep.

cGetFirstNDivisors :: Int -> Canon -> Either String [Canon] Source #

Return the first N divisors of a hyper expression (if possible)

cN1 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c0 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c1 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c2 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c3 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c4 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c5 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c6 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c7 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c8 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

c9 :: Canon Source #

Define some small canons for convenience from (-1 to 9)

data CycloMap Source #

CycloMap is a newtype hiding the details of a map of CR_ to pairs of integers and corresponding cyclotomic polynomials.

Instances
Eq CycloMap Source # 
Instance details

Defined in Math.NumberTheory.Canon.AurifCyclo

Show CycloMap Source # 
Instance details

Defined in Math.NumberTheory.Canon.AurifCyclo

getIntegerBasedCycloMap :: CycloMap -> Map Integer CycloPair Source #

Unwrap the CycloMap and convert the internal canon rep keys to Integers, returning a "raw" map

crCycloInitMap :: CycloMap Source #

This is an initial map with the cyclotomic polynomials for 1.