hspray-0.5.2.0: Multivariate polynomials and fractions of multivariate polynomials.
Copyright(c) Stéphane Laurent 2022-2024
LicenseGPL-3
Maintainerlaurent_step@outlook.fr
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.Algebra.Hspray

Description

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

Synopsis

Classes

class FunctionLike b where Source #

A spray represents a multivariate polynomial so it like a function. We introduce a class because it will be assigned to the ratios of sprays too.

Associated Types

type BaseRing b Source #

The type of the coefficients (this is a for both Spray a and RatioOfSprays a)

type VariablesType b Source #

The type of the variables (this is Spray a for both Spray a and RatioOfSprays a)

Methods

numberOfVariables :: b -> Int Source #

Number of variables in a function-like object

permuteVariables Source #

Arguments

:: [Int]

permutation

-> b

function-like object whose variables will be permuted

-> b

the function-like object with permuted variables

Permutes the variables of a function-like object

>>> 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
>>> spray = f x1 x2 x3
permuteVariables [3, 1, 2] spray == f x3 x1 x2

swapVariables Source #

Arguments

:: (Int, Int)

the indices of the variables to be swapped (starting at 1)

-> b

function-like object whose variables will be swapped

-> b

the function-like object with swapped variables

Swaps two variables of a function-like object

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

involvesVariable Source #

Arguments

:: b

function-like object

-> Int

index of the variable

-> Bool 

dropVariables Source #

Arguments

:: Int

number of leading variables to drop

-> b

a function-like object

-> b 

Drops a given number of leading variables in a function-like object; very unsafe, dropVariables n x should not be used if involvesVariable x i is True for some i in 1, ... n

dropVariables 1 (qlone 2 ^+^ qlone 3) == qlone 1 ^+^ qlone 2

derivative Source #

Arguments

:: Int

index of the variable of differentiation (starting at 1)

-> b

the object to be derivated

-> b

the derivated object

Derivative of a function-like object

>>> x = lone 1 :: Spray Int
>>> y = lone 2 :: Spray Int
>>> spray = 2*^x ^-^ 3*^y^**^8
>>> spray' = derivative 1 spray
>>> putStrLn $ prettyNumSpray spray'
2

(^+^) :: C b => b -> b -> b infixl 6 Source #

Addition of two function-like objects

(^-^) :: C b => b -> b -> b infixl 6 Source #

Substraction of two function-like objects

(^*^) :: C b => b -> b -> b infixl 7 Source #

Multiplication of two function-like objects

(^**^) :: C b => b -> Int -> b infixr 8 Source #

Power of a function-like object

(*^) :: BaseRing b -> b -> b infixr 7 Source #

Multiply a function-like object by a scalar

(+>) :: BaseRing b -> b -> b infixl 6 Source #

Add a function-like object to a constant

x +> spray == constantSpray x ^+^ spray

(<+) :: b -> BaseRing b -> b infixr 6 Source #

Add a constant to a function-like object

object <+ x == x +> object

evaluate Source #

Arguments

:: b

function-like object to be evaluated, e.g. a spray

-> [BaseRing b]

list of values to be substituted to its variables

-> BaseRing b 

Evaluation (replacing the variables with some values) of a function-like object

>>> x = lone 1 :: Spray Int
>>> y = lone 2 :: Spray Int
>>> spray = 2*^x^**^2 ^-^ 3*^y
>>> evaluate spray [2, 1]
5

evaluateAt :: [BaseRing b] -> b -> BaseRing b Source #

Flipped version of evaluate

evaluateAt [2, 1] spray == evaluate spray [2, 1]

substitute Source #

Arguments

:: [Maybe (BaseRing b)]

Just x to replace the variable with x, Nothing for no replacement

-> b

function-like object to be partially evaluated

-> b 

Partial evaluation of a function-like object (replace some variables with some values)

>>> x1 = lone 1 :: Spray Int
>>> x2 = lone 2 :: Spray Int
>>> x3 = lone 3 :: Spray Int
>>> spray = x1^**^2 ^-^ x2 ^+^ x3 ^-^ unitSpray
>>> spray' = substitute [Just 2, Nothing, Just 3] spray
>>> putStrLn $ prettyNumSprayX1X2X3 "x" spray'
-x2 + 6 

changeVariables Source #

Arguments

:: b

function-like object such as a spray

-> [VariablesType b]

list of new variables

-> b 

Polynomial change of variables of a function-like object

>>> x = lone 1 :: Spray Int
>>> y = lone 2 :: Spray Int
>>> spray = x ^*^ y
>>> spray' = changeVariables spray [x ^+^ y, x ^-^ y]
>>> putStrLn $ prettyNumSpray' spray'
X^2 - Y^2

Instances

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

Defined in Math.Algebra.Hspray

Associated Types

type BaseRing (Polynomial a) Source #

type VariablesType (Polynomial a) Source #

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

Defined in Math.Algebra.Hspray

Methods

numberOfVariables :: RatioOfPolynomials a -> Int Source #

permuteVariables :: [Int] -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

swapVariables :: (Int, Int) -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

involvesVariable :: RatioOfPolynomials a -> Int -> Bool Source #

dropVariables :: Int -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

derivative :: Int -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(^+^) :: RatioOfPolynomials a -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(^-^) :: RatioOfPolynomials a -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(^*^) :: RatioOfPolynomials a -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(^**^) :: RatioOfPolynomials a -> Int -> RatioOfPolynomials a Source #

(*^) :: BaseRing (RatioOfPolynomials a) -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(+>) :: BaseRing (RatioOfPolynomials a) -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(<+) :: RatioOfPolynomials a -> BaseRing (RatioOfPolynomials a) -> RatioOfPolynomials a Source #

evaluate :: RatioOfPolynomials a -> [BaseRing (RatioOfPolynomials a)] -> BaseRing (RatioOfPolynomials a) Source #

evaluateAt :: [BaseRing (RatioOfPolynomials a)] -> RatioOfPolynomials a -> BaseRing (RatioOfPolynomials a) Source #

