NumberTheory-0.1.0.1: A library for number theoretic computations, written in Haskell.

Safe HaskellSafe
LanguageHaskell98

NumberTheory

Description

A library for doing number-theoretic computations. This includes computations in Z mod m (henceforth also written Zm), Z, Z x Zi (the Gaussian integers), and some computations with continued fractions.

Synopsis

Documentation

pythSide :: Integral a => a -> [(a, a, a)] Source

List all pythagorean triples that include a given length (either as a leg or hypotenuse).

pythLeg :: Integral a => a -> [(a, a, a)] Source

List all pythagorean triples that include a given leg length.

pythHyp :: Integral a => a -> [(a, a, a)] Source

List all pythagorean triples with a given hypotenuse.

primPythHyp :: Integral a => a -> [(a, a, a)] Source

List all primitive pythagorean triples with a given hypotenuse.

primPythLeg :: Integral a => a -> [(a, a, a)] Source

List all primitive pythagorean triples that include a given leg length.

canon :: Integral a => a -> a -> a Source

The canonical representation of x in Z mod m.

evalPoly :: forall a. Integral a => a -> a -> [a] -> a Source

Evaluate a polynomial (in Zm) with given coefficients at a given point using Horner's method.

polyCong :: Integral a => a -> [a] -> [a] Source

Find the zeros to a given polynomial in Zm, where the coefficients are given in order of descending degree.

exponentiate :: Integral a => a -> a -> a -> a Source

Raise a to the power of e in Zm.

rsaGenKeys :: Integral a => a -> a -> [(Key a, Key a)] Source

Given primes p and q, generate all pairs of public/private keys derived from those values.

rsaEval :: Integral a => Key a -> a -> a Source

Use the given key to encode/decode the message or ciphertext.

units :: Integral a => a -> [a] Source

Compute the group of units of Zm.

nilpotents :: Integral a => a -> [a] Source

Compute the nilpotent elements of Zm.

idempotents :: Integral a => a -> [a] Source

Compute the idempotent elements of Zm.

roots :: Integral a => a -> [a] Source

Compute the primitive roots of Zm.

almostRoots :: forall a. Integral a => a -> [a] Source

Compute the "almost roots" of Zm. An almost root is a unit, is not a primitive root, and generates the whole group of units when exponentiated.

order :: Integral a => a -> a -> a Source

Compute the order of x in Zm.

orders :: Integral a => a -> [a] Source

Computes the orders of all units in Zm.

expressAsRoots :: Integral a => a -> a -> [(a, a)] Source

Find powers of all the primitive roots of Zm that are equal to x. Equivalently, express x as powers of roots (almost or primitive) in Zm.

powerCong :: Integral a => a -> a -> a -> [a] Source

Solve the power congruence for x, given e, k, m: x^e = k (mod m)

ilogBM :: Integral a => a -> a -> a -> [a] Source

Compute the integer log base B of k in Zm. Equivalently, given 2 elements of Zm, find what powers of b produce k, if any.

divisors :: Integral a => a -> [a] Source

List all divisors of n (not just proper divisors).

factorize :: Integral a => a -> [(a, a)] Source

List the prime factors of n, and their multiplicities.

nonUnitFactorize :: Integral a => a -> [(a, a)] Source

primes :: Integral a => a -> [a] Source

List the unique prime factors of n.

isPrime :: Integral a => a -> Bool Source

Compute if n is prime.

areCoprime :: Integral a => a -> a -> Bool Source

Compute whether two integers are relatively prime to each other. That is, if their GCD == 1.

legendre :: Integral a => a -> a -> a Source

Compute the Legendre symbol of p and q.

kronecker :: Integral a => a -> a -> a Source

Compute the Kronecker symbol (a|n).

totient :: Integral a => a -> a Source

Compute Euler's phi. This is equal to the number of integers <= n that are relatively prime to n.

tau :: Integral a => a -> a Source

Compute tau(n), the number of divisors of n.

sigma :: Integral a => a -> a -> a Source

Compute sigma(n), the sum of powers of divisors of n.

mobius :: Integral a => a -> a Source

Compute mobius(n): (-1)^littleOmega(n) if n is square-free, 0 otherwise.

littleOmega :: Integral a => a -> a Source

Compute littleOmega(n), the number of unique prime factors.

bigOmega :: Integral a => a -> a Source

Compute bigOmega(n), the number of prime factors of n (including multiplicities).

