numeric-prelude-0.0.5: An experimental alternative hierarchy of numeric type classesSource codeContentsIndex
MathObj.Polynomial
Description

Polynomials and rational functions in a single indeterminate. Polynomials are represented by a list of coefficients. All non-zero coefficients are listed, but there may be extra '0's at the end.

Usage: Say you have the ring of Integer numbers and you want to add a transcendental element x, that is an element, which does not allow for simplifications. More precisely, for all positive integer exponents n the power x^n cannot be rewritten as a sum of powers with smaller exponents. The element x must be represented by the polynomial [0,1].

In principle, you can have more than one transcendental element by using polynomials whose coefficients are polynomials as well. However, most algorithms on multi-variate polynomials prefer a different (sparse) representation, where the ordering of elements is not so fixed.

If you want division, you need Number.Ratios of polynomials with coefficients from a Algebra.Field.

You can also compute with an algebraic element, that is an element which satisfies an algebraic equation like x^3-x-1==0. Actually, powers of x with exponents above 3 can be simplified, since it holds x^3==x+1. You can perform these computations with Number.ResidueClass of polynomials, where the divisor is the polynomial equation that determines x. If the polynomial is irreducible (in our case x^3-x-1 cannot be written as a non-trivial product) then the residue classes also allow unrestricted division (except by zero, of course). That is, using residue classes of polynomials you can work with roots of polynomial equations without representing them by radicals (powers with fractional exponents). It is well-known, that roots of polynomials of degree above 4 may not be representable by radicals.

Synopsis
data T a
fromCoeffs :: [a] -> T a
coeffs :: T a -> [a]
showsExpressionPrec :: (Show a, C a, C a) => Int -> String -> T a -> String -> String
const :: a -> T a
evaluate :: C a => T a -> a -> a
evaluateCoeffVector :: C a v => T v -> a -> v
evaluateArgVector :: (C a v, C v) => T a -> v -> v
compose :: C a => T a -> T a -> T a
equal :: (Eq a, C a) => [a] -> [a] -> Bool
add :: C a => [a] -> [a] -> [a]
sub :: C a => [a] -> [a] -> [a]
negate :: C a => [a] -> [a]
horner :: C a => a -> [a] -> a
hornerCoeffVector :: C a v => a -> [v] -> v
hornerArgVector :: (C a v, C v) => v -> [a] -> v
shift :: C a => [a] -> [a]
unShift :: [a] -> [a]
mul :: C a => [a] -> [a] -> [a]
scale :: C a => a -> [a] -> [a]
divMod :: (C a, C a) => [a] -> [a] -> ([a], [a])
tensorProduct :: C a => [a] -> [a] -> [[a]]
tensorProductAlt :: C a => [a] -> [a] -> [[a]]
mulShear :: C a => [a] -> [a] -> [a]
mulShearTranspose :: C a => [a] -> [a] -> [a]
progression :: C a => [a]
differentiate :: C a => [a] -> [a]
integrate :: C a => a -> [a] -> [a]
integrateInt :: (C a, C a) => a -> [a] -> [a]
fromRoots :: C a => [a] -> T a
alternate :: C a => [a] -> [a]
Documentation
data T a Source
show/hide Instances
Functor T
C T
C a b => C a (T b)
(C a, C a b) => C a (T b)
(Eq a, C a) => Eq (T a)
(C a, Eq a, Show a, C a) => Fractional (T a)
(C a, Eq a, Show a, C a) => Num (T a)
Show a => Show (T a)
(Arbitrary a, C a) => Arbitrary (T a)
(C a, C a) => C (T a)
C a => C (T a)
C a => C (T a)
C a => C (T a)
C a => C (T a)
(C a, C a) => C (T a)
(C a, C a) => C (T a)
(C a, C a) => C (T a)
fromCoeffs :: [a] -> T aSource
coeffs :: T a -> [a]Source
showsExpressionPrec :: (Show a, C a, C a) => Int -> String -> T a -> String -> StringSource
const :: a -> T aSource
evaluate :: C a => T a -> a -> aSource
evaluateCoeffVector :: C a v => T v -> a -> vSource
Here the coefficients are vectors, for example the coefficients are real and the coefficents are real vectors.
evaluateArgVector :: (C a v, C v) => T a -> v -> vSource
Here the argument is a vector, for example the coefficients are complex numbers or square matrices and the coefficents are reals.
compose :: C a => T a -> T a -> T aSource

compose is the functional composition of polynomials.

It fulfills eval x . eval y == eval (compose x y)

equal :: (Eq a, C a) => [a] -> [a] -> BoolSource
add :: C a => [a] -> [a] -> [a]Source
sub :: C a => [a] -> [a] -> [a]Source
negate :: C a => [a] -> [a]Source
horner :: C a => a -> [a] -> aSource
Horner's scheme for evaluating a polynomial in a ring.
hornerCoeffVector :: C a v => a -> [v] -> vSource
Horner's scheme for evaluating a polynomial in a module.
hornerArgVector :: (C a v, C v) => v -> [a] -> vSource
shift :: C a => [a] -> [a]Source
Multiply by the variable, used internally.
unShift :: [a] -> [a]Source
mul :: C a => [a] -> [a] -> [a]Source
mul is fast if the second argument is a short polynomial, MathObj.PowerSeries.** relies on that fact.
scale :: C a => a -> [a] -> [a]Source
divMod :: (C a, C a) => [a] -> [a] -> ([a], [a])Source
tensorProduct :: C a => [a] -> [a] -> [[a]]Source
tensorProductAlt :: C a => [a] -> [a] -> [[a]]Source
mulShear :: C a => [a] -> [a] -> [a]Source
mulShearTranspose :: C a => [a] -> [a] -> [a]Source
progression :: C a => [a]Source
differentiate :: C a => [a] -> [a]Source
integrate :: C a => a -> [a] -> [a]Source
integrateInt :: (C a, C a) => a -> [a] -> [a]Source
Integrates if it is possible to represent the integrated polynomial in the given ring. Otherwise undefined coefficients occur.
fromRoots :: C a => [a] -> T aSource
alternate :: C a => [a] -> [a]Source
Produced by Haddock version 2.6.0