Characteristic classes of coincident root loci ============================================== Coincident root loci (or discriminant strata) are subsets of the space of homogeneous polynomials in two variables defined by root multiplicities: A nonzero degree _n_ polynomial has _n_ roots in the complex projective line P^1, but some of these can coincide, which gives us a partition of _n_. Hence for each partition _lambda_ we get a set of polynomials (those with root multiplicities given by _lambda_), which together stratify the space of these polynomials, which (modulo multiplying by scalars) is P^n. These are quasi-projective varieties, invariant under the action of GL(2); their closures are highly singular projective varieties, making them a good example for studying invariants of singular varieties. This package contains a number of different algorithms to compute invariants and characteristic classes of these varieties: - degree - Euler characteristic - the fundamental class in equivariant cohomology - Chern-Schwartz-MacPherson (CSM) class, Segre-SM class - equivariant CSM class - Hirzebruch Chi-y genus - Todd class, motivic Hirzebruch class - motivic Chern class - equivariant motivic Chern class Some of the algorithms are implemented in Mathematica instead of (or in addition to) Haskell. Another (better organized) Mathematica implementation is available at . Example usage ============= For example if you want to know what is the equivariant CSM class of the (open) loci corresponding to the partition [2,2,1,1], you can use the following piece of code: {-# LANGUAGE TypeApplications #-} import Math.Combinat.Partitions import Math.RootLoci.Algebra.SymmPoly ( AB ) import Math.Algebra.Polynomial.Pretty ( pretty ) import Math.RootLoci.CSM.Equivariant.Umbral csm ps = umbralOpenCSM @AB (mkPartition ps) main = do putStrLn $ pretty $ csm [2,2,1,1]