polynomial-algebra-0.1.0.1: Multivariate polynomial rings

Safe HaskellSafe
LanguageHaskell2010

Math.Algebra.Polynomial.FreeModule

Contents

Description

Free modules over some generator set.

This module should be imported qualified.

Synopsis

Partial monoids

class PartialMonoid a where Source #

Minimal complete definition

pmUnit

Methods

pmUnit :: a Source #

pmAdd :: a -> a -> Maybe a Source #

pmSum :: [a] -> Maybe a Source #

Instances
KnownNat n => PartialMonoid (SgnExt var n) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Exterior.Indexed

Methods

pmUnit :: SgnExt var n Source #

pmAdd :: SgnExt var n -> SgnExt var n -> Maybe (SgnExt var n) Source #

pmSum :: [SgnExt var n] -> Maybe (SgnExt var n) Source #

A type class

class Ord (BaseF a) => FreeModule a where Source #

The reason for this type class is to make using newtype wrappers more convenient

Associated Types

type BaseF a :: * Source #

type CoeffF a :: * Source #

Instances
Ord b => FreeModule (FreeMod c b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.FreeModule

Associated Types

type BaseF (FreeMod c b) :: Type Source #

type CoeffF (FreeMod c b) :: Type Source #

FreeModule (Poly c v) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Multivariate.Infinite

Associated Types

type BaseF (Poly c v) :: Type Source #

type CoeffF (Poly c v) :: Type Source #

Methods

toFreeModule :: Poly c v -> FreeMod (CoeffF (Poly c v)) (BaseF (Poly c v)) Source #

fromFreeModule :: FreeMod (CoeffF (Poly c v)) (BaseF (Poly c v)) -> Poly c v Source #

Ord v => FreeModule (Poly c v) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Multivariate.Generic

Associated Types

type BaseF (Poly c v) :: Type Source #

type CoeffF (Poly c v) :: Type Source #

Methods

toFreeModule :: Poly c v -> FreeMod (CoeffF (Poly c v)) (BaseF (Poly c v)) Source #

fromFreeModule :: FreeMod (CoeffF (Poly c v)) (BaseF (Poly c v)) -> Poly c v Source #

FreeModule (Univariate c v) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Univariate

Associated Types

type BaseF (Univariate c v) :: Type Source #

type CoeffF (Univariate c v) :: Type Source #

FreeModule (Poly c v n) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Multivariate.Indexed

Associated Types

type BaseF (Poly c v n) :: Type Source #

type CoeffF (Poly c v n) :: Type Source #

Methods

toFreeModule :: Poly c v n -> FreeMod (CoeffF (Poly c v n)) (BaseF (Poly c v n)) Source #

fromFreeModule :: FreeMod (CoeffF (Poly c v n)) (BaseF (Poly c v n)) -> Poly c v n Source #

FreeModule (Poly c v n) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Multivariate.Compact

Associated Types

type BaseF (Poly c v n) :: Type Source #

type CoeffF (Poly c v n) :: Type Source #

Methods

toFreeModule :: Poly c v n -> FreeMod (CoeffF (Poly c v n)) (BaseF (Poly c v n)) Source #

fromFreeModule :: FreeMod (CoeffF (Poly c v n)) (BaseF (Poly c v n)) -> Poly c v n Source #

FreeModule (ExtAlg c v n) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Exterior.Indexed

Associated Types

type BaseF (ExtAlg c v n) :: Type Source #

type CoeffF (ExtAlg c v n) :: Type Source #

Methods

toFreeModule :: ExtAlg c v n -> FreeMod (CoeffF (ExtAlg c v n)) (BaseF (ExtAlg c v n)) Source #

fromFreeModule :: FreeMod (CoeffF (ExtAlg c v n)) (BaseF (ExtAlg c v n)) -> ExtAlg c v n Source #

Free modules

newtype FreeMod coeff base Source #

Free module over a coefficient ring with the given base. Internally a map storing the coefficients. We maintain the invariant that the coefficients are never zero.

Constructors

FreeMod 

Fields

Instances
(Eq base, Eq coeff) => Eq (FreeMod coeff base) Source # 
Instance details

Defined in Math.Algebra.Polynomial.FreeModule

Methods

(==) :: FreeMod coeff base -> FreeMod coeff base -> Bool #

(/=) :: FreeMod coeff base -> FreeMod coeff base -> Bool #

(Monoid b, Ord b, Eq c, Num c) => Num (FreeMod c b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.FreeModule

Methods

(+) :: FreeMod c b -> FreeMod c b -> FreeMod c b #

(-) :: FreeMod c b -> FreeMod c b -> FreeMod c b #

(*) :: FreeMod c b -> FreeMod c b -> FreeMod c b #

negate :: FreeMod c b -> FreeMod c b #

abs :: FreeMod c b -> FreeMod c b #

signum :: FreeMod c b -> FreeMod c b #

fromInteger :: Integer -> FreeMod c b #

(Ord base, Ord coeff) => Ord (FreeMod coeff base) Source # 
Instance details

Defined in Math.Algebra.Polynomial.FreeModule

Methods

compare :: FreeMod coeff base -> FreeMod coeff base -> Ordering #

(<) :: FreeMod coeff base -> FreeMod coeff base -> Bool #

(<=) :: FreeMod coeff base -> FreeMod coeff base -> Bool #

(>) :: FreeMod coeff base -> FreeMod coeff base -> Bool #

(>=) :: FreeMod coeff base -> FreeMod coeff base -> Bool #

max :: FreeMod coeff base -> FreeMod coeff base -> FreeMod coeff base #

min :: FreeMod coeff base -> FreeMod coeff base -> FreeMod coeff base #

(Show base, Show coeff) => Show (FreeMod coeff base) Source # 
Instance details

Defined in Math.Algebra.Polynomial.FreeModule

Methods

showsPrec :: Int -> FreeMod coeff base -> ShowS #

show :: FreeMod coeff base -> String #

showList :: [FreeMod coeff base] -> ShowS #

Ord b => FreeModule (FreeMod c b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.FreeModule

Associated Types

type BaseF (FreeMod c b) :: Type Source #

type CoeffF (FreeMod c b) :: Type Source #

(Num c, Eq c, Pretty c, IsSigned c, Pretty b) => Pretty (FreeMod c b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Pretty

type BaseF (FreeMod c b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.FreeModule

type BaseF (FreeMod c b) = b
type CoeffF (FreeMod c b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.FreeModule

type CoeffF (FreeMod c b) = c

type ZMod base = FreeMod Integer base Source #

Free module with integer coefficients

type QMod base = FreeMod Rational base Source #

Free module with rational coefficients

Support

size :: FreeMod c b -> Int Source #

Number of terms

supportList :: Ord b => FreeMod c b -> [b] Source #

The support as a list

supportSet :: Ord b => FreeMod c b -> Set b Source #

The support as a set

Sanity checking

normalize :: (Ord b, Eq c, Num c) => FreeMod c b -> FreeMod c b Source #

Should be the identity function

safeEq :: (Ord b, Eq b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> Bool Source #

Safe equality testing (should be identical to ==)

Constructing and deconstructing

zero :: FreeMod c b Source #

The additive unit

isZero :: Ord b => FreeMod c b -> Bool Source #

Testing for equality with zero (WARNING: this assumes that the invariant of never having zero coefficients actually holds!)

generator :: Num c => b -> FreeMod c b Source #

A module generator

singleton :: (Ord b, Num c, Eq c) => b -> c -> FreeMod c b Source #

A single generator with a coefficient

fromList :: (Eq c, Num c, Ord b) => [(b, c)] -> FreeMod c b Source #

Conversion from list. This should handle repeated generators correctly (adding their coefficients).

fromMap :: (Eq c, Num c, Ord b) => Map b c -> FreeMod c b Source #

fromGeneratorSet :: (Ord b, Num c) => Set b -> FreeMod c b Source #

Returns the sum of the given generator elements

fromGeneratorList :: (Ord b, Eq c, Num c) => [b] -> FreeMod c b Source #

Returns the sum of the given generator elements

toList :: FreeMod c b -> [(b, c)] Source #

Conversion to list

coeffOf :: (Ord b, Num c) => b -> FreeMod c b -> c Source #

Extract the coefficient of a generator

findMaxTerm :: Ord b => FreeMod c b -> Maybe (b, c) Source #

Finds the term with the largest generator (in the natural ordering of the generators)

findMinTerm :: Ord b => FreeMod c b -> Maybe (b, c) Source #

Finds the term with the smallest generator (in the natural ordering of the generators)

Basic operations

neg :: Num c => FreeMod c b -> FreeMod c b Source #

Negation

add :: (Ord b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> FreeMod c b Source #

Additions

sub :: (Ord b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> FreeMod c b Source #

Subtraction

scale :: (Ord b, Eq c, Num c) => c -> FreeMod c b -> FreeMod c b Source #

Scaling by a number

divideByConst :: (Ord b, Eq c, Integral c, Show c) => c -> FreeMod c b -> FreeMod c b Source #

Dividing by a number (assuming that the coefficient ring is integral, and each coefficient is divisible by the given number)

addScale :: (Ord b, Eq c, Num c) => FreeMod c b -> c -> FreeMod c b -> FreeMod c b Source #

Addition after scaling: A + c*B.

subScale :: (Ord b, Eq c, Num c) => FreeMod c b -> c -> FreeMod c b -> FreeMod c b Source #

Subtraction after scaling: A - c*B. This is a handy optimization for conversion algorithms.

sum :: (Ord b, Eq c, Num c) => [FreeMod c b] -> FreeMod c b Source #

Summation

linComb :: (Ord b, Eq c, Num c) => [(c, FreeMod c b)] -> FreeMod c b Source #

Linear combination

flatMap :: (Ord b1, Ord b2, Eq c, Num c) => (b1 -> FreeMod c b2) -> FreeMod c b1 -> FreeMod c b2 Source #

Expand each generator into a term in another module and then sum the results

flatMap' :: (Ord b1, Ord b2, Eq c2, Num c2) => (c1 -> c2) -> (b1 -> FreeMod c2 b2) -> FreeMod c1 b1 -> FreeMod c2 b2 Source #

histogram :: (Ord b, Num c) => [b] -> FreeMod c b Source #

The histogram of a multiset of generators is naturally an element of the given Z-module.

Rings (at least some simple ones, where the basis form a partial monoid)

one :: (Monoid b, Num c) => FreeMod c b Source #

The multiplicative unit

konst :: (Monoid b, Eq c, Num c) => c -> FreeMod c b Source #

A constant

mul :: (Ord b, Monoid b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> FreeMod c b Source #

Multiplying two ring elements

mul' :: (Ord b, PartialMonoid b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> FreeMod c b Source #

Multiplying two ring elements, when the base forms a partial monoid

product :: (Ord b, Monoid b, Eq c, Num c) => [FreeMod c b] -> FreeMod c b Source #

Product

product' :: (Ord b, PartialMonoid b, Eq c, Num c) => [FreeMod c b] -> FreeMod c b Source #

Product, when the base forms a partial monoid

mulWith :: (Ord b, Eq c, Num c) => (b -> b -> b) -> FreeMod c b -> FreeMod c b -> FreeMod c b Source #

Multiplying two ring elements, using the given monoid operation on base

mulWith' :: (Ord b, Eq c, Num c) => (b -> b -> Maybe b) -> FreeMod c b -> FreeMod c b -> FreeMod c b Source #

Multiplication using a "truncated" operation on the base

mulWith'' :: (Ord b, Eq c, Num c) => (b -> b -> Maybe (b, c)) -> FreeMod c b -> FreeMod c b -> FreeMod c b Source #

productWith :: (Ord b, Eq c, Num c) => b -> (b -> b -> b) -> [FreeMod c b] -> FreeMod c b Source #

Product, using the given Monoid empty and operation.

Implementation note: we only use the user-supported empty value in case of an empty product.

productWith' :: (Ord b, Eq c, Num c) => b -> (b -> b -> Maybe b) -> [FreeMod c b] -> FreeMod c b Source #

productWith'' :: (Ord b, Eq c, Num c) => b -> (b -> b -> Maybe (b, c)) -> [FreeMod c b] -> FreeMod c b Source #

mulByMonom :: (Eq c, Num c, Ord b, Monoid b) => b -> FreeMod c b -> FreeMod c b Source #

Multiplies by a monomial

unsafeMulByMonom :: (Ord b, Monoid b) => b -> FreeMod c b -> FreeMod c b Source #

Multiplies by a monomial (NOTE: we assume that this is an injective operation!!!)

mulByMonom' :: (Eq c, Num c, Ord b, PartialMonoid b) => b -> FreeMod c b -> FreeMod c b Source #

Multiplies by a partial monomial

Integer / Rational conversions

fromZMod :: (Num c, Typeable c, Eq c, Num c, Ord b, Typeable b) => ZMod b -> FreeMod c b Source #

This is an optimized coefficient ring change function. It detects runtime whether the output coefficient ring is also the integers, and does nothing in that case.

fromQMod :: (Fractional c, Typeable c, Eq c, Num c, Ord b, Typeable b) => QMod b -> FreeMod c b Source #

This is an optimized coefficient ring change function. It detects runtime whether the output coefficient ring is also the rational, and does nothing in that case.

unsafeCoeffChange :: (Typeable c1, Typeable c2, Eq c2, Num c2, Ord b, Typeable b) => (c1 -> c2) -> FreeMod c1 b -> FreeMod c2 b Source #

This is an optimized coefficient ring change function. It detects runtime whether the output coefficient ring is the same as the input, and does nothing in that case.

For this to be valid, it is required that the supported function is identity in the case c1 ~ c2 !!!

unsafeZModFromQMod :: Ord b => QMod b -> ZMod b Source #

Given a polynomial with formally rational coefficients, but whose coeffiecients are actually integers, we return the corresponding polynomial with integer coefficients

Misc

mapBase :: (Ord a, Ord b, Eq c, Num c) => (a -> b) -> FreeMod c a -> FreeMod c b Source #

Changing the base set

unsafeMapBase :: (Ord a, Ord b) => (a -> b) -> FreeMod c a -> FreeMod c b Source #

Changing the base set (the user must guarantee that the map is injective!!)

mapCoeff :: (Ord b, Eq c2, Num c2) => (c1 -> c2) -> FreeMod c1 b -> FreeMod c2 b Source #

Changing the coefficient ring

mapCoeffWithKey :: (Ord b, Eq c2, Num c2) => (b -> c1 -> c2) -> FreeMod c1 b -> FreeMod c2 b Source #

filterBase :: Ord b => (b -> Bool) -> FreeMod c b -> FreeMod c b Source #

Extract a subset of terms

mapMaybeBase :: (Ord a, Ord b, Eq c, Num c) => (a -> Maybe b) -> FreeMod c a -> FreeMod c b Source #

Map and extract a subset of terms

unsafeMapMaybeBase :: (Ord a, Ord b) => (a -> Maybe b) -> FreeMod c a -> FreeMod c b Source #

Like mapMaybeBase, but the user must guarantee that the Just part of the map is injective!

mapMaybeBaseCoeff :: (Ord a, Ord b, Eq c, Num c) => (a -> Maybe (b, c)) -> FreeMod c a -> FreeMod c b Source #

onFreeMod :: (Ord a, Ord b) => (Map a c -> Map b c) -> FreeMod c a -> FreeMod c b Source #

NOTE: This is UNSAFE! The user must guarantee that the map respects the invariants!

onFreeMod' :: (Ord a, Ord b) => (Map a c -> Map b d) -> FreeMod c a -> FreeMod d b Source #