polynomial-0.6: Polynomials

Math.Polynomial

Synopsis

Documentation

data Endianness Source

Constructors

BE

Big-Endian (head is highest-order term)

LE

Little-Endian (head is const term)

data Poly a Source

Instances

Functor Poly 
(Num a, Eq a) => Eq (Poly a) 
Num a => Num (Poly a) 
Num a => Show (Poly a) 
NFData a => NFData (Poly a) 
(Pretty a, Num a, Ord a) => Pretty (Poly a) 
(RealFloat a, Pretty (Complex a)) => Pretty (Poly (Complex a)) 
VectorSpace a => VectorSpace (Poly a) 
AdditiveGroup a => AdditiveGroup (Poly a) 

poly :: Num a => Endianness -> [a] -> Poly aSource

Make a Poly from a list of coefficients using the specified coefficient order.

polyCoeffs :: Num a => Endianness -> Poly a -> [a]Source

Get the coefficients of a a Poly in the specified order.

zero :: Num a => Poly aSource

The polynomial "0"

one :: Num a => Poly aSource

The polynomial "1"

constPoly :: Num a => a -> Poly aSource

Given some constant k, construct the polynomial whose value is constantly k.

x :: Num a => Poly aSource

The polynomial (in x) "x"

scalePoly :: Num a => a -> Poly a -> Poly aSource

Given some scalar s and a polynomial f, computes the polynomial g such that:

 evalPoly g x = s * evalPoly f x

negatePoly :: Num a => Poly a -> Poly aSource

Given some polynomial f, computes the polynomial g such that:

 evalPoly g x = negate (evalPoly f x)

composePoly :: Num a => Poly a -> Poly a -> Poly aSource

composePoly f g constructs the polynomial h such that:

 evalPoly h = evalPoly f . evalPoly g

This is a very expensive operation and, in general, returns a polynomial that is quite a bit more expensive to evaluate than f and g together (because it is of a much higher order than either). Unless your polynomials are quite small or you are quite certain you need the coefficients of the composed polynomial, it is recommended that you simply evaluate f and g and explicitly compose the resulting functions. This will usually be much more efficient.

addPoly :: Num a => Poly a -> Poly a -> Poly aSource

Given polynomials f and g, computes the polynomial h such that:

 evalPoly h x = evalPoly f x + evalPoly g x

sumPolys :: Num a => [Poly a] -> Poly aSource

multPoly :: Num a => Poly a -> Poly a -> Poly aSource

Given polynomials f and g, computes the polynomial h such that:

 evalPoly h x = evalPoly f x * evalPoly g x

powPoly :: (Num a, Integral b) => Poly a -> b -> Poly aSource

Given a polynomial f and exponent n, computes the polynomial g such that:

 evalPoly g x = evalPoly f x ^ n

quotRemPoly :: Fractional a => Poly a -> Poly a -> (Poly a, Poly a)Source

Given polynomials a and b, with b not zero, computes polynomials q and r such that:

 addPoly (multPoly q b) r == a

quotPoly :: Fractional a => Poly a -> Poly a -> Poly aSource

remPoly :: Fractional a => Poly a -> Poly a -> Poly aSource

evalPoly :: Num a => Poly a -> a -> aSource

Evaluate a polynomial at a point or, equivalently, convert a polynomial to the function it represents. For example, evalPoly x = id and evalPoly (constPoly k) = const k.

evalPolyDeriv :: Num a => Poly a -> a -> (a, a)Source

Evaluate a polynomial and its derivative (respectively) at a point.

evalPolyDerivs :: Num a => Poly a -> a -> [a]Source

Evaluate a polynomial and all of its nonzero derivatives at a point. This is roughly equivalent to:

 evalPolyDerivs p x = map (`evalPoly` x) (takeWhile (not . polyIsZero) (iterate polyDeriv p))

contractPoly :: Num a => Poly a -> a -> (Poly a, a)Source

"Contract" a polynomial by attempting to divide out a root.

contractPoly p a returns (q,r) such that q*(x-a) + r == p

gcdPoly :: Fractional a => Poly a -> Poly a -> Poly aSource

gcdPoly a b computes the highest order monic polynomial that is a divisor of both a and b. If both a and b are zero, the result is undefined.

separateRoots :: Fractional a => Poly a -> [Poly a]Source

Separate a nonzero polynomial into a set of factors none of which have multiple roots, and the product of which is the original polynomial. Note that if division is not exact, it may fail to separate roots. Rational coefficients is a good idea.

Useful when applicable as a way to simplify root-finding problems.

polyDeriv :: Num a => Poly a -> Poly aSource

Compute the derivative of a polynomial.

polyIntegral :: Fractional a => Poly a -> Poly aSource

Compute the definite integral (from 0 to x) of a polynomial.