-- | Comparing the Chern root vs. the Chern class versions for stuff in -- "Math.RootLoci.CSM.Equivariant.Ordered" {-# LANGUAGE Rank2Types, GADTs, TypeFamilies #-} module Tests.RootVsClass.Ordered where -------------------------------------------------------------------------------- import Data.Proxy import Math.Combinat.Partitions import Math.RootLoci.Algebra import Math.RootLoci.Geometry import Math.RootLoci.Misc import Math.RootLoci.CSM.Equivariant.Ordered import Tests.Common import Tests.RootVsClass.Check import Test.Tasty import Test.Tasty.HUnit -------------------------------------------------------------------------------- all_tests = testGroup "ordered" [ testCase "tangent Chern class" (forAllInt 9 "failed" prop_tangentChernClass ) , testCase "small diagonals" (forAllInt 9 "failed" prop_smallDiagonal ) , testCase "open stratum" (forAllInt 7 "failed" prop_openStratumCSM ) , testCase "any stratum" (forAllSetp 6 "failed" prop_anyStratumCSM ) , testCase "formula for Q-poly" (forList [-3.. 20] "failed" prop_formulaQPoly ) , testCase "formula U(n)" (forAllInt 10 "failed" prop_formulaDistinctCSM ) ] -------------------------------------------------------------------------------- prop_tangentChernClass n = checkOmega (tangentChernClass n) prop_smallDiagonal n = checkOmega (smallDiagonal n) prop_openStratumCSM n = checkOmega (computeOpenStratumCSM n) prop_anyStratumCSM setp = checkOmega (computeAnyStratumCSM setp) prop_formulaDistinctCSM n = checkOmega (formulaDistinctCSM n) prop_formulaQPoly n = checkZMod (formulaQPoly n) --------------------------------------------------------------------------------