Safe Haskell | None |
---|---|
Language | Haskell98 |
This module implements polynomial functions on plain lists. We use such functions in order to implement methods of other datatypes.
The module organization differs from that of ResidueClass
:
Here the Polynomial
module exports the type
that fits to the NumericPrelude type classes,
whereas in ResidueClass
the sub-modules export various flavors of them.
Synopsis
- horner :: C a => a -> [a] -> a
- hornerCoeffVector :: C a v => a -> [v] -> v
- hornerArgVector :: (C a v, C v) => v -> [a] -> v
- normalize :: C a => [a] -> [a]
- shift :: C a => [a] -> [a]
- unShift :: [a] -> [a]
- equal :: (Eq a, C a) => [a] -> [a] -> Bool
- add :: C a => [a] -> [a] -> [a]
- sub :: C a => [a] -> [a] -> [a]
- negate :: C a => [a] -> [a]
- scale :: C a => a -> [a] -> [a]
- collinear :: (Eq a, C a) => [a] -> [a] -> Bool
- tensorProduct :: C a => [a] -> [a] -> [[a]]
- tensorProductAlt :: C a => [a] -> [a] -> [[a]]
- mul :: C a => [a] -> [a] -> [a]
- mulShear :: C a => [a] -> [a] -> [a]
- mulShearTranspose :: C a => [a] -> [a] -> [a]
- divMod :: (C a, C a) => [a] -> [a] -> ([a], [a])
- divModRev :: (C a, C a) => [a] -> [a] -> ([a], [a])
- stdUnit :: (C a, C a) => [a] -> a
- progression :: C a => [a]
- differentiate :: C a => [a] -> [a]
- integrate :: C a => a -> [a] -> [a]
- integrateInt :: (C a, C a) => a -> [a] -> [a]
- mulLinearFactor :: C a => a -> [a] -> [a]
- alternate :: C a => [a] -> [a]
- dilate :: C a => a -> [a] -> [a]
- shrink :: C a => a -> [a] -> [a]
Documentation
hornerCoeffVector :: C a v => a -> [v] -> v Source #
Horner's scheme for evaluating a polynomial in a module.
hornerArgVector :: (C a v, C v) => v -> [a] -> v Source #
normalize :: C a => [a] -> [a] Source #
It's also helpful to put a polynomial in canonical form.
normalize
strips leading coefficients that are zero.
tensorProduct :: C a => [a] -> [a] -> [[a]] Source #
\(QC.NonEmpty xs) (QC.NonEmpty ys) -> PolyCore.tensorProduct xs ys == List.transpose (PolyCore.tensorProduct ys (intPoly xs))
tensorProductAlt :: C a => [a] -> [a] -> [[a]] Source #
mulShear :: C a => [a] -> [a] -> [a] Source #
\xs ys -> PolyCore.equal (intPoly $ PolyCore.mul xs ys) (PolyCore.mulShear xs ys)
mulShearTranspose :: C a => [a] -> [a] -> [a] Source #
divMod :: (C a, C a) => [a] -> [a] -> ([a], [a]) Source #
\x y -> case (PolyCore.normalize x, PolyCore.normalize y) of (nx, ny) -> not (null (ratioPoly ny)) ==> mapSnd PolyCore.normalize (PolyCore.divMod nx ny) == mapPair (PolyCore.normalize, PolyCore.normalize) (PolyCore.divMod x y)
\x y -> not (isZero (ratioPoly y)) ==> let z = fst $ PolyCore.divMod (Poly.coeffs x) y in PolyCore.normalize z == z
\x y -> case PolyCore.normalize $ ratioPoly y of ny -> not (null ny) ==> List.length (snd $ PolyCore.divMod x y) < List.length ny
divModRev :: (C a, C a) => [a] -> [a] -> ([a], [a]) Source #
The modulus will always have one element less than the divisor.
This means that the modulus will be denormalized in some cases,
e.g. mod [2,1,1] [1,1,1] == [1,0]
instead of [1]
.
progression :: C a => [a] Source #
differentiate :: C a => [a] -> [a] Source #
integrateInt :: (C a, C a) => a -> [a] -> [a] Source #
Integrates if it is possible to represent the integrated polynomial in the given ring. Otherwise undefined coefficients occur.
mulLinearFactor :: C a => a -> [a] -> [a] Source #