Copyright | (c) 2019 Andrew Lelechenko |
---|---|
License | BSD3 |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Dense polynomials and a Semiring
-based interface.
Synopsis
- data Poly v a
- type VPoly = Poly Vector
- type UPoly = Poly Vector
- unPoly :: Poly v a -> v a
- leading :: Vector v a => Poly v a -> Maybe (Word, a)
- toPoly :: (Eq a, Semiring a, Vector v a) => v a -> Poly v a
- monomial :: (Eq a, Semiring a, Vector v a) => Word -> a -> Poly v a
- scale :: (Eq a, Semiring a, Vector v a) => Word -> a -> Poly v a -> Poly v a
- pattern X :: (Eq a, Semiring a, Vector v a, Eq (v a)) => Poly v a
- eval :: (Semiring a, Vector v a) => Poly v a -> a -> a
- deriv :: (Eq a, Semiring a, Vector v a) => Poly v a -> Poly v a
- newtype PolyOverFractional poly = PolyOverFractional {
- unPolyOverFractional :: poly
Documentation
Polynomials of one variable 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 + 0>>>
(X + 1) * (X - 1) :: UPoly Int
1 * X^2 + 0 * X + (-1)
Polynomials are stored normalized, without leading
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.
Instances
unPoly :: Poly v a -> v a Source #
Convert Poly
to a vector of coefficients
(first element corresponds to a constant term).
leading :: Vector v a => Poly v a -> Maybe (Word, a) Source #
Return a leading power and coefficient of a non-zero polynomial.
>>>
leading ((2 * X + 1) * (2 * X^2 - 1) :: UPoly Int)
Just (3,4)>>>
leading (0 :: UPoly Int)
Nothing
Semiring interface
toPoly :: (Eq a, Semiring a, Vector v a) => v a -> Poly v a Source #
Make Poly
from a vector of coefficients
(first element corresponds to a constant term).
>>>
:set -XOverloadedLists
>>>
toPoly [1,2,3] :: VPoly Integer
3 * X^2 + 2 * X + 1>>>
toPoly [0,0,0] :: UPoly Int
0
monomial :: (Eq a, Semiring a, Vector v a) => Word -> a -> Poly v a Source #
Create a monomial from a power and a coefficient.
scale :: (Eq a, Semiring a, Vector v 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 + 0 * X^3 + 3 * X^2 + 0 * X + 0
pattern X :: (Eq a, Semiring a, Vector v a, Eq (v a)) => Poly v a Source #
Create an identity polynomial.
eval :: (Semiring a, Vector v a) => Poly v a -> a -> a Source #
Evaluate at a given point.
>>>
eval (X^2 + 1 :: UPoly Int) 3
10>>>
eval (X^2 + 1 :: VPoly (UPoly Int)) (X + 1)
1 * X^2 + 2 * X + 2
deriv :: (Eq a, Semiring a, Vector v a) => Poly v a -> Poly v a Source #
Take a derivative.
>>>
deriv (X^3 + 3 * X) :: UPoly Int
3 * X^2 + 0 * X + 3
Fractional coefficients
newtype PolyOverFractional poly Source #
Wrapper over polynomials,
providing a faster GcdDomain
instance,
when coefficients are Fractional
.