data GaussInt a Source

A Gaussian integer is a+bi, where a and b are both integers.

Constructors

a :+ a infix 6 

Instances

Eq a => Eq (GaussInt a) Source 
Ord a => Ord (GaussInt a) Source 
(Show a, Ord a, Num a) => Show (GaussInt a) Source 
Monoid a => Monoid (GaussInt a) Source 

real :: GaussInt a -> a Source

The real part of a Gaussian integer.

imag :: GaussInt a -> a Source

The imaginary part of a Gaussian integer.

conjugate :: Num a => GaussInt a -> GaussInt a Source

Conjugate a Gaussian integer.

magnitude :: Num a => GaussInt a -> a Source

The square of the magnitude of a Gaussian integer.

(.+) :: Num a => GaussInt a -> GaussInt a -> GaussInt a Source

Add two Gaussian integers together.

(.-) :: Num a => GaussInt a -> GaussInt a -> GaussInt a Source

Subtract one Gaussian integer from another.

(.*) :: Num a => GaussInt a -> GaussInt a -> GaussInt a Source

Multiply two Gaussian integers.

(./) :: Integral a => GaussInt a -> GaussInt a -> GaussInt a Source

Divide one Gaussian integer by another.

(.%) :: Integral a => GaussInt a -> GaussInt a -> GaussInt a Source

Compute the remainder when dividing one Gaussian integer by another.

gIsPrime :: Integral a => GaussInt a -> Bool Source

Compute whether a given Gaussian integer is prime.

gPrimes :: Integral a => [GaussInt a] Source

An infinte list of the Gaussian primes. This list is in order of ascending magnitude.

gGCD :: Integral a => GaussInt a -> GaussInt a -> GaussInt a Source

Compute the GCD of two Gaussian integers.

gFindPrime :: Integral a => a -> [GaussInt a] Source

Find a Gaussian integer whose magnitude squared is the given prime number.

gExponentiate :: Integral a => GaussInt a -> a -> GaussInt a Source

Raise a Gaussian integer to a given power.

gFactorize :: forall a. Integral a => GaussInt a -> [(GaussInt a, a)] Source

Compute the prime factorization of a Gaussian integer. This is unique up to units (+- 1, +- i).

factorial :: Integral a => a -> a Source

Compute the factorial of a given integer.

fibonacci :: Num a => [a] Source

The Fibonacci sequence.

permute :: Integral a => a -> a -> a Source

Given a set of n elements, compute the number of ways to arrange k elements of it.

choose :: Integral a => a -> a -> a Source

Given a set of n elements, compute the number of ways to choose r elements of it.

enumerate :: [[a]] -> [[a]] Source

Given a list of spots, where each spot is a list of its possible values, enumerate all possible assignments of values to spots.

asSumOfSquares :: Integral a => a -> [(a, a)] Source

Given an integer n, find all ways of expressing n as the sum of two squares.

data ContinuedFraction a Source

A (simple) continued fraction can be represented as a list of coefficients. This list is either finite (in the case of rational numbers), or infinite (in the case of irrational numbers. If the fraction represents a quadratic number (that is, a number that can be the root of some quadratic polynomial), then the infinite list of coefficients consists of a finite sequence of coefficients followed by a (finite) sequence of coefficients that repeats indefinitely.

Constructors

Finite [a] 
Infinite ([a], [a]) 

Instances

continuedFractionFromDouble :: forall a. Integral a => Double -> a -> ContinuedFraction a Source

Convert a Double to a (finite) continued fraction. This is inherently lossy.

continuedFractionFromRational :: Integral a => Ratio a -> ContinuedFraction a Source

Convert a rational number to a continued fraction. This is an exact conversion.

continuedFractionFromQuadratic :: forall a. Integral a => a -> a -> a -> ContinuedFraction a Source

Convert the quadratic number (m0 + sqrt(d)) / q0 to its continued fraction representation.

continuedFractionToRational :: Integral a => ContinuedFraction a -> Ratio a Source

Convert a continued fraction to a rational number. If the fraction is finite, then this is an exact conversion. If the fraction is infinite, this conversion is necessarily lossy, since the fraction does not represent a rational number.

continuedFractionToFractional :: Fractional a => ContinuedFraction Integer -> a Source

Convert a continued fraction to a Fractional type. This is lossy due to precision in the Fractional type, and due to conversion of irrational continued fractions to rational types.