computational-algebra-0.3.0.0: Well-kinded computational algebra library, currently supporting Groebner basis.

Safe HaskellNone

Algebra.Algorithms.Groebner.Monomorphic

Contents

Description

Monomorphic interface for Groenber basis.

Synopsis

Documentation

class (Eq r, Field r, NoetherianRing r) => Groebnerable r Source

Synonym

Instances

Polynomial division

divModPolynomialWith :: forall ord r. (IsMonomialOrder ord, Groebnerable r) => ord -> Polynomial r -> [Polynomial r] -> ([(Polynomial r, Polynomial r)], Polynomial r)Source

Groebner basis

calcGroebnerBasisWith :: forall ord r. (Groebnerable r, IsMonomialOrder ord) => ord -> [Polynomial r] -> [Polynomial r]Source

syzygyBuchbergerWith :: forall ord r. (Groebnerable r, IsMonomialOrder ord) => ord -> [Polynomial r] -> [Polynomial r]Source

syzygyBuchbergerWithStrategy :: forall strategy ord r. (Groebnerable r, IsMonomialOrder ord, SelectionStrategy strategy, Ord (Weight strategy ord)) => strategy -> ord -> [Polynomial r] -> [Polynomial r]Source

primeTestBuchbergerWith :: forall ord r. (Groebnerable r, IsMonomialOrder ord) => ord -> [Polynomial r] -> [Polynomial r]Source

simpleBuchbergerWith :: forall ord r. (Groebnerable r, IsMonomialOrder ord) => ord -> [Polynomial r] -> [Polynomial r]Source

Ideal operations

intersection :: forall r. Groebnerable r => [[Polynomial r]] -> [Polynomial r]Source

Calculate a intersection of given ideals.

thEliminationIdeal :: Groebnerable r => Int -> [Polynomial r] -> [Polynomial r]Source

Computes nth elimination ideal.

eliminate :: forall r. Groebnerable r => [Variable] -> [Polynomial r] -> [Polynomial r]Source

eliminateWith :: forall r ord. (IsMonomialOrder ord, Groebnerable r) => ord -> [Variable] -> [Polynomial r] -> [Polynomial r]Source

Computes the ideal with specified variables eliminated.

quotIdeal :: Groebnerable r => [Polynomial r] -> [Polynomial r] -> [Polynomial r]Source

Calculate the ideal quotient of I of J.

quotByPrincipalIdeal :: Groebnerable r => [Polynomial r] -> Polynomial r -> [Polynomial r]Source

Calculate ideal quotient of I by principal ideal

saturationIdeal :: Groebnerable r => [Polynomial r] -> [Polynomial r] -> [Polynomial r]Source

Calculate saturation ideal.

saturationByPrincipalIdeal :: Groebnerable r => [Polynomial r] -> Polynomial r -> [Polynomial r]Source

Calculate saturation ideal by the principal ideal generated by the second argument.

Resultant

resultant :: forall r. Groebnerable r => Polynomial r -> Polynomial r -> rSource

Calculates resultants for given two unary-polynomials.

hasCommonFactor :: (Eq r, Division r, NoetherianRing r) => Polynomial r -> Polynomial r -> BoolSource

Determin if given two unary polynomials have common factor.

Re-exports

data Lex Source

Lexicographical order

Constructors

Lex 

Instances

data Revlex Source

Reversed lexicographical order

Constructors

Revlex 

data Grlex Source

Graded lexicographical order. Same as Graded Lex.

Constructors

Grlex 

data Grevlex Source

Graded reversed lexicographical order. Same as Graded Revlex.

Constructors

Grevlex 

class IsOrder ordering whereSource

Class to lookup ordering from its (type-level) name.

Methods

cmpMonomial :: Proxy ordering -> MonomialOrderSource

Instances

IsOrder Grlex 
IsOrder Grevlex 
IsOrder Revlex 
IsOrder Lex 
IsOrder ord => IsOrder (Graded ord) 
(SingRep Nat n, IsMonomialOrder ord) => IsOrder (WeightedEliminationOrder n ord) 
(ToWeightVector ws, IsOrder ord) => IsOrder (WeightOrder ws ord) 
(IsOrder ord, IsOrder ord', SingRep Nat n) => IsOrder (ProductOrder n ord ord') 

class SelectionStrategy s whereSource

Type-class for selection strategies in Buchberger's algorithm.

Associated Types

type Weight s ord :: *Source

Methods

calcWeight :: (IsPolynomial r n, IsMonomialOrder ord) => Proxy s -> OrderedPolynomial r ord n -> OrderedPolynomial r ord n -> Weight s ordSource

Instances

SelectionStrategy GradedStrategy

Choose the pair with the least LCM(LT(f), LT(g)) w.r.t. graded current ordering.

SelectionStrategy GrevlexStrategy 
SelectionStrategy NormalStrategy 
SelectionStrategy s => SelectionStrategy (SugarStrategy s) 

data NormalStrategy Source

Buchberger's normal selection strategy. This selects the pair with the least LCM(LT(f), LT(g)) w.r.t. current monomial ordering.

Constructors

NormalStrategy 

data SugarStrategy s Source

Sugar strategy. This chooses the pair with the least phantom homogenized degree and then break the tie with the given strategy (say s).

Constructors

SugarStrategy s 

data GrevlexStrategy Source

Choose the pair with the least LCM(LT(f), LT(g)) w.r.t. Grevlex order.

Constructors

GrevlexStrategy 

data GradedStrategy Source

Constructors

GradedStrategy 

Instances

Eq GradedStrategy 
Ord GradedStrategy 
Read GradedStrategy 
Show GradedStrategy 
SelectionStrategy GradedStrategy

Choose the pair with the least LCM(LT(f), LT(g)) w.r.t. graded current ordering.

calcWeight' :: (SelectionStrategy s, IsPolynomial r n, IsMonomialOrder ord, Ord (Weight s ord)) => s -> OrderedPolynomial r ord n -> OrderedPolynomial r ord n -> Weight s ordSource

Calculate the weight of given polynomials w.r.t. the given strategy. Buchberger's algorithm proccesses the pair with the most least weight first. This function requires the Ord instance for the weight; this constraint is not required in the calcWeight because of the ease of implementation. So use this function.