Safe Haskell | None |
---|---|
Language | Haskell2010 |
- Trivial series
- Basic operations on power series
- Convolution (product)
- Reciprocals of general power series
- Composition of formal power series
- Lagrange inversions
- Differentiation and integration
- Power series expansions of elementary functions
- "Coin" series
- Reciprocals of products of polynomials
- Reciprocals of polynomials
Some basic univariate power series expansions. This module is not re-exported by Math.Combinat.
Note: the "convolveWithXXX
" functions are much faster than the equivalent
(XXX `convolve`)
!
TODO: better names for these functions.
Synopsis
- unitSeries :: Num a => [a]
- zeroSeries :: Num a => [a]
- constSeries :: Num a => a -> [a]
- idSeries :: Num a => [a]
- powerTerm :: Num a => Int -> [a]
- addSeries :: Num a => [a] -> [a] -> [a]
- sumSeries :: Num a => [[a]] -> [a]
- subSeries :: Num a => [a] -> [a] -> [a]
- negateSeries :: Num a => [a] -> [a]
- scaleSeries :: Num a => a -> [a] -> [a]
- mulSeries :: Num a => [a] -> [a] -> [a]
- mulSeriesNaive :: Num a => [a] -> [a] -> [a]
- productOfSeries :: Num a => [[a]] -> [a]
- convolve :: Num a => [a] -> [a] -> [a]
- convolveMany :: Num a => [[a]] -> [a]
- divSeries :: (Eq a, Fractional a) => [a] -> [a] -> [a]
- reciprocalSeries :: (Eq a, Fractional a) => [a] -> [a]
- integralReciprocalSeries :: (Eq a, Num a) => [a] -> [a]
- composeSeries :: (Eq a, Num a) => [a] -> [a] -> [a]
- substitute :: (Eq a, Num a) => [a] -> [a] -> [a]
- composeSeriesNaive :: (Eq a, Num a) => [a] -> [a] -> [a]
- substituteNaive :: (Eq a, Num a) => [a] -> [a] -> [a]
- lagrangeInversion :: (Eq a, Fractional a) => [a] -> [a]
- lagrangeCoeff :: Partition -> Integer
- integralLagrangeInversionNaive :: (Eq a, Num a) => [a] -> [a]
- lagrangeInversionNaive :: (Eq a, Fractional a) => [a] -> [a]
- differentiateSeries :: Num a => [a] -> [a]
- integrateSeries :: Fractional a => [a] -> [a]
- expSeries :: Fractional a => [a]
- cosSeries :: Fractional a => [a]
- sinSeries :: Fractional a => [a]
- cosSeries2 :: Fractional a => [a]
- sinSeries2 :: Fractional a => [a]
- coshSeries :: Fractional a => [a]
- sinhSeries :: Fractional a => [a]
- log1Series :: Fractional a => [a]
- dyckSeries :: Num a => [a]
- coinSeries :: [Int] -> [Integer]
- coinSeries' :: Num a => [(a, Int)] -> [a]
- convolveWithCoinSeries :: [Int] -> [Integer] -> [Integer]
- convolveWithCoinSeries' :: Num a => [(a, Int)] -> [a] -> [a]
- productPSeries :: [[Int]] -> [Integer]
- productPSeries' :: Num a => [[(a, Int)]] -> [a]
- convolveWithProductPSeries :: [[Int]] -> [Integer] -> [Integer]
- convolveWithProductPSeries' :: Num a => [[(a, Int)]] -> [a] -> [a]
- pseries :: [Int] -> [Integer]
- convolveWithPSeries :: [Int] -> [Integer] -> [Integer]
- pseries' :: Num a => [(a, Int)] -> [a]
- convolveWithPSeries' :: Num a => [(a, Int)] -> [a] -> [a]
- signedPSeries :: [(Sign, Int)] -> [Integer]
- convolveWithSignedPSeries :: [(Sign, Int)] -> [Integer] -> [Integer]
Trivial series
unitSeries :: Num a => [a] Source #
The series [1,0,0,0,0,...], which is the neutral element for the convolution.
zeroSeries :: Num a => [a] Source #
Constant zero series
constSeries :: Num a => a -> [a] Source #
Power series representing a constant function
Basic operations on power series
negateSeries :: Num a => [a] -> [a] Source #
scaleSeries :: Num a => a -> [a] -> [a] Source #
mulSeries :: Num a => [a] -> [a] -> [a] Source #
A different implementation, taken from:
M. Douglas McIlroy: Power Series, Power Serious
mulSeriesNaive :: Num a => [a] -> [a] -> [a] Source #
Multiplication of power series. This implementation is a synonym for convolve
productOfSeries :: Num a => [[a]] -> [a] Source #
Convolution (product)
convolve :: Num a => [a] -> [a] -> [a] Source #
Convolution of series (that is, multiplication of power series). The result is always an infinite list. Warning: This is slow!
convolveMany :: Num a => [[a]] -> [a] Source #
Convolution (= product) of many series. Still slow!
Reciprocals of general power series
divSeries :: (Eq a, Fractional a) => [a] -> [a] -> [a] Source #
Division of series.
Taken from: M. Douglas McIlroy: Power Series, Power Serious
reciprocalSeries :: (Eq a, Fractional a) => [a] -> [a] Source #
Given a power series, we iteratively compute its multiplicative inverse
integralReciprocalSeries :: (Eq a, Num a) => [a] -> [a] Source #
Given a power series starting with 1
, we can compute its multiplicative inverse
without divisions.
Composition of formal power series
composeSeries :: (Eq a, Num a) => [a] -> [a] -> [a] Source #
g `composeSeries` f
is the power series expansion of g(f(x))
.
This is a synonym for flip substitute
.
This implementation is taken from
M. Douglas McIlroy: Power Series, Power Serious
substitute :: (Eq a, Num a) => [a] -> [a] -> [a] Source #
substitute f g
is the power series corresponding to g(f(x))
.
Equivalently, this is the composition of univariate functions (in the "wrong" order).
Note: for this to be meaningful in general (not depending on convergence properties),
we need that the constant term of f
is zero.
composeSeriesNaive :: (Eq a, Num a) => [a] -> [a] -> [a] Source #
Naive implementation of composeSeries
(via substituteNaive
)
substituteNaive :: (Eq a, Num a) => [a] -> [a] -> [a] Source #
Naive implementation of substitute
Lagrange inversions
lagrangeInversion :: (Eq a, Fractional a) => [a] -> [a] Source #
We expect the input series to match (0:a1:_)
. with a1 nonzero The following is true for the result (at least with exact arithmetic):
substitute f (lagrangeInversion f) == (0 : 1 : repeat 0) substitute (lagrangeInversion f) f == (0 : 1 : repeat 0)
This implementation is taken from:
M. Douglas McIlroy: Power Series, Power Serious
lagrangeCoeff :: Partition -> Integer Source #
Coefficients of the Lagrange inversion
integralLagrangeInversionNaive :: (Eq a, Num a) => [a] -> [a] Source #
We expect the input series to match (0:1:_)
. The following is true for the result (at least with exact arithmetic):
substitute f (integralLagrangeInversion f) == (0 : 1 : repeat 0) substitute (integralLagrangeInversion f) f == (0 : 1 : repeat 0)
lagrangeInversionNaive :: (Eq a, Fractional a) => [a] -> [a] Source #
Naive implementation of lagrangeInversion
Differentiation and integration
differentiateSeries :: Num a => [a] -> [a] Source #
integrateSeries :: Fractional a => [a] -> [a] Source #
Power series expansions of elementary functions
expSeries :: Fractional a => [a] Source #
Power series expansion of exp(x)
cosSeries :: Fractional a => [a] Source #
Power series expansion of cos(x)
sinSeries :: Fractional a => [a] Source #
Power series expansion of sin(x)
cosSeries2 :: Fractional a => [a] Source #
Alternative implementation using differential equations.
Taken from: M. Douglas McIlroy: Power Series, Power Serious
sinSeries2 :: Fractional a => [a] Source #
Alternative implementation using differential equations.
Taken from: M. Douglas McIlroy: Power Series, Power Serious
coshSeries :: Fractional a => [a] Source #
Power series expansion of cosh(x)
sinhSeries :: Fractional a => [a] Source #
Power series expansion of sinh(x)
log1Series :: Fractional a => [a] Source #
Power series expansion of log(1+x)
dyckSeries :: Num a => [a] Source #
Power series expansion of (1-Sqrt[1-4x])/(2x)
(the coefficients are the Catalan numbers)
"Coin" series
coinSeries :: [Int] -> [Integer] Source #
Power series expansion of
1 / ( (1-x^k_1) * (1-x^k_2) * ... * (1-x^k_n) )
Example:
(coinSeries [2,3,5])!!k
is the number of ways
to pay k
dollars with coins of two, three and five dollars.
TODO: better name?
coinSeries' :: Num a => [(a, Int)] -> [a] Source #
Generalization of the above to include coefficients: expansion of
1 / ( (1-a_1*x^k_1) * (1-a_2*x^k_2) * ... * (1-a_n*x^k_n) )
convolveWithCoinSeries' :: Num a => [(a, Int)] -> [a] -> [a] Source #
Reciprocals of products of polynomials
productPSeries :: [[Int]] -> [Integer] Source #
Convolution of many pseries
, that is, the expansion of the reciprocal
of a product of polynomials
productPSeries' :: Num a => [[(a, Int)]] -> [a] Source #
The same, with coefficients.
convolveWithProductPSeries' :: Num a => [[(a, Int)]] -> [a] -> [a] Source #
This is the most general function in this module; all the others are special cases of this one.
Reciprocals of polynomials
pseries :: [Int] -> [Integer] Source #
The power series expansion of
1 / (1 - x^k_1 - x^k_2 - x^k_3 - ... - x^k_n)
convolveWithPSeries :: [Int] -> [Integer] -> [Integer] Source #
Convolve with (the expansion of)
1 / (1 - x^k_1 - x^k_2 - x^k_3 - ... - x^k_n)
pseries' :: Num a => [(a, Int)] -> [a] Source #
The expansion of
1 / (1 - a_1*x^k_1 - a_2*x^k_2 - a_3*x^k_3 - ... - a_n*x^k_n)
convolveWithPSeries' :: Num a => [(a, Int)] -> [a] -> [a] Source #
Convolve with (the expansion of)
1 / (1 - a_1*x^k_1 - a_2*x^k_2 - a_3*x^k_3 - ... - a_n*x^k_n)
convolveWithSignedPSeries :: [(Sign, Int)] -> [Integer] -> [Integer] Source #
Convolve with (the expansion of)
1 / (1 +- x^k_1 +- x^k_2 +- x^k_3 +- ... +- x^k_n)
Should be faster than using convolveWithPSeries'
.
Note: Plus
corresponds to the coefficient -1
in pseries'
(since
there is a minus sign in the definition there)!