canon-0.1.0.3: Massive Number Arithmetic

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

Math.NumberTheory.Canon

Description

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

Synopsis

Documentation

data Canon Source #

Canon: GADT for either Bare (Integer) or some variation of a canonical form (see CanonValueType).

Instances

Enum Canon Source # 
Eq Canon Source #

Instances for Canon

Methods

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

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

Fractional Canon Source # 
Integral Canon Source # 
Num Canon Source # 
Ord Canon Source # 

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 # 

Methods

toRational :: Canon -> Rational #

Show Canon Source # 

Methods

showsPrec :: Int -> Canon -> ShowS #

show :: Canon -> String #

showList :: [Canon] -> ShowS #

CanonConv Canon Source #

Instance of CanonConv class

makeCanon :: Integer -> Canon Source #

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

data BareStatus Source #

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

Constructors

Simplified 
NotSimplified 

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

cGCD :: Canon -> Canon -> Canon Source #

GCD and LCM functions for Canon

cLCM :: Canon -> Canon -> Canon Source #

GCD and LCM functions for Canon

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

Mod function

cOdd :: Canon -> Bool Source #

Check if a Canon is an odd Integer. Note: Return False if the Canon is not integral. See CanonValueType for possible cases.

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

Totient functions

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

Totient functions

cLog :: Canon -> Rational Source #

Compute log as a Rational number.

cLogDouble :: Canon -> Double Source #

Compute log as a Double.

cNegative :: Canon -> Bool Source #

Functions to check if a canon is negative/positive

cPositive :: Canon -> Bool Source #

Functions to check if a canon is negative/positive

cIntegral :: Canon -> Bool Source #

Functions to check if a Canon is Integral, (Ir)Rational, Simplified or a prime tower

cRational :: Canon -> Bool Source #

Functions to check if a Canon is Integral, (Ir)Rational, Simplified or a prime tower

cIrrational :: Canon -> Bool Source #

Functions to check if a Canon is Integral, (Ir)Rational, Simplified or a prime tower

cSimplify :: Canon -> Canon Source #

Force the expression to be simplified. This could potentially be very expensive.

cSimplified :: Canon -> Bool Source #

Functions to check if a Canon is Integral, (Ir)Rational, Simplified or a prime tower

cDepth :: Canon -> Integer Source #

Determines the depth/height of maximum prime tower in the Canon.

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

Split a Canon into the numerator and denominator.

cNumerator :: Canon -> Canon Source #

cNumerator and cDenominator are for processing "rational" canon reps.

cDenominator :: Canon -> Canon Source #

cNumerator and cDenominator are for processing "rational" canon reps.

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

cIsPrimeTower :: Canon -> Bool Source #

Functions to check if a Canon is Integral, (Ir)Rational, Simplified or a prime tower

cPrimeTowerLevel :: Canon -> Integer Source #

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

cTetration :: Canon -> Integer -> CycloMap -> (Canon, CycloMap) Source #

Tetration function

cPentation :: Canon -> Integer -> CycloMap -> (Canon, CycloMap) Source #

Pentation Function

cHexation :: Canon -> Integer -> CycloMap -> (Canon, CycloMap) Source #

Hexation Function

cHyperOp :: Integer -> Canon -> Integer -> CycloMap -> (Canon, CycloMap) Source #

Generalized Hyperoperation Function (https:/en.wikipedia.orgwiki/Hyperoperation)

(>^) :: CanonRoot a b c => a -> b -> c infixr 9 Source #

Root operator

(<^) :: CanonExpnt a b c => a -> b -> c infixr 9 Source #

Exponentiation operator

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

The thinking around the hyperoperators is that they should look progressively scarier :)

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

The thinking around the hyperoperators is that they should look progressively scarier :)

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

The thinking around the hyperoperators is that they should look progressively scarier :)

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're allow for further generality in the definition of a Canon.

getBase :: CanonElement -> Canon Source #

Return the base b from a Canon Element (equivalent to b^e)

getExponent :: CanonElement -> Canon Source #

Return the exponent e from a Canon Element (equivalent to b^e)

getBases :: Canon -> [Canon] Source #

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

getExponents :: Canon -> [Canon] Source #

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

getElements :: Canon -> [CanonElement] Source #

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

cNumDivisors :: Canon -> Either String Canon Source #

Divisor functions should be called with integral Canons. Restricted to positive divisors. Returns Either String Canon

cTau :: Canon -> Either String Canon Source #

Divisor functions 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.

data CycloMap Source #

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

fromCycloMap :: CycloMap -> CycloMapInternal Source #

Unwrap the CycloMap newtype.

cmLookup :: CR_ -> CycloMap -> Maybe CycloPair Source #

showCyclo :: CR_ -> CycloMap -> [Char] Source #

This will display the cyclotomic polynomials for a CR.

crCycloInitMap :: CycloMap Source #

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