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

Safe HaskellNone
LanguageHaskell2010

Math.RootLoci.Algebra.SymmPoly

Contents

Description

Symmetric polynomials in two variables alpha and beta.

We provide three representation:

  • symmetric polynomials in alpha and beta (Chern roots)
  • polynomials in the elementary symmetric polynomials c1=alpha+beta and c2=alpha*beta (Chern classes)
  • Schur polynomials s[i,j]

The monomials of the first two of these form monoids (the product of monomials is again a monomial), and can be used uniformly with the help of some type-level hackery.

How to use the unified interface? Suppose you have a function like this:

tau :: ChernBase base => Int -> ZMod base

When calling it, you want to specify the output type (either ZMod AB or ZMod Chern). You can do that three ways:

x = tau @AB 10                  -- this needs -XTypeApplications
x = (tau 10 :: ZMod AB)
x = spec1' ChernRoot $ tau 10

The first one is the most convenient, but it only works with GHC 8 and later. The other two work with older GHC versions, too.

Synopsis

Base monomials

data AB Source #

Chern roots: alpha^i * beta^j, monomial base of Z[alpha,beta]

Constructors

AB !Int !Int 

Instances

Eq AB Source # 

Methods

(==) :: AB -> AB -> Bool #

(/=) :: AB -> AB -> Bool #

Ord AB Source # 

Methods

compare :: AB -> AB -> Ordering #

(<) :: AB -> AB -> Bool #

(<=) :: AB -> AB -> Bool #

(>) :: AB -> AB -> Bool #

(>=) :: AB -> AB -> Bool #

max :: AB -> AB -> AB #

min :: AB -> AB -> AB #

Show AB Source # 

Methods

showsPrec :: Int -> AB -> ShowS #

show :: AB -> String #

showList :: [AB] -> ShowS #

Monoid AB Source # 

Methods

mempty :: AB #

mappend :: AB -> AB -> AB #

mconcat :: [AB] -> AB #

Pretty AB Source # 

Methods

pretty :: AB -> String Source #

Graded AB Source # 

Methods

grade :: AB -> Int Source #

ChernBase AB Source # 

data Schur Source #

Schur basis function: S[i,j]

Constructors

Schur !Int !Int 

alphaBeta :: AB Source #

alpha * beta = c2

c1 :: Chern Source #

c1 = alpha + beta

c2 :: Chern Source #

c2 = alpha * beta

Unified interface

data Sing base where Source #

A singleton for distinguishing the two cases

Constructors

ChernRoot :: Sing AB 
ChernClass :: Sing Chern 

Instances

Eq (Sing base) Source # 

Methods

(==) :: Sing base -> Sing base -> Bool #

(/=) :: Sing base -> Sing base -> Bool #

Ord (Sing base) Source # 

Methods

compare :: Sing base -> Sing base -> Ordering #

(<) :: Sing base -> Sing base -> Bool #

(<=) :: Sing base -> Sing base -> Bool #

(>) :: Sing base -> Sing base -> Bool #

(>=) :: Sing base -> Sing base -> Bool #

max :: Sing base -> Sing base -> Sing base #

min :: Sing base -> Sing base -> Sing base #

class (Eq base, Ord base, Monoid base, Graded base, Pretty base) => ChernBase base where Source #

Common interface to work with Chern classes and Chern roots uniformly

Methods

chernTag :: base -> Sing base Source #

chernTag1 :: f base -> Sing base Source #

chernTag2 :: f (g base) -> Sing base Source #

chernTag3 :: f (g (h base)) -> Sing base Source #

fromAB :: ZMod AB -> ZMod base Source #

fromChern :: ZMod Chern -> ZMod base Source #

fromSchur :: ZMod Schur -> ZMod base Source #

toAB :: ZMod base -> ZMod AB Source #

toChern :: ZMod base -> ZMod Chern Source #

toSchur :: ZMod base -> ZMod Schur Source #

Helper functions for constructing and specializing uniform things

select0 :: (AB, Chern) -> ChernBase base => base Source #

Constructing uniform things

select1 :: (f AB, f Chern) -> ChernBase base => f base Source #

select2 :: (f (g AB), f (g Chern)) -> ChernBase base => f (g base) Source #

select3 :: (f (g (h AB)), f (g (h Chern))) -> ChernBase base => f (g (h base)) Source #

select0' :: (AB, Chern) -> ChernBase base => Sing base -> base Source #

Constructing unifom things using a tag

select1' :: (f AB, f Chern) -> ChernBase base => Sing base -> f base Source #

select2' :: (f (g AB), f (g Chern)) -> ChernBase base => Sing base -> f (g base) Source #

select3' :: (f (g (h AB)), f (g (h Chern))) -> ChernBase base => Sing base -> f (g (h base)) Source #

spec0' :: ChernBase base => Sing base -> (forall b. ChernBase b => b) -> base Source #

Specializing uniform things

spec1' :: ChernBase base => Sing base -> (forall b. ChernBase b => f b) -> f base Source #

spec2' :: ChernBase base => Sing base -> (forall b. ChernBase b => f (g b)) -> f (g base) Source #

spec3' :: ChernBase base => Sing base -> (forall b. ChernBase b => f (g (h b))) -> f (g (h base)) Source #

Grading

class Graded a where Source #

Minimal complete definition

grade

Methods

grade :: a -> Int Source #

Instances

Graded Schur Source # 

Methods

grade :: Schur -> Int Source #

Graded Chern Source # 

Methods

grade :: Chern -> Int Source #

Graded AB Source # 

Methods

grade :: AB -> Int Source #

Graded HS Source # 

Methods

grade :: HS -> Int Source #

Graded US Source # 

Methods

grade :: US -> Int Source #

Graded G Source # 

Methods

grade :: G -> Int Source #

Graded H Source # 

Methods

grade :: H -> Int Source #

Graded U Source # 

Methods

grade :: U -> Int Source #

Graded ab => Graded (Gam ab) Source # 

Methods

grade :: Gam ab -> Int Source #

Graded ab => Graded (Eta ab) Source # 

Methods

grade :: Eta ab -> Int Source #

Graded ab => Graded (Omega ab) Source # 

Methods

grade :: Omega ab -> Int Source #

filterGrade :: (Ord b, Graded b) => Int -> ZMod b -> ZMod b Source #

Conversions

abToChern :: ZMod AB -> ZMod Chern Source #

Converts a symmetric polynomial in the AB base (Chern roots) to the Chern base (elementary symmetric polynomials or Chern classes)

symmetricReduction :: ZMod AB -> Either (ZMod Chern, ZMod AB) (ZMod Chern) Source #

Left means there is a non-symmetric remainder; Right means that input was symmetric.

schurToAB :: ZMod Schur -> ZMod AB Source #

Convert Schur to Chern roots

schurToChern :: ZMod Schur -> ZMod Chern Source #

Convert Schur to Chern classes (elementary symmetric polynomials)

random polynomials for testing