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

Safe HaskellNone
LanguageHaskell2010

Algebra.Algorithms.Groebner

Contents

Synopsis

Groebner basis

isGroebnerBasis :: (IsOrderedPolynomial poly, Field (Coefficient poly)) => Ideal poly -> Bool Source #

Test if the given ideal is Groebner basis, using Buchberger criteria and relatively primeness.

calcGroebnerBasis :: (Field (Coefficient poly), IsOrderedPolynomial poly) => Ideal poly -> [poly] Source #

Caliculating reduced Groebner basis of the given ideal.

calcGroebnerBasisWith :: (IsOrderedPolynomial poly, Field (Coefficient poly), IsMonomialOrder (Arity poly) order) => order -> Ideal poly -> [OrderedPolynomial (Coefficient poly) order (Arity poly)] Source #

Caliculating reduced Groebner basis of the given ideal w.r.t. the specified monomial order.

calcGroebnerBasisWithStrategy :: (Field (Coefficient poly), IsOrderedPolynomial poly, SelectionStrategy (Arity poly) strategy, Ord (Weight (Arity poly) strategy (MOrder poly))) => strategy -> Ideal poly -> [poly] Source #

Caliculating reduced Groebner basis of the given ideal w.r.t. the specified monomial order.

buchberger :: (Field (Coefficient poly), IsOrderedPolynomial poly) => Ideal poly -> [poly] Source #

Calculate Groebner basis applying (modified) Buchberger's algorithm. This function is same as syzygyBuchberger.

syzygyBuchberger :: (Field (Coefficient poly), IsOrderedPolynomial poly) => Ideal poly -> [poly] Source #

Buchberger's algorithm greately improved using the syzygy theory with the sugar strategy. Utilizing priority queues, this function reduces division complexity and comparison time. If you don't have strong reason to avoid this function, this function is recommended to use.

simpleBuchberger :: (Field (Coefficient poly), IsOrderedPolynomial poly) => Ideal poly -> [poly] Source #

The Naive buchberger's algorithm to calculate Groebner basis for the given ideal.

primeTestBuchberger :: (Field (Coefficient poly), IsOrderedPolynomial poly) => Ideal poly -> [poly] Source #

Buchberger's algorithm slightly improved by discarding relatively prime pair.

reduceMinimalGroebnerBasis :: (Field (Coefficient poly), IsOrderedPolynomial poly) => [poly] -> [poly] Source #

Reduce minimum Groebner basis into reduced Groebner basis.

minimizeGroebnerBasis :: (Field (Coefficient poly), IsOrderedPolynomial poly) => [poly] -> [poly] Source #

Selection Strategies

syzygyBuchbergerWithStrategy :: (Field (Coefficient poly), IsOrderedPolynomial poly, SelectionStrategy (Arity poly) strategy, Ord (Weight (Arity poly) strategy (MOrder poly))) => strategy -> Ideal poly -> [poly] Source #

apply buchberger's algorithm using given selection strategy.

class SelectionStrategy n s where Source #

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

Minimal complete definition

calcWeight

Associated Types

type Weight n s ord :: * Source #

Methods

calcWeight :: (IsOrderedPolynomial poly, n ~ Arity poly) => Proxy s -> poly -> poly -> Weight n s (MOrder poly) Source #

Calculates the weight for the given pair of polynomial used for selection strategy.

Instances

SelectionStrategy * n GradedStrategy Source #

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

Associated Types

type Weight n (GradedStrategy :: Nat) (s :: n) ord :: * Source #

Methods

calcWeight :: (IsOrderedPolynomial poly, (Nat ~ GradedStrategy) (Arity poly)) => Proxy n s -> poly -> poly -> Weight n GradedStrategy s (MOrder poly) Source #

SelectionStrategy * n GrevlexStrategy Source # 

Associated Types

type Weight n (GrevlexStrategy :: Nat) (s :: n) ord :: * Source #

Methods

calcWeight :: (IsOrderedPolynomial poly, (Nat ~ GrevlexStrategy) (Arity poly)) => Proxy n s -> poly -> poly -> Weight n GrevlexStrategy s (MOrder poly) Source #

SelectionStrategy * n NormalStrategy Source # 

Associated Types

type Weight n (NormalStrategy :: Nat) (s :: n) ord :: * Source #

Methods

calcWeight :: (IsOrderedPolynomial poly, (Nat ~ NormalStrategy) (Arity poly)) => Proxy n s -> poly -> poly -> Weight n NormalStrategy s (MOrder poly) Source #

SelectionStrategy * n s => SelectionStrategy * n (SugarStrategy s) Source # 

Associated Types

type Weight n (SugarStrategy s :: Nat) (s :: n) ord :: * Source #

Methods

calcWeight :: (IsOrderedPolynomial poly, (Nat ~ SugarStrategy s) (Arity poly)) => Proxy n s -> poly -> poly -> Weight n (SugarStrategy s) s (MOrder poly) Source #

calcWeight' :: (SelectionStrategy (Arity poly) s, IsOrderedPolynomial poly) => s -> poly -> poly -> Weight (Arity poly) s (MOrder poly) Source #

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.

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 

Ideal operations

isIdealMember :: (Field (Coefficient poly), IsOrderedPolynomial poly) => poly -> Ideal poly -> Bool Source #

Test if the given polynomial is the member of the ideal.

intersection :: forall poly k. (Field (Coefficient poly), IsOrderedPolynomial poly) => Sized k (Ideal poly) -> Ideal poly Source #

An intersection ideal of given ideals (using WeightedEliminationOrder).

thEliminationIdeal :: forall poly n. (IsMonomialOrder (Arity poly - n) (MOrder poly), Field (Coefficient poly), IsOrderedPolynomial poly, (n :<= Arity poly) ~ True) => SNat n -> Ideal poly -> Ideal (OrderedPolynomial (Coefficient poly) (MOrder poly) (Arity poly :-. n)) Source #

Calculate n-th elimination ideal using WeightedEliminationOrder ordering.

thEliminationIdealWith :: (IsOrderedPolynomial poly, m ~ Arity poly, k ~ Coefficient poly, Field k, KnownNat (m :-. n), (n :<= m) ~ True, EliminationType m n ord) => ord -> SNat n -> Ideal poly -> Ideal (OrderedPolynomial k Grevlex (m :-. n)) Source #

Calculate n-th elimination ideal using the specified n-th elimination type order.

unsafeThEliminationIdealWith :: (IsOrderedPolynomial poly, m ~ Arity poly, k ~ Coefficient poly, Field k, IsMonomialOrder m ord, KnownNat (m :-. n), (n :<= m) ~ True) => ord -> SNat n -> Ideal poly -> Ideal (OrderedPolynomial k Grevlex (m :-. n)) Source #

Calculate n-th elimination ideal using the specified n-th elimination type order. This function should be used carefully because it does not check whether the given ordering is n-th elimintion type or not.

quotIdeal :: forall poly l. (IsOrderedPolynomial poly, Field (Coefficient poly)) => Ideal poly -> Sized l poly -> Ideal poly Source #

Ideal quotient by the given ideal.

quotByPrincipalIdeal :: (Field (Coefficient poly), IsOrderedPolynomial poly) => Ideal poly -> poly -> Ideal poly Source #

Ideal quotient by a principal ideals.

saturationIdeal :: forall poly l. (Field (Coefficient poly), IsOrderedPolynomial poly) => Ideal poly -> Sized l poly -> Ideal poly Source #

Saturation ideal

saturationByPrincipalIdeal :: forall poly. (IsOrderedPolynomial poly, Field (Coefficient poly)) => Ideal poly -> poly -> Ideal poly Source #

Saturation by a principal ideal.

Resultant

resultant :: forall poly. (Field (Coefficient poly), IsOrderedPolynomial poly, Arity poly ~ 1) => poly -> poly -> Coefficient poly Source #

Calculate resultant for given two unary polynomimals.

hasCommonFactor :: (Field (Coefficient poly), IsOrderedPolynomial poly, Arity poly ~ 1) => poly -> poly -> Bool Source #

Determine whether two polynomials have a common factor with positive degree using resultant.

lcmPolynomial :: forall poly. (Field (Coefficient poly), IsOrderedPolynomial poly) => poly -> poly -> poly Source #

Calculates the Least Common Multiply of the given pair of polynomials.

gcdPolynomial :: (Field (Coefficient poly), IsOrderedPolynomial poly) => poly -> poly -> poly Source #

Calculates the Greatest Common Divisor of the given pair of polynomials.