Copyright | Copyright 2025 Yoo Chung |
---|---|
License | Apache-2.0 |
Maintainer | dev@chungyc.org |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Symtegration.Integration.Rational
Contents
Description
Integrates rational functions. Rational functions are ratios of two polynomials, not functions of rational numbers. Only rational number coefficients are supported.
Synopsis
- integrate :: Text -> Expression -> Maybe Expression
- hermiteReduce :: RationalFunction -> ([RationalFunction], RationalFunction)
- rationalIntegralLogTerms :: RationalFunction -> Maybe [(IndexedPolynomial, IndexedPolynomialWith IndexedPolynomial)]
- complexLogTermToAtan :: Text -> IndexedPolynomial -> IndexedPolynomial -> Expression
- complexLogTermToRealTerm :: (IndexedPolynomial, IndexedPolynomialWith IndexedPolynomial) -> ((IndexedPolynomialWith IndexedPolynomial, IndexedPolynomialWith IndexedPolynomial), (IndexedPolynomialWith (IndexedPolynomialWith IndexedPolynomial), IndexedPolynomialWith (IndexedPolynomialWith IndexedPolynomial)))
- type RationalFunction = Function IndexedPolynomial
Integration
integrate :: Text -> Expression -> Maybe Expression Source #
Integrate a ratio of two polynomials with rational number coefficients.
For example,
>>>
let p = "x" ** 7 - 24 * "x" ** 4 - 4 * "x" ** 2 + 8 * "x" - 8
>>>
let q = "x" ** 8 + 6 * "x" ** 6 + 12 * "x" ** 4 + 8 * "x" ** 2
>>>
toHaskell . simplify <$> integrate "x" (p / q)
Just "3 / (2 + x ** 2) + (4 + 8 * x ** 2) / (4 * x + 4 * x ** 3 + x ** 5) + log x"
so that
∫x7−24x4−4x2+8x−8x8+6x6+12x4+8x2dx=3x2+2+8x2+4x5+4x3+4x+logx
For another example,
>>>
let f = 36 / ("x" ** 5 - 2 * "x" ** 4 - 2 * "x" ** 3 + 4 * "x" ** 2 + "x" - 2)
>>>
toHaskell . simplify <$> integrate "x" f
Just "(-4) * log (8 + 8 * x) + 4 * log (16 + (-8) * x) + (6 + 12 * x) / ((-1) + x ** 2)"
so that
∫36x5−2x4−2x3+4x2+x−2dx=12x+6x2−1+4log(x−2)−4log(x+1)
This function will attempt to find a real function integral if it can, but if it cannot, it will try to find an integral which includes complex logarithms.
Algorithms
Algorithms used for integrating rational functions.
hermiteReduce :: RationalFunction -> ([RationalFunction], RationalFunction) Source #
Applies Hermite reduction to a rational function. Returns a list of rational functions whose sums add up to the integral and a rational function which remains to be integrated. Only rational functions with rational number coefficients and where the numerator and denominator are coprime are supported.
Specifically, for rational function f=AD,
where A and D are coprime polynomials, then for return value (gs, h)
,
the sum of gs
is equal to g and h
is equal to h in the following:
AD=dgdx+h
This is equivalent to the following:
∫ADdx=g+∫hdx
If preconditions are satisfied, i.e., D≠0 and A and D are coprime, then h will have a squarefree denominator.
For example,
>>>
let p = power 7 - 24 * power 4 - 4 * power 2 + 8 * power 1 - 8 :: IndexedPolynomial
>>>
let q = power 8 + 6 * power 6 + 12 * power 4 + 8 * power 2 :: IndexedPolynomial
>>>
hermiteReduce $ fromPolynomials p q
([Function (3) (x^2 + 2),Function (8x^2 + 4) (x^5 + 4x^3 + 4x)],Function (1) (x))
so that
∫x7−24x4−4x2+8x−8x8+6x6+12x4+8x2dx=3x2+2+8x2+4x5+4x3+4x+∫1xdx
g is returned as a list of rational functions which sum to g instead of a single rational function, because the former could sometimes be simpler to read.
rationalIntegralLogTerms :: RationalFunction -> Maybe [(IndexedPolynomial, IndexedPolynomialWith IndexedPolynomial)] Source #
For rational function AD, where deg(A)<deg(D), and D is non-zero, squarefree, and coprime with A, returns the components which form the logarithmic terms of ∫ADdx. Specifically, when a list of (Qi(t),Si(t,x)) is returned, where Qi(t) are polynomials of t and Si(t,x) are polynomials of x with coefficients formed from polynomials of t, then
∫ADdx=n∑i=1∑a∈{t∣Qi(t)=0}alog(Si(a,x))
For example,
>>>
let p = power 4 - 3 * power 2 + 6 :: IndexedPolynomial
>>>
let q = power 6 - 5 * power 4 + 5 * power 2 + 4 :: IndexedPolynomial
>>>
let f = fromPolynomials p q
>>>
let gs = rationalIntegralLogTerms f
>>>
length <$> gs
Just 1>>>
fst . head <$> gs
Just x^2 + (1 % 4)>>>
foldTerms (\e c -> show (e, c) <> " ") . snd . head <$> gs
Just "(0,792x^2 + (-16)) (1,(-2440)x^3 + 32x) (2,(-400)x^2 + 7) (3,800x^3 + (-14)x) "
so it is the case that
∫x4−3x2+6x6−5x4+5x2+4dx=∑a∣a2+14=0alog((800a3−14a)x3+(−400a2+7)x2+(−2440a3+32a)x+792a2−16)
It may return Nothing
if AD is not in the expected form.
Arguments
:: Text | Symbol for the variable. |
-> IndexedPolynomial | Polynomial A. |
-> IndexedPolynomial | Polynomial B. |
-> Expression | Sum f of inverse tangents. |
Given polynomials A and B, return a sum f of inverse tangents such that the following is true.
dfdx=ddxilog(A+iBA−iB)
This allows integrals to be evaluated with only real-valued functions. It also avoids the discontinuities in real-valued indefinite integrals which may result when the integral uses logarithms with complex arguments.
For example,
>>>
toHaskell $ simplify $ complexLogTermToAtan "x" (power 3 - 3 * power 1) (power 2 - 2)
"2 * atan x + 2 * atan ((x + (-3) * x ** 3 + x ** 5) / 2) + 2 * atan (x ** 3)"
so it is the case that
ddx(ilog((x3−3x)+i(x2−2)(x3−3x)−i(x2−2)))=ddx(2tan−1(x5−3x3+x2)+2tan−1(x3)+2tan−1x)
complexLogTermToRealTerm :: (IndexedPolynomial, IndexedPolynomialWith IndexedPolynomial) -> ((IndexedPolynomialWith IndexedPolynomial, IndexedPolynomialWith IndexedPolynomial), (IndexedPolynomialWith (IndexedPolynomialWith IndexedPolynomial), IndexedPolynomialWith (IndexedPolynomialWith IndexedPolynomial))) Source #
For the ingredients of a complex logarithm, return the ingredients of an equivalent real function in terms of an indefinite integral.
Specifically, for polynomials (R(t),S(t,x)) such that
dfdx=ddx∑α∈{t∣R(t)=0}(αlog(S(α,x)))
then with return value ((P(u,v),Q(u,v)),(A(u,v,x),B(u,v,x))),
and a return value guv from complexLogTermToAtan
for A(u,v) and B(u,v), the real function is
dfdx=ddx(∑(a,b)∈{(u,v)∈(R,R)∣P(u,v)=Q(u,v)=0,b>0}(alog(A(a,b,x)2+B(a,b,x)2)+bgab(x))+∑a∈{t∈R∣R(t)=0}(alog(S(a,x))))
The return value are polynomials ((P,Q),(A,B)), where
- P is a u-polynomial, i.e., a polynomial with variable u, with coefficients which are v-polynomials.
- Q is a u-polynomial, with coefficients which are v-polynomials.
- A is an x-polynomial, with coefficients which are u-polynomials, which in turn have coefficients with v-polynomials.
- B is an x-polynomial, with coefficients which are u-polynomials, which in turn have coefficients with v-polynomials.
For example,
>>>
let r = 4 * power 2 + 1 :: IndexedPolynomial
>>>
let s = power 3 + scale (2 * power 1) (power 2) - 3 * power 1 - scale (4 * power 1) 1 :: IndexedPolynomialWith IndexedPolynomial
>>>
complexLogTermToRealTerm (r, s)
(([(0,(-4)x^2 + 1),(2,4)],[(1,8x)]),([(0,[(1,(-4))]),(1,[(0,(-3))]),(2,[(1,2)]),(3,[(0,1)])],[(0,[(0,(-4)x)]),(2,[(0,2x)])]))
While the return value may be hard to parse, this means:
P=4u2−4v2+1Q=8uvA=x3+2ux2−3x−4uB=2vx2−4v
Types
type RationalFunction = Function IndexedPolynomial Source #
Rational functions which can be integrated by this module.