polynomial-0.6.5: Polynomials

Math.Polynomial.Type

Description

Low-level interface for the Poly type.

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, 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)) 
VectorSpace a => VectorSpace (Poly a) 
AdditiveGroup a => AdditiveGroup (Poly a) 

zero :: Poly aSource

The polynomial "0"

poly :: (Num a, Eq a) => Endianness -> [a] -> Poly aSource

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

polyN :: (Num a, Eq a) => Int -> Endianness -> [a] -> Poly aSource

Make a Poly from a list of coefficients, at most n of which are significant.

unboxedPoly :: (Unbox a, Num a, Eq a) => Endianness -> [a] -> Poly aSource

unboxedPolyN :: (Unbox a, Num a, Eq a) => Int -> Endianness -> [a] -> Poly aSource

mapPoly :: (a -> a) -> Poly a -> Poly aSource

Like fmap, but able to preserve unboxedness

rawListPoly :: Endianness -> [a] -> Poly aSource

Make a Poly from a list of coefficients using the specified coefficient order, without the Num context (and therefore without trimming zeroes from the coefficient list)

trim :: (a -> Bool) -> Poly a -> Poly aSource

Trim zeroes from a polynomial (given a predicate for identifying zero). In particular, drops zeroes from the highest-order coefficients, so that 0x^n + 0x^(n-1) + 0x^(n-2) + ... + ax^k + ..., a /= 0 is normalized to ax^k + ....

The Eq instance for Poly and all the standard constructors / destructors are defined using trim (0==).

polyIsZero :: (Num a, Eq a) => Poly a -> BoolSource

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

polyCoeffs :: (Num a, Eq a) => Endianness -> Poly a -> [a]Source

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

polyDegree :: (Num a, Eq a) => Poly a -> IntSource

Get the degree of a a Poly (the highest exponent with nonzero coefficient)