Copyright | (c) Stéphane Laurent 2023 |
---|---|
License | GPL-3 |
Maintainer | laurent_step@outlook.fr |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Math.Algebra.Hspray
Contents
- Main types
- Basic sprays
- Operations on sprays
- Showing a spray
- Univariate polynomials and fractions of univariate polynomials
- Symbolic sprays
- Queries on a spray
- Evaluation of a spray
- Differentiation of a spray
- Permutation of the variables of a spray
- Division of a spray
- Gröbner basis
- Symmetric polynomials
- Resultant and subresultants
- Greatest common divisor
- Miscellaneous
Description
Deals with multivariate polynomials on a commutative ring. See README for examples.
Synopsis
- data Powers = Powers {
- exponents :: Seq Int
- nvariables :: Int
- type Spray a = HashMap Powers a
- type QSpray = Spray Rational
- type QSpray' = Spray Rational'
- type Monomial a = (Powers, a)
- lone :: C a => Int -> Spray a
- unitSpray :: C a => Spray a
- zeroSpray :: (Eq a, C a) => Spray a
- constantSpray :: (C a, Eq a) => a -> Spray a
- (*^) :: (C a, Eq a) => a -> Spray a -> Spray a
- (.^) :: (C a, Eq a) => Int -> Spray a -> Spray a
- (^+^) :: (C a, Eq a) => Spray a -> Spray a -> Spray a
- (^-^) :: (C a, Eq a) => Spray a -> Spray a -> Spray a
- (^*^) :: (C a, Eq a) => Spray a -> Spray a -> Spray a
- (^**^) :: (C a, Eq a) => Spray a -> Int -> Spray a
- prettySpray :: Show a => Spray a -> String
- prettySpray' :: Show a => Spray a -> String
- prettySpray'' :: Show a => String -> Spray a -> String
- prettySprayXYZ :: Show a => [String] -> Spray a -> String
- prettySprayX1X2X3 :: Show a => String -> Spray a -> String
- showSpray :: (a -> String) -> (String, String) -> ([Seq Int] -> [String]) -> Spray a -> String
- showSprayXYZ :: (a -> String) -> (String, String) -> [String] -> Spray a -> String
- showSprayXYZ' :: (a -> String) -> [String] -> Spray a -> String
- showSprayX1X2X3 :: (a -> String) -> (String, String) -> String -> Spray a -> String
- showSprayX1X2X3' :: (a -> String) -> String -> Spray a -> String
- showNumSpray :: (Num a, Ord a) => ([Seq Int] -> [String]) -> (a -> String) -> Spray a -> String
- showQSpray :: ([Seq Int] -> [String]) -> QSpray -> String
- showQSpray' :: ([Seq Int] -> [String]) -> QSpray' -> String
- prettyNumSprayX1X2X3 :: (Num a, Ord a, Show a) => String -> Spray a -> String
- prettyQSprayX1X2X3 :: String -> QSpray -> String
- prettyQSprayX1X2X3' :: String -> QSpray' -> String
- prettyNumSprayXYZ :: (Num a, Ord a, Show a) => [String] -> Spray a -> String
- prettyQSprayXYZ :: [String] -> QSpray -> String
- prettyQSprayXYZ' :: [String] -> QSpray' -> String
- prettyNumSpray :: (Num a, Ord a, Show a) => Spray a -> String
- prettyNumSpray' :: (Num a, Ord a, Show a) => Spray a -> String
- prettyQSpray :: QSpray -> String
- prettyQSpray'' :: QSpray -> String
- prettyQSpray' :: QSpray' -> String
- prettyQSpray''' :: QSpray' -> String
- newtype A a = A a
- type Rational' = Rational
- type Q = A Rational'
- scalarQ :: Rational' -> Q
- type Polynomial a = T (A a)
- type RatioOfPolynomials a = T (Polynomial a)
- type QPolynomial = Polynomial Rational'
- type RatioOfQPolynomials = RatioOfPolynomials Rational'
- (^/^) :: (Eq a, C a) => Polynomial a -> Polynomial a -> RatioOfPolynomials a
- prettyRatioOfPolynomials :: (Eq a, C a, Show a) => String -> RatioOfPolynomials a -> String
- prettyRatioOfQPolynomials :: String -> RatioOfQPolynomials -> String
- (*.) :: (Eq a, C a) => a -> RatioOfPolynomials a -> RatioOfPolynomials a
- constPoly :: a -> Polynomial a
- polyFromCoeffs :: [a] -> Polynomial a
- outerVariable :: C a => Polynomial a
- constQPoly :: Rational' -> QPolynomial
- qpolyFromCoeffs :: [Rational'] -> QPolynomial
- outerQVariable :: QPolynomial
- evalRatioOfPolynomials :: C a => a -> RatioOfPolynomials a -> a
- type SymbolicSpray a = Spray (RatioOfPolynomials a)
- type SymbolicQSpray = SymbolicSpray Rational'
- prettySymbolicSprayX1X2X3 :: (Eq a, Show a, C a) => String -> String -> SymbolicSpray a -> String
- prettySymbolicSprayXYZ :: (Eq a, Show a, C a) => String -> [String] -> SymbolicSpray a -> String
- prettySymbolicSpray :: (Eq a, Show a, C a) => String -> SymbolicSpray a -> String
- prettySymbolicSpray' :: (Eq a, Show a, C a) => String -> SymbolicSpray a -> String
- prettySymbolicQSprayX1X2X3 :: String -> String -> SymbolicQSpray -> String
- prettySymbolicQSprayXYZ :: String -> [String] -> SymbolicQSpray -> String
- prettySymbolicQSpray :: String -> SymbolicQSpray -> String
- prettySymbolicQSpray' :: String -> SymbolicQSpray -> String
- simplifySymbolicSpray :: (Eq a, C a) => SymbolicSpray a -> SymbolicSpray a
- evalSymbolicSpray :: C a => SymbolicSpray a -> a -> Spray a
- evalSymbolicSpray' :: C a => SymbolicSpray a -> a -> [a] -> a
- evalSymbolicSpray'' :: (Eq a, C a) => SymbolicSpray a -> [a] -> RatioOfPolynomials a
- getCoefficient :: C a => [Int] -> Spray a -> a
- getConstantTerm :: C a => Spray a -> a
- numberOfVariables :: Spray a -> Int
- sprayTerms :: Spray a -> HashMap (Seq Int) a
- evalSpray :: C a => Spray a -> [a] -> a
- substituteSpray :: (Eq a, C a) => [Maybe a] -> Spray a -> Spray a
- composeSpray :: forall a. (C a, Eq a) => Spray a -> [Spray a] -> Spray a
- derivSpray :: (C a, Eq a) => Int -> Spray a -> Spray a
- permuteVariables :: [Int] -> Spray a -> Spray a
- swapVariables :: (Int, Int) -> Spray a -> Spray a
- sprayDivision :: forall a. (Eq a, C a) => Spray a -> Spray a -> (Spray a, Spray a)
- sprayDivisionRemainder :: forall a. (Eq a, C a) => Spray a -> [Spray a] -> Spray a
- groebner :: forall a. (Eq a, C a) => [Spray a] -> Bool -> [Spray a]
- reduceGroebnerBasis :: forall a. (Eq a, C a) => [Spray a] -> [Spray a]
- esPolynomial :: (C a, Eq a) => Int -> Int -> Spray a
- psPolynomial :: forall a. (C a, Eq a) => Int -> Int -> Spray a
- isSymmetricSpray :: forall a. (C a, Eq a) => Spray a -> Bool
- resultant :: (Eq a, C a) => Int -> Spray a -> Spray a -> Spray a
- resultant' :: forall a. (Eq a, C a) => Int -> Spray a -> Spray a -> Spray a
- resultant1 :: (Eq a, C a) => Spray a -> Spray a -> a
- subresultants :: (Eq a, C a) => Int -> Spray a -> Spray a -> [Spray a]
- subresultants1 :: (Eq a, C a) => Spray a -> Spray a -> [a]
- gcdSpray :: forall a. (Eq a, C a) => Spray a -> Spray a -> Spray a
- fromList :: (C a, Eq a) => [([Int], a)] -> Spray a
- toList :: Spray a -> [([Int], a)]
- fromRationalSpray :: Spray Rational -> Spray Double
- leadingTerm :: Spray a -> Monomial a
- isPolynomialOf :: forall a. (C a, Eq a) => Spray a -> [Spray a] -> (Bool, Maybe (Spray a))
- bombieriSpray :: C a => Spray a -> Spray a
- collinearSprays :: (Eq a, C a) => Spray a -> Spray a -> Bool
Main types
Instances
Show Powers Source # | |
Eq Powers Source # | |
Hashable Powers Source # | |
Defined in Math.Algebra.Hspray | |
(C a, Eq a) => C a (Spray a) Source # | |
Defined in Math.Algebra.Hspray | |
(C a, Eq a) => C (Spray a) Source # | |
(C a, Eq a) => C (Spray a) Source # | |
(Eq a, C a) => C (Polynomial a) (SymbolicSpray a) Source # | |
Defined in Math.Algebra.Hspray Methods (*>) :: Polynomial a -> SymbolicSpray a -> SymbolicSpray a # |
Basic sprays
lone :: C a => Int -> Spray a Source #
The n
-th polynomial variable x_n
as a spray; one usually builds a
spray by introducing these variables and combining them with the arithmetic
operations
>>>
x :: lone 1 :: Spray Int
>>>
y :: lone 2 :: Spray Int
>>>
spray = 2*^x^**^2 ^-^ 3*^y
>>>
putStrLn $ prettyNumSpray spray
2*x^2 - 3*y
lone 0 == unitSpray
constantSpray :: (C a, Eq a) => a -> Spray a Source #
Constant spray
constantSpray 3 == 3 *^ unitSpray
Operations on sprays
(*^) :: (C a, Eq a) => a -> Spray a -> Spray a infixr 7 Source #
Scale a spray by a scalar; if you import the Algebra.Module module
then it is the same operation as (*>)
from this module
(.^) :: (C a, Eq a) => Int -> Spray a -> Spray a infixr 7 Source #
Scale a spray by an integer
3 .^ p == p ^+^ p ^+^ p
Showing a spray
prettySpray :: Show a => Spray a -> String Source #
Pretty form of a spray with monomials displayed in the style of "x.z^2"
;
you should rather use prettyNumSpray
or prettyQSpray
if you deal with
sprays with numeric coefficients
>>>
x = lone 1 :: Spray Int
>>>
y = lone 2 :: Spray Int
>>>
z = lone 3 :: Spray Int
>>>
p = 2*^x ^+^ 3*^y^**^2 ^-^ 4*^z^**^3
>>>
putStrLn $ prettySpray p
(2)*x + (3)*y^2 + (-4)*z^3>>>
putStrLn $ prettySpray (p ^+^ lone 4)
(2)*x1 + (3)*x2^2 + (-4)*x3^3 + x4
prettySpray spray == prettySprayXYZ ["x", "y", "z"] spray
prettySpray' :: Show a => Spray a -> String Source #
Pretty form of a spray, with monomials shown as "x1.x3^2"
; use
prettySprayX1X2X3
to change the letter (or prettyNumSprayX1X2X3
or prettyQSprayX1X2X3
if the coefficients are numeric)
>>>
x = lone 1 :: Spray Int
>>>
y = lone 2 :: Spray Int
>>>
z = lone 3 :: Spray Int
>>>
p = 2*^x ^+^ 3*^y^**^2 ^-^ 4*^z^**^3
>>>
putStrLn $ prettySpray' p
(2)*x1 + (3)*x2^2 + (-4)*x3^3
Pretty form of a spray; you will probably prefer prettySpray
or prettySpray'
>>>
x = lone 1 :: Spray Int
>>>
y = lone 2 :: Spray Int
>>>
z = lone 3 :: Spray Int
>>>
p = 2*^x ^+^ 3*^y^**^2 ^-^ 4*^z^**^3
>>>
putStrLn $ prettySpray'' "x" p
(2)*x^(1) + (3)*x^(0, 2) + (-4)*x^(0, 0, 3)
Arguments
:: Show a | |
=> [String] | typically some letters, to print the variables |
-> Spray a | the spray to be printed |
-> String |
Pretty form of a spray with monomials displayed in the style of "x.z^2"
;
you should rather use prettyNumSprayXYZ
or prettyQSprayXYZ
if your
coefficients are numeric
>>>
x = lone 1 :: Spray Int
>>>
y = lone 2 :: Spray Int
>>>
z = lone 3 :: Spray Int
>>>
p = 2*^x ^+^ 3*^y^**^2 ^-^ 4*^z^**^3
>>>
putStrLn $ prettySprayXYZ ["X", "Y", "Z"] p
(2)*X + (3)*Y^2 + (-4)*Z^3>>>
putStrLn $ prettySprayXYZ ["X", "Y"] p
(2)*X1 + (3)*X2^2 + (-4)*X3^3
Arguments
:: Show a | |
=> String | typically a letter, to print the non-indexed variables |
-> Spray a | the spray to be printed |
-> String |
Pretty form of a spray with monomials displayed in the style of "x1.x3^2"
;
you should rather use prettyNumSprayX1X2X3
or prettyQSprayX1X2X3
if your
coefficients are numeric
>>>
x = lone 1 :: Spray Int
>>>
y = lone 2 :: Spray Int
>>>
z = lone 3 :: Spray Int
>>>
spray = 2*^x ^+^ 3*^y^**^2 ^-^ 4*^z^**^3
>>>
putStrLn $ prettySprayX1X2X3 "X" spray
(2)*X1 + (3)*X2^2 + (-4)*X3^3
Arguments
:: (a -> String) | function mapping a coefficient to a string, typically |
-> (String, String) | pair of braces to enclose the coefficients |
-> ([Seq Int] -> [String]) | function mapping a list of exponents to a list of strings representing the monomials corresponding to these exponents |
-> Spray a | the spray to be printed |
-> String |
Prints a spray; this function is exported for possible usage in other packages
Arguments
:: (a -> String) | function mapping a coefficient to a string, typically |
-> (String, String) | used to enclose the coefficients, usually a pair of braces |
-> [String] | strings, typically some letters, to print the variables |
-> Spray a | the spray to be printed |
-> String |
Prints a spray, with monomials shown as "x.z^2", and with a user-defined showing function for the coefficients
Arguments
:: (a -> String) | function mapping a coefficient to a string, typically |
-> [String] | strings, typically some letters, to print the variables |
-> Spray a | the spray to be printed |
-> String |
Prints a spray, with monomials shown as "x.z^2"
, and with
a user-defined showing function for the coefficients; this is the same as
the function showSprayXYZ
with the pair of braces ("(", ")")
Arguments
:: (a -> String) | function mapping a coefficient to a string, typically |
-> (String, String) | used to enclose the coefficients |
-> String | typically a letter, to print the non-indexed variables |
-> Spray a | the spray to be printed |
-> String |
Pretty form of a spray, with monomials shown as "x1.x3^2", and with a user-defined showing function for the coefficients
Arguments
:: (a -> String) | function mapping a coefficient to a string, e.g. |
-> String | typically a letter, to print the non-indexed variables |
-> Spray a | the spray to be printed |
-> String |
Pretty form of a spray, with monomials shown as "x1.x3^2", and with
a user-defined showing function for the coefficients; this is the same as
the function showSprayX1X2X3
with the pair of braces ("(", ")")
used to
enclose the coefficients
Arguments
:: (Num a, Ord a) | |
=> ([Seq Int] -> [String]) | function mapping a list of monomial exponents to a list of strings representing the monomials |
-> (a -> String) | function mapping a positive coefficient to a string |
-> Spray a | |
-> String |
Show a spray with numeric coefficients; this function is exported for possible usage in other packages
Prints a QSpray
; for internal usage but exported for usage in other packages
Arguments
:: ([Seq Int] -> [String]) | function mapping a list of monomials exponents to a list of strings |
-> QSpray' | |
-> String |
Prints a QSpray'
; for internal usage but exported for usage in other packages
Arguments
:: (Num a, Ord a, Show a) | |
=> String | usually a letter such as |
-> Spray a | |
-> String |
Pretty form of a spray with numeric coefficients, printing monomials as "x1.x3^2"
>>>
x = lone 1 :: Spray Int
>>>
y = lone 2 :: Spray Int
>>>
z = lone 3 :: Spray Int
>>>
p = 2*^x ^+^ 3*^y^**^2 ^-^ 4*^z^**^3
>>>
putStrLn $ prettyNumSprayX1X2X3 "x" p
2*x1 + 3*x2^2 - 4*x3^3
Arguments
:: String | usually a letter such as |
-> QSpray | |
-> String |
Pretty form of a spray with rational coefficients, printing monomials in
the style of "x1.x3^2"
>>>
x = lone 1 :: QSpray
>>>
y = lone 2 :: QSpray
>>>
z = lone 3 :: QSpray
>>>
p = 2*^x ^+^ 3*^y^**^2 ^-^ (4%3)*^z^**^3
>>>
putStrLn $ prettyQSprayX1X2X3 "x" p
2*x1 + 3*x2^2 - (4/3)*x3^3
Arguments
:: String | usually a letter such as |
-> QSpray' | |
-> String |
Same as prettyQSprayX1X2X3
but for a QSpray'
spray
Arguments
:: (Num a, Ord a, Show a) | |
=> [String] | usually some letters, denoting the variables |
-> Spray a | |
-> String |
Pretty form of a spray with numeric coefficients, printing monomials as "x.z^2"
if possible, i.e. if enough letters are provided, otherwise as "x1.x3^2"
>>>
x = lone 1 :: Spray Int
>>>
y = lone 2 :: Spray Int
>>>
z = lone 3 :: Spray Int
>>>
w = lone 4 :: Spray Int
>>>
p = 2*^x ^+^ 3*^y^**^2 ^-^ 4*^z^**^3
>>>
putStrLn $ prettyNumSprayXYZ ["x","y","z"] p
2*x + 3*y^2 - 4*z^3>>>
putStrLn $ prettyNumSprayXYZ ["x","y","z"] (p ^+^ w)
2*x1 + 3*x2^2 - 4*x3^3 + x4>>>
putStrLn $ prettyNumSprayXYZ ["a","b","c"] (p ^+^ w)
2*a1 + 3*a2^2 - 4*a3^3 + a4
Pretty form of a spray with rational coefficients, printing monomials in
the style of "x.z^2"
with the provided letters if possible, i.e. if enough
letters are provided, otherwise in the style "x1.x3^2"
, taking the first
provided letter to denote the non-indexed variables
>>>
x = lone 1 :: QSpray
>>>
y = lone 2 :: QSpray
>>>
z = lone 3 :: QSpray
>>>
p = 2*^x ^+^ 3*^y^**^2 ^-^ (4%3)*^z^**^3
>>>
putStrLn $ prettyQSprayXYZ ["x","y","z"] p
2*x + 3*y^2 - (4/3)*z^3>>>
putStrLn $ prettyQSprayXYZ ["x","y"] p
2*x1 + 3*x2^2 - (4%3)*x3^3>>>
putStrLn $ prettyQSprayXYZ ["a","b"] p
2*a1 + 3*a2^2 - (4/3)*a3^3
Same as prettyQSprayXYZ
but for a QSpray'
spray
prettyNumSpray :: (Num a, Ord a, Show a) => Spray a -> String Source #
Pretty printing of a spray with numeric coefficients prop> prettyNumSpray == prettyNumSprayXYZ ["x", "y", "z"]
prettyQSpray :: QSpray -> String Source #
Pretty printing of a spray with rational coefficients prop> prettyQSpray == prettyQSprayXYZ ["x", "y", "z"]
prettyQSpray'' :: QSpray -> String Source #
prettyQSpray' :: QSpray' -> String Source #
Pretty printing of a spray with rational coefficients prop> prettyQSpray' == prettyQSprayXYZ' ["x", "y", "z"]
prettyQSpray''' :: QSpray' -> String Source #
Univariate polynomials and fractions of univariate polynomials
Constructors
A a |
Instances
Eq a => Eq (A a) Source # | |
C a => C (A a) Source # | |
C a => C (A a) Source # | |
C a => C (A a) Source # | |
(Eq a, C a) => C (A a) Source # | |
Defined in Math.Algebra.Hspray | |
(Eq a, C a) => C (A a) (RatioOfPolynomials a) Source # | |
Defined in Math.Algebra.Hspray Methods (*>) :: A a -> RatioOfPolynomials a -> RatioOfPolynomials a # | |
(Eq a, C a) => C (Polynomial a) (RatioOfPolynomials a) Source # | |
Defined in Math.Algebra.Hspray Methods (*>) :: Polynomial a -> RatioOfPolynomials a -> RatioOfPolynomials a # | |
(Eq a, C a) => C (Polynomial a) (SymbolicSpray a) Source # | |
Defined in Math.Algebra.Hspray Methods (*>) :: Polynomial a -> SymbolicSpray a -> SymbolicSpray a # |
type Polynomial a = T (A a) Source #
type RatioOfPolynomials a = T (Polynomial a) Source #
type QPolynomial = Polynomial Rational' Source #
(^/^) :: (Eq a, C a) => Polynomial a -> Polynomial a -> RatioOfPolynomials a Source #
Division of univariate polynomials; this is an application of :%
followed by a simplification of the obtained fraction of the two polynomials
prettyRatioOfPolynomials Source #
Arguments
:: (Eq a, C a, Show a) | |
=> String | string (usually a single letter) to denote the variable, e.g. |
-> RatioOfPolynomials a | |
-> String |
Pretty form of a ratio of univariate polynomials
prettyRatioOfQPolynomials Source #
Arguments
:: String | a string to denote the variable, e.g. |
-> RatioOfQPolynomials | |
-> String |
Pretty form of a ratio of univariate polynomials with rational coefficients
(*.) :: (Eq a, C a) => a -> RatioOfPolynomials a -> RatioOfPolynomials a infixr 7 Source #
Scale a ratio of univariate polynomials by a scalar
constPoly :: a -> Polynomial a Source #
Constant univariate polynomial
polyFromCoeffs :: [a] -> Polynomial a Source #
Univariate polynomial from its coefficients (ordered by increasing degrees)
outerVariable :: C a => Polynomial a Source #
The variable of a univariate polynomial; it is called "outer" because
this is the variable occuring in the polynomial coefficients of a SymbolicSpray
constQPoly :: Rational' -> QPolynomial Source #
Constant rational univariate polynomial
>>>
import Number.Ratio ( (%) )
>>>
constQPoly (2 % 3)
constQPoly (2 % 3) == qpolyFromCoeffs [2 % 3]
qpolyFromCoeffs :: [Rational'] -> QPolynomial Source #
Rational univariate polynomial from coefficients
>>>
import Number.Ratio ( (%) )
>>>
qpolyFromCoeffs [2 % 3, 5, 7 % 4]
outerQVariable :: QPolynomial Source #
The variable of a univariate rational polynomial; it is called "outer"
because it is the variable occuring in the coefficients of a SymbolicQSpray
(but I do not like this name - see README)
outerQVariable == qpolyFromCoeffs [0, 1]
evalRatioOfPolynomials Source #
Arguments
:: C a | |
=> a | the value at which the evaluation is desired |
-> RatioOfPolynomials a | |
-> a |
Evaluates a ratio of univariate polynomials
Symbolic sprays
type SymbolicSpray a = Spray (RatioOfPolynomials a) Source #
type SymbolicQSpray = SymbolicSpray Rational' Source #
prettySymbolicSprayX1X2X3 Source #
Arguments
:: (Eq a, Show a, C a) | |
=> String | string to denote the outer variable of the spray, e.g. |
-> String | typically a letter, to denote the non-indexed variables |
-> SymbolicSpray a | a symbolic spray; note that this function does not simplify it |
-> String |
Pretty form of a symbolic spray, using a string (typically a letter) followed by an index to denote the variables
prettySymbolicSprayXYZ Source #
Arguments
:: (Eq a, Show a, C a) | |
=> String | string to denote the outer variable of the spray, e.g. |
-> [String] | typically some letters, to denote the main variables |
-> SymbolicSpray a | a symbolic spray; note that this function does not simplify it |
-> String |
Pretty form of a symbolic spray, using some given strings (typically some
letters) to denote the variables if possible, i.e. if enough letters are
provided; otherwise this function behaves exactly like
prettySymbolicQSprayX1X2X3 a
where a
is the first provided letter
Arguments
:: (Eq a, Show a, C a) | |
=> String | string to denote the outer variable of the spray, e.g. |
-> SymbolicSpray a | a symbolic spray; note that this function does not simplify it |
-> String |
Pretty form of a symbolic spray; see the definition below and see
prettySymbolicSprayXYZ
prettySymbolicSpray a spray == prettySymbolicSprayXYZ a ["x","y","z"] spray
Arguments
:: (Eq a, Show a, C a) | |
=> String | string to denote the outer variable of the spray, e.g. |
-> SymbolicSpray a | a symbolic spray; note that this function does not simplify it |
-> String |
Pretty form of a symbolic spray; see the definition below and see
prettySymbolicSprayXYZ
prettySymbolicSpray' a spray == prettySymbolicSprayXYZ a ["X","Y","Z"] spray
prettySymbolicQSprayX1X2X3 Source #
Arguments
:: String | string to denote the outer variable of the spray, e.g. |
-> String | string to denote the non-indexed variables of the spray |
-> SymbolicQSpray | a symbolic qspray; note that this function does not simplify it |
-> String |
Pretty form of a symbolic rational spray, using a string (typically a letter) followed by an index to denote the variables
prettySymbolicQSprayXYZ Source #
Arguments
:: String | string to denote the outer variable of the spray, e.g. |
-> [String] | usually some letters, to denote the variables of the spray |
-> SymbolicQSpray | a symbolic qspray; note that this function does not simplify it |
-> String |
Pretty form of a symbolic rational spray, using some given strings (typically some
letters) to denote the variables if possible, i.e. if enough letters are
provided; otherwise this function behaves exactly like
prettySymbolicQSprayX1X2X3 a
where a
is the first provided letter
Arguments
:: String | string to denote the outer variable of the spray, e.g. |
-> SymbolicQSpray | the symbolic qspray to be printed; note that this function does not simplify it |
-> String |
Pretty form of a symbolic rational spray, using "x"
, "y"
and "z"
for the variables
if possible; i.e. if the spray does not have more than three variables, otherwise
"x1"
, "x2"
, ... are used to denote the variables
prettySymbolicQSpray a == prettySymbolicQSprayXYZ a ["x","y","z"]
prettySymbolicQSpray' Source #
Arguments
:: String | string to denote the outer variable of the spray, e.g. |
-> SymbolicQSpray | the symbolic qsprayto be printed; note that this function does not simplify it |
-> String |
simplifySymbolicSpray :: (Eq a, C a) => SymbolicSpray a -> SymbolicSpray a Source #
Simplifies the coefficients (the fractions of univariate polynomials) of a symbolic spray
evalSymbolicSpray :: C a => SymbolicSpray a -> a -> Spray a Source #
Substitutes a value to the outer variable of a symbolic spray (the variable occuring in the coefficients)
Arguments
:: C a | |
=> SymbolicSpray a | symbolic spray to be evaluated |
-> a | a value for the outer variable |
-> [a] | some values for the inner variables |
-> a |
Substitutes a value to the outer variable of a symbolic spray as well as some values to the inner variables of this spray
evalSymbolicSpray'' :: (Eq a, C a) => SymbolicSpray a -> [a] -> RatioOfPolynomials a Source #
Substitutes some values to the inner variables of a symbolic spray
Queries on a spray
getCoefficient :: C a => [Int] -> Spray a -> a Source #
Get coefficient of a term of a spray
>>>
x = lone 1 :: Spray Int
>>>
y = lone 2 :: Spray Int
>>>
z = lone 3 :: Spray Int
>>>
p = 2 *^ (2 *^ (x^**^3 ^*^ y^**^2)) ^+^ 4*^z ^+^ 5*^unitSpray
>>>
getCoefficient [3, 2, 0] p
4>>>
getCoefficient [0, 4] p
0
getConstantTerm :: C a => Spray a -> a Source #
Get the constant term of a spray
getConstantTerm p == getCoefficient [] p
numberOfVariables :: Spray a -> Int Source #
number of variables in a spray
Evaluation of a spray
evalSpray :: C a => Spray a -> [a] -> a Source #
Evaluates a spray
>>>
x :: lone 1 :: Spray Int
>>>
y :: lone 2 :: Spray Int
>>>
p = 2*^x^**^2 ^-^ 3*^y
>>>
evalSpray p [2, 1]
5
substituteSpray :: (Eq a, C a) => [Maybe a] -> Spray a -> Spray a Source #
Substitutes some variables in a spray by some values
>>>
x1 :: lone 1 :: Spray Int
>>>
x2 :: lone 2 :: Spray Int
>>>
x3 :: lone 3 :: Spray Int
>>>
p = x1^**^2 ^-^ x2 ^+^ x3 ^-^ unitSpray
>>>
p' = substituteSpray [Just 2, Nothing, Just 3] p
>>>
putStrLn $ prettyNumSpray p'
-x2 + 6
composeSpray :: forall a. (C a, Eq a) => Spray a -> [Spray a] -> Spray a Source #
Sustitutes the variables of a spray with some sprays (e.g. change of variables)
>>>
x :: lone 1 :: Spray Int
>>>
y :: lone 2 :: Spray Int
>>>
z :: lone 3 :: Spray Int
>>>
p = x ^+^ y
>>>
q = composeSpray p [z, x ^+^ y ^+^ z]
>>>
putStrLn $ prettyNumSpray' q
X + Y + 2*Z
Differentiation of a spray
Arguments
:: (C a, Eq a) | |
=> Int | index of the variable of differentiation (starting at 1) |
-> Spray a | the spray to be derivated |
-> Spray a | the derivated spray |
Derivative of a spray
>>>
x :: lone 1 :: Spray Int
>>>
y :: lone 2 :: Spray Int
>>>
spray = 2*^x ^-^ 3*^y^**^8
>>>
spray' = derivSpray 1 spray
>>>
putStrLn $ prettyNumSpray spray'
2
Permutation of the variables of a spray
permuteVariables :: [Int] -> Spray a -> Spray a Source #
Permutes the variables of a spray
>>>
f :: Spray Rational -> Spray Rational -> Spray Rational -> Spray Rational
>>>
f p1 p2 p3 = p1^**^4 ^+^ (2*^p2^**^3) ^+^ (3*^p3^**^2) ^-^ (4*^unitSpray)
>>>
x1 = lone 1 :: Spray Rational
>>>
x2 = lone 2 :: Spray Rational
>>>
x3 = lone 3 :: Spray Rational
>>>
p = f x1 x2 x3
permuteVariables [3, 1, 2] p == f x3 x1 x2
swapVariables :: (Int, Int) -> Spray a -> Spray a Source #
Swaps two variables whithin a spray
swapVariables (1, 3) spray == permuteVariables [3, 2, 1] spray
Division of a spray
Arguments
:: forall a. (Eq a, C a) | |
=> Spray a | dividend |
-> Spray a | divisor |
-> (Spray a, Spray a) | (quotient, remainder) |
Division of a spray by a spray
sprayDivisionRemainder :: forall a. (Eq a, C a) => Spray a -> [Spray a] -> Spray a Source #
Remainder of the division of a spray by a list of divisors, using the lexicographic ordering of the monomials
Gröbner basis
Arguments
:: forall a. (Eq a, C a) | |
=> [Spray a] | list of sprays |
-> Bool | whether to return the reduced basis |
-> [Spray a] |
Gröbner basis, always minimal and possibly reduced
groebner sprays True == reduceGroebnerBasis (groebner sprays False)
reduceGroebnerBasis :: forall a. (Eq a, C a) => [Spray a] -> [Spray a] Source #
Reduces a Groebner basis
Symmetric polynomials
Elementary symmetric polynomial
>>>
putStrLn $ prettySpray' (esPolynomial 3 2)
(1)*x1x2 + (1)*x1x3 + (1)*x2x3
Power sum polynomial
isSymmetricSpray :: forall a. (C a, Eq a) => Spray a -> Bool Source #
Whether a spray is a symmetric polynomial, an inefficient algorithm (use the function with the same name in the jackpolynomials package if you need efficiency)
Resultant and subresultants
Arguments
:: (Eq a, C a) | |
=> Int | indicator of the variable with respect to which the resultant is desired (e.g. 1 for x) |
-> Spray a | |
-> Spray a | |
-> Spray a |
Resultant of two sprays
Arguments
:: forall a. (Eq a, C a) | |
=> Int | indicator of the variable with respect to which the resultant is desired (e.g. 1 for x) |
-> Spray a | |
-> Spray a | |
-> Spray a |
Resultant of two sprays with coefficients in a field; this function is more
efficient than the function resultant
Arguments
:: (Eq a, C a) | |
=> Int | indicator of the variable with respect to which the subresultants are desired (e.g. 1 for x) |
-> Spray a | |
-> Spray a | |
-> [Spray a] |
Subresultants of two sprays
subresultants1 :: (Eq a, C a) => Spray a -> Spray a -> [a] Source #
Subresultants of two univariate sprays
Greatest common divisor
gcdSpray :: forall a. (Eq a, C a) => Spray a -> Spray a -> Spray a Source #
Greatest common divisor of two sprays with coefficients in a field
Miscellaneous
fromRationalSpray :: Spray Rational -> Spray Double Source #
Converts a spray with rational coefficients to a spray with double coefficients (useful for evaluation)
leadingTerm :: Spray a -> Monomial a Source #
Leading term of a spray
isPolynomialOf :: forall a. (C a, Eq a) => Spray a -> [Spray a] -> (Bool, Maybe (Spray a)) Source #
Whether a spray can be written as a polynomial of a given list of sprays (the sprays in the list must belong to the same polynomial ring as the spray); this polynomial is returned if this is true
>>>
x = lone 1 :: Spray Rational
>>>
y = lone 2 :: Spray Rational
>>>
p1 = x ^+^ y
>>>
p2 = x ^-^ y
>>>
p = p1 ^*^ p2
isPolynomialOf p [p1, p2] == (True, Just $ x ^*^ y)