-- | We compute the open CSM classes directly, generalizing Aluffi's argument -- to the equivariant case: -- -- First we compute the CSM of set of the distinct /ordered/ points, then -- push that forward first with @delta_*@ then with @pi_*@ to get the -- CSM of the distinct unordered points with given multiplicities. -- -- After that, we can get the closed CSM classes by summing over the -- strata in the closure. -- -- This is faster, especially since we have a (recursive) formula for the -- CSM of the distinct ordered points. {-# LANGUAGE BangPatterns, TypeSynonymInstances, FlexibleInstances #-} module Math.RootLoci.CSM.Equivariant.Direct ( directOpenCSM , directClosedCSM ) where -------------------------------------------------------------------------------- import Math.Combinat.Partitions.Integer import qualified Data.Set as Set import Math.RootLoci.Algebra import Math.RootLoci.Geometry import Math.RootLoci.Misc import qualified Math.RootLoci.Algebra.FreeMod as ZMod import Math.RootLoci.CSM.Equivariant.PushForward import qualified Math.RootLoci.CSM.Equivariant.Ordered as Ordered -------------------------------------------------------------------------------- -- | CSM class of the open strata. -- -- We just push-forward first with Delta then down with Pi the conjectured -- (recursive) formula for the CSM of the set of distinct ordered points -- directOpenCSM :: ChernBase base => Partition -> ZMod (Gam base) directOpenCSM = polyCache2 directCalcOpenCSM where directCalcOpenCSM :: ChernBase base => Partition -> ZMod (Gam base) directCalcOpenCSM part@(Partition xs) = result where m = partitionWeight part result = ZMod.invScale (aut part) $ pi_star m middle middle = delta_star_ part distinct distinct = Ordered.formulaDistinctCSM (length xs) -------------------------------------------------------------------------------- -- | To compute the CSM of the closed loci, we just some over the open strata -- in the closure. directClosedCSM :: ChernBase base => Partition -> ZMod (Gam base) directClosedCSM = polyCache2 calc where calc :: ChernBase base => Partition -> ZMod (Gam base) calc part = ZMod.sum [ directOpenCSM q | q <- Set.toList (closureSet part) ] --------------------------------------------------------------------------------