-- | Comparing the Chern root vs. the Chern class versions for stuff in -- "Math.RootLoci.CSM.Equivariant.Umbral" {-# LANGUAGE Rank2Types, GADTs, TypeFamilies #-} module Tests.RootVsClass.Umbral 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.Umbral import Tests.Common import Tests.RootVsClass.Check import Test.Tasty import Test.Tasty.HUnit -------------------------------------------------------------------------------- all_tests = testGroup "umbral" [ testCase "open affine CSM" (forAllPart 11 "failed" prop_umbralAffOpenCSM ) , testCase "closed affine CSM" (forAllPart 11 "failed" prop_umbralAffClosedCSM) -- , testCase "theta" (forAllPosInt 15 "failed" prop_theta ) -- , testCase "thetaQ" (forAllPosInt 15 "failed" prop_thetaQ) ] -- prop_theta n = checkMixedST (theta n) -- prop_thetaQ n = checkMixedST (thetaQ n) prop_umbralAffOpenCSM part = checkZMod (umbralAffOpenCSM part) prop_umbralAffClosedCSM part = checkZMod (umbralAffClosedCSM part) --------------------------------------------------------------------------------