hspray-0.2.5.0: Multivariate polynomials.
Copyright(c) Stéphane Laurent 2023
LicenseGPL-3
Maintainerlaurent_step@outlook.fr
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.Algebra.Hspray

Description

Deals with multivariate polynomials on a commutative ring. See README for examples.

Synopsis

Types

data Powers Source #

Constructors

Powers 

Fields

Instances

Instances details
Show Powers Source # 
Instance details

Defined in Math.Algebra.Hspray

Eq Powers Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

(==) :: Powers -> Powers -> Bool #

(/=) :: Powers -> Powers -> Bool #

Hashable Powers Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

hashWithSalt :: Int -> Powers -> Int #

hash :: Powers -> Int #

(C a, Eq a) => C a (Spray a) Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

(*>) :: a -> Spray a -> Spray a #

(C a, Eq a) => C (Spray a) Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

zero :: Spray a #

(+) :: Spray a -> Spray a -> Spray a #

(-) :: Spray a -> Spray a -> Spray a #

negate :: Spray a -> Spray a #

(C a, Eq a) => C (Spray a) Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

(*) :: Spray a -> Spray a -> Spray a #

one :: Spray a #

fromInteger :: Integer -> Spray a #

(^) :: Spray a -> Integer -> Spray a #

(Eq a, C a) => C (Polynomial a) (SymbolicSpray a) Source # 
Instance details

Defined in Math.Algebra.Hspray

type Monomial a = (Powers, a) Source #

Basic sprays

lone :: C a => Int -> Spray a Source #

Spray corresponding to the basic monomial x_n

>>> x :: lone 1 :: Spray Int
>>> y :: lone 2 :: Spray Int
>>> p = 2*^x^**^2 ^-^ 3*^y
>>> putStrLn $ prettySpray' p
(2) x1^2 + (-3) x2
lone 0 == unitSpray

unitSpray :: C a => Spray a Source #

The unit spray

p ^*^ unitSpray == p

zeroSpray :: (Eq a, C a) => Spray a Source #

The null spray

p ^+^ zeroSpray == p

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

(.^) :: (C a, Eq a) => Int -> Spray a -> Spray a infixr 7 Source #

Scale a spray by an integer

3 .^ p == p ^+^ p ^+^ p

(^+^) :: (C a, Eq a) => Spray a -> Spray a -> Spray a infixl 6 Source #

Addition of two sprays

(^-^) :: (C a, Eq a) => Spray a -> Spray a -> Spray a infixl 6 Source #

Substraction of two sprays

(^*^) :: (C a, Eq a) => Spray a -> Spray a -> Spray a infixl 7 Source #

Multiply two sprays

(^**^) :: (C a, Eq a) => Spray a -> Int -> Spray a infixr 8 Source #

Power of a spray

Showing a spray

prettySpray Source #

Arguments

:: (a -> String)

function mapping a coefficient to a string, typically show

-> String

a string denoting the variable, e.g. "x"

-> Spray a

the spray

-> String 

Pretty form of a spray

>>> 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 show "x" p
(2) * x^(1) + (3) * x^(0, 2) + (-4) * x^(0, 0, 3)

prettySpray' :: Show a => Spray a -> String Source #

Pretty form of a spray, with monomials shown as "x1x3^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 $ prettySpray' p
(2) x1 + (3) x2^2 + (-4) x3^3 

prettySpray'' :: (a -> String) -> Spray a -> String Source #

Pretty form of a spray, with monomials shown as "x1x3^2", and with a user-defined showing function for the coefficients

prettySpray' p == prettySpray'' show p

prettySprayXYZ :: Show a => Spray a -> String Source #

Pretty form of a spray having at more three variables

>>> 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 p
(2) X + (3) Y^2 + (-4) Z^3

Univariate polynomials

newtype A a Source #

Constructors

A a 

Instances

Instances details
Eq a => Eq (A a) Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

(==) :: A a -> A a -> Bool #

(/=) :: A a -> A a -> Bool #

C a => C (A a) Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

zero :: A a #

(+) :: A a -> A a -> A a #

(-) :: A a -> A a -> A a #

negate :: A a -> A a #

C a => C (A a) Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

