polynomial-0.7.3: Polynomials

Safe HaskellNone
LanguageHaskell98

Math.Polynomial.Type

Description

Low-level interface for the Poly type.

Synopsis

Documentation

data Poly a Source #

Instances

Functor Poly Source # 

Methods

fmap :: (a -> b) -> Poly a -> Poly b #

(<$) :: a -> Poly b -> Poly a #

(AdditiveGroup a, Eq a) => Eq (Poly a) Source # 

Methods

(==) :: Poly a -> Poly a -> Bool #

(/=) :: Poly a -> Poly a -> Bool #

Show a => Show (Poly a) Source # 

Methods

showsPrec :: Int -> Poly a -> ShowS #

show :: Poly a -> String #

showList :: [Poly a] -> ShowS #

NFData a => NFData (Poly a) Source # 

Methods

rnf :: Poly a -> () #

(Eq a, VectorSpace a, AdditiveGroup (Scalar a), Eq (Scalar a)) => VectorSpace (Poly a) Source # 

Associated Types

type Scalar (Poly a) :: * #

Methods

(*^) :: Scalar (Poly a) -> Poly a -> Poly a #

AdditiveGroup a => AdditiveGroup (Poly a) Source # 

Methods

zeroV :: Poly a #

(^+^) :: Poly a -> Poly a -> Poly a #

negateV :: Poly a -> Poly a #

(^-^) :: Poly a -> Poly a -> Poly a #

type Scalar (Poly a) Source # 
type Scalar (Poly a) = Scalar a

zero :: Poly a Source #

The polynomial "0"

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

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

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

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 a Source #

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

mapPoly :: (Num a, Eq a) => (a -> a) -> Poly a -> Poly a Source #

Like fmap, but able to preserve unboxedness

rawMapPoly :: (a -> a) -> Poly a -> Poly a Source #

wrapPoly :: Poly a -> Poly (WrappedNum a) Source #

like fmap WrapNum but using unsafeCoerce to avoid a pointless traversal

unwrapPoly :: Poly (WrappedNum a) -> Poly a Source #

like fmap unwrapNum but using unsafeCoerce to avoid a pointless traversal

unboxPoly :: Unbox a => Poly a -> Poly a Source #

rawListPoly :: Endianness -> [a] -> Poly a Source #

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 a Source #

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==).

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

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

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

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

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

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

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

polyDegree :: (Num a, Eq a) => Poly a -> Int Source #

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