substitute :: [Maybe (BaseRing (RatioOfPolynomials a))] -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

changeVariables :: RatioOfPolynomials a -> [VariablesType (RatioOfPolynomials a)] -> RatioOfPolynomials a Source #

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Associated Types

type BaseRing (Spray a) Source #

type VariablesType (Spray a) Source #

isConstant :: FunctionLike b => b -> Bool Source #

Whether a function-like object has a constant value

isUnivariate :: FunctionLike b => b -> Bool Source #

Whether a function-like object represents an univariate function; it is considered that it is univariate if it is constant

isBivariate :: FunctionLike b => b -> Bool Source #

Whether a function-like object represents a bivariate function; it is considered that it is bivariate if it is univariate

isTrivariate :: FunctionLike b => b -> Bool Source #

Whether a function-like object represents a trivariate function; it is considered that it is trivariate if it is bivariate

Main types

data Powers Source #

The type Powers is used to represent the exponents of the monomial occurring in a term of a spray. The integer in the field nvariables is the number of variables involved in this monomial (it is 3, not 2, for a monomial such as x^2.z^3, because the exponents of this monomial is the sequence (2, 0, 3)). Actually this integer is always the length of the sequence in the field exponents. The reason of the presence of the field nvariables is that I thought that it was necessary when I started to develop the package, but now I think it is useless. The type Powers will possibly be abandoned in a future version of the package. However we cannot simply use the type Exponents to represent the exponents, because two sequences of exponents that differ only by some trailing zeros must be considered as identical, and they are considered as such with the type Powers thanks to its Eq instance. Instead of Powers, a new type encapsulating the Exponents type with such an Eq instance should be enough to represent the exponents.

Constructors

Powers 

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 #

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

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

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

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

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

(<*) :: ParametricSpray a -> a -> ParametricSpray a #

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

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

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

Defined in Math.Algebra.Hspray

Associated Types

type BaseRing (Spray a) Source #

type VariablesType (Spray a) Source #

(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) (OneParameterSpray a) Source # 
Instance details

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

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

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

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

type BaseRing (Spray a) Source # 
Instance details

Defined in Math.Algebra.Hspray

type BaseRing (Spray a) = a
type VariablesType (Spray a) Source # 
Instance details

Defined in Math.Algebra.Hspray

type Spray a = HashMap Powers a Source #

An object of type Spray a represents a multivariate polynomial whose coefficients are represented by the objects of type a, which must have a ring instance in order that we can add and multiply two polynomials.

type QSpray = Spray Rational Source #

Most often, one deals with sprays with rational coefficients, so we dedicate a type alias for such sprays.

type QSpray' = Spray Rational' Source #

The type Rational' is helpful when dealing with OneParameterSpray sprays, but this type of sprays lost its interest in version 0.4.0.0 (see CHANGELOG or README).

type Term a = (Powers, a) Source #

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

qlone :: Int -> QSpray Source #

The n-th polynomial variable for rational sprays; this is just a specialization of lone

lone' Source #

Arguments

:: C a 
=> Int

index

-> Int

exponent

-> Spray a 

The spray x_n^p; more efficient than exponentiating lone n

lone' 2 10 = lone 2 ^**^ 10

qlone' Source #

Arguments

:: Int

index

-> Int

exponent

-> QSpray 

The rational spray x_n^p

monomial Source #

Arguments

:: C a 
=> [(Int, Int)]

list of (index, exponent); duplicates are deleted

-> Spray a 

Monomial spray, e.g. monomial [(1,4),(3,2)] is x^4.z^2; indices and exponents must be positive but this is not checked prop> monomial [(1, 4), (3, 2)] == (lone 1 ^**^ 4) ^*^ (lone 3 ^**^ 2)

qmonomial :: [(Int, Int)] -> QSpray Source #

Monomial rational spray, a specialization of monomial

qmonomial [(1, 4), (3, 2)] == (qlone 1 ^**^ 4) ^*^ (qlone 3 ^**^ 2)

unitSpray :: C a => Spray a Source #

The unit spray

spray ^*^ unitSpray == spray

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

The null spray

spray ^+^ zeroSpray == spray

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

Constant spray

constantSpray 3 == 3 *^ unitSpray

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 

prettySpray'' Source #

Arguments

:: Show a 
=> String

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

-> Spray a

the spray

-> String 

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)

prettySprayXYZ Source #

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

prettySprayX1X2X3 Source #

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

showSpray Source #

Arguments

:: (a -> String)

function mapping a coefficient to a string, typically show

-> (String, String)

pair of braces to enclose the coefficients

