Safe Haskell | None |
---|---|
Language | Haskell98 |
- evaluate :: C a => [a] -> a -> a
- evaluateCoeffVector :: C a v => [v] -> a -> v
- evaluateArgVector :: (C a v, C v) => [a] -> v -> v
- approximate :: C a => [a] -> a -> [a]
- approximateCoeffVector :: C a v => [v] -> a -> [v]
- approximateArgVector :: (C a v, C v) => [a] -> v -> [v]
- alternate :: C a => [a] -> [a]
- holes2 :: C a => [a] -> [a]
- holes2alternate :: C a => [a] -> [a]
- insertHoles :: C a => Int -> [a] -> [a]
- add :: C a => [a] -> [a] -> [a]
- sub :: C a => [a] -> [a] -> [a]
- negate :: C a => [a] -> [a]
- scale :: C a => a -> [a] -> [a]
- mul :: C a => [a] -> [a] -> [a]
- stripLeadZero :: C a => [a] -> [a] -> ([a], [a])
- divMod :: (C a, C a) => [a] -> [a] -> ([a], [a])
- divide :: C a => [a] -> [a] -> [a]
- divideStripZero :: (C a, C a) => [a] -> [a] -> [a]
- progression :: C a => [a]
- recipProgression :: C a => [a]
- differentiate :: C a => [a] -> [a]
- integrate :: C a => a -> [a] -> [a]
- sqrt :: C a => (a -> a) -> [a] -> [a]
- pow :: C a => (a -> a) -> a -> [a] -> [a]
- exp :: C a => (a -> a) -> [a] -> [a]
- sinCos :: C a => (a -> (a, a)) -> [a] -> ([a], [a])
- sinCosScalar :: C a => a -> (a, a)
- sin :: C a => (a -> (a, a)) -> [a] -> [a]
- cos :: C a => (a -> (a, a)) -> [a] -> [a]
- tan :: C a => (a -> (a, a)) -> [a] -> [a]
- log :: C a => (a -> a) -> [a] -> [a]
- derivedLog :: C a => [a] -> [a]
- atan :: C a => (a -> a) -> [a] -> [a]
- asin :: C a => (a -> a) -> (a -> a) -> [a] -> [a]
- acos :: C a => (a -> a) -> (a -> a) -> [a] -> [a]
- compose :: C a => [a] -> [a] -> [a]
- composeTaylor :: C a => (a -> [a]) -> [a] -> [a]
- inv :: (Eq a, C a) => [a] -> (a, [a])
- invDiff :: C a => [a] -> (a, [a])
Documentation
evaluateCoeffVector :: C a v => [v] -> a -> v Source #
evaluateArgVector :: (C a v, C v) => [a] -> v -> v Source #
approximate :: C a => [a] -> a -> [a] Source #
approximateCoeffVector :: C a v => [v] -> a -> [v] Source #
approximateArgVector :: (C a v, C v) => [a] -> v -> [v] Source #
Simple series manipulation
alternate :: C a => [a] -> [a] Source #
For the series of a real function f
compute the series for x -> f (-x)
holes2 :: C a => [a] -> [a] Source #
For the series of a real function f
compute the series for x -> (f x + f (-x)) / 2
holes2alternate :: C a => [a] -> [a] Source #
For the series of a real function f
compute the real series for x -> (f (i*x) + f (-i*x)) / 2
insertHoles :: C a => Int -> [a] -> [a] Source #
For power series of f x
, compute the power series of f(x^n)
.
Series arithmetic
stripLeadZero :: C a => [a] -> [a] -> ([a], [a]) Source #
divide :: C a => [a] -> [a] -> [a] Source #
Divide two series where the absolute term of the divisor is non-zero. That is, power series with leading non-zero terms are the units in the ring of power series.
Knuth: Seminumerical algorithms
divideStripZero :: (C a, C a) => [a] -> [a] -> [a] Source #
Divide two series also if the divisor has leading zeros.
progression :: C a => [a] Source #
recipProgression :: C a => [a] Source #
differentiate :: C a => [a] -> [a] Source #
sqrt :: C a => (a -> a) -> [a] -> [a] Source #
We need to compute the square root only of the first term. That is, if the first term is rational, then all terms of the series are rational.
pow :: C a => (a -> a) -> a -> [a] -> [a] Source #
Input series must start with a non-zero term, even better with a positive one.
exp :: C a => (a -> a) -> [a] -> [a] Source #
The first term needs a transcendent computation but the others do not. That's why we accept a function which computes the first term.
(exp . x)' = (exp . x) * x' (sin . x)' = (cos . x) * x' (cos . x)' = - (sin . x) * x'
sinCosScalar :: C a => a -> (a, a) Source #
derivedLog :: C a => [a] -> [a] Source #
Computes (log x)'
, that is x'/x
compose :: C a => [a] -> [a] -> [a] Source #
Since the inner series must start with a zero, the first term is omitted in y.
composeTaylor :: C a => (a -> [a]) -> [a] -> [a] Source #
Compose two power series where the outer series can be developed for any expansion point. To be more precise: The outer series must be expanded with respect to the leading term of the inner series.
inv :: (Eq a, C a) => [a] -> (a, [a]) Source #
This function returns the series of the inverse function in the form: (point of the expansion, power series).
That is, say we have the equation:
y = a + f(x)
where function f is given by a power series with f(0) = 0. We want to solve for x:
x = f^-1(y-a)
If you pass the power series of a+f(x)
to inv
,
you get (a, f^-1)
as answer, where f^-1
is a power series.
The linear term of f
(the coefficient of x
) must be non-zero.
This needs cubic run-time and thus is exceptionally slow. Computing inverse series for special power series might be faster.