numeric-prelude-0.0.5: An experimental alternative hierarchy of numeric type classesSource codeContentsIndex
MathObj.PowerSeries
Contents
Simple series manipulation
Series arithmetic
Description
Power series, either finite or unbounded. (zipWith does exactly the right thing to make it work almost transparently.)
Synopsis
newtype T a = Cons {
coeffs :: [a]
}
fromCoeffs :: [a] -> T a
lift0 :: [a] -> T a
lift1 :: ([a] -> [a]) -> T a -> T a
lift2 :: ([a] -> [a] -> [a]) -> T a -> T a -> T a
const :: a -> T a
appPrec :: Int
truncate :: Int -> T a -> T a
eval :: C a => [a] -> a -> a
evaluate :: C a => T a -> a -> a
evalCoeffVector :: C a v => [v] -> a -> v
evaluateCoeffVector :: C a v => T v -> a -> v
evalArgVector :: (C a v, C v) => [a] -> v -> v
evaluateArgVector :: (C a v, C v) => T a -> v -> v
approx :: C a => [a] -> a -> [a]
approximate :: C a => T a -> a -> [a]
approxCoeffVector :: C a v => [v] -> a -> [v]
approximateCoeffVector :: C a v => T v -> a -> [v]
approxArgVector :: (C a v, C v) => [a] -> v -> [v]
approximateArgVector :: (C a v, C v) => T a -> v -> [v]
alternate :: C a => [a] -> [a]
holes2 :: C a => [a] -> [a]
holes2alternate :: C a => [a] -> [a]
sub :: C a => [a] -> [a] -> [a]
add :: 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])
divide :: C a => [a] -> [a] -> [a]
divideStripZero :: (C a, C a) => [a] -> [a] -> [a]
divMod :: (C a, C a) => [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)
cos :: C a => (a -> (a, a)) -> [a] -> [a]
sin :: 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]
acos :: C a => (a -> a) -> (a -> a) -> [a] -> [a]
asin :: C a => (a -> a) -> (a -> a) -> [a] -> [a]
compose :: (C a, C a) => T a -> T a -> T a
comp :: C a => [a] -> [a] -> [a]
composeTaylor :: C a => (a -> [a]) -> [a] -> [a]
inv :: C a => [a] -> (a, [a])
Documentation
newtype T a Source
Constructors
Cons
coeffs :: [a]
show/hide Instances
Functor T
C T
C a b => C a (T b)
(C a, C a b) => C a (T b)
(Eq a, C a) => Eq (T a)
(Ord a, C a) => Ord (T a)
Show a => Show (T a)
C a => C (T a)
C a => C (T a)
C a => C (T a)
(C a, C a) => C (T a)
C a => C (T a)
C a => C (T a)
C a => C (T a)
fromCoeffs :: [a] -> T aSource
lift0 :: [a] -> T aSource
lift1 :: ([a] -> [a]) -> T a -> T aSource
lift2 :: ([a] -> [a] -> [a]) -> T a -> T a -> T aSource
const :: a -> T aSource
appPrec :: IntSource
truncate :: Int -> T a -> T aSource
eval :: C a => [a] -> a -> aSource
Evaluate (truncated) power series.
evaluate :: C a => T a -> a -> aSource
evalCoeffVector :: C a v => [v] -> a -> vSource
Evaluate (truncated) power series.
evaluateCoeffVector :: C a v => T v -> a -> vSource
evalArgVector :: (C a v, C v) => [a] -> v -> vSource
evaluateArgVector :: (C a v, C v) => T a -> v -> vSource
approx :: C a => [a] -> a -> [a]Source
Evaluate approximations that is evaluate all truncations of the series.
approximate :: C a => T a -> a -> [a]Source
approxCoeffVector :: C a v => [v] -> a -> [v]Source
Evaluate approximations that is evaluate all truncations of the series.
approximateCoeffVector :: C a v => T v -> a -> [v]Source
approxArgVector :: (C a v, C v) => [a] -> v -> [v]Source
Evaluate approximations that is evaluate all truncations of the series.
approximateArgVector :: (C a v, C v) => T 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
Series arithmetic
sub :: C a => [a] -> [a] -> [a]Source
add :: C a => [a] -> [a] -> [a]Source
negate :: C a => [a] -> [a]Source
scale :: C a => a -> [a] -> [a]Source
mul :: C a => [a] -> [a] -> [a]Source
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.
divMod :: (C a, C a) => [a] -> [a] -> ([a], [a])Source
progression :: C a => [a]Source
recipProgression :: C a => [a]Source
differentiate :: C a => [a] -> [a]Source
integrate :: C a => 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 non-zero term.
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'
sinCos :: C a => (a -> (a, a)) -> [a] -> ([a], [a])Source
sinCosScalar :: C a => a -> (a, a)Source
cos :: C a => (a -> (a, a)) -> [a] -> [a]Source
sin :: C a => (a -> (a, a)) -> [a] -> [a]Source
tan :: C a => (a -> (a, a)) -> [a] -> [a]Source
log :: C a => (a -> a) -> [a] -> [a]Source
Input series must start with non-zero term.
derivedLog :: C a => [a] -> [a]Source
Computes (log x)', that is x'/x
atan :: C a => (a -> a) -> [a] -> [a]Source
acos :: C a => (a -> a) -> (a -> a) -> [a] -> [a]Source
asin :: C a => (a -> a) -> (a -> a) -> [a] -> [a]Source
compose :: (C a, C a) => T a -> T a -> T aSource
It fulfills evaluate x . evaluate y == evaluate (compose x y)
comp :: 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 :: C a => [a] -> (a, [a])Source

This function returns the series of the function in the form: (point of the expansion, power series)

This is exceptionally slow and needs cubic run-time.

Produced by Haddock version 2.6.0