polynomial-0.7.2: Polynomials

Safe HaskellNone
LanguageHaskell98

Math.Polynomial.VectorSpace

Description

Same general interface as Math.Polynomial, but using AdditiveGroup, VectorSpace, etc., instead of Num where sensible.

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 
(AdditiveGroup a, Eq a) => Eq (Poly a) 
(Num a, Eq a) => Num (Poly a) 
Show 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)) 
(Eq a, VectorSpace a, AdditiveGroup (Scalar a), Eq (Scalar a)) => VectorSpace (Poly a) 
AdditiveGroup a => AdditiveGroup (Poly a) 
type Scalar (Poly a) = Scalar a 

poly :: (Eq a, AdditiveGroup a) => Endianness -> [a] -> Poly a Source

vPolyCoeffs :: (Eq a, AdditiveGroup a) => Endianness -> Poly a -> [a] Source

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

polyIsOne :: (Num a, Eq a) => Poly a -> Bool Source

zero :: Poly a Source

The polynomial "0"

one :: (Num a, Eq a) => Poly a Source

The polynomial "1"

constPoly :: (Eq a, AdditiveGroup a) => a -> Poly a Source

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

x :: (Num a, Eq a) => Poly a Source

The polynomial (in x) "x"

scalePoly :: (Eq a, VectorSpace a, AdditiveGroup (Scalar a), Eq (Scalar a)) => Scalar a -> Poly a -> Poly a Source

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

evalPoly g x = s * evalPoly f x

negatePoly :: (AdditiveGroup a, Eq a) => Poly a -> Poly a Source

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

evalPoly g x = negate (evalPoly f x)

composePolyWith :: (AdditiveGroup a, Eq a) => (a -> a -> a) -> Poly a -> Poly a -> Poly a Source

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 :: (AdditiveGroup a, Eq a) => Poly a -> Poly a -> Poly a Source

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

evalPoly h x = evalPoly f x + evalPoly g x

sumPolys :: (AdditiveGroup a, Eq a) => [Poly a] -> Poly a Source

multPolyWith :: (AdditiveGroup a, Eq a) => (a -> a -> a) -> Poly a -> Poly a -> Poly a Source

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

evalPoly h x = evalPoly f x * evalPoly g x

powPolyWith :: (AdditiveGroup a, Eq a, Integral b) => a -> (a -> a -> a) -> Poly a -> b -> Poly a Source

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

evalPoly g x = evalPoly f x ^ n

quotRemPolyWith :: (AdditiveGroup a, Eq a) => (a -> a -> a) -> (a -> a -> 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

quotPolyWith :: (AdditiveGroup a, Eq a) => (a -> a -> a) -> (a -> a -> a) -> Poly a -> Poly a -> Poly a Source

remPolyWith :: (AdditiveGroup a, Eq a) => (a -> a -> a) -> (a -> a -> a) -> Poly a -> Poly a -> Poly a Source

evalPoly :: (VectorSpace a, Eq a, AdditiveGroup (Scalar a), Eq (Scalar a)) => Poly a -> Scalar a -> a Source

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 :: (VectorSpace a, Eq a) => Poly a -> Scalar a -> (a, a) Source

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

evalPolyDerivs :: (VectorSpace a, Eq a, Num (Scalar a)) => Poly a -> Scalar 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 :: (VectorSpace a, Eq a) => Poly a -> Scalar 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

monicPolyWith :: (AdditiveGroup a, Eq a) => a -> (a -> a -> a) -> Poly a -> Poly a Source

Normalize a polynomial so that its highest-order coefficient is 1

gcdPolyWith :: (AdditiveGroup a, Eq a) => a -> (a -> a -> a) -> (a -> a -> a) -> Poly a -> Poly a -> Poly a Source

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.

polyDeriv :: (VectorSpace a, Eq a, Num (Scalar a)) => Poly a -> Poly a Source

Compute the derivative of a polynomial.

polyDerivs :: (VectorSpace a, Eq a, Num (Scalar a)) => Poly a -> [Poly a] Source

Compute all nonzero derivatives of a polynomial, starting with its "zero'th derivative", the original polynomial itself.

polyIntegral :: (VectorSpace a, Eq a, Fractional (Scalar a)) => Poly a -> Poly a Source

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