{-# LANGUAGE ScopedTypeVariables, BangPatterns #-}
module Math.RootLoci.Segre.Equivariant where
import Math.Combinat.Classes
import Math.Combinat.Numbers
import Math.Combinat.Sign
import Math.Combinat.Compositions
import Math.Combinat.Partitions.Integer
import Math.Combinat.Numbers.Series
import Data.Array (Array)
import Data.Array.IArray
import Math.RootLoci.Algebra
import Math.RootLoci.Geometry
import Math.RootLoci.Misc
import qualified Math.Algebra.Polynomial.FreeModule as ZMod
import Math.RootLoci.CSM.Equivariant.Umbral
affTotalChernClass :: ChernBase base => Int -> ZMod base
affTotalChernClass :: Int -> ZMod base
affTotalChernClass Int
m = (FreeMod Integer AB, FreeMod Integer Chern)
-> ChernBase base => ZMod base
forall (f :: * -> *) base.
(f AB, f Chern) -> ChernBase base => f base
select1 (FreeMod Integer AB
total , FreeMod Integer AB -> FreeMod Integer Chern
abToChern FreeMod Integer AB
total) where
total :: FreeMod Integer AB
total = [FreeMod Integer AB] -> FreeMod Integer AB
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product [ FreeMod Integer AB
1 FreeMod Integer AB -> FreeMod Integer AB -> FreeMod Integer AB
forall a. Num a => a -> a -> a
+ FreeMod Integer AB
w | FreeMod Integer AB
w <- Int -> [FreeMod Integer AB]
affineWeights Int
m ]
affTotalChernClassByDegree :: ChernBase base => Int -> [ZMod base]
affTotalChernClassByDegree :: Int -> [ZMod base]
affTotalChernClassByDegree = Array Int (ZMod base) -> [ZMod base]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
elems (Array Int (ZMod base) -> [ZMod base])
-> (Int -> Array Int (ZMod base)) -> Int -> [ZMod base]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZMod base -> Array Int (ZMod base)
forall b. (Ord b, Graded b) => ZMod b -> Array Int (ZMod b)
separateGradedParts (ZMod base -> Array Int (ZMod base))
-> (Int -> ZMod base) -> Int -> Array Int (ZMod base)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ZMod base
forall base. ChernBase base => Int -> ZMod base
affTotalChernClass
recipTotalChernClass :: forall base. ChernBase base => Int -> [ZMod base]
recipTotalChernClass :: Int -> [ZMod base]
recipTotalChernClass Int
m = [(ZMod base, Int)] -> [ZMod base]
forall a. Num a => [(a, Int)] -> [a]
pseries' [(ZMod base, Int)]
coeffs where
coeffs :: [(ZMod base, Int)]
coeffs = [ZMod base] -> [Int] -> [(ZMod base, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip ((ZMod base -> ZMod base) -> [ZMod base] -> [ZMod base]
forall a b. (a -> b) -> [a] -> [b]
map ZMod base -> ZMod base
forall c b. Num c => FreeMod c b -> FreeMod c b
ZMod.neg [ZMod base]
prodWeights) [Int
1..]
prodWeights :: [ZMod base]
prodWeights = [ZMod base] -> [ZMod base]
forall a. [a] -> [a]
tail (Int -> [ZMod base]
forall base. ChernBase base => Int -> [ZMod base]
affTotalChernClassByDegree Int
m)
recipTotalChernClass2 :: forall base. ChernBase base => Int -> [ZMod base]
recipTotalChernClass2 :: Int -> [ZMod base]
recipTotalChernClass2 Int
m = [ZMod base] -> [ZMod base]
forall a. (Eq a, Num a) => [a] -> [a]
integralReciprocalSeries (Int -> [ZMod base]
forall base. ChernBase base => Int -> [ZMod base]
affTotalChernClassByDegree Int
m) where
recipTotalChernClassSlow :: forall base. ChernBase base => Int -> [ZMod base]
recipTotalChernClassSlow :: Int -> [ZMod base]
recipTotalChernClassSlow Int
m = ([FreeMod Integer AB], [FreeMod Integer Chern])
-> ChernBase base => [ZMod base]
forall (f :: * -> *) (g :: * -> *) base.
(f (g AB), f (g Chern)) -> ChernBase base => f (g base)
select2 ([FreeMod Integer AB]
list , (FreeMod Integer AB -> FreeMod Integer Chern)
-> [FreeMod Integer AB] -> [FreeMod Integer Chern]
forall a b. (a -> b) -> [a] -> [b]
map FreeMod Integer AB -> FreeMod Integer Chern
abToChern [FreeMod Integer AB]
list) where
weights :: [FreeMod Integer AB]
weights = Int -> [FreeMod Integer AB]
affineWeights Int
m
list :: [FreeMod Integer AB]
list = [ Int -> FreeMod Integer AB
grade Int
d | Int
d <- [Int
0..] ]
grade :: Int -> ZMod AB
grade :: Int -> FreeMod Integer AB
grade Int
d = Int -> FreeMod Integer AB -> FreeMod Integer AB
forall a b. (Integral a, Num b) => a -> b -> b
negateIfOdd Int
d
(FreeMod Integer AB -> FreeMod Integer AB)
-> FreeMod Integer AB -> FreeMod Integer AB
forall a b. (a -> b) -> a -> b
$ [FreeMod Integer AB] -> FreeMod Integer AB
forall b c. (Ord b, Eq c, Num c) => [FreeMod c b] -> FreeMod c b
ZMod.sum (([Int] -> FreeMod Integer AB) -> [[Int]] -> [FreeMod Integer AB]
forall a b. (a -> b) -> [a] -> [b]
map [Int] -> FreeMod Integer AB
mkProduct ([[Int]] -> [FreeMod Integer AB])
-> [[Int]] -> [FreeMod Integer AB]
forall a b. (a -> b) -> a -> b
$ Int -> Int -> [[Int]]
forall a. Integral a => a -> a -> [[Int]]
compositions (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
d)
mkProduct :: [Int] -> FreeMod Integer AB
mkProduct [Int]
es = [FreeMod Integer AB] -> FreeMod Integer AB
forall b c.
(Ord b, Monoid b, Eq c, Num c) =>
[FreeMod c b] -> FreeMod c b
ZMod.product [ (Array Int [FreeMod Integer AB]
weightPowersArray Int [FreeMod Integer AB] -> Int -> [FreeMod Integer AB]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!Int
i) [FreeMod Integer AB] -> Int -> FreeMod Integer AB
forall a. [a] -> Int -> a
!! Int
e | (Int
i,Int
e) <- [Int] -> [Int] -> [(Int, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..Int
m] [Int]
es ]
weightPowers :: Array Int [ZMod AB]
weightPowers :: Array Int [FreeMod Integer AB]
weightPowers = (Int, Int)
-> [[FreeMod Integer AB]] -> Array Int [FreeMod Integer AB]
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
listArray (Int
0,Int
m) [ FreeMod Integer AB -> [FreeMod Integer AB]
wtPowList ([FreeMod Integer AB]
weights [FreeMod Integer AB] -> Int -> FreeMod Integer AB
forall a. [a] -> Int -> a
!! Int
i) | Int
i <- [Int
0..Int
m] ]
wtPowList :: ZMod AB -> [ZMod AB]
wtPowList :: FreeMod Integer AB -> [FreeMod Integer AB]
wtPowList FreeMod Integer AB
w = FreeMod Integer AB -> [FreeMod Integer AB]
go FreeMod Integer AB
1 where { go :: FreeMod Integer AB -> [FreeMod Integer AB]
go !FreeMod Integer AB
x = FreeMod Integer AB
x FreeMod Integer AB -> [FreeMod Integer AB] -> [FreeMod Integer AB]
forall a. a -> [a] -> [a]
: FreeMod Integer AB -> [FreeMod Integer AB]
go (FreeMod Integer AB
xFreeMod Integer AB -> FreeMod Integer AB -> FreeMod Integer AB
forall a. Num a => a -> a -> a
*FreeMod Integer AB
w) }
divideByTotalChernClass :: ChernBase base => Int -> ZMod base -> [ZMod base]
divideByTotalChernClass :: Int -> ZMod base -> [ZMod base]
divideByTotalChernClass Int
m ZMod base
what = [(ZMod base, Int)] -> [ZMod base] -> [ZMod base]
forall a. Num a => [(a, Int)] -> [a] -> [a]
convolveWithPSeries' [(ZMod base, Int)]
coeffs [ZMod base]
numerList where
numerArr :: Array Int (ZMod base)
numerArr = ZMod base -> Array Int (ZMod base)
forall b. (Ord b, Graded b) => ZMod b -> Array Int (ZMod b)
separateGradedParts ZMod base
what
numerList :: [ZMod base]
numerList = Array Int (ZMod base) -> [ZMod base]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
elems Array Int (ZMod base)
numerArr
coeffs :: [(ZMod base, Int)]
coeffs = [ZMod base] -> [Int] -> [(ZMod base, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip ((ZMod base -> ZMod base) -> [ZMod base] -> [ZMod base]
forall a b. (a -> b) -> [a] -> [b]
map ZMod base -> ZMod base
forall c b. Num c => FreeMod c b -> FreeMod c b
ZMod.neg [ZMod base]
prodWeights) [Int
1..]
prodWeights :: [ZMod base]
prodWeights = [ZMod base] -> [ZMod base]
forall a. [a] -> [a]
tail (Int -> [ZMod base]
forall base. ChernBase base => Int -> [ZMod base]
affTotalChernClassByDegree Int
m)
divideByTotalChernClassSlow :: ChernBase base => Int -> ZMod base -> [ZMod base]
divideByTotalChernClassSlow :: Int -> ZMod base -> [ZMod base]
divideByTotalChernClassSlow Int
m ZMod base
what = [ZMod base]
final where
(Int
0,Int
n) = Array Int (ZMod base) -> (Int, Int)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
bounds Array Int (ZMod base)
numerArr
numerArr :: Array Int (ZMod base)
numerArr = ZMod base -> Array Int (ZMod base)
forall b. (Ord b, Graded b) => ZMod b -> Array Int (ZMod b)
separateGradedParts ZMod base
what
denomList :: [ZMod base]
denomList = Int -> [ZMod base]
forall base. ChernBase base => Int -> [ZMod base]
recipTotalChernClassSlow Int
m
final :: [ZMod base]
final = [ Int -> ZMod base
part Int
d | Int
d <- [Int
0..] ]
part :: Int -> ZMod base
part Int
deg = [ZMod base] -> ZMod base
forall b c. (Ord b, Eq c, Num c) => [FreeMod c b] -> FreeMod c b
ZMod.sum
[ (Array Int (ZMod base)
numerArr Array Int (ZMod base) -> Int -> ZMod base
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
! Int
i) ZMod base -> ZMod base -> ZMod base
forall a. Num a => a -> a -> a
* ([ZMod base]
denomList [ZMod base] -> Int -> ZMod base
forall a. [a] -> Int -> a
!! Int
j)
| Int
j <- [ Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
degInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n) .. Int
deg ]
, let i :: Int
i = Int
deg Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
j
]
affineOpenSegreSM :: ChernBase base => Partition -> [ZMod base]
affineOpenSegreSM :: Partition -> [ZMod base]
affineOpenSegreSM Partition
part = Int -> ZMod base -> [ZMod base]
forall base. ChernBase base => Int -> ZMod base -> [ZMod base]
divideByTotalChernClass Int
m (Partition -> ZMod base
forall base. ChernBase base => Partition -> ZMod base
umbralAffOpenCSM Partition
part) where
m :: Int
m = Partition -> Int
forall a. HasWeight a => a -> Int
weight Partition
part
affineZeroSegreSM :: ChernBase base => Int -> [ZMod base]
affineZeroSegreSM :: Int -> [ZMod base]
affineZeroSegreSM Int
m = Int -> ZMod base -> [ZMod base]
forall base. ChernBase base => Int -> ZMod base -> [ZMod base]
divideByTotalChernClass Int
m (Int -> ZMod base
forall base. ChernBase base => Int -> ZMod base
affineZeroCSM Int
m)
affineClosedSegreSM :: ChernBase base => Partition -> [ZMod base]
affineClosedSegreSM :: Partition -> [ZMod base]
affineClosedSegreSM Partition
part = Int -> ZMod base -> [ZMod base]
forall base. ChernBase base => Int -> ZMod base -> [ZMod base]
divideByTotalChernClass Int
m (Partition -> ZMod base
forall base. ChernBase base => Partition -> ZMod base
umbralAffClosedCSM Partition
part) where
m :: Int
m = Partition -> Int
forall a. HasWeight a => a -> Int
weight Partition
part