coincident-root-loci-0.3: Equivariant CSM classes of coincident root loci
Safe HaskellNone
LanguageHaskell2010

Math.RootLoci.CSM.Equivariant.Ordered

Description

CSM classes of the (open) strata in the set of ordered n-tuples, that is, Q^n = P^1 x P^1 x ... x P^1

Of special interest is the open stratum of distinct points, since any other stratum can be computed from that stratum by a simple push-forward.

The open stratum of distinct points can be computed recursively, since the full space Q^n is the disjoint union of all stratums (indexed by set partitions).

But we also have a recursive formula, which makes the computation significantly faster.

Synopsis

The product of projective lines P^1 x ... x P^1

tangentChernClass Source #

Arguments

:: ChernBase base 
=> Int

the number of projective lines

-> ZMod (Omega base)

the tangent chern class of their product

Chern class of the tangent bundle of a product of projective lines.

The formula is:

c(T(P^1 x P^1 ... x P^1)) = prod_i (1 + alpha + beta + 2*omega_i)

because

c(T(PV)) = \prod_k (1 + w_i + omega)  `mod`  prod_k (w_i + omega) 

and

(1+alpha+omega) * (1+beta+omega) = 1 + alpha + beta + 2*omega 

since the quadratic term is c_2 of a line bundle which is zero

Diagonal embedding

j_star :: ChernBase base => [[Int]] -> ZMod (Omega base) -> ZMod (Omega base) Source #

Diagonal embeddings of ordered products of P^1-s

smallDiagonal :: forall base. ChernBase base => Int -> ZMod (Omega base) Source #

The CSM of the small diagonal in P^1 x ... x P^1

Recursive computation of the CSM of the strata

computeOpenStratumCSM :: ChernBase base => Int -> ZMod (Omega base) Source #

Recursively compute the CSM of the Zariski-open set U^n of distinct ordered points in Q^d = P^1 x ... x P^1. We can compute this by we can subtract all the distinct fat diagonals from the Chern class of Q^d, and the diagonals are just pushforwards of the same thing for smaller d-s.

NOTE: We also have a more explicit formula for the result (which is much faster to compute) and we can compare the two.

Note: Forgetting the alpha/beta part, this should equal to

(1-h1-h2-...-hd)^(d-3)

But, remember that in this formula, h_i^2 = 0 for all i!

Including also alpha and beta we have instead the umbral formula

(q-h1-h2-...-hd)^(d-3)

where we also have to do the umbral substitution q^k -> Q_k, and the polynomials Q_k(alpha,beta) are defined recursively, and are defined for k >= -3.

computeAnyStratumCSM :: ChernBase base => SetPartition -> ZMod (Omega base) Source #

Simply the pushforward of the CSM of the open stratum along the diagonal map corresponding to the given set partition

computeClosureOfAnyStratumCSM :: ChernBase base => SetPartition -> ZMod (Omega base) Source #

We sum over the closure

The structure lemma

newtype QPow Source #

A formal monomial q^k

Constructors

QPow Int 

Instances

Instances details
Eq QPow Source # 
Instance details

Defined in Math.RootLoci.CSM.Equivariant.Ordered

Methods

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

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

Ord QPow Source # 
Instance details

Defined in Math.RootLoci.CSM.Equivariant.Ordered

Methods

compare :: QPow -> QPow -> Ordering #

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

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

(>) :: QPow -> QPow -> Bool #

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

max :: QPow -> QPow -> QPow #

min :: QPow -> QPow -> QPow #

Show QPow Source # 
Instance details

Defined in Math.RootLoci.CSM.Equivariant.Ordered

Methods

showsPrec :: Int -> QPow -> ShowS #

show :: QPow -> String #

showList :: [QPow] -> ShowS #

Semigroup QPow Source # 
Instance details

Defined in Math.RootLoci.CSM.Equivariant.Ordered

Methods

(<>) :: QPow -> QPow -> QPow #

sconcat :: NonEmpty QPow -> QPow #

stimes :: Integral b => b -> QPow -> QPow #

Monoid QPow Source # 
Instance details

Defined in Math.RootLoci.CSM.Equivariant.Ordered

Methods

mempty :: QPow #

mappend :: QPow -> QPow -> QPow #

mconcat :: [QPow] -> QPow #

Pretty QPow Source # 
Instance details

Defined in Math.RootLoci.CSM.Equivariant.Ordered

umbralDistinctFormula :: Int -> ZMod (Omega QPow) Source #

The umbral formula for the open stratum of the CSM of distinct ordered point:

(q - u1 - u2 - ... - un)^(n-3)

where u_i^2 = 1. This also works n = 0,1,2,3 For these we have the expansion:

(q - u1 - u2 - u3)^0   =  q^0
(q - u1 - u2     )^-1  =  1/q + u1/q^2 + u2/q^2 + (2*u1*u2)/q^3
(q - u1          )^-2  =  1/q^2 + (2*u1)/q^3
(q               )^-3  =  1/q^3

umbralSubstQPow :: ChernBase base => (QPow -> ZMod base) -> ZMod (Omega QPow) -> ZMod (Omega base) Source #

Given a function specifying what to substitute in the place of q^k, we do the substitution.

computeQPolys :: Int -> ZMod AB Source #

It is not hard to prove (by considering the pushforward along the map forgetting one of the points), that the CSM of the locus U^n of the distinct points has the following form (for n>=3):

csm(U^n) = sum_{k=0}^{n-3} \frac{(n-3)!}{k!} (-1)^{n-3-k} \sigma_{n-3-k}(u) Q_k(a,b)

We can already compute all CSM-s recursively, and from that information we can determine these polynomials.

Which then we can compare with the recursive formula for the polynomials itself (which is much faster to evaluate)

The recursive formula for the Q_k(a,b) polynomials

formulaQPoly :: ChernBase base => Int -> ZMod base Source #

The Fibonacci-type recursive formula for the Q_k(a,b) polynomials

Q_{-3} = 1
Q_k    = Q_{k-1} * (1 - (k+1)*(a+b)) - Q_{k-2} * a*b * (k-1)*(k+2)
       = Q_{k-1} * (1 - (k+1)* c_1 ) - Q_{k-2} * c_2 * (k-1)*(k+2)

We provide both the Chern root and the Chern class version in a uniform way for convenience.

Formula for the CSM class of the stratum of distinct points

formulaDistinctCSM :: ChernBase base => Int -> ZMod (Omega base) Source #

The formula for the CSM of the set of distinct ordered points using the formula for the Q_k(a,b) polynomials above

formulaAnyStratumCSM :: ChernBase base => SetPartition -> ZMod (Omega base) Source #

Just the pushforward of the previous along Delta_mu