poly-0.5.0.0: Polynomials

Copyright(c) 2020 Andrew Lelechenko
LicenseBSD3
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Poly.Sparse.Laurent

Description

Synopsis

Documentation

type Laurent (v :: Type -> Type) (a :: Type) = MultiLaurent v 1 a Source #

Laurent polynomials of one variable with coefficients from a, backed by a Vector v (boxed, unboxed, storable, etc.).

Use pattern X and operator ^- for construction:

>>> (X + 1) + (X^-1 - 1) :: VLaurent Integer
1 * X + 1 * X^-1
>>> (X + 1) * (1 - X^-1) :: ULaurent Int
1 * X + (-1) * X^-1

Polynomials are stored normalized, without zero coefficients, so 0 * X + 1 + 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.

type VLaurent (a :: Type) = Laurent Vector a Source #

Laurent polynomials backed by boxed vectors.

type ULaurent (a :: Type) = Laurent Vector a Source #

Laurent polynomials backed by unboxed vectors.

unLaurent :: Laurent v a -> (Int, Poly v a) Source #

Deconstruct a Laurent polynomial into an offset (largest possible) and a regular polynomial.

>>> unLaurent (2 * X + 1 :: ULaurent Int)
(0,2 * X + 1)
>>> unLaurent (1 + 2 * X^-1 :: ULaurent Int)
(-1,1 * X + 2)
>>> unLaurent (2 * X^2 + X :: ULaurent Int)
(1,2 * X + 1)
>>> unLaurent (0 :: ULaurent Int)
(0,0)

toLaurent :: Vector v (Vector 1 Word, a) => Int -> Poly v a -> Laurent v a Source #

Construct Laurent polynomial from an offset and a regular polynomial. One can imagine it as scale, but allowing negative offsets.

>>> toLaurent 2 (2 * Data.Poly.Sparse.X + 1) :: ULaurent Int
2 * X^3 + 1 * X^2
>>> toLaurent (-2) (2 * Data.Poly.Sparse.X + 1) :: ULaurent Int
2 * X^-1 + 1 * X^-2

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

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

>>> leading ((2 * X + 1) * (2 * X^2 - 1) :: ULaurent Int)
Just (3,4)
>>> leading (0 :: ULaurent Int)
Nothing

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

Create a monomial from a power and a coefficient.

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

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

>>> scale 2 3 (X^-2 + 1) :: ULaurent Int
3 * X^2 + 3

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

Create an identity polynomial.

(^-) :: (Eq a, Semiring a, Vector v (Vector 1 Word, a)) => Laurent v a -> Int -> Laurent v a Source #

This operator can be applied only to monomials with unit coefficients, but is instrumental to express Laurent polynomials in mathematical fashion:

>>> X + 2 + 3 * (X^2)^-1 :: ULaurent Int
1 * X + 2 + 3 * X^-2

eval :: (Field a, Vector v (Vector 1 Word, a)) => Laurent v a -> a -> a Source #

Evaluate at a given point.

>>> eval (X^-2 + 1 :: ULaurent Double) 2
1.25

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

Substitute another polynomial instead of X.

>>> import Data.Poly.Sparse (UPoly)
>>> subst (Data.Poly.Sparse.X^2 + 1 :: UPoly Int) (X^-1 + 1 :: ULaurent Int)
2 + 2 * X^-1 + 1 * X^-2

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

Take a derivative.

>>> deriv (X^-3 + 3 * X) :: ULaurent Int
3 + (-3) * X^-4