| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Math.RootLoci.Motivic.Classes
Contents
Synopsis
- newtype Dim = Dim Int
- unDim :: Dim -> Int
- dimVector :: Partition -> [Dim]
- dimTuples :: [Dim] -> [[Dim]]
- class Degree a where
- type MultiDegree a :: *
- totalDegree :: a -> Int
- multiDegree :: a -> MultiDegree a
- class Empty a where
- empty :: a
- class Normalize a where
- normalize :: a -> a
- class SuperNormalize a where
- superNormalize :: a -> a
- class Cross a where
- cross :: a -> a -> a
- crossMany :: [a] -> a
- crossInterleave :: a -> a -> a
- class SingleToMulti s t | s -> t, t -> s where
- singleToMulti :: s -> t
- omegaZeroError :: a
- class Omega a where
- class Omega123 a where
- omega123 :: a -> a
- class Psi t s | t -> s where
- psi :: t -> s
- class PsiEvenOdd t where
- psiEvenOdd :: t -> t
- class Pontrjagin a where
- pontrjaginOne :: a
- pontrjaginMul :: a -> a -> a
- class ExtendToCommonSize a where
- extendToCommonSize :: (a, a) -> (a, a)
- class Permute a where
- permute :: Permutation -> a -> a
- class Theta a where
- theta :: a -> a
Dimensions
A dimension (d in Sym^d(X))
Classes
Degree of something
Associated Types
type MultiDegree a :: * Source #
Instances
| Degree MultiLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract Associated Types type MultiDegree MultiLam Source # Methods totalDegree :: MultiLam -> Int Source # | |
| Degree SingleLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract Associated Types type MultiDegree SingleLam Source # Methods totalDegree :: SingleLam -> Int Source # | |
| KnownNat n => Degree (XS v n) Source # | |
Defined in Math.RootLoci.Motivic.Classes Associated Types type MultiDegree (XS v n) Source # | |
Instances
| Empty Int Source # | |
Defined in Math.RootLoci.Motivic.Classes | |
| Empty MultiLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Empty SingleLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Empty Multi Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Empty Single Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Empty Bindings Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Empty [a] Source # | |
Defined in Math.RootLoci.Motivic.Classes | |
| Empty (Maybe a) Source # | |
Defined in Math.RootLoci.Motivic.Classes | |
| KnownNat n => Empty (XS v n) Source # | |
Defined in Math.RootLoci.Motivic.Classes | |
class Normalize a where Source #
Normalize terms and lambdas
class SuperNormalize a where Source #
This is a hack because there is some issue when this is included in normalize that i don't want to debug right now
Methods
superNormalize :: a -> a Source #
Instances
| SuperNormalize MultiLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract Methods superNormalize :: MultiLam -> MultiLam Source # | |
| SuperNormalize Multi Source # | |
Defined in Math.RootLoci.Motivic.Abstract Methods superNormalize :: Multi -> Multi Source # | |
| (Eq c, Num c) => SuperNormalize (FreeMod c MultiLam) Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
Exterior (or cross) product
Minimal complete definition
class SingleToMulti s t | s -> t, t -> s where Source #
Conversion from scalar to vector
Methods
singleToMulti :: s -> t Source #
Instances
| SingleToMulti SingleLam MultiLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract Methods singleToMulti :: SingleLam -> MultiLam Source # | |
| SingleToMulti Single Multi Source # | |
Defined in Math.RootLoci.Motivic.Abstract Methods singleToMulti :: Single -> Multi Source # | |
| SingleToMulti (KRing c) (GRing c) Source # | |
Defined in Math.RootLoci.Motivic.Homology Methods singleToMulti :: KRing c -> GRing c Source # | |
| (Eq c, Num c) => SingleToMulti (FreeMod c SingleLam) (FreeMod c MultiLam) Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
omegaZeroError :: a Source #
replicating points (power map)
class Omega123 a where Source #
Omega^{1,2,3,...}class Psi t s | t -> s where Source #
The merging (or multiplication) map
class PsiEvenOdd t where Source #
The interleaved pairwise merging map
Methods
psiEvenOdd :: t -> t Source #
Instances
| PsiEvenOdd MultiLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract Methods psiEvenOdd :: MultiLam -> MultiLam Source # | |
| PsiEvenOdd Multi Source # | |
Defined in Math.RootLoci.Motivic.Abstract Methods psiEvenOdd :: Multi -> Multi Source # | |
| PsiEvenOdd (ZMod MultiLam) Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
class Pontrjagin a where Source #
Pontrjagin ring
Instances
| Pontrjagin MultiLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Pontrjagin SingleLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract Methods pontrjaginOne :: SingleLam Source # pontrjaginMul :: SingleLam -> SingleLam -> SingleLam Source # | |
class ExtendToCommonSize a where Source #
Methods
extendToCommonSize :: (a, a) -> (a, a) Source #
Instances
| ExtendToCommonSize MultiLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| ExtendToCommonSize Multi Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Empty a => ExtendToCommonSize [a] Source # | |
Defined in Math.RootLoci.Motivic.Classes Methods extendToCommonSize :: ([a], [a]) -> ([a], [a]) Source # | |
class Permute a where Source #
Applying permutations
Methods
permute :: Permutation -> a -> a Source #
Instances
| Permute MultiLam Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Permute Multi Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
| Permute [a] Source # | |
Defined in Math.RootLoci.Motivic.Classes Methods permute :: Permutation -> [a] -> [a] Source # | |
| Permute (ZMod MultiLam) Source # | |
Defined in Math.RootLoci.Motivic.Abstract | |
The custom pusforward Theta appearing in the algorithm
we subdivide the input as [z;x1,y1,x2,y2,x3,y3...]
and then duplicate each of y1,y2,y3..., then combine the left copies of y_i with
z, and the right copies of y_i with the corresponding x_i-s, resulting in
[z*y1*y2*...;x1*y1,x2*y2,...]