constructive-algebra-0.3.0: A library of constructive algebra.

Algebra.UPoly

Description

Univariate polynomials parametrised by the variable name.

Synopsis

Documentation

newtype CommutativeRing r => UPoly r x Source

Polynomials over a commutative ring, indexed by a phantom type x that denote the name of the variable that the polynomial is over. For example UPoly Q X_ is Q[x] and UPoly Q T_ is Q[t].

Constructors

UP [r] 

Instances

Eq r => Eq (UPoly r x) 
(Show r, Field r, Num r, Show x) => Num (UPoly r x) 
(Show k, Field k, Num k, Show x) => Num (FieldOfRationalFunctions k x) 
Ord r => Ord (UPoly r x) 
(CommutativeRing r, Eq r, Show r, Show x) => Show (UPoly r x) 
(CommutativeRing r, Eq r, Arbitrary r) => Arbitrary (UPoly r x) 
(CommutativeRing r, Eq r) => Ring (UPoly r x) 
(CommutativeRing r, Eq r) => CommutativeRing (UPoly r x) 
(CommutativeRing r, Eq r) => IntegralDomain (UPoly r x) 
(Field k, Eq k) => EuclideanDomain (UPoly k x) 
(ExplicitUnits a, Eq a) => ExplicitUnits (UPoly a x) 
(Field k, Eq k) => PruferDomain (UPoly k x) 

deg :: CommutativeRing r => UPoly r x -> IntegerSource

The degree of the polynomial.

type Qx = UPoly Q X_Source

Useful shorthand for Q[x].

x :: QxSource

The variable x in Q[x].

toUPoly :: (CommutativeRing r, Eq r) => [r] -> UPoly r xSource

Take a list and construct a polynomial by removing all zeroes in the end.

monomial :: CommutativeRing r => r -> Integer -> UPoly r xSource

Take an element of the ring and the degree of the desired monomial, for example: monomial 3 7 = 3x^7

lt :: CommutativeRing r => UPoly r x -> rSource

Compute the leading term of a polynomial.

deriv :: CommutativeRing r => UPoly r x -> UPoly r xSource

Formal derivative of polynomials in k[x].

cont :: (GCDDomain a, Eq a) => UPoly a x -> aSource

Compute the content of a polynomial, i.e. the gcd of the coefficients.

isPrimitive :: (ExplicitUnits a, GCDDomain a, Eq a) => UPoly a x -> BoolSource

If all coefficients are relatively prime then the polynomial is primitive.

toPrimitive :: (GCDDomain a, Eq a) => UPoly (FieldOfFractions a) x -> (FieldOfFractions a, UPoly a x)Source

Lemma 4.2: Given a polynomial p in K[x] where K=Quot(A) we can find c in K and q primitive in A[x] such that p = cq.

gaussLemma :: (ExplicitUnits a, GCDDomain a, Eq a) => UPoly a x -> UPoly a x -> PropertySource

Gauss lemma says that if p and q are polynomials over a GCD domain then cont(pq) = cont(p) * cont(q).

gcdUPolyWitness :: (GCDDomain a, Eq a) => UPoly a x -> UPoly a x -> (UPoly a x, UPoly a x, UPoly a x)Source

Proof that if A is a GCD domain then A[x] also is a GCD domain. This also computes witnesses that the computed GCD divides the given polynomials.

sqfr :: (Num k, Field k) => UPoly k x -> UPoly k xSource

Square free decomposition of a polynomial.

sqfrDec :: (Num k, Field k) => UPoly k x -> [UPoly k x]Source

Distinct power factorization, aka square free decomposition