numeric-prelude-0.4.3: An experimental alternative hierarchy of numeric type classes

Copyright(c) Henning Thielemann 2004-2006
Maintainernumericprelude@henning-thielemann.de
Stabilityprovisional
Portabilityrequires multi-parameter type classes
Safe HaskellNone
LanguageHaskell98

MathObj.LaurentPolynomial

Contents

Description

Polynomials with negative and positive exponents.

Synopsis

Documentation

data T a Source #

Polynomial including negative exponents

Constructors

Cons 

Fields

Instances

Functor T Source # 

Methods

fmap :: (a -> b) -> T a -> T b #

(<$) :: a -> T b -> T a #

C T Source # 

Methods

zero :: C a => T a Source #

(<+>) :: C a => T a -> T a -> T a Source #

(*>) :: C a => a -> T a -> T a Source #

C a b => C a (T b) Source # 

Methods

(*>) :: a -> T b -> T b Source #

(C a, C a b) => C a (T b) Source # 
(Eq a, C a) => Eq (T a) Source # 

Methods

(==) :: T a -> T a -> Bool #

(/=) :: T a -> T a -> Bool #

Show a => Show (T a) Source # 

Methods

showsPrec :: Int -> T a -> ShowS #

show :: T a -> String #

showList :: [T a] -> ShowS #

C a => C (T a) Source # 

Methods

zero :: T a Source #

(+) :: T a -> T a -> T a Source #

(-) :: T a -> T a -> T a Source #

negate :: T a -> T a Source #

C a => C (T a) Source # 

Methods

(*) :: T a -> T a -> T a Source #

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

(C a, C a) => C (T a) Source # 

Methods

(/) :: T a -> T a -> T a Source #

recip :: T a -> T a Source #

fromRational' :: Rational -> T a Source #

(^-) :: T a -> Integer -> T a Source #

Basic Operations

const :: a -> T a Source #

(!) :: C a => T a -> Int -> a Source #

fromCoeffs :: [a] -> T a Source #

fromShiftCoeffs :: Int -> [a] -> T a Source #

bounds :: T a -> (Int, Int) Source #

shift :: Int -> T a -> T a Source #

translate :: Int -> T a -> T a Source #

Deprecated: In order to avoid confusion with Polynomial.translate, use shift instead

Show

Additive

add :: C a => T a -> T a -> T a Source #

series :: C a => [T a] -> T a Source #

addShiftedMany :: C a => [Int] -> [[a]] -> [a] Source #

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] Source #

negate :: C a => T a -> T a Source #

sub :: C a => T a -> T a -> T a Source #

Module

Ring

mul :: C a => T a -> T a -> T a Source #

Field.C

div :: (C a, C a) => T a -> T a -> T a Source #

Comparisons

equivalent :: (Eq a, C a) => T a -> T a -> Bool Source #

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 Source #

isAbsolute :: C a => T a -> Bool Source #

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 Source #

p(z) -> p(-z)

reverse :: T a -> T a Source #

p(z) -> p(1/z)

adjoint :: C a => T (T a) -> T (T a) Source #

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.