coincident-root-loci-0.2: Equivariant CSM classes of coincident root loci

Safe HaskellNone
LanguageHaskell2010

Math.RootLoci.Algebra.FreeMod

Contents

Description

Free modules.

This module should be imported qualified

Synopsis

Documentation

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 coeff, Eq base) => Eq (FreeMod coeff base) Source # 

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 # 

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 #

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

Methods

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

show :: FreeMod coeff base -> String #

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

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

Methods

pretty :: FreeMod c b -> String Source #

type ZMod base = FreeMod Integer base Source #

Free module with integer coefficients

type QMod base = FreeMod Rational base Source #

Free module with rational coefficients

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

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

A module generator

singleton :: Ord b => 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. Note that we assume here that each generator appears at most once!

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

invScale :: (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)

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

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

The multiplicative unit

konst :: Monoid b => 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

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

Product

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

Multiplies by a monomial

Misc

symPoly :: (Ord a, Monoid a) => Int -> [a] -> ZMod a Source #

A symmetric polynomial of some generators

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

Changing the base set

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

Changing the coefficient ring

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

Extract a subset of terms

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

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