numeric-prelude-0.0.2: An experimental alternative hierarchy of numeric type classesContentsIndex
MathObj.LaurentPolynomial
Portabilityrequires multi-parameter type classes
Stabilityprovisional
Maintainernumericprelude@henning-thielemann.de
Contents
Basic Operations
Show
Additive
Module
Ring
Field.C
Comparisons
Transformations of arguments
Description
Polynomials with negative and positive exponents.
Synopsis
data T a = Cons {
expon :: Int
coeffs :: [a]
}
const :: a -> T a
(!) :: C a => T a -> Int -> a
fromCoeffs :: [a] -> T a
fromShiftCoeffs :: Int -> [a] -> T a
fromPolynomial :: T a -> T a
fromPowerSeries :: T a -> T a
bounds :: T a -> (Int, Int)
translate :: Int -> T a -> T a
appPrec :: Int
add :: C a => T a -> T a -> T a
series :: C a => [T a] -> T a
addShiftedMany :: C a => [Int] -> [[a]] -> [a]
addShifted :: C a => Int -> [a] -> [a] -> [a]
negate :: C a => T a -> T a
sub :: C a => T a -> T a -> T a
scale :: C a => a -> [a] -> [a]
mul :: C a => T a -> T a -> T a
div :: (C a, C a) => T a -> T a -> T a
divExample :: T Rational
equivalent :: (Eq a, C a) => T a -> T a -> Bool
identical :: Eq a => T a -> T a -> Bool
isAbsolute :: C a => T a -> Bool
alternate :: C a => T a -> T a
reverse :: T a -> T a
adjoint :: C a => T (T a) -> T (T a)
Documentation
data T a
Polynomial including negative exponents
Constructors
Cons
expon :: Int
coeffs :: [a]
show/hide Instances
C T
Functor T
C a b => C a (T b)
(C a, C a b) => C a (T b)
C a => C (T a)
C a => C (T a)
(C a, C a) => C (T a)
(Eq a, C a) => Eq (T a)
Show a => Show (T a)
Basic Operations
const :: a -> T a
(!) :: C a => T a -> Int -> a
fromCoeffs :: [a] -> T a
fromShiftCoeffs :: Int -> [a] -> T a
fromPolynomial :: T a -> T a
fromPowerSeries :: T a -> T a
bounds :: T a -> (Int, Int)
translate :: Int -> T a -> T a
Show
appPrec :: Int
Additive
add :: C a => T a -> T a -> T a
series :: C a => [T a] -> T a
addShiftedMany :: C a => [Int] -> [[a]] -> [a]

Add lists of numbers respecting a relative shift between the starts of the lists. The shifts must be non-negative. The list of relative shifts is one element shorter than the list of summands. Infinitely many summands are permitted, provided that runs of zero shifts are all finite.

We could add the lists either with foldl or with foldr, foldl would be straightforward, but more time consuming (quadratic time) whereas foldr is not so obvious but needs only linear time.

(stars denote the coefficients, frames denote what is contained in the interim results) foldl sums this way:

 | | | *******************************
 | | +--------------------------------
 | |          ************************
 | +----------------------------------
 |                        ************
 +------------------------------------

I.e. foldl would use much time find the time differences by successive subtraction 1.

foldr mixes this way:

     +--------------------------------
     | *******************************
     |      +-------------------------
     |      | ************************
     |      |           +-------------
     |      |           | ************
addShifted :: C a => Int -> [a] -> [a] -> [a]
negate :: C a => T a -> T a
sub :: C a => T a -> T a -> T a
Module
scale :: C a => a -> [a] -> [a]
Ring
mul :: C a => T a -> T a -> T a
Field.C
div :: (C a, C a) => T a -> T a -> T a
divExample :: T Rational
Comparisons
equivalent :: (Eq a, C a) => T a -> T a -> Bool
Two polynomials may be stored differently. This function checks whether two values of type LaurentPolynomial actually represent the same polynomial.
identical :: Eq a => T a -> T a -> Bool
isAbsolute :: C a => T a -> Bool
Check whether a Laurent polynomial has only the absolute term, that is, it represents the constant polynomial.
Transformations of arguments
alternate :: C a => T a -> T a
p(z) -> p(-z)
reverse :: T a -> T a
p(z) -> p(1/z)
adjoint :: C a => T (T a) -> T (T a)

p(exp(i·x)) -> conjugate(p(exp(i·x)))

If you interpret (p*) as a linear operator on the space of Laurent polynomials, then (adjoint p *) is the adjoint operator.

Produced by Haddock version 0.7