numeric-prelude-0.4.4: An experimental alternative hierarchy of numeric type classes
Safe HaskellNone
LanguageHaskell98

MathObj.PowerSeries.Core

Synopsis

Documentation

>>> import qualified MathObj.PowerSeries.Core as PS
>>> import qualified MathObj.PowerSeries.Example as PSE
>>> import Test.NumericPrelude.Utility (equalTrunc, (/\))
>>> import qualified Test.QuickCheck as QC
>>> import NumericPrelude.Numeric as NP
>>> import NumericPrelude.Base as P
>>> import Prelude ()
>>> import Control.Applicative (liftA3)
>>> 
>>> checkHoles ::
>>> Int -> ([Rational] -> [Rational]) ->
>>> Rational -> [Rational] -> QC.Property
>>> checkHoles trunc f x xs =
>>> QC.choose (1,10) /\ \expon ->
>>> equalTrunc trunc
>>> (f (PS.insertHoles expon (x:xs)) ++ repeat zero)
>>> (PS.insertHoles expon (f (x:xs)) ++ repeat zero)
>>> 
>>> genInvertible :: QC.Gen [Rational]
>>> genInvertible =
>>> liftA3 (\x0 x1 xs -> x0:x1:xs)
>>> QC.arbitrary (fmap QC.getNonZero QC.arbitrary) QC.arbitrary

evaluate :: C a => [a] -> a -> a Source #

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).

QC.choose (1,10) /\ \m -> QC.choose (1,10) /\ \n xs -> equalTrunc 100 (PS.insertHoles m $ PS.insertHoles n xs) (PS.insertHoles (m*n) xs)

Series arithmetic

add :: C a => [a] -> [a] -> [a] Source #

sub :: 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 #

divMod :: (C a, 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 #

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.

equalTrunc 50 PSE.sqrtExpl (PS.sqrt (\1 -> 1) [1,1])
equalTrunc 500 (1:1:repeat 0) (PS.sqrt (\1 -> 1) (PS.mul [1,1] [1,1]))
checkHoles 50 (PS.sqrt (\1 -> 1)) 1

pow :: C a => (a -> a) -> a -> [a] -> [a] Source #

Input series must start with a non-zero term, even better with a positive one.

equalTrunc 100 (PSE.powExpl (-1/3)) (PS.pow (\1 -> 1) (-1/3) [1,1])
equalTrunc 50 (PSE.powExpl (-1/3)) (PS.exp (\0 -> 1) (PS.scale (-1/3) PSE.log))
checkHoles 30 (PS.pow (\1 -> 1) (1/3)) 1
checkHoles 30 (PS.pow (\1 -> 1) (2/5)) 1

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'
equalTrunc 500 PSE.expExpl (PS.exp (\0 -> 1) [0,1])
equalTrunc 100 (1:1:repeat 0) (PS.exp (\0 -> 1) PSE.log)
checkHoles 30 (PS.exp (\0 -> 1)) 0

sinCos :: C a => (a -> (a, a)) -> [a] -> ([a], [a]) Source #

sinCosScalar :: C a => a -> (a, a) Source #

sin :: C a => (a -> (a, a)) -> [a] -> [a] Source #

equalTrunc 500 PSE.sinExpl (PS.sin (\0 -> (0,1)) [0,1])
equalTrunc 50 (0:1:repeat 0) (PS.sin (\0 -> (0,1)) PSE.asin)
checkHoles 20 (PS.sin (\0 -> (0,1))) 0

cos :: C a => (a -> (a, a)) -> [a] -> [a] Source #

equalTrunc 500 PSE.cosExpl (PS.cos (\0 -> (0,1)) [0,1])
checkHoles 20 (PS.cos (\0 -> (0,1))) 0

tan :: C a => (a -> (a, a)) -> [a] -> [a] Source #

equalTrunc 50 PSE.tanExpl (PS.tan (\0 -> (0,1)) [0,1])
equalTrunc 50 (0:1:repeat 0) (PS.tan (\0 -> (0,1)) PSE.atan)
checkHoles 20 (PS.tan (\0 -> (0,1))) 0

log :: C a => (a -> a) -> [a] -> [a] Source #

Input series must start with non-zero term.

equalTrunc 500 PSE.logExpl (PS.log (\1 -> 0) [1,1])
equalTrunc 100 (0:1:repeat 0) (PS.log (\1 -> 0) PSE.exp)
checkHoles 30 (PS.log (\1 -> 0)) 1

derivedLog :: C a => [a] -> [a] Source #

Computes (log x)', that is x'/x

atan :: C a => (a -> a) -> [a] -> [a] Source #

equalTrunc 500 PSE.atan (PS.atan (\0 -> 0) [0,1])
equalTrunc 50 (0:1:repeat 0) (PS.atan (\0 -> 0) PSE.tan)
checkHoles 20 (PS.atan (\0 -> 0)) 0

asin :: C a => (a -> a) -> (a -> a) -> [a] -> [a] Source #

equalTrunc 100 (0:1:repeat 0) (PS.asin (\1 -> 1) (\0 -> 0) PSE.sin)
equalTrunc 50 PSE.asin (PS.asin (\1 -> 1) (\0 -> 0) [0,1])
checkHoles 30 (PS.asin (\1 -> 1) (\0 -> 0)) 0

acos :: C a => (a -> a) -> (a -> a) -> [a] -> [a] Source #

Would be a nice test, but we cannot compute exactly with pi:

equalTrunc 50 PSE.acos (PS.acos (\1 -> 1) (\0 -> pi/2) [0,1])

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.

genInvertible /\ \xs -> let (y,ys) = PS.inv xs; (z,zs) = PS.invDiff xs in y==z && equalTrunc 15 ys zs

invDiff :: C a => [a] -> (a, [a]) Source #