(/) :: A a -> A a -> A a #

recip :: A a -> A a #

fromRational' :: Rational -> A a #

(^-) :: A a -> Integer -> A a #

C a => C (A a) Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

(*) :: A a -> A a -> A a #

one :: A a #

fromInteger :: Integer -> A a #

(^) :: A a -> Integer -> A a #

(Eq a, C a) => C (A a) Source # 
Instance details

Defined in Math.Algebra.Hspray

Methods

isZero :: A a -> Bool #

(Eq a, C a) => C (A a) (RatioOfPolynomials a) Source # 
Instance details

Defined in Math.Algebra.Hspray

(Eq a, C a) => C (Polynomial a) (RatioOfPolynomials a) Source # 
Instance details

Defined in Math.Algebra.Hspray

(Eq a, C a) => C (Polynomial a) (SymbolicSpray a) Source # 
Instance details

Defined in Math.Algebra.Hspray

scalarQ :: Rational' -> Q Source #

Identify a rational to a A Rational' element

type Polynomial a = T (A a) Source #

prettyRatioOfPolynomials Source #

Arguments

:: (Eq a, C a, Show a) 
=> String

a string to denote the variable, e.g. "a"

-> RatioOfPolynomials a 
-> String 

Pretty form of a ratio of univariate polynomials

prettyRatioOfQPolynomials Source #

Arguments

:: String

a string to denote the variable, e.g. "a"

-> RatioOfQPolynomials 
-> String 

Pretty form of a ratio of univariate qpolynomials

(*.) :: (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)

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 qpolynomial; it is called "outer" because this is the variable occuring in the polynomial coefficients of a SymbolicQSpray

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 (with univariate polynomials coefficients)

prettySymbolicSpray Source #

Arguments

:: (Eq a, Show a, C a) 
=> String

a string to denote the outer variable of the spray, e.g. "a"

-> SymbolicSpray a

a symbolic spray; note that this function does not simplify it

-> String 

Pretty form of a symbolic spray

prettySymbolicQSpray Source #

Arguments

:: String

a string to denote the outer variable of the spray, e.g. "a"

-> SymbolicQSpray

a symbolic qspray; note that this function does not simplify it

-> String 

Pretty form of a symbolic qspray

simplifySymbolicSpray :: (Eq a, C a) => SymbolicSpray a -> SymbolicSpray a Source #

Simplifies the coefficients (the ratio 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

evalSymbolicSpray' Source #

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

sprayTerms :: Spray a -> HashMap (Seq Int) a Source #

Terms of 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 $ prettySpray' p'
(-1) 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 $ prettySprayXYZ q
(1) X + (1) Y + (2) Z

Differentiation of a spray

derivSpray Source #

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

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 of a spray

swapVariables (1, 3) p == permuteVariables [3, 2, 1] p

Division of a spray

sprayDivision Source #

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

groebner Source #

Arguments

:: forall a. (Eq a, C a) 
=> [Spray a]

list of sprays

-> Bool

whether to return the reduced basis

-> [Spray a] 

Groebner 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

esPolynomial Source #

Arguments

:: (C a, Eq a) 
=> Int

number of variables

-> Int

index

-> Spray a 

Elementary symmetric polynomial

>>> putStrLn $ prettySpray' (esPolynomial 3 2)
(1) x1x2 + (1) x1x3 + (1) x2x3

psPolynomial Source #

Arguments

:: forall a. (C a, Eq a) 
=> Int

number of variables

-> Int

power

-> Spray a 

Power sum polynomial

isSymmetricSpray :: forall a. (C a, Eq a) => Spray a -> Bool Source #

Whether a spray is a symmetric polynomial

Resultant and subresultants

resultant Source #

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

resultant' Source #

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

resultant1 :: (Eq a, C a) => Spray a -> Spray a -> a Source #

Resultant of two univariate sprays

subresultants Source #

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

fromList :: (C a, Eq a) => [([Int], a)] -> Spray a Source #

Creates a spray from a list of terms

toList :: Spray a -> [([Int], a)] Source #

Spray as a list

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)

bombieriSpray :: C a => Spray a -> Spray a Source #

Bombieri spray (for internal usage in the 'scubature' library)