-- | Checking polymorphic functions {-# LANGUAGE Rank2Types, GADTs, TypeFamilies, ScopedTypeVariables, PackageImports #-} module Tests.RootVsClass.Check where -------------------------------------------------------------------------------- -- import Data.Proxy -- import Math.Combinat.Partitions import Data.Array import Math.RootLoci.Algebra import Math.RootLoci.Misc import Math.RootLoci.Geometry.Cohomology import qualified "polynomial-algebra" Math.Algebra.Polynomial.FreeModule as ZMod import Math.RootLoci.CSM.Equivariant.Umbral ( ST ) -------------------------------------------------------------------------------- checkZMod :: (forall b. ChernBase b => ZMod b) -> Bool checkZMod polymorph = ( abToChern (spec1' ChernRoot polymorph) == spec1' ChernClass polymorph ) && ( spec1' ChernRoot polymorph == chernToAB (spec1' ChernClass polymorph) ) {- checkZModExt :: forall f. Equivariant f => (forall b. ChernBase b => ZMod (f b)) -> Bool checkZModExt polymorph = ( convertEquiv abToChern (spec2' ChernRoot polymorph) == spec2' ChernClass polymorph ) && ( spec2' ChernRoot polymorph == convertEquiv chernToAB (spec2' ChernClass polymorph) ) -} -------------------------------------------------------------------------------- {- checkGam :: (forall b. ChernBase b => ZMod (Gam b)) -> Bool checkOmega :: (forall b. ChernBase b => ZMod (Omega b)) -> Bool checkEta :: (forall b. ChernBase b => ZMod (Eta b)) -> Bool checkGam = checkZModExt checkOmega = checkZModExt checkEta = checkZModExt -} checkOmega :: (forall b. ChernBase b => ZMod (Omega b)) -> Bool checkOmega polymorph = ( convertOmega abToChern (spec2' ChernRoot polymorph) == spec2' ChernClass polymorph ) && ( spec2' ChernRoot polymorph == convertOmega chernToAB (spec2' ChernClass polymorph) ) checkEta :: (forall b. ChernBase b => ZMod (Eta b)) -> Bool checkEta polymorph = ( convertEta abToChern (spec2' ChernRoot polymorph) == spec2' ChernClass polymorph ) && ( spec2' ChernRoot polymorph == convertEta chernToAB (spec2' ChernClass polymorph) ) checkGam :: (forall b. ChernBase b => ZMod (Gam b)) -> Bool checkGam polymorph = ( convertGam abToChern (spec2' ChernRoot polymorph) == spec2' ChernClass polymorph ) && ( spec2' ChernRoot polymorph == convertGam chernToAB (spec2' ChernClass polymorph) ) -------------------------------------------------------------------------------- checkArrZMod :: (forall b. ChernBase b => Array Int (ZMod b)) -> Bool checkArrZMod polymorph = ( fmap abToChern (spec2' ChernRoot polymorph) == spec2' ChernClass polymorph ) && ( spec2' ChernRoot polymorph == fmap chernToAB (spec2' ChernClass polymorph) ) checkArrGam :: (forall b. ChernBase b => Array Int (ZMod (Gam b))) -> Bool checkArrGam polymorph = ( fmap fwd (spec3' ChernRoot polymorph) == spec3' ChernClass polymorph ) && ( spec3' ChernRoot polymorph == fmap bwd (spec3' ChernClass polymorph) ) where fwd = convertGam abToChern bwd = convertGam chernToAB -------------------------------------------------------------------------------- {- checkMixedST :: forall c. (Eq c, Num c) => (forall b. ChernBase b => FreeMod (FreeMod c b) ST) -> Bool checkMixedST polymorph = ( fwd (spec2' ChernRoot polymorph) == spec2' ChernClass polymorph ) && ( spec2' ChernRoot polymorph == bwd (spec2' ChernClass polymorph) ) where fwd :: FreeMod (FreeMod c AB ) ST -> FreeMod (FreeMod c Chern) ST bwd :: FreeMod (FreeMod c Chern) ST -> FreeMod (FreeMod c AB ) ST fwd = ZMod.mapCoeff abToChern bwd = ZMod.mapCoeff chernToAB -} --------------------------------------------------------------------------------