poly-0.5.1.0: Polynomials
Copyright(c) 2019 Andrew Lelechenko
LicenseBSD3
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Poly.Sparse.Semiring

Description

Sparse polynomials with a Semiring instance.

Since: 0.3.0.0

Synopsis

Documentation

type Poly (v :: Type -> Type) (a :: Type) = MultiPoly v 1 a Source #

Sparse univariate polynomials with coefficients from a, backed by a Vector v (boxed, unboxed, storable, etc.).

Use pattern X for construction:

>>> (X + 1) + (X - 1) :: VPoly Integer
2 * X
>>> (X + 1) * (X - 1) :: UPoly Int
1 * X^2 + (-1)

Polynomials are stored normalized, without zero coefficients, so 0 * X + 1 equals to 1.

Ord instance does not make much sense mathematically, it is defined only for the sake of Set, Map, etc.

Due to being polymorphic by multiple axis, the performance of Poly crucially depends on specialisation of instances. Clients are strongly recommended to compile with ghc-options: -fspecialise-aggressively and suggested to enable -O2.

Since: 0.3.0.0

type VPoly (a :: Type) = Poly Vector a Source #

Polynomials backed by boxed vectors.

Since: 0.3.0.0

type UPoly (a :: Type) = Poly Vector a Source #

Polynomials backed by unboxed vectors.

Since: 0.3.0.0

unPoly :: (Vector v (Word, a), Vector v (Vector 1 Word, a)) => Poly v a -> v (Word, a) Source #

Convert a Poly to a vector of coefficients.

Since: 0.3.0.0

toPoly :: (Eq a, Semiring a, Vector v (Word, a), Vector v (Vector 1 Word, a)) => v (Word, a) -> Poly v a Source #

Make a Poly from a list of (power, coefficient) pairs.

>>> :set -XOverloadedLists
>>> toPoly [(0,1),(1,2),(2,3)] :: VPoly Integer
3 * X^2 + 2 * X + 1
>>> toPoly [(0,0),(1,0),(2,0)] :: UPoly Int
0

Since: 0.3.0.0

leading :: Vector v (Vector 1 Word, a) => Poly v a -> Maybe (Word, a) Source #

Return the leading power and coefficient of a non-zero polynomial.

>>> import Data.Poly.Sparse (UPoly)
>>> leading ((2 * X + 1) * (2 * X^2 - 1) :: UPoly Int)
Just (3,4)
>>> leading (0 :: UPoly Int)
Nothing

Since: 0.3.0.0

monomial :: (Eq a, Semiring a, Vector v (Vector 1 Word, a)) => Word -> a -> Poly v a Source #

Create a monomial from a power and a coefficient.

Since: 0.3.0.0

scale :: (Eq a, Semiring a, Vector v (Vector 1 Word, a)) => Word -> a -> Poly v a -> Poly v a Source #

Multiply a polynomial by a monomial, expressed as a power and a coefficient.

>>> scale 2 3 (X^2 + 1) :: UPoly Int
3 * X^4 + 3 * X^2

Since: 0.3.0.0

pattern X :: (Eq a, Semiring a, Vector v (Vector 1 Word, a)) => Poly v a Source #

The polynomial X.

X == monomial 1 one

Since: 0.3.0.0

eval :: (Semiring a, Vector v (Vector 1 Word, a)) => Poly v a -> a -> a Source #

Evaluate the polynomial at a given point.

>>> eval (X^2 + 1 :: UPoly Int) 3
10

Since: 0.3.0.0

subst :: (Eq a, Semiring a, Vector v (Vector 1 Word, a), Vector w (Vector 1 Word, a)) => Poly v a -> Poly w a -> Poly w a Source #

Substitute another polynomial instead of X.

>>> subst (X^2 + 1 :: UPoly Int) (X + 1 :: UPoly Int)
1 * X^2 + 2 * X + 2

Since: 0.3.3.0

deriv :: (Eq a, Semiring a, Vector v (Vector 1 Word, a)) => Poly v a -> Poly v a Source #

Take the derivative of the polynomial.

>>> deriv (X^3 + 3 * X) :: UPoly Int
3 * X^2 + 3

Since: 0.3.0.0

integral :: (Field a, Vector v (Vector 1 Word, a)) => Poly v a -> Poly v a Source #

Compute an indefinite integral of the polynomial, setting the constant term to zero.

>>> integral (3 * X^2 + 3) :: UPoly Double
1.0 * X^3 + 3.0 * X

Since: 0.3.2.0

denseToSparse :: (Eq a, Semiring a, Vector v a, Vector v (Vector 1 Word, a)) => Poly v a -> Poly v a Source #

Convert from dense to sparse polynomials.

>>> :set -XFlexibleContexts
>>> denseToSparse (1 `Data.Semiring.plus` Data.Poly.X^2) :: Data.Poly.Sparse.UPoly Int
1 * X^2 + 1

Since: 0.5.0.0

sparseToDense :: (Semiring a, Vector v a, Vector v (Vector 1 Word, a)) => Poly v a -> Poly v a Source #

Convert from sparse to dense polynomials.

>>> :set -XFlexibleContexts
>>> sparseToDense (1 `Data.Semiring.plus` Data.Poly.Sparse.X^2) :: Data.Poly.UPoly Int
1 * X^2 + 0 * X + 1

Since: 0.5.0.0