-- | Aluffi's computation of the non-equivariant CSM in @P^n@ -- -- See: Paolo Aluffi: Characteristic classes of discriminants and enumerative geometry, Comm. in Algebra 26(10), 3165-3193 (1998). -- {-# LANGUAGE BangPatterns, TypeSynonymInstances, FlexibleInstances #-} module Math.RootLoci.CSM.Aluffi where -------------------------------------------------------------------------------- import Data.List import Control.Monad import Math.Combinat.Classes import Math.Combinat.Numbers import Math.Combinat.Sign import Math.Combinat.Partitions.Integer import Math.Combinat.Sets import qualified Data.Map as Map ; import Data.Map (Map) import qualified Data.Set as Set ; import Data.Set (Set) import Data.Array (Array) import Data.Array.IArray import Math.RootLoci.Algebra import Math.RootLoci.Geometry import Math.RootLoci.Classic import Math.RootLoci.Misc import qualified Math.Algebra.Polynomial.FreeModule as ZMod -------------------------------------------------------------------------------- -- * CSM computation -- | Paolo Aluffi's explicit formula for the (non-equivariant) CSM of open coincident root loci aluffiOpenCSM :: Partition -> ZMod G aluffiOpenCSM part@(Partition ps) = ZMod.divideByConst (aut part) xsum where n = sum ps d = length ps xsum = ZMod.fromList [ ( G (n-d+k) , coeff k ) | k<-[0..d] ] coeff k = negateIfOdd k $ signedBinomial (d-3) k * factorial k * factorial (d-k) * symPolyNum (d-k) (map fromIntegral ps) -- | Summing together the open loci CSMs, we got the CSMs of the closures of the strata aluffiClosedCSM :: Partition -> ZMod G aluffiClosedCSM part@(Partition ps) = ZMod.sum opens where opens = [ aluffiOpenCSM q | q <- Set.toList (closureSet part) ] -------------------------------------------------------------------------------- -- * Euler characteristics -- | Euler characteristic, computed form 'aluffiOpenCSM' aluffiOpenEuler :: Partition -> Integer aluffiOpenEuler p = ZMod.coeffOf (G n) (aluffiOpenCSM p) where n = partitionWeight p -- | Euler characteristic, computed form 'aluffiClosedCSM' aluffiClosedEuler :: Partition -> Integer aluffiClosedEuler p = ZMod.coeffOf (G n) (aluffiClosedCSM p) where n = partitionWeight p -------------------------------------------------------------------------------- -- | It is easy to see from Aluffi\'s formula that only dimensions 1 and 2 has nonzero Euler characteristic. -- This function implements the resulting rather trivial formula: -- -- > chi( X_{n} ) = 2 -- > chi( X_{p,q} ) = if p==q then 1 else 2 -- > chi( X_{...} ) = 0 -- openEulerChar :: Partition -> Integer openEulerChar (Partition ps) = case ps of [n] -> 2 [a,b] -> if a==b then 1 else 2 _ -> 0 -------------------------------------------------------------------------------- -- * General linear sections -- | Converts the CSM class of a (locally closed?) projective variety Z to the Euler characteristics -- of general linear sections of Z (so the first number will be @chi(Z)@, the second will be -- @chi(Z cap H1)@, the third @chi(Z cap H1 cap H2)@ with @H1@, @H2@... being generic hyperplanes. -- Finally the codim-th number will be the degree. -- -- See: Paolo Aluffi: EULER CHARACTERISTICS OF GENERAL LINEAR SECTIONS AND POLYNOMIAL CHERN CLASSES, -- Proposition 2.6 -- csmToEulerOfLinearSections :: Int -- ^ the dimension of the ambient projective space @P^n@ -> ZMod G -- ^ the CSM class -> [Integer] -- ^ the resulting sequence of Euler characteristics csmToEulerOfLinearSections n csm = [ euler i | i<-[0..n] ] where csmArr = accumArray (flip const) 0 (0,n) [ (i,c) | (G i, c) <- ZMod.toList csm ] :: Array Int Integer euler k = foldl' (+) 0 [ signedBinomial (-k) i * csmArr ! (n-k-i) | i<-[0..n-k] ] -- | We can compute the degree of the closures of the strata by intersection them -- with @dim(X)@ generic hiperplanes. aluffiDegree :: Partition -> Integer aluffiDegree part = list !! dimension part where list = csmToEulerOfLinearSections (weight part) (aluffiClosedCSM part) --------------------------------------------------------------------------------