coincident-root-loci-0.3: Equivariant CSM classes of coincident root loci
Safe HaskellNone
LanguageHaskell2010

Math.RootLoci.Geometry.Cohomology

Description

Bases in the cohomology of the spaces appearing in the computations.

We have three different spaces:

  • Q^n = P^1 x P^1 x ... x P^1 (n times; m = length lambda)
  • Q^m = P^1 x P^1 x ... x P^1 x P^1 (m times, m = sum lambda >= n)
  • P^m = P(Sym^m C^2)

Furthermore, we have GL2 acting naturally on these spaces.

Synopsis

The non-equivariant case

newtype U Source #

a (ring) generator of H^*(Q^n) (note that u_i^2 = 0)

Constructors

U Int 

Instances

Instances details
Eq U Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(==) :: U -> U -> Bool #

(/=) :: U -> U -> Bool #

Ord U Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

compare :: U -> U -> Ordering #

(<) :: U -> U -> Bool #

(<=) :: U -> U -> Bool #

(>) :: U -> U -> Bool #

(>=) :: U -> U -> Bool #

max :: U -> U -> U #

min :: U -> U -> U #

Show U Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

showsPrec :: Int -> U -> ShowS #

show :: U -> String #

showList :: [U] -> ShowS #

Pretty U Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

pretty :: U -> String #

prettyInParens :: U -> String #

Graded U Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

grade :: U -> Int Source #

newtype H Source #

(a ring) generator of H^*(Q^m) (note that h_i^2 = 0)

Constructors

H Int 

Instances

Instances details
Eq H Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(==) :: H -> H -> Bool #

(/=) :: H -> H -> Bool #

Ord H Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

compare :: H -> H -> Ordering #

(<) :: H -> H -> Bool #

(<=) :: H -> H -> Bool #

(>) :: H -> H -> Bool #

(>=) :: H -> H -> Bool #

max :: H -> H -> H #

min :: H -> H -> H #

Show H Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

showsPrec :: Int -> H -> ShowS #

show :: H -> String #

showList :: [H] -> ShowS #

Pretty H Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

pretty :: H -> String #

prettyInParens :: H -> String #

Graded H Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

grade :: H -> Int Source #

newtype G Source #

the generator of H^*(P^n) (with g^(n+1) = 0)

Constructors

G Int 

Instances

Instances details
Eq G Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(==) :: G -> G -> Bool #

(/=) :: G -> G -> Bool #

Ord G Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

compare :: G -> G -> Ordering #

(<) :: G -> G -> Bool #

(<=) :: G -> G -> Bool #

(>) :: G -> G -> Bool #

(>=) :: G -> G -> Bool #

max :: G -> G -> G #

min :: G -> G -> G #

Show G Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

showsPrec :: Int -> G -> ShowS #

show :: G -> String #

showList :: [G] -> ShowS #

Semigroup G Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(<>) :: G -> G -> G #

sconcat :: NonEmpty G -> G #

stimes :: Integral b => b -> G -> G #

Monoid G Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

mempty :: G #

mappend :: G -> G -> G #

mconcat :: [G] -> G #

Pretty G Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

pretty :: G -> String #

prettyInParens :: G -> String #

Graded G Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

grade :: G -> Int Source #

newtype US Source #

A monomial in u_i (encoded as a subset of [1..n], as u_i^2=0)

Constructors

US [U] 

Instances

Instances details
Eq US Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(==) :: US -> US -> Bool #

(/=) :: US -> US -> Bool #

Ord US Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

compare :: US -> US -> Ordering #

(<) :: US -> US -> Bool #

(<=) :: US -> US -> Bool #

(>) :: US -> US -> Bool #

(>=) :: US -> US -> Bool #

max :: US -> US -> US #

min :: US -> US -> US #

Show US Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

showsPrec :: Int -> US -> ShowS #

show :: US -> String #

showList :: [US] -> ShowS #

Semigroup US Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(<>) :: US -> US -> US #

sconcat :: NonEmpty US -> US #

stimes :: Integral b => b -> US -> US #

Monoid US Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

mempty :: US #

mappend :: US -> US -> US #

mconcat :: [US] -> US #

Pretty US Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Graded US Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

grade :: US -> Int Source #

newtype HS Source #

A monomial in h_i (encoded as a subset of [1..m], as h_i^2=0)

Constructors

HS [H] 

Instances

Instances details
Eq HS Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(==) :: HS -> HS -> Bool #

(/=) :: HS -> HS -> Bool #

Ord HS Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

compare :: HS -> HS -> Ordering #

(<) :: HS -> HS -> Bool #

