-- | We compute the @GL2@-equivariant open and closed CSM classes recursively, -- starting from smallest strata. -- -- The idea is that we have a smooth resolution of the /closure/ of the strata @X_mu@, -- namely, the set of @n=length(mu)@ ordered points: @Q^n = P^1 x ... x P^1@ -- -- We can pushforward this to @Q^m@, and get a linear combination of the strata of -- the CSM-s we want to compute. Since the smallest strata is actually closed, -- we know that, and can work upward from that. -- -- This is rather slow, however as it's a very different algorithm copmared to -- the direct approach, it's useful for checking if the two agrees. -- {-# LANGUAGE BangPatterns, TypeSynonymInstances, FlexibleInstances #-} module Math.RootLoci.CSM.Equivariant.Recursive where -------------------------------------------------------------------------------- import qualified Data.Set as Set ; import Data.Set (Set) import qualified Data.Map as Map ; import Data.Map (Map) import Math.Combinat.Partitions.Integer import Math.Combinat.Partitions.Set import qualified Math.RootLoci.CSM.Equivariant.Ordered as Ordered import Math.RootLoci.CSM.Equivariant.PushForward import Math.RootLoci.Algebra import Math.RootLoci.Geometry import Math.RootLoci.Misc import qualified Math.RootLoci.Algebra.FreeMod as ZMod -------------------------------------------------------------------------------- -- * CSM calculation -- | This is just the pushforward along @Delta_nu@ of the tangent Chern class. -- -- As @Delta@ is injective, the resulting class is just the CSM class of the -- closed /ordered/ strata corresponding to one of the set partitions which -- matches the given partition ---- upperClass :: ChernBase base => SetPartition -> ZMod (Eta base) upperClass = polyCache2 calcUpper where calcUpper :: ChernBase base => SetPartition -> ZMod (Eta base) calcUpper part@(SetPartition ps) = delta_star part (Ordered.tangentChernClass d) where d = length ps -- | pushforward of `upperCSM` to the space of unordered points lowerClass :: ChernBase base => Partition -> ZMod (Gam base) lowerClass = polyCache2 calcLower where calcLower :: ChernBase base => Partition -> ZMod (Gam base) calcLower part = pi_star n (upperClass $ defaultSetPartition part) where n = partitionWeight part -------------------------------------------------------------------------------- -- | We know from the pushforward property of CSM clsses that @(pi_* upperCSM) = sum (chi * openCSM)@. -- we can use this to recursively compute the CSM classes of the open loci -- openCSM :: ChernBase base => Partition -> ZMod (Gam base) openCSM = polyCache2 calcOpenCSM where calcOpenCSM :: ChernBase base => Partition -> ZMod (Gam base) calcOpenCSM part = ZMod.invScale thisCoeff (pushdown `ZMod.sub` smaller) where n = partitionWeight part pushdown = lowerClass part smaller = ZMod.linComb [ (c , openCSM q) | (q,c) <- Map.assocs theClosure ] (thisCoeff,theClosure) = preimageView part -- closureView' part -- | To compute the CSM of the closed loci, we just some over the open strata -- in the closure. closedCSM :: ChernBase base => Partition -> ZMod (Gam base) closedCSM = polyCache2 calcClosedCSM where calcClosedCSM :: ChernBase base => Partition -> ZMod (Gam base) calcClosedCSM part = ZMod.sum [ openCSM q | q <- Set.toList (closureSet part) ] -------------------------------------------------------------------------------- {- equivDualClass :: Partition -> ZMod Gam equivDualClass part = filterGrade (codim part) (closedCSM part) equivOpenEuler :: Partition -> ZMod Gam equivOpenEuler part = filterGrade (partitionWeight part) (openCSM part) equivClosedEuler :: Partition -> ZMod Gam equivClosedEuler part = filterGrade (partitionWeight part) (closedCSM part) -} --------------------------------------------------------------------------------