-> ([Exponents] -> [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

showSprayXYZ Source #

Arguments

:: (a -> String)

function mapping a coefficient to a string, typically show

-> (String, String)

used to enclose the coefficients, usually a pair of braces

-> [String]

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

showSprayXYZ' Source #

Arguments

:: (a -> String)

function mapping a coefficient to a string, typically show

-> [String]

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 ("(", ")")

showSprayX1X2X3 Source #

Arguments

:: (a -> String)

function mapping a coefficient to a string, typically show

-> (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

showSprayX1X2X3' Source #

Arguments

:: (a -> String)

function mapping a coefficient to a string, e.g. show

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

showNumSpray Source #

Arguments

:: (Num a, Ord a) 
=> ([Exponents] -> [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

showQSpray Source #

Arguments

:: ([Exponents] -> [String])

function printing monomials

-> QSpray 
-> String 

Prints a QSpray; for internal usage but exported for usage in other packages

showQSpray' Source #

Arguments

:: ([Exponents] -> [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

prettyNumSprayX1X2X3 Source #

Arguments

:: (Num a, Ord a, Show a) 
=> String

usually a letter such as "x" to denote the non-indexed variables

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

prettyQSprayX1X2X3 Source #

Arguments

:: String

usually a letter such as "x", to denote the non-indexed variables

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

prettyQSprayX1X2X3' Source #

Arguments

:: String

usually a letter such as "x", to denote the non-indexed variables

-> QSpray' 
-> String 

Same as prettyQSprayX1X2X3 but for a QSpray' spray

prettyNumSprayXYZ Source #

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

prettyQSprayXYZ Source #

Arguments

:: [String]

usually some letters, to denote the variables

-> QSpray 
-> String 

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

prettyQSprayXYZ' Source #

Arguments

:: [String]

usually some letters, to denote the variables

-> QSpray' 
-> String 

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"]

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 #

Pretty printing of a spray with rational coefficients prop> prettyQSpray'' == prettyQSprayXYZ [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 #

Pretty printing of a spray with rational coefficients prop> prettyQSpray''' == prettyQSprayXYZ' [X, Y, Z]

Univariate polynomials and fractions of univariate polynomials

The univariate polynomials and the fractions of univariate polynomials are used to defined the OneParameterSpray sprays, which represent multivariate polynomials depending on a unique parameter. These sprays lost their interest in version 0.4.0.0 (see CHANGELOG or README).

newtype A a Source #

The new type A a is used to attribute some instances to the type Polynomial a; it is needed to avoid orphan instances.

Constructors

A a 

Instances

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

showsPrec :: Int -> A a -> ShowS #

show :: A a -> String #

showList :: [A a] -> ShowS #

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

Defined in Math.Algebra.Hspray

Methods

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

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

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

Defined in Math.Algebra.Hspray

Associated Types

type BaseRing (Polynomial a) Source #

type VariablesType (Polynomial a) Source #

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

Defined in Math.Algebra.Hspray

Methods

numberOfVariables :: RatioOfPolynomials a -> Int Source #

permuteVariables :: [Int] -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

swapVariables :: (Int, Int) -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

involvesVariable :: RatioOfPolynomials a -> Int -> Bool Source #

dropVariables :: Int -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

derivative :: Int -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(^+^) :: RatioOfPolynomials a -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(^-^) :: RatioOfPolynomials a -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(^*^) :: RatioOfPolynomials a -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(^**^) :: RatioOfPolynomials a -> Int -> RatioOfPolynomials a Source #

(*^) :: BaseRing (RatioOfPolynomials a) -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(+>) :: BaseRing (RatioOfPolynomials a) -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

(<+) :: RatioOfPolynomials a -> BaseRing (RatioOfPolynomials a) -> RatioOfPolynomials a Source #

evaluate :: RatioOfPolynomials a -> [BaseRing (RatioOfPolynomials a)] -> BaseRing (RatioOfPolynomials a) Source #

evaluateAt :: [BaseRing (RatioOfPolynomials a)] -> RatioOfPolynomials a -> BaseRing (RatioOfPolynomials a) Source #

substitute :: [Maybe (BaseRing (RatioOfPolynomials a))] -> RatioOfPolynomials a -> RatioOfPolynomials a Source #

changeVariables :: RatioOfPolynomials a -> [VariablesType (RatioOfPolynomials a)] -> RatioOfPolynomials a Source #

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) (OneParameterSpray 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 (A a) (RatioOfPolynomials a) Source # 
Instance details

Defined in Math.Algebra.Hspray

(Eq a, C a) => C (Polynomial a) (OneParameterSpray 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

type BaseRing (Polynomial a) Source # 
Instance details

Defined in Math.Algebra.Hspray

type BaseRing (Polynomial a) = a
type BaseRing (RatioOfPolynomials a) Source # 
Instance details

Defined in Math.Algebra.Hspray

type VariablesType (Polynomial a) Source # 
Instance details

Defined in Math.Algebra.Hspray

type VariablesType (RatioOfPolynomials a) Source # 
Instance details

Defined in Math.Algebra.Hspray

type Rational' = Rational Source #

The type Rational' is used to introduce the univariate polynomials with rational coefficients (QPolynomial). It is similar to the well-known type Rational (actually these two types are the same but Rational' has more instances and we need them for the univariate polynomials).

type Polynomial a = T (A a) Source #

The type Polynomial a is used to represent univariate polynomials.

prettyRatioOfPolynomials Source #

Arguments

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

string (usually a single letter) 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 polynomials with rational coefficients

constPoly :: a -> Polynomial a Source #

Constant univariate polynomial

polyFromCoeffs :: [a] -> Polynomial a Source #

Univariate polynomial from its coefficients (ordered by increasing degrees)

soleParameter :: C a => Polynomial a Source #

The variable of a univariate polynomial; it is called "soleParameter" because this it represents the parameter of a OneParameterSpray spray

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]

qsoleParameter :: QPolynomial Source #

The variable of a univariate rational polynomial; it is called "qsoleParameter" because it represents the parameter of a OneParameterQSpray spray

qsoleParameter == 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

One-parameter sprays

The OneParameterSpray sprays represent multivariate polynomials with coefficients depending on a unique parameter. These sprays lost their interest in version 0.4.0.0 (see CHANGELOG or README). One can use the more general ParametricSpray sprays instead.

prettyOneParameterSprayX1X2X3 Source #

Arguments

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

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

-> String

typically a letter, to denote the non-indexed variables

-> OneParameterSpray a

a one-parameter spray; note that this function does not simplify it

-> String 

Pretty form of a one-parameter spray, using a string (typically a letter) followed by an index to denote the variables

prettyOneParameterSprayXYZ Source #

Arguments

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

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

-> [String]

typically some letters, to denote the main variables

-> OneParameterSpray a

a one-parameter spray; note that this function does not simplify it

-> String 

Pretty form of a one-parameter 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 prettyOneParameterSprayX1X2X3 a where a is the first provided letter

prettyOneParameterSpray Source #

Arguments

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

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

-> OneParameterSpray a

a one-parameter spray; note that this function does not simplify it

-> String 

Pretty form of a one-parameter spray; see the definition below and see prettyOneParameterSprayXYZ

prettyOneParameterSpray a spray == prettyOneParameterSprayXYZ a ["x","y","z"] spray

prettyOneParameterSpray' Source #

Arguments

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

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

-> OneParameterSpray a

a one-parameter spray; note that this function does not simplify it

-> String 

Pretty form of a one-parameter spray; see the definition below and see prettyOneParameterSprayXYZ

prettyOneParameterSpray' a spray == prettyOneParameterSprayXYZ a ["X","Y","Z"] spray

prettyOneParameterQSprayX1X2X3 Source #

Arguments

:: String

usually a letter, to denote the parameter of the spray, e.g. "a"

-> String

usually a letter, to denote the non-indexed variables of the spray

-> OneParameterQSpray

a one-parameter rational spray; note that this function does not simplify it

-> String 

Pretty form of a one-parameter rational spray, using a string (typically a letter) followed by an index to denote the variables

prettyOneParameterQSprayXYZ Source #

Arguments

:: String

usually a letter, to denote the parameter of the spray, e.g. "a"

-> [String]

usually some letters, to denote the variables of the spray

-> OneParameterQSpray

a one-parameter rational spray; note that this function does not simplify it

-> String 

Pretty form of a one-parameter 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 prettyOneParameterQSprayX1X2X3 a where a is the first provided letter

prettyOneParameterQSpray Source #

Arguments

:: String

usually a letter, to denote the parameter of the spray, e.g. "a"

-> OneParameterQSpray

the one-parameter rational spray to be printed; note that this function does not simplify it

-> String 

Pretty form of a one-parameter 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

prettyOneParameterQSpray a == prettyOneParameterQSprayXYZ a ["x","y","z"]

prettyOneParameterQSpray' Source #

Arguments

:: String

usually a letter, to denote the parameter of the spray, e.g. "a"

-> OneParameterQSpray

the one-parameter rational spray to be printed; note that this function does not simplify it

-> String 

Pretty form of a one-parameter 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

prettyOneParameterQSpray' a == prettyOneParameterQSprayXYZ a ["X","Y","Z"]

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

Substitutes a value to the parameter of a one-parameter spray (the variable occurring in its coefficients)

evalOneParameterSpray spray x == substituteParameters spray [x]

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

Substitutes a value to the parameter of a one-parameter spray; same as evalOneParameterSpray

substituteTheParameter spray x == substituteParameters spray [x]

evalOneParameterSpray' Source #

Arguments

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

one-parameter spray to be evaluated

-> a

a value for the parameter

-> [a]

some values for the variables

-> a 

Substitutes a value to the parameter of a one-parameter spray as well as some values to the variables of this spray

evalOneParameterSpray' spray a xs == evalParametricSpray' spray [a] xs

evalOneParameterSpray'' :: (Eq a, C a) => OneParameterSpray a -> [a] -> RatioOfPolynomials a Source #

Substitutes some values to the variables of a one-parameter spray; same as evalParametricSpray

Ratios of sprays

An object of type RatioOfSprays represents a fraction of two multivariate polynomials.

data RatioOfSprays a Source #

A RatioOfSprays a object represents a fraction of two multivariate polynomials whose coefficients are of type a, which represents a field. These two polynomials are represented by two Spray a objects. Generally we do not use this constructor to build a ratio of sprays: we use the %//% operator instead, because it always returns an irreducible ratio of sprays, meaning that its corresponding fraction of polynomials is irreducible, i.e. its numerator and its denominator are coprime. You can use this constructor if you are sure that the numerator and the denominator are coprime. This can save some computation time, but unfortunate consequences can occur if the numerator and the denominator are not coprime. An arithmetic operation on ratios of sprays always returns an irreducible ratio of sprays under the condition that the ratios of sprays it involves are irreducible. Moreover, it never returns a ratio of sprays with a constant denominator other than the unit spray. If you use this constructor with a constant denominator, always set this denominator to the unit spray (by dividing the numerator by the constant value of the denominator).

Constructors

RatioOfSprays 

Fields

Instances

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

Defined in Math.Algebra.Hspray

Methods

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

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

Defined in Math.Algebra.Hspray

Methods

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

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

Defined in Math.Algebra.Hspray

Methods

(<*) :: ParametricSpray a -> a -> ParametricSpray a #

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

Defined in Math.Algebra.Hspray

Methods

(<*) :: RatioOfSprays a -> a -> RatioOfSprays a #

Show a => Show (RatioOfSprays a) Source # 
Instance details

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

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

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

Defined in Math.Algebra.Hspray

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

Defined in Math.Algebra.Hspray

Methods

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

type BaseRing (RatioOfSprays a) Source # 
Instance details

Defined in Math.Algebra.Hspray

type BaseRing (RatioOfSprays a) = a
type VariablesType (RatioOfSprays a) Source # 
Instance details

Defined in Math.Algebra.Hspray

(%:%) :: Spray a -> Spray a -> RatioOfSprays a infixl 7 Source #

Ratio of sprays from numerator and denominator, without reducing the fraction

(%//%) :: (Eq a, C a) => Spray a -> Spray a -> RatioOfSprays a infixl 7 Source #

Irreducible ratio of sprays from numerator and denominator; alias of (^/^)

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

Irreducible ratio of sprays from numerator and denominator; alias of (%//%)

(%/%) :: (Eq a, C a) => RatioOfSprays a -> Spray a -> RatioOfSprays a infixl 7 Source #

Division of a ratio of sprays by a spray; the result is an irreducible fraction

isConstantRatioOfSprays :: (Eq a, C a) => RatioOfSprays a -> Bool Source #

Whether a ratio of sprays is constant; same as isConstant

isPolynomialRatioOfSprays :: (Eq a, C a) => RatioOfSprays a -> Bool Source #

Whether a ratio of sprays actually is polynomial, that is, whether its denominator is a constant spray (and then it should be the unit spray)

>>> x = qlone 1
>>> y = qlone 2
>>> p = x^**^4 ^-^ y^**^4
>>> q = x ^-^ y
>>> isPolynomialRatioOfSprays $ p %//% q
True
>>> isPolynomialRatioOfSprays $ p %:% q
False

zeroRatioOfSprays :: (C a, Eq a) => RatioOfSprays a Source #

The null ratio of sprays

zeroROS :: (C a, Eq a) => RatioOfSprays a Source #

The null ratio of sprays

unitRatioOfSprays :: (C a, Eq a) => RatioOfSprays a Source #

The unit ratio of sprays

unitROS :: (C a, Eq a) => RatioOfSprays a Source #

The unit ratio of sprays

constantRatioOfSprays :: (Eq a, C a) => a -> RatioOfSprays a Source #

Constant ratio of sprays

asRatioOfSprays :: C a => Spray a -> RatioOfSprays a Source #

Coerces a spray to a ratio of sprays

evalRatioOfSprays :: (Eq a, C a) => RatioOfSprays a -> [a] -> a Source #

Evaluates a ratio of sprays; same as evaluate

substituteRatioOfSprays :: (Eq a, C a) => [Maybe a] -> RatioOfSprays a -> RatioOfSprays a Source #

Substitutes some values to some variables of a ratio of sprays; same as substitute

fromRatioOfPolynomials :: (Eq a, C a) => RatioOfPolynomials a -> RatioOfSprays a Source #

Converts a ratio of polynomials to a ratio of sprays

fromRatioOfQPolynomials :: RatioOfQPolynomials -> RatioOfQSprays Source #

Converts a ratio of rational polynomials to a ratio of rational sprays; this is not a specialization of fromRatioOfPolynomials because RatioOfQPolynomials is RatioOfPolynomials a with a = Rational', not with a = Rational

showRatioOfSprays Source #

Arguments

:: (Eq a, C a) 
=> ((Spray a, Spray a) -> (String, String))

function which prints a pair of sprays that will be applied to the numerator and the denominator

-> (String, String)

pair of braces to enclose the numerator and the denominator

-> String

represents the quotient bar

-> RatioOfSprays a 
-> String 

General function to print a RatioOfSprays object

showRatioOfNumSprays Source #

Arguments

:: (Num a, Ord a, C a) 
=> (a -> String)

function mapping a positive coefficient to a string

-> ([Exponents] -> [String])

prints the monomials

-> (String, String)

pair of braces to enclose the numerator and the denominator

-> String

represents the quotient bar

-> RatioOfSprays a 
-> String 

Prints a ratio of sprays with numeric coefficients

showRatioOfQSprays Source #

Arguments

:: ([Exponents] -> [String])

prints the monomials

-> (String, String)

pair of braces to enclose the numerator and the denominator

-> String

represents the quotient bar

-> RatioOfQSprays 
-> String 

Prints a ratio of sprays with rational coefficients

showRatioOfSpraysXYZ Source #

Arguments

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

typically some letters, to represent the variables

-> (a -> String)

function mapping a coefficient to a string, typically show

-> (String, String)

used to enclose the coefficients, usually a pair of braces

-> (String, String)

pair of braces to enclose the numerator and the denominator

-> String

represents the quotient bar

-> RatioOfSprays a 
-> String 

Prints a ratio of sprays

showRatioOfSpraysXYZ' Source #

Arguments

:: (Eq a, C a) 
=> [String]

typically some letters, to represent the variables

-> (a -> String)

function mapping a coefficient to a string, typically show

-> RatioOfSprays a 
-> String 

Prints a ratio of sprays

showRatioOfSpraysX1X2X3 Source #

Arguments

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

typically a letter, to represent the variables

-> (a -> String)

function mapping a coefficient to a string, typically show

-> (String, String)

used to enclose the coefficients, usually a pair of braces

-> (String, String)

pair of braces to enclose the numerator and the denominator

-> String

represents the quotient bar

-> RatioOfSprays a 
-> String 

Prints a ratio of sprays

showRatioOfSpraysX1X2X3' Source #

Arguments

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

typically a letter, to represent the variables

-> (a -> String)

function mapping a coefficient to a string, typically show

-> RatioOfSprays a 
-> String 

Prints a ratio of sprays

prettyRatioOfQSpraysXYZ Source #

Arguments

:: [String]

typically some letters, to represent the variables

-> RatioOfQSprays 
-> String 

Prints a ratio of sprays with rational coefficients

prettyRatioOfQSpraysX1X2X3 Source #

Arguments

:: String

typically a letter, to represent the non-indexed variables

-> RatioOfQSprays 
-> String 

Prints a ratio of sprays with rational coefficients, printing the monomials in the style of "x1^2.x2.x3^3"

prettyRatioOfQSprays :: RatioOfQSprays -> String Source #

Prints a ratio of sprays with rational coefficients

prettyRatioOfQSprays rOS == prettyRatioOfQSpraysXYZ ["x","y","z"] rOS

prettyRatioOfQSprays' :: RatioOfQSprays -> String Source #

Prints a ratio of sprays with rational coefficients

prettyRatioOfQSprays' rOS == prettyRatioOfQSpraysXYZ ["X","Y","Z"] rOS

prettyRatioOfNumSpraysXYZ Source #

Arguments

:: (Num a, Ord a, C a, Show a) 
=> [String]

typically some letters, to represent the variables

-> RatioOfSprays a 
-> String 

Prints a ratio of sprays with numeric coefficients

prettyRatioOfNumSpraysX1X2X3 Source #

Arguments

:: (Num a, Ord a, C a, Show a) 
=> String

typically a letter, to represent the variables

-> RatioOfSprays a 
-> String 

Prints a ratio of sprays with numeric coefficients, printing the monomials in the style of "x1^2.x2.x3^3"

prettyRatioOfNumSprays :: (Num a, Ord a, C a, Show a) => RatioOfSprays a -> String Source #

Prints a ratio of sprays with numeric coefficients

prettyRatioOfNumSprays rOS == prettyRatioOfNumSpraysXYZ ["x","y","z"] rOS

prettyRatioOfNumSprays' :: (Num a, Ord a, C a, Show a) => RatioOfSprays a -> String Source #

Prints a ratio of sprays with numeric coefficients

prettyRatioOfNumSprays' rOS == prettyRatioOfNumSpraysXYZ ["X","Y","Z"] rOS

Parametric sprays

There are three types of parametric sprays: OneParameterSpray, SimpleParametricSpray and ParametricSpray. These are sprays of type Spray b where b has the class FunctionLike. When we say "parametric spray" in the documentation, we mean either such a spray or more precisely a ParametricSpray spray.

canCoerceToSimpleParametricSpray :: (Eq a, C a) => ParametricSpray a -> Bool Source #

Whether the coefficients of a parametric spray polynomially depend on their parameters; I do not know why, but it seems to be the case for the Jacobi polynomials

>>> canCoerceToSimpleParametricSpray (jacobiPolynomial 8)
True

asSimpleParametricSprayUnsafe :: ParametricSpray a -> SimpleParametricSpray a Source #

Coerces a parametric spray to a simple parametric spray, without checking this makes sense with canCoerceToSimpleParametricSpray

asSimpleParametricSpray :: (Eq a, C a) => ParametricSpray a -> SimpleParametricSpray a Source #

Coerces a parametric spray to a simple parametric spray, after checking this makes sense with canCoerceToSimpleParametricSpray

fromOneParameterSpray :: (Eq a, C a) => OneParameterSpray a -> ParametricSpray a Source #

Converts a `OneParameterSpray a` spray to a `ParametricSpray a`

parametricSprayToOneParameterSpray :: forall a. (Eq a, C a) => ParametricSpray a -> OneParameterSpray a Source #

Converts a parametric spray to a one-parameter spray, without checking the conversion makes sense

parametricQSprayToOneParameterQSpray :: ParametricQSpray -> OneParameterQSpray Source #

Converts a rational parametric spray to a rational one-parameter spray, without checking the conversion makes sense

gegenbauerPolynomial :: Int -> SimpleParametricQSpray Source #

Gegenbauer polynomials; we mainly provide them to give an example of the SimpleParametricSpray type

>>> gp = gegenbauerPolynomial 3
>>> putStrLn $ prettySimpleParametricQSpray gp
{ (4/3)*a^3 + 4*a^2 + (8/3)*a }*X^3 + { -2*a^2 - 2*a }*X
>>> putStrLn $ prettyQSpray'' $ substituteParameters gp [1]
8*X^3 - 4*X

jacobiPolynomial :: Int -> ParametricQSpray Source #

Jacobi polynomial; the n-th Jacobi polynomial is a univariate polynomial of degree n with two parameters, except for the case n=0 where it has no parameter

>>> jP = jacobiPolynomial 1
>>> putStrLn $ prettyParametricQSprayABCXYZ ["alpha", "beta"] ["X"] jP
{ [ (1/2)*alpha + (1/2)*beta + 1 ] }*X + { [ (1/2)*alpha - (1/2)*beta ] }

numberOfParameters :: FunctionLike b => Spray b -> Int Source #

Number of parameters in a parametric spray

>>> numberOfParameters (jacobiPolynomial 4)
2

changeParameters Source #

Arguments

:: (FunctionLike b, Eq b, C b) 
=> Spray b

OneParameterSpray a, SimpleParametricSpray a, or ParametricSpray a

-> [VariablesType b]

[Polynomial a] or [Spray a], the new variables

-> Spray b 

Apply polynomial transformations to the parameters of a parametric spray; e.g. you have a two-parameters polynomial \(P_{a, b}(X, Y, Z)\) and you want to get \(P_{a^2, b^2}(X, Y, Z)\), or the one-parameter polynomial \(P_{a, a}(X, Y, Z)\)

>>> jp = jacobiPolynomial 4
>>> a = qlone 1
>>> b = qlone 2
>>> changeParameters jp [a^**^2, b^**^2]

substituteParameters Source #

Arguments

:: (FunctionLike b, Eq (BaseRing b), C (BaseRing b)) 
=> Spray b

OneParameterSpray a, SimpleParametricSpray a, or ParametricSpray a

-> [BaseRing b]

values of type a to be substituted to the parameters

-> Spray (BaseRing b)

output: a Spray a spray

Substitutes some values to the parameters of a parametric spray

>>> jacobi3 = jacobiPolynomial 3
>>> legendre3 = substituteParameters jp [0, 0]

evalParametricSpray Source #

Arguments

:: (Eq b, C (BaseRing b) b, C b) 
=> Spray b

OneParameterSpray a, SimpleParametricSpray a, or ParametricSpray a

-> [BaseRing b]

values of type a to be substituted to the variables

-> b 

Substitutes some values to the variables of a parametric spray

evalParametricSpray' Source #

Arguments

:: (FunctionLike b, Eq (BaseRing b), C (BaseRing b) b) 
=> Spray b

OneParameterSpray a, SimpleParametricSpray a, or ParametricSpray a

-> [BaseRing b]

values of type a to be substituted to the parameters

-> [BaseRing b]

values of type a to be substituted to the variables

-> BaseRing b

result: a value of type a

Substitutes some values to the parameters of a parametric spray as well as some values to its variables

prettyParametricQSprayABCXYZ Source #

Arguments

:: [String]

usually some letters, to denote the parameters of the spray

-> [String]

usually some letters, to denote the variables of the spray

-> ParametricQSpray

a parametric rational spray

-> String 

Pretty form of a parametric rational spray, using some given strings (typically some letters) to denote the parameters and some given strings (typically some letters) to denote the variables

>>> type PQS = ParametricQSpray
>>> :{
>>> f :: (QSpray, QSpray) -> (PQS, PQS, PQS) -> PQS
>>> f (a, b) (x, y, z) =
>>> (a %:% (a ^+^ b)) *^ x^**^2  ^+^  (b %:% (a ^+^ b)) *^ (y ^*^ z)
>>> :}
>>> a = qlone 1
>>> b = qlone 2
>>> x = lone 1 :: PQS
>>> y = lone 2 :: PQS
>>> z = lone 3 :: PQS
>>> pqs = f (a, b) (x, y, z)
>>> putStrLn $ prettyParametricQSprayABCXYZ ["a","b"] ["X","Y","Z"] pqs
{ [ a ] %//% [ a + b ] }*X^2 + { [ b ] %//% [ a + b ] }*Y.Z

prettyParametricQSpray :: ParametricQSpray -> String Source #

Pretty form of a parametric rational spray

prettyParametricQSpray == prettyParametricQSprayABCXYZ ["a"] ["X","Y","Z"]

prettyParametricNumSprayABCXYZ Source #

Arguments

:: (Num a, Ord a, Show a, C a) 
=> [String]

usually some letters, to denote the parameters of the spray

-> [String]

usually some letters, to denote the variables of the spray

-> ParametricSpray a

a parametric numeric spray

-> String 

Pretty form of a numeric parametric spray, using some given strings (typically some letters) to denote the parameters and some given strings (typically some letters) to denote the variables; rather use prettyParametricQSprayABCXYZ for a rational parametric spray

prettyParametricNumSpray Source #

Arguments

:: (Num a, Ord a, Show a, C a) 
=> ParametricSpray a

a parametric numeric spray

-> String 

Pretty form of a numeric parametric spray; rather use prettyParametricQSpray for a rational parametric spray

prettyParametricNumSpray == prettyParametricNumSprayABCXYZ ["a"] ["X","Y","Z"]

prettySimpleParametricQSprayABCXYZ Source #

Arguments

:: [String]

usually some letters, to denote the parameters of the spray

-> [String]

usually some letters, to denote the variables of the spray

-> SimpleParametricQSpray

a parametric rational spray

-> String 

Pretty form of a simple parametric rational spray, using some given strings (typically some letters) to denote the parameters and some given strings (typically some letters) to denote the variables

>>> type SPQS = SimpleParametricQSpray
>>> :{
>>> f :: (QSpray, QSpray) -> (SPQS, SPQS, SPQS) -> SPQS
>>> f (a, b) (x, y, z) =
>>> (a ^+^ b) *^ x^**^2  ^+^  (a^**^2 ^+^ b^**^2) *^ (y ^*^ z)
>>> :}
>>> a = qlone 1
>>> b = qlone 2
>>> x = lone 1 :: SPQS
>>> y = lone 2 :: SPQS
>>> z = lone 3 :: SPQS
>>> spqs = f (a, b) (x, y, z)
>>> putStrLn $ prettySimpleParametricQSprayABCXYZ ["a","b"] ["X","Y","Z"] spqs
{ a + b }*X^2 + { a^2 + b^2 }*Y.Z

prettySimpleParametricQSpray :: SimpleParametricQSpray -> String Source #

Pretty form of a simple parametric rational spray

prettySimpleParametricQSpray == prettySimpleParametricQSprayABCXYZ ["a"] ["X","Y","Z"]

prettySimpleParametricNumSprayABCXYZ Source #

Arguments

:: (Num a, Ord a, Show a, C a) 
=> [String]

usually some letters, to denote the parameters of the spray

-> [String]

usually some letters, to denote the variables of the spray

-> SimpleParametricSpray a

a numeric simple parametric spray

-> String 

Pretty form of a numeric simple parametric spray, using some given strings (typically some letters) to denote the parameters and some given strings (typically some letters) to denote the variables; rather use prettySimpleParametricQSprayABCXYZ for a rational simple parametric spray

prettySimpleParametricNumSpray Source #

Arguments

:: (Num a, Ord a, Show a, C a) 
=> SimpleParametricSpray a

a numeric simple parametric spray

-> String 

Pretty form of a numeric simple parametric spray; rather use prettySimpleParametricQSpray for a numeric simple parametric spray

prettySimpleParametricNumSpray == prettySimpleParametricNumSprayABCXYZ ["a"] ["X","Y","Z"]

Queries on a spray

getCoefficient Source #

Arguments

:: C a 
=> [Int]

sequence of exponents; trailing zeros are dropped

-> Spray a

spray

-> a

coefficient of the monomial given by the sequence of exponents

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] p -- coefficient of x^3.y^2
4
>>> getCoefficient [3, 2, 0] p -- same as getCoefficient [3, 2] p
4
>>> getCoefficient [0, 4] p -- coefficient of y^4
0

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

Get the constant term of a spray

getConstantTerm p == getCoefficient [] p

isZeroSpray :: Spray a -> Bool Source #

Whether a spray is the zero spray

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

Whether a spray is constant; same as isConstant

isHomogeneousSpray :: (Eq a, C a) => Spray a -> (Bool, Maybe Int) Source #

Checks whether the multivariate polynomial defined by a spray is homogeneous and also returns the degree in case this is true

allExponents :: Spray a -> [Exponents] Source #

Get all the exponents of a spray

allCoefficients :: Spray a -> [a] Source #

Get all the coefficients of a spray

Evaluation of a spray

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

Evaluates a spray; same as evaluate

>>> x = lone 1 :: Spray Int
>>> y = lone 2 :: Spray Int
>>> spray = 2*^x^**^2 ^-^ 3*^y
>>> evalSpray spray [2, 1]
5

substituteSpray :: (Eq a, C a) => [Maybe a] -> Spray a -> Spray a Source #

Substitutes some values to some variables of a spray; same as substitute

>>> 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 $ prettyNumSprayX1X2X3 "x" 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; same as changeVariables

>>> x = lone 1 :: Spray Int
>>> y = lone 2 :: Spray Int
>>> z = lone 3 :: Spray Int
>>> p = x ^+^ y
>>> q = composeSpray p [x ^+^ y ^+^ z, z]
>>> putStrLn $ prettyNumSpray' q
X + Y + 2*Z

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

Evaluates the coefficients of a spray with spray coefficients; same as substituteParameters

Division of sprays

sprayDivision Source #

Arguments

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

dividand

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

pseudoDivision Source #

Arguments

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

A

-> Spray a

B

-> (Spray a, (Spray a, Spray a))

(C, (Q, R)) such that C^*^A = B^*^Q ^+^ R

Pseudo-division of two sprays A and B such that deg(A) >= deg(B) where deg is the degree with respect to the outermost variable.

Gröbner basis

groebnerBasis Source #

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

groebnerBasis sprays True == reduceGroebnerBasis (groebnerBasis sprays False)

reduceGroebnerBasis :: forall a. (Eq a, C a) => [Spray a] -> [Spray a] Source #

Reduces a Gröbner 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)*x1.x2 + (1)*x1.x3 + (1)*x2.x3

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, an inefficient algorithm (use the function with the same name in the jackpolynomials package if you need efficiency)

Resultant, subresultants, and Sturm-Habicht sequence

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 (the principal subresultants, while the polynomialSubresultants function returns the polynomial subresultants). This function makes several calls to detLaplace and then it can be slow.

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

Subresultants of two univariate sprays. This function makes several calls to detLaplace and then it can be slow.

polynomialSubresultants Source #

Arguments

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

index of the variable with respect to which the subresultants will be computed (e.g. 2 for y)

-> Spray a 
-> Spray a 
-> [Spray a] 

Polynomial subresultants of two sprays (the subresultants function computes the principal subresultants). This function makes several calls to detLaplace and then it can be slow.

sturmHabichtSequence Source #

Arguments

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

index of the variable with respect to which the Sturm-Habicht sequence will be computed (e.g. 2 for y)

-> Spray a 
-> [Spray a] 

Sturm-Habicht sequence of a spray. This function calls polynomialSubresultants and then it can be slow.

principalSturmHabichtSequence Source #

Arguments

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

index of the variable with respect to which the Sturm-Habicht sequence will be computed (e.g. 2 for y)

-> Spray a 
-> [Spray a] 

Principal Sturm-Habicht sequence of a spray. This function calls sturmHabicht sequence and then it can be slow.

Number of real roots of a univariate spray. These functions can be very

numberOfRealRoots :: (Eq a, C a, Num a) => Spray a -> Int Source #

Number of real roots of a spray (that makes sense only for a spray on a ring embeddable in the real numbers). The roots are not counted with their multiplicity.

numberOfRealRoots' :: (Eq a, C a) => Spray a -> Int Source #

Number of real roots of a spray (that makes sense only for a spray on a ring embeddable in the real numbers). The roots are not counted with their multiplicity.

numberOfRealRootsInOpenInterval Source #

Arguments

:: (Num a, C a, Ord a) 
=> Spray a

a spray

-> Maybe a

lower bound of the interval; use Just for a finite bound, and Nothing for minus infinity

-> Maybe a

upper bound of the interval; use Just for a finite bound, and Nothing for minus infinity

-> Int 

Number of real roots of a spray in an open interval (that makes sense only for a spray on a ring embeddable in the real numbers).

numberOfRealRootsInOpenInterval' Source #

Arguments

:: (C a, Ord a) 
=> Spray a

a spray

-> Maybe a

lower bound of the interval; use Just for a finite bound, and Nothing for minus infinity

-> Maybe a

upper bound of the interval; use Just for a finite bound, and Nothing for minus infinity

-> Int 

Number of real roots of a spray in an open interval (that makes sense only for a spray on a ring embeddable in the real numbers).

numberOfRealRootsInClosedInterval Source #

Arguments

:: (Num a, C a, Ord a) 
=> Spray a

a spray

-> Maybe a

lower bound of the interval; use Just for a finite bound, and Nothing for minus infinity

-> Maybe a

upper bound of the interval; use Just for a finite bound, and Nothing for minus infinity

-> Int 

Number of real roots of a spray in a closed interval (that makes sense only for a spray on a ring embeddable in the real numbers). The roots are not counted with their multiplicity.

numberOfRealRootsInClosedInterval' Source #

Arguments

:: (C a, Ord a) 
=> Spray a

a spray

-> Maybe a

lower bound of the interval; use Just for a finite bound, and Nothing for minus infinity

-> Maybe a

upper bound of the interval; use Just for a finite bound, and Nothing for minus infinity

-> Int 

Number of real roots of a spray in a closed interval (that makes sense only for a spray on a ring embeddable in the real numbers). The roots are not counted with their multiplicity.

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

Matrices

detLaplace :: forall a. (Eq a, C a) => Matrix a -> a Source #

Determinant of a matrix with entries in a ring by using Laplace expansion (this is slow); the numeric-prelude package provides some stuff to deal with matrices over a ring but it does not provide the determinant

detLaplace' :: forall a. (Eq a, C a) => T a -> a Source #

Determinant of a matrix over a ring by using Laplace expansion; this is the same as detLaplace but for a matrix from the numeric-prelude package

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

Characteristic polynomial of a square matrix

>>> import Data.Matrix (Matrix, fromLists)
>>> m = fromLists [ [12, 16, 4]
>>> , [16, 2, 8]
>>> , [8, 18, 10] ] :: Matrix Int
>>> spray = characteristicPolynomial m
>>> putStrLn $ prettyNumSpray spray
-x^3 + 24*x^2 + 268*x - 1936

Miscellaneous

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

Sum of sprays

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

Product of sprays

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

Scale by an integer (I do not find this operation in numeric-prelude)

3 .^ x == x Algebra.Additive.+ x Algebra.Additive.+ x

(/>) :: (C k, C k a) => a -> k -> a infixr 7 Source #

Divides by a scalar in a module over a field

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

Divides a spray by a scalar; you can equivalently use (/>) if the type of the scalar is not ambiguous

fromList Source #

Arguments

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

list of (exponents, coefficient)

-> Spray a 

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)

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; 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 :: (Eq a, C a) => Spray a -> Spray a Source #

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

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

Whether two sprays are equal up to a scalar factor