Safe Haskell | Safe |
---|---|
Language | Haskell98 |
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.
- pythSide :: Integral a => a -> [(a, a, a)]
- pythLeg :: Integral a => a -> [(a, a, a)]
- pythHyp :: Integral a => a -> [(a, a, a)]
- primPythHyp :: Integral a => a -> [(a, a, a)]
- primPythLeg :: Integral a => a -> [(a, a, a)]
- canon :: Integral a => a -> a -> a
- evalPoly :: forall a. Integral a => a -> a -> [a] -> a
- polyCong :: Integral a => a -> [a] -> [a]
- exponentiate :: Integral a => a -> a -> a -> a
- rsaGenKeys :: Integral a => a -> a -> [(Key a, Key a)]
- rsaEval :: Integral a => Key a -> a -> a
- units :: Integral a => a -> [a]
- nilpotents :: Integral a => a -> [a]
- idempotents :: Integral a => a -> [a]
- roots :: Integral a => a -> [a]
- almostRoots :: forall a. Integral a => a -> [a]
- order :: Integral a => a -> a -> a
- orders :: Integral a => a -> [a]
- expressAsRoots :: Integral a => a -> a -> [(a, a)]
- powerCong :: Integral a => a -> a -> a -> [a]
- ilogBM :: Integral a => a -> a -> a -> [a]
- divisors :: Integral a => a -> [a]
- factorize :: Integral a => a -> [(a, a)]
- nonUnitFactorize :: Integral a => a -> [(a, a)]
- primes :: Integral a => a -> [a]
- isPrime :: Integral a => a -> Bool
- areCoprime :: Integral a => a -> a -> Bool
- legendre :: Integral a => a -> a -> a
- kronecker :: Integral a => a -> a -> a
- totient :: Integral a => a -> a
- tau :: Integral a => a -> a
- sigma :: Integral a => a -> a -> a
- mobius :: Integral a => a -> a
- littleOmega :: Integral a => a -> a
- bigOmega :: Integral a => a -> a
- data GaussInt a = a :+ a
- real :: GaussInt a -> a
- imag :: GaussInt a -> a
- conjugate :: Num a => GaussInt a -> GaussInt a
- magnitude :: Num a => GaussInt a -> a
- (.+) :: Num a => GaussInt a -> GaussInt a -> GaussInt a
- (.-) :: Num a => GaussInt a -> GaussInt a -> GaussInt a
- (.*) :: Num a => GaussInt a -> GaussInt a -> GaussInt a
- (./) :: Integral a => GaussInt a -> GaussInt a -> GaussInt a
- (.%) :: Integral a => GaussInt a -> GaussInt a -> GaussInt a
- gIsPrime :: Integral a => GaussInt a -> Bool
- gPrimes :: Integral a => [GaussInt a]
- gGCD :: Integral a => GaussInt a -> GaussInt a -> GaussInt a
- gFindPrime :: Integral a => a -> [GaussInt a]
- gExponentiate :: Integral a => GaussInt a -> a -> GaussInt a
- gFactorize :: forall a. Integral a => GaussInt a -> [(GaussInt a, a)]
- factorial :: Integral a => a -> a
- fibonacci :: Num a => [a]
- permute :: Integral a => a -> a -> a
- choose :: Integral a => a -> a -> a
- enumerate :: [[a]] -> [[a]]
- asSumOfSquares :: Integral a => a -> [(a, a)]
- data ContinuedFraction a
- continuedFractionFromDouble :: forall a. Integral a => Double -> a -> ContinuedFraction a
- continuedFractionFromRational :: Integral a => Ratio a -> ContinuedFraction a
- continuedFractionFromQuadratic :: forall a. Integral a => a -> a -> a -> ContinuedFraction a
- continuedFractionToRational :: Integral a => ContinuedFraction a -> Ratio a
- continuedFractionToFractional :: Fractional a => ContinuedFraction Integer -> a
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.
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.
nilpotents :: Integral a => a -> [a] Source
Compute the nilpotent elements of Zm.
idempotents :: Integral a => a -> [a] Source
Compute the idempotent elements 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.
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.
factorize :: Integral a => a -> [(a, a)] Source
List the prime factors of n, and their multiplicities.
nonUnitFactorize :: Integral a => a -> [(a, a)] Source
areCoprime :: Integral a => a -> a -> Bool Source
Compute whether two integers are relatively prime to each other. That is, if their GCD == 1.
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.
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).
A Gaussian integer is a+bi, where a and b are both integers.
a :+ a infix 6 |
(.-) :: Num a => GaussInt a -> GaussInt a -> GaussInt a Source
Subtract one Gaussian integer from another.
(./) :: 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).
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.
Show a => Show (ContinuedFraction a) Source |
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.