(<=) :: HS -> HS -> Bool #

(>) :: HS -> HS -> Bool #

(>=) :: HS -> HS -> Bool #

max :: HS -> HS -> HS #

min :: HS -> HS -> HS #

Show HS Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

showsPrec :: Int -> HS -> ShowS #

show :: HS -> String #

showList :: [HS] -> ShowS #

Semigroup HS Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(<>) :: HS -> HS -> HS #

sconcat :: NonEmpty HS -> HS #

stimes :: Integral b => b -> HS -> HS #

Monoid HS Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

mempty :: HS #

mappend :: HS -> HS -> HS #

mconcat :: [HS] -> HS #

Pretty HS Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Graded HS Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

grade :: HS -> Int Source #

The equivariant case

data Omega ab Source #

A monomial generator of Z[alpha,beta;u1,u2,...,u_nd]/(...), the cohomology ring of Q^n.

The encoding is that the list is the list of indices of u which appear.

Constructors

Omega ![Int] !ab 

Instances

Instances details
Functor Omega Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

fmap :: (a -> b) -> Omega a -> Omega b #

(<$) :: a -> Omega b -> Omega a #

Equivariant Omega Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

injectMonom :: x -> Omega x Source #

projectMonom :: Omega x -> x Source #

Eq ab => Eq (Omega ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(==) :: Omega ab -> Omega ab -> Bool #

(/=) :: Omega ab -> Omega ab -> Bool #

Ord ab => Ord (Omega ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

compare :: Omega ab -> Omega ab -> Ordering #

(<) :: Omega ab -> Omega ab -> Bool #

(<=) :: Omega ab -> Omega ab -> Bool #

(>) :: Omega ab -> Omega ab -> Bool #

(>=) :: Omega ab -> Omega ab -> Bool #

max :: Omega ab -> Omega ab -> Omega ab #

min :: Omega ab -> Omega ab -> Omega ab #

Show ab => Show (Omega ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

showsPrec :: Int -> Omega ab -> ShowS #

show :: Omega ab -> String #

showList :: [Omega ab] -> ShowS #

Semigroup ab => Semigroup (Omega ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(<>) :: Omega ab -> Omega ab -> Omega ab #

sconcat :: NonEmpty (Omega ab) -> Omega ab #

stimes :: Integral b => b -> Omega ab -> Omega ab #

Monoid ab => Monoid (Omega ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

mempty :: Omega ab #

mappend :: Omega ab -> Omega ab -> Omega ab #

mconcat :: [Omega ab] -> Omega ab #

(Pretty ab, Monoid ab, Eq ab) => Pretty (Omega ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

pretty :: Omega ab -> String #

prettyInParens :: Omega ab -> String #

Graded ab => Graded (Omega ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

grade :: Omega ab -> Int Source #

data Eta ab Source #

A monomial generator of Z[alpha,beta;eta1,eta2...eta_m]/(...), he cohomology ring of Q^m.

The encoding is that the list is the list of indices of eta which appear.

Constructors

Eta ![Int] !ab 

Instances

Instances details
Functor Eta Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

fmap :: (a -> b) -> Eta a -> Eta b #

(<$) :: a -> Eta b -> Eta a #

Equivariant Eta Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

injectMonom :: x -> Eta x Source #

projectMonom :: Eta x -> x Source #

Eq ab => Eq (Eta ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(==) :: Eta ab -> Eta ab -> Bool #

(/=) :: Eta ab -> Eta ab -> Bool #

Ord ab => Ord (Eta ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

compare :: Eta ab -> Eta ab -> Ordering #

(<) :: Eta ab -> Eta ab -> Bool #

(<=) :: Eta ab -> Eta ab -> Bool #

(>) :: Eta ab -> Eta ab -> Bool #

(>=) :: Eta ab -> Eta ab -> Bool #

max :: Eta ab -> Eta ab -> Eta ab #

min :: Eta ab -> Eta ab -> Eta ab #

Show ab => Show (Eta ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

showsPrec :: Int -> Eta ab -> ShowS #

show :: Eta ab -> String #

showList :: [Eta ab] -> ShowS #

Semigroup ab => Semigroup (Eta ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(<>) :: Eta ab -> Eta ab -> Eta ab #

sconcat :: NonEmpty (Eta ab) -> Eta ab #

stimes :: Integral b => b -> Eta ab -> Eta ab #

Monoid ab => Monoid (Eta ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

mempty :: Eta ab #

mappend :: Eta ab -> Eta ab -> Eta ab #

mconcat :: [Eta ab] -> Eta ab #

(Pretty ab, Monoid ab, Eq ab) => Pretty (Eta ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

pretty :: Eta ab -> String #

prettyInParens :: Eta ab -> String #

Graded ab => Graded (Eta ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

grade :: Eta ab -> Int Source #

data Gam ab Source #

A monomial generator of Z[alpha,beta;gamma]/(...), the cohomology ring of P^m.

Constructors

Gam !Int !ab 

Instances

Instances details
Functor Gam Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

fmap :: (a -> b) -> Gam a -> Gam b #

(<$) :: a -> Gam b -> Gam a #

Equivariant Gam Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

injectMonom :: x -> Gam x Source #

projectMonom :: Gam x -> x Source #

Eq ab => Eq (Gam ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(==) :: Gam ab -> Gam ab -> Bool #

(/=) :: Gam ab -> Gam ab -> Bool #

Ord ab => Ord (Gam ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

compare :: Gam ab -> Gam ab -> Ordering #

(<) :: Gam ab -> Gam ab -> Bool #

(<=) :: Gam ab -> Gam ab -> Bool #

(>) :: Gam ab -> Gam ab -> Bool #

(>=) :: Gam ab -> Gam ab -> Bool #

max :: Gam ab -> Gam ab -> Gam ab #

min :: Gam ab -> Gam ab -> Gam ab #

Show ab => Show (Gam ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

showsPrec :: Int -> Gam ab -> ShowS #

show :: Gam ab -> String #

showList :: [Gam ab] -> ShowS #

Semigroup ab => Semigroup (Gam ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

(<>) :: Gam ab -> Gam ab -> Gam ab #

sconcat :: NonEmpty (Gam ab) -> Gam ab #

stimes :: Integral b => b -> Gam ab -> Gam ab #

Monoid ab => Monoid (Gam ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

mempty :: Gam ab #

mappend :: Gam ab -> Gam ab -> Gam ab #

mconcat :: [Gam ab] -> Gam ab #

(Pretty ab, Monoid ab, Eq ab) => Pretty (Gam ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

pretty :: Gam ab -> String #

prettyInParens :: Gam ab -> String #

Graded ab => Graded (Gam ab) Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

grade :: Gam ab -> Int Source #

class Functor f => Equivariant f where Source #

Class of monomial bases which form modules over the H^*(BGL2)

Methods

injectMonom :: x -> f x Source #

projectMonom :: f x -> x Source #

Instances

Instances details
Equivariant Gam Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

injectMonom :: x -> Gam x Source #

projectMonom :: Gam x -> x Source #

Equivariant Eta Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

injectMonom :: x -> Eta x Source #

projectMonom :: Eta x -> x Source #

Equivariant Omega Source # 
Instance details

Defined in Math.RootLoci.Geometry.Cohomology

Methods

injectMonom :: x -> Omega x Source #

projectMonom :: Omega x -> x Source #

injectZMod :: (Equivariant f, ChernBase base, Ord (f base)) => ZMod base -> ZMod (f base) Source #

forgetGamma :: Ord base => ZMod (Gam base) -> ZMod base Source #

forgetEquiv :: ChernBase base => ZMod (Gam base) -> ZMod G Source #

Conversion between different bases

convertOmega :: (Ord ab, Ord cd) => (ZMod ab -> ZMod cd) -> ZMod (Omega ab) -> ZMod (Omega cd) Source #

convertEta :: (Ord ab, Ord cd) => (ZMod ab -> ZMod cd) -> ZMod (Eta ab) -> ZMod (Eta cd) Source #

convertGam :: (Ord ab, Ord cd) => (ZMod ab -> ZMod cd) -> ZMod (Gam ab) -> ZMod (Gam cd) Source #

convertEach :: forall f x y ab cd. (Functor f, Ord ab, Ord cd, Ord (f ab), Ord (f cd), Ord x) => (forall y. f y -> x) -> (forall y. f y -> y) -> (forall y. x -> y -> f y) -> (ZMod ab -> ZMod cd) -> ZMod (f ab) -> ZMod (f cd) Source #

A generic function which can convert the GL2 representations

unsafeEtaToOmega :: (Eq coeff, Num coeff, Ord ab) => FreeMod coeff (Eta ab) -> FreeMod coeff (Omega ab) Source #

This is a hack to reuse the same pushforward code

unsafeOmegaToEta :: (Eq coeff, Num coeff, Ord ab) => FreeMod coeff (Omega ab) -> FreeMod coeff (Eta ab) Source #