module Math.RootLoci.CSM.Equivariant.Umbral where
import Math.Combinat.Classes
import Math.Combinat.Numbers
import Math.Combinat.Partitions.Integer
import Data.Array.IArray
import qualified Data.Set as Set
import Math.RootLoci.Algebra
import Math.RootLoci.Geometry
import Math.RootLoci.Misc
import qualified Math.RootLoci.Algebra.FreeMod as ZMod
import Math.RootLoci.CSM.Equivariant.PushForward ( tau , piStarTableAff , piStarTableProj )
import Math.RootLoci.CSM.Equivariant.Ordered ( formulaQPoly )
import qualified Math.RootLoci.CSM.Equivariant.Direct as Direct
data ST
= ST !Int !Int
deriving (Eq,Ord,Show)
instance Monoid ST where
mempty = ST 0 0
(ST s1 t1) `mappend` (ST s2 t2) = ST (s1+s2) (t1+t2)
instance Pretty ST where
pretty st = case st of
ST 0 0 -> ""
ST e 0 -> showVarPower "s" e
ST 0 f -> showVarPower "t" f
ST e f -> showVarPower "s" e ++ "*" ++ showVarPower "t" f
prettyMixedST :: forall b c. (Pretty b, Num c, Eq c, IsSigned c, Show c) => FreeMod (FreeMod c b) ST -> String
prettyMixedST = prettyFreeMod'' prettyInner pretty where
prettyInner :: FreeMod c b -> String
prettyInner = paren . pretty
theta :: ChernBase base => Int -> FreeMod (ZMod base) ST
theta p
| p >= 1 = ZMod.fromList (term0 ++ term1)
| otherwise = error "theta: non-positive input"
where
term0 = [ (ST 0 i , ZMod.scale (binomial p i) ( tau (pi1)) ) | i<-[0..p1] ]
term1 = [ (ST 1 i , ZMod.scale (binomial p i) (ZMod.mulMonom c2_monom $ tau (pi2)) ) | i<-[0..p2] ]
++ [ (ST 1 p , ZMod.konst (1) ) ]
c2_monom = select0 (alphaBeta,c2)
thetaQ :: ChernBase b => Int -> FreeMod (QMod b) ST
thetaQ p = ZMod.mapCoeff (ZMod.mapCoeff fromIntegral) (theta p)
integralUmbralFormula :: ChernBase base => Partition -> FreeMod (ZMod base) ST
integralUmbralFormula (Partition ps) = ZMod.product [ theta p | p <- ps ]
umbralFormula :: ChernBase base => Partition -> FreeMod (QMod base) ST
umbralFormula mu@(Partition ps) = result where
result = ZMod.mapCoeff (ZMod.scale (1 / autmu))
$ ZMod.product [ thetaQ p | p <- ps ]
autmu :: Rational
autmu = fromIntegral (aut mu)
umbralSubstPolyAff :: ChernBase base => Partition -> ST -> ZMod base
umbralSubstPolyAff part = fun where
n = numberOfParts part
m = weight part
tablePPoly = piStarTableAff m
fun (ST k j)
| k >= 3 && k <= n3 && j >= 0 && j <= m = ZMod.scale falling (qpoly `ZMod.mul` ppoly)
| otherwise = ZMod.zero
where
falling :: Integer
falling = product [ fromIntegral (n3i) | i<-[0..k1] ]
qpoly = formulaQPoly (n3k)
ppoly = tablePPoly ! j
umbralSubstitutionAff :: (ChernBase base) => Partition -> FreeMod (ZMod base) ST -> ZMod base
umbralSubstitutionAff part input = output where
output = ZMod.sum [ ab `ZMod.mul` (substfun st) | (st,ab) <- ZMod.toList input ]
substfun = umbralSubstPolyAff part
umbralAffOpenCSM :: ChernBase base => Partition -> ZMod base
umbralAffOpenCSM = polyCache1 calc where
calc mu
| n < 3 = forgetGamma (Direct.directOpenCSM mu)
| otherwise = ZMod.invScale (aut mu)
$ umbralSubstitutionAff mu
$ integralUmbralFormula mu
where
n = numberOfParts mu
umbralAffClosedCSM :: ChernBase base => Partition -> ZMod base
umbralAffClosedCSM = polyCache1 calc where
calc :: ChernBase base => Partition -> ZMod base
calc part = ZMod.sum [ umbralAffOpenCSM q | q <- Set.toList (closureSet part) ]
umbralSubstPolyProj :: forall base. ChernBase base => Partition -> ST -> ZMod (Gam base)
umbralSubstPolyProj part = fun where
n = numberOfParts part
m = weight part
tablePPoly = piStarTableProj m
fun (ST k j)
| k >= 3 && k <= n3 && j >= 0 && j <= m = ZMod.scale falling (qpoly `ZMod.mul` ppoly)
| otherwise = ZMod.zero
where
falling :: Integer
falling = product [ fromIntegral (n3i) | i<-[0..k1] ]
qpoly = injectZMod (formulaQPoly (n3k)) :: ZMod (Gam base)
ppoly = tablePPoly ! j :: ZMod (Gam base)
umbralSubstitutionProj :: (ChernBase base) => Partition -> FreeMod (ZMod base) ST -> ZMod (Gam base)
umbralSubstitutionProj part input = output where
output = ZMod.sum [ injectZMod ab `ZMod.mul` (substfun st) | (st,ab) <- ZMod.toList input ]
substfun = umbralSubstPolyProj part
umbralOpenCSM :: ChernBase base => Partition -> ZMod (Gam base)
umbralOpenCSM = polyCache2 calc where
calc mu
| n < 3 = Direct.directOpenCSM mu
| otherwise = ZMod.invScale (aut mu)
$ umbralSubstitutionProj mu
$ integralUmbralFormula mu
where
n = numberOfParts mu
umbralClosedCSM :: ChernBase base => Partition -> ZMod (Gam base)
umbralClosedCSM = polyCache2 calc where
calc :: ChernBase base => Partition -> ZMod (Gam base)
calc part = ZMod.sum [ umbralOpenCSM q | q <- Set.toList (closureSet part) ]