halg-polynomials-0.6.0.0: Polynomial rings and basic Gröbner basis computation, part of halg computational algebra suite.
Safe HaskellNone
LanguageHaskell2010

Algebra.Ring.Polynomial.Univariate

Description

Polynomial type optimized to univariate polynomial.

Synopsis

Documentation

data Unipol r Source #

Univariate polynomial. It uses IntMap as its internal representation; so if you want to treat the power greater than maxBound :: Int, please consider using other represntation.

Instances

Instances details
Foldable Unipol Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

fold :: Monoid m => Unipol m -> m #

foldMap :: Monoid m => (a -> m) -> Unipol a -> m #

foldMap' :: Monoid m => (a -> m) -> Unipol a -> m #

foldr :: (a -> b -> b) -> b -> Unipol a -> b #

foldr' :: (a -> b -> b) -> b -> Unipol a -> b #

foldl :: (b -> a -> b) -> b -> Unipol a -> b #

foldl' :: (b -> a -> b) -> b -> Unipol a -> b #

foldr1 :: (a -> a -> a) -> Unipol a -> a #

foldl1 :: (a -> a -> a) -> Unipol a -> a #

toList :: Unipol a -> [a] #

null :: Unipol a -> Bool #

length :: Unipol a -> Int #

elem :: Eq a => a -> Unipol a -> Bool #

maximum :: Ord a => Unipol a -> a #

minimum :: Ord a => Unipol a -> a #

sum :: Num a => Unipol a -> a #

product :: Num a => Unipol a -> a #

Unital r => IsLabel "x" (Unipol r) Source #

By this instance, you can use #x for the unique variable of Unipol r.

Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

fromLabel :: Unipol r #

(DecidableZero r, RightModule Integer r) => RightModule Integer (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(*.) :: Unipol r -> Integer -> Unipol r #

(DecidableZero r, RightModule Natural r) => RightModule Natural (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(*.) :: Unipol r -> Natural -> Unipol r #

(DecidableZero r, LeftModule Integer r) => LeftModule Integer (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(.*) :: Integer -> Unipol r -> Unipol r #

(DecidableZero r, LeftModule Natural r) => LeftModule Natural (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(.*) :: Natural -> Unipol r -> Unipol r #

(Eq r, DecidableZero r) => Eq (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(==) :: Unipol r -> Unipol r -> Bool #

(/=) :: Unipol r -> Unipol r -> Bool #

CoeffRing r => Num (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(+) :: Unipol r -> Unipol r -> Unipol r #

(-) :: Unipol r -> Unipol r -> Unipol r #

(*) :: Unipol r -> Unipol r -> Unipol r #

negate :: Unipol r -> Unipol r #

abs :: Unipol r -> Unipol r #

signum :: Unipol r -> Unipol r #

fromInteger :: Integer -> Unipol r #

(Ord r, DecidableZero r) => Ord (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

compare :: Unipol r -> Unipol r -> Ordering #

(<) :: Unipol r -> Unipol r -> Bool #

(<=) :: Unipol r -> Unipol r -> Bool #

(>) :: Unipol r -> Unipol r -> Bool #

(>=) :: Unipol r -> Unipol r -> Bool #

max :: Unipol r -> Unipol r -> Unipol r #

min :: Unipol r -> Unipol r -> Unipol r #

(CoeffRing r, PrettyCoeff r) => Show (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

showsPrec :: Int -> Unipol r -> ShowS #

show :: Unipol r -> String #

showList :: [Unipol r] -> ShowS #

(Eq r, Field r) => UFD (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

(Eq r, Field r) => PID (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

egcd :: Unipol r -> Unipol r -> (Unipol r, Unipol r, Unipol r) #

(Eq r, Field r) => GCDDomain (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

gcd :: Unipol r -> Unipol r -> Unipol r #

reduceFraction :: Unipol r -> Unipol r -> (Unipol r, Unipol r) #

lcm :: Unipol r -> Unipol r -> Unipol r #

(Eq r, Field r) => IntegralDomain (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

divides :: Unipol r -> Unipol r -> Bool #

maybeQuot :: Unipol r -> Unipol r -> Maybe (Unipol r) #

(Eq r, Field r) => Euclidean (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

degree :: Unipol r -> Maybe Natural #

divide :: Unipol r -> Unipol r -> (Unipol r, Unipol r) #

quot :: Unipol r -> Unipol r -> Unipol r #

rem :: Unipol r -> Unipol r -> Unipol r #

(Eq r, Field r) => ZeroProductSemiring (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

(Eq r, Field r) => UnitNormalForm (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

splitUnit :: Unipol r -> (Unipol r, Unipol r) #

(CoeffRing r, DecidableZero r) => Ring (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

fromInteger :: Integer -> Unipol r

(CoeffRing r, DecidableZero r) => Rig (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

fromNatural :: Natural -> Unipol r #

DecidableZero r => DecidableZero (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

isZero :: Unipol r -> Bool #

(Eq r, Field r) => DecidableUnits (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

recipUnit :: Unipol r -> Maybe (Unipol r) #

isUnit :: Unipol r -> Bool #

(^?) :: Integral n => Unipol r -> n -> Maybe (Unipol r) #

(Eq r, Field r) => DecidableAssociates (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

isAssociate :: Unipol r -> Unipol r -> Bool #

(CoeffRing r, Unital r) => Unital (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

one :: Unipol r #

pow :: Unipol r -> Natural -> Unipol r #

productWith :: Foldable f => (a -> Unipol r) -> f a -> Unipol r #

(CoeffRing r, Commutative r) => Commutative (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

(CoeffRing r, DecidableZero r) => Semiring (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

(CoeffRing r, Multiplicative r) => Multiplicative (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(*) :: Unipol r -> Unipol r -> Unipol r #

pow1p :: Unipol r -> Natural -> Unipol r #

productWith1 :: Foldable1 f => (a -> Unipol r) -> f a -> Unipol r #

DecidableZero r => Monoidal (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

zero :: Unipol r #

sinnum :: Natural -> Unipol r -> Unipol r #

sumWith :: Foldable f => (a -> Unipol r) -> f a -> Unipol r #

(DecidableZero r, Group r) => Group (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(-) :: Unipol r -> Unipol r -> Unipol r #

negate :: Unipol r -> Unipol r #

subtract :: Unipol r -> Unipol r -> Unipol r #

times :: Integral n => n -> Unipol r -> Unipol r #

DecidableZero r => Additive (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(+) :: Unipol r -> Unipol r -> Unipol r #

sinnum1p :: Natural -> Unipol r -> Unipol r #

sumWith1 :: Foldable1 f => (a -> Unipol r) -> f a -> Unipol r #

(DecidableZero r, Abelian r) => Abelian (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

(DecidableZero r, Hashable r) => Hashable (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

hashWithSalt :: Int -> Unipol r -> Int #

hash :: Unipol r -> Int #

NFData r => NFData (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

rnf :: Unipol r -> () #

CoeffRing r => IsPolynomial (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Associated Types

type Coefficient (Unipol r) #

type Arity (Unipol r) :: Nat #

Methods

liftMap :: (Module (Scalar (Coefficient (Unipol r))) alg, Ring alg, Commutative alg) => (Ordinal (Arity (Unipol r)) -> alg) -> Unipol r -> alg #

subst :: (Ring alg, Commutative alg, Module (Scalar (Coefficient (Unipol r))) alg) => Sized (Arity (Unipol r)) alg -> Unipol r -> alg #

substWith :: Ring m => (Coefficient (Unipol r) -> m -> m) -> Sized (Arity (Unipol r)) m -> Unipol r -> m #

sArity' :: Unipol r -> SNat (Arity (Unipol r)) #

sArity :: proxy (Unipol r) -> SNat (Arity (Unipol r)) #

arity :: proxy (Unipol r) -> Integer #

injectCoeff :: Coefficient (Unipol r) -> Unipol r #

injectCoeff' :: proxy (Unipol r) -> Coefficient (Unipol r) -> Unipol r #

monomials :: Unipol r -> HashSet (Monomial (Arity (Unipol r))) #

terms' :: Unipol r -> Map (Monomial (Arity (Unipol r))) (Coefficient (Unipol r)) #

coeff' :: Monomial (Arity (Unipol r)) -> Unipol r -> Coefficient (Unipol r) #

constantTerm :: Unipol r -> Coefficient (Unipol r) #

fromMonomial :: Monomial (Arity (Unipol r)) -> Unipol r #

toPolynomial' :: (Coefficient (Unipol r), Monomial (Arity (Unipol r))) -> Unipol r #

polynomial' :: Map (Monomial (Arity (Unipol r))) (Coefficient (Unipol r)) -> Unipol r #

totalDegree' :: Unipol r -> Int #

var :: Ordinal (Arity (Unipol r)) -> Unipol r #

mapCoeff' :: (Coefficient (Unipol r) -> Coefficient (Unipol r)) -> Unipol r -> Unipol r #

(>|*) :: Monomial (Arity (Unipol r)) -> Unipol r -> Unipol r #

(*|<) :: Unipol r -> Monomial (Arity (Unipol r)) -> Unipol r #

(!*) :: Coefficient (Unipol r) -> Unipol r -> Unipol r #

_Terms' :: Iso' (Unipol r) (Map (Monomial (Arity (Unipol r))) (Coefficient (Unipol r))) #

mapMonomial :: (Monomial (Arity (Unipol r)) -> Monomial (Arity (Unipol r))) -> Unipol r -> Unipol r #

CoeffRing r => IsOrderedPolynomial (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Associated Types

type MOrder (Unipol r) #

(DecidableZero r, Semiring r) => RightModule (Scalar r) (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(*.) :: Unipol r -> Scalar r -> Unipol r #

(DecidableZero r, Semiring r) => LeftModule (Scalar r) (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

Methods

(.*) :: Scalar r -> Unipol r -> Unipol r #

type Arity (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

type Arity (Unipol r) = 1
type Coefficient (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

type Coefficient (Unipol r) = r
type MOrder (Unipol r) Source # 
Instance details

Defined in Algebra.Ring.Polynomial.Univariate

type MOrder (Unipol r) = Grevlex

naiveMult :: (DecidableZero r, Multiplicative r) => Unipol r -> Unipol r -> Unipol r Source #

Polynomial multiplication, naive version.

karatsuba :: forall r. CoeffRing r => Unipol r -> Unipol r -> Unipol r Source #

Polynomial multiplication using Karatsuba's method.

coeffList :: Monoidal k => Unipol k -> [k] Source #

The list of coefficients, in ascending order.

cutoff :: forall k. Natural -> Unipol k -> Unipol k Source #

'cutoff m f gives the polynomial \(f\) but with terms degree strictly less than \(m\); i.e. \(\sum_{0 \leq i < m} a_i X^i\) for \(f = \sum_{i = 0}^n a_n X^n\).

divModUnipolByMult :: (Eq r, Field r) => Unipol r -> Unipol r -> (Unipol r, Unipol r) Source #

divModUnipol :: (CoeffRing r, Field r) => Unipol r -> Unipol r -> (Unipol r, Unipol r) Source #

mapCoeffUnipol :: DecidableZero b => (a -> b) -> Unipol a -> Unipol b Source #

liftMapUnipol :: (Module (Scalar k) r, Monoidal k, Unital r) => (Ordinal 1 -> r) -> Unipol k -> r Source #