Safe Haskell | None |
---|---|
Language | Haskell98 |
AUTHOR
- Dr. Alistair Ward
DESCRIPTION
- Describes a http://en.wikipedia.org/wiki/Univariate polynomial and operations on it.
- http://en.wikipedia.org/wiki/Polynomial.
- http://mathworld.wolfram.com/Polynomial.html.
- data Polynomial coefficient exponent
- zero :: Polynomial c e
- one :: (Eq c, Num c, Num e) => Polynomial c e
- evaluate :: (Num n, Integral e, Show e) => n -> Polynomial n e -> n
- getDegree :: Num e => Polynomial c e -> e
- getLeadingTerm :: Polynomial c e -> Monomial c e
- lift :: (MonomialList c1 e1 -> MonomialList c2 e2) -> Polynomial c1 e1 -> Polynomial c2 e2
- mod' :: Integral c => Polynomial c e -> c -> Polynomial c e
- normalise :: (Eq c, Num c, Ord e) => Polynomial c e -> Polynomial c e
- raiseModulo :: (Integral c, Integral power, Num e, Ord e, Show power) => Polynomial c e -> power -> c -> Polynomial c e
- realCoefficientsToFrac :: (Real r, Fractional f) => Polynomial r e -> Polynomial f e
- terms :: Polynomial c e -> Int
- mkConstant :: (Eq c, Num c, Num e) => c -> Polynomial c e
- mkLinear :: (Eq c, Num c, Num e) => c -> c -> Polynomial c e
- mkPolynomial :: (Eq c, Num c, Ord e) => MonomialList c e -> Polynomial c e
- (*=) :: (Eq c, Num c, Num e) => Polynomial c e -> Monomial c e -> Polynomial c e
- areCongruentModulo :: (Integral c, Num e, Ord e) => Polynomial c e -> Polynomial c e -> c -> Bool
- inAscendingOrder :: Ord e => Polynomial c e -> Bool
- inDescendingOrder :: Ord e => Polynomial c e -> Bool
- isMonic :: (Eq c, Num c) => Polynomial c e -> Bool
- isMonomial :: Polynomial c e -> Bool
- isNormalised :: (Eq c, Num c, Ord e) => Polynomial c e -> Bool
- isPolynomial :: Integral e => Polynomial c e -> Bool
- isZero :: Polynomial c e -> Bool
Types
Type-synonyms
Data-types,
data Polynomial coefficient exponent Source
- The type of an arbitrary univariate polynomial;
actually it's more general, since it permits negative powers (http://en.wikipedia.org/wiki/Laurent_polynomials).
It can't describe multivariate polynomials, which would require a list of exponents.
Rather than requiring the exponent to implement the type-class
Integral
, this is implemented at the function-level, as required. - The structure permits gaps between exponents, in which coefficients are inferred to be zero, thus enabling efficient representation of sparse polynomials.
- CAVEAT: the
MonomialList
is required to; be ordered by descending exponent (ie. reverse http://en.wikipedia.org/wiki/Monomial_order); have had zero coefficients removed; and to have had like terms merged; so the raw data-constructor isn't exported.
(Eq coefficient, Eq exponent) => Eq (Polynomial coefficient exponent) | |
(Show coefficient, Show exponent) => Show (Polynomial coefficient exponent) | |
(Eq c, Num c, Num e, Ord e) => Ring (Polynomial c e) | Makes Polynomial a |
(Eq c, Fractional c, Num e, Ord e) => QuotientRing (Polynomial c e) | Defines the ability to divide polynomials. |
Constants
zero :: Polynomial c e Source
Constructs a polynomial with zero terms.
one :: (Eq c, Num c, Num e) => Polynomial c e Source
Constructs a constant monomial, independent of the indeterminate.
Functions
:: (Num n, Integral e, Show e) | |
=> n | The indeterminate. |
-> Polynomial n e | |
-> n | The Result. |
- Evaluate the polynomial at a specific indeterminate.
- CAVEAT: requires positive exponents; but it wouldn't really be a polynomial otherwise.
- If the polynomial is very sparse, this may be inefficient, since it memoizes the complete sequence of powers up to the polynomial's degree.
getDegree :: Num e => Polynomial c e -> e Source
- Return the degree (AKA order) of the polynomial.
- http://en.wikipedia.org/wiki/Degree_of_a_polynomial.
- http://mathworld.wolfram.com/PolynomialDegree.html.
getLeadingTerm :: Polynomial c e -> Monomial c e Source
Return the highest-degree monomial.
lift :: (MonomialList c1 e1 -> MonomialList c2 e2) -> Polynomial c1 e1 -> Polynomial c2 e2 Source
- Transforms the data behind the constructor.
- CAVEAT: similar to
fmap
, butPolynomial
isn't an instance ofFunctor
since we may want to operate on both type-parameters. - CAVEAT: the caller is required to re-
normalise
the resulting polynomial depending on the nature of the transformation of the data.
:: Integral c | |
=> Polynomial c e | |
-> c | Modulus. |
-> Polynomial c e |
Reduces all the coefficients using modular arithmetic.
normalise :: (Eq c, Num c, Ord e) => Polynomial c e -> Polynomial c e Source
Sorts into descending order of exponents, groups like exponents, and calls pruneCoefficients
.
:: (Integral c, Integral power, Num e, Ord e, Show power) | |
=> Polynomial c e | The base. |
-> power | The exponent to which the base should be raised. |
-> c | The modulus. |
-> Polynomial c e | The result. |
- Raise a polynomial to the specified positive integral power, but using modulo-arithmetic.
- Whilst one could naively implement this as
(x Data.Ring.=^ n)
, this will result in arithmetic operatons on unnecessarily big integers.mod
m
realCoefficientsToFrac :: (Real r, Fractional f) => Polynomial r e -> Polynomial f e Source
Convert the type of the coefficients.
terms :: Polynomial c e -> Int Source
Returns the number of non-zero terms in the polynomial.
Constructors
mkConstant :: (Eq c, Num c, Num e) => c -> Polynomial c e Source
Constructs an arbitrary zeroeth-degree polynomial, ie. independent of the indeterminate.
:: (Eq c, Num c, Num e) | |
=> c | Gradient. |
-> c | Constant. |
-> Polynomial c e |
Constructs an arbitrary first-degree polynomial.
mkPolynomial :: (Eq c, Num c, Ord e) => MonomialList c e -> Polynomial c e Source
Smart constructor. Constructs an arbitrary polynomial.
Operators
(*=) :: (Eq c, Num c, Num e) => Polynomial c e -> Monomial c e -> Polynomial c e infixl 7 Source
- Scale-up the specified polynomial by a constant monomial factor.
- http://en.wikipedia.org/wiki/Scalar_multiplication.
Predicates
:: (Integral c, Num e, Ord e) | |
=> Polynomial c e | LHS. |
-> Polynomial c e | RHS. |
-> c | Modulus. |
-> Bool |
True
if the two specified polynomials are congruent in modulo-arithmetic.- http://planetmath.org/encyclopedia/PolynomialCongruence.html.
inAscendingOrder :: Ord e => Polynomial c e -> Bool Source
True if the exponents of successive terms are in ascending order.
inDescendingOrder :: Ord e => Polynomial c e -> Bool Source
True if the exponents of successive terms are in descending order.
isMonic :: (Eq c, Num c) => Polynomial c e -> Bool Source
True
if the leading coefficient is one.- http://en.wikipedia.org/wiki/Monic_polynomial#Classifications.
isMonomial :: Polynomial c e -> Bool Source
True if there's exactly one term.
isNormalised :: (Eq c, Num c, Ord e) => Polynomial c e -> Bool Source
True if no term has a coefficient of zero and the exponents of successive terms are in descending order.
isPolynomial :: Integral e => Polynomial c e -> Bool Source
True if all exponents are positive integers as required.
isZero :: Polynomial c e -> Bool Source
True if there are zero terms.