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

Safe HaskellNone
LanguageHaskell2010

Algebra.Algorithms.ZeroDim

Contents

Description

Algorithms for zero-dimensional ideals.

Since 0.4.0.0

Synopsis

Root finding for zero-dimensional ideal

solveM :: forall m r ord n. (Normed r, Ord r, MonadRandom m, Field r, CoeffRing r, KnownNat n, IsMonomialOrder n ord, Convertible r Double, (0 :< n) ~ True) => Ideal (OrderedPolynomial r ord n) -> m [Sized n (Complex Double)] Source #

Finds complex approximate roots of given zero-dimensional ideal, using randomized altorithm.

See also solve' and solveViaCompanion.

solve' :: forall r n ord. (Field r, CoeffRing r, KnownNat n, (0 :< n) ~ True, IsMonomialOrder n ord, Convertible r Double) => Double -> Ideal (OrderedPolynomial r ord n) -> [Sized n (Complex Double)] Source #

solve' err is finds numeric approximate root of the given zero-dimensional polynomial system is, with error <err.

See also solveViaCompanion and solveM.

solveViaCompanion :: forall r ord n. (Ord r, Field r, CoeffRing r, KnownNat n, IsMonomialOrder n ord, Convertible r Double) => Double -> Ideal (OrderedPolynomial r ord n) -> [Sized n (Complex Double)] Source #

solveViaCompanion err is finds numeric approximate root of the given zero-dimensional polynomial system is, with error <err.

See also solve' and solveM.

solveLinear :: (Ord r, Fractional r) => Matrix r -> Vector r -> Maybe (Vector r) Source #

Solves linear system. If the given matrix is degenerate, this returns Nothing.

Radical computation

radical :: forall r ord n. (Ord r, CoeffRing r, KnownNat n, Field r, IsMonomialOrder n ord) => Ideal (OrderedPolynomial r ord n) -> Ideal (OrderedPolynomial r ord n) Source #

Calculate the radical of the given zero-dimensional ideal.

isRadical :: forall r ord n. (Ord r, CoeffRing r, KnownNat n, (0 :< n) ~ True, Field r, IsMonomialOrder n ord) => Ideal (OrderedPolynomial r ord n) -> Bool Source #

Test if the given zero-dimensional ideal is radical or not.

Converting monomial ordering to Lex using FGLM algorithm

fglm :: (Ord r, KnownNat n, Field r, IsMonomialOrder n ord, (0 :< n) ~ True) => Ideal (OrderedPolynomial r ord n) -> ([OrderedPolynomial r Lex n], [OrderedPolynomial r Lex n]) Source #

Calculate the Groebner basis w.r.t. lex ordering of the zero-dimensional ideal using FGLM algorithm. If the given ideal is not zero-dimensional this function may diverge.

fglmMap Source #

Arguments

:: (Ord k, Field k, (0 :< n) ~ True, IsMonomialOrder n ord, CoeffRing k, KnownNat n) 
=> (OrderedPolynomial k ord n -> Vector k)

Linear map from polynomial ring.

-> ([OrderedPolynomial k Lex n], [OrderedPolynomial k Lex n])

The tuple of:

  • lex-Groebner basis of the kernel of the given linear map.
  • The vector basis of the image of the linear map.

Compute the kernel and image of the given linear map using generalized FGLM algorithm.

Internal helper function

solveWith :: forall r n ord. (DecidableZero r, Normed r, Ord r, Field r, CoeffRing r, (0 :< n) ~ True, IsMonomialOrder n ord, KnownNat n, Convertible r Double) => OrderedPolynomial r ord n -> Ideal (OrderedPolynomial r ord n) -> Maybe [Sized n (Complex Double)] Source #

solveWith f is finds complex approximate roots of the given zero-dimensional n-variate polynomial system is, using the given relatively prime polynomial f.

univPoly :: forall r ord n. (Ord r, Field r, CoeffRing r, KnownNat n, IsMonomialOrder n ord) => Ordinal n -> Ideal (OrderedPolynomial r ord n) -> OrderedPolynomial r ord n Source #

Calculate the monic generator of k[X_0, ..., X_n] intersect k[X_i].

reduction :: (CoeffRing r, KnownNat n, IsMonomialOrder n ord, Field r) => Ordinal n -> OrderedPolynomial r ord n -> OrderedPolynomial r ord n Source #

Calculates n-th reduction of f: f div ∂_{x_n} f.

matrixRep :: (DecidableZero t, Eq t, Field t, KnownNat n, IsMonomialOrder n order, Reifies ideal (QIdeal (OrderedPolynomial t order n))) => Quotient (OrderedPolynomial t order n) ideal -> [[t]] Source #

vectorRep :: forall poly ideal. (IsOrderedPolynomial poly, Reifies ideal (QIdeal poly)) => Quotient poly ideal -> Vector (Coefficient poly) Source #