Operads-1.0: Groebner basis computation for Operads.

Math.Operad

Contents

Synopsis

Pretty printing

class PPrint a whereSource

This yields user interface functions for human readable printing of objects. The idea is to use Show instances for marshalling of data, and PPrint for user interaction.

Methods

pp :: a -> StringSource

pP :: a -> IO ()Source

Instances

PPrint Int 
PPrint Integer 
PPrint a => PPrint [a] 
PPrint a => PPrint (Maybe a) 
(PPrint a, PPrint b) => PPrint (Either a b) 
(PPrint a, PPrint b) => PPrint (a, b) 
(Ord a, Show a, TreeOrdering t) => PPrint (OrderedTree a t) 
(Ord a, Show a, Show b) => PPrint (PreDecoratedTree a b) 
(PPrint a, PPrint b, PPrint c) => PPrint (a, b, c) 
(Ord a, Show a, Show n, TreeOrdering t) => PPrint (OperadElement a n t) 
(PPrint a, PPrint b, PPrint c, PPrint d) => PPrint (a, b, c, d) 
(PPrint a, PPrint b, PPrint c, PPrint d, PPrint e) => PPrint (a, b, c, d, e) 

type MonomialMap a t n = Map a t nSource

newtype (Ord a, Show a, TreeOrdering t) => OperadElement a n t Source

The type carrying operadic elements. An element in an operad is an associative array with keys being labeled trees and values being their coefficients.

Constructors

OE (MonomialMap a t n) 

Instances

(Eq n, Ord a, Show a, TreeOrdering t) => Eq (OperadElement a n t) 
(Ord a, Show a, Num n, TreeOrdering t) => Num (OperadElement a n t)

Arithmetic in the operad.

(Ord a, Ord n, Show a, TreeOrdering t) => Ord (OperadElement a n t) 
(Ord a, Read a, Read n, Read t, Show a, TreeOrdering t) => Read (OperadElement a n t) 
(Ord a, Show a, Show n, TreeOrdering t) => Show (OperadElement a n t) 
(Ord a, Show a, Show n, TreeOrdering t) => PPrint (OperadElement a n t) 

extractMap :: (Ord a, Show a, TreeOrdering t) => OperadElement a n t -> MonomialMap a t nSource

Extracting the internal structure of the an element of the free operad.

(.*.) :: (Ord a, Show a, Eq n, Show n, Num n, TreeOrdering t) => n -> OperadElement a n t -> OperadElement a n tSource

Scalar multiplication in the operad.

mapMonomials :: (Show a, Ord a, Show b, Ord b, Num n, TreeOrdering s, TreeOrdering t) => (OrderedTree a s -> OrderedTree b t) -> OperadElement a n s -> OperadElement b n tSource

Apply a function to each monomial tree in the operad element.

foldMonomials :: (Show a, Ord a, Num n, TreeOrdering t) => ((OrderedTree a t, n) -> [b] -> [b]) -> OperadElement a n t -> [b]Source

Fold a function over all monomial trees in an operad element, collating the results in a list.

fromList :: (TreeOrdering t, Show a, Ord a, Num n) => [(OrderedTree a t, n)] -> OperadElement a n tSource

Given a list of (tree,coefficient)-pairs, reconstruct the corresponding operad element.

toList :: (TreeOrdering t, Show a, Ord a) => OperadElement a n t -> [(OrderedTree a t, n)]Source

Given an operad element, extract a list of (tree, coefficient) pairs.

Handling polynomials in the free operad

oe :: (Ord a, Show a, TreeOrdering t, Num n) => [(OrderedTree a t, n)] -> OperadElement a n tSource

Construct an element in the free operad from its internal structure. Use this instead of the constructor.

oet :: (Ord a, Show a, TreeOrdering t, Num n) => DecoratedTree a -> OperadElement a n tSource

Construct a monomial in the free operad from a tree and a tree ordering. It's coefficient will be 1.

oek :: (Ord a, Show a, TreeOrdering t, Num n) => DecoratedTree a -> n -> OperadElement a n tSource

Construct a monomial in the free operad from a tree, a tree ordering and a coefficient.

zero :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n tSource

Return the zero of the corresponding operad, with type appropriate to the given element. Can be given an appropriately casted undefined to construct a zero.

isZero :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> BoolSource

Check whether an element is equal to 0.

leadingOTerm :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> OperadElement a n tSource

Extract the leading term of an operad element as an operad element.

leadingTerm :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> (OrderedTree a t, n)Source

Extract the leading term of an operad element.

leadingOMonomial :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> OrderedTree a tSource

Extract the ordered tree for the leading term of an operad element.

leadingMonomial :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> DecoratedTree aSource

Extract the tree for the leading term of an operad element.

leadingCoefficient :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> nSource

Extract the leading coefficient of an operad element.

getTrees :: (TreeOrdering t, Show a, Ord a) => OperadElement a n t -> [OrderedTree a t]Source

Extract all occurring monomial trees from an operad element.

Decorated and ordered trees

data (Ord a, Show a) => PreDecoratedTree a b Source

The fundamental tree data type used. Leaves carry labels - most often integral - and these are expected to control, e.g., composition points in shuffle operad compositions. The vertices carry labels, used for the ordering on trees and to distinguish different basis corollas of the same arity.

Constructors

DTLeaf !b 
DTVertex 

Fields

vertexType :: !a
 
subTrees :: ![PreDecoratedTree a b]
 

Instances

(Ord a, Show a) => Monad (PreDecoratedTree a) 
(Ord a, Show a) => Functor (PreDecoratedTree a) 
(Ord a, Show a) => Foldable (PreDecoratedTree a) 
(Ord a, Show a) => Traversable (PreDecoratedTree a) 
(Eq b, Ord a, Show a) => Eq (PreDecoratedTree a b) 
(Ord a, Ord b, Show a) => Ord (PreDecoratedTree a b) 
(Ord a, Read a, Read b, Show a) => Read (PreDecoratedTree a b) 
(Ord a, Show a, Show b) => Show (PreDecoratedTree a b) 
(Ord a, Show a, Show b) => PPrint (PreDecoratedTree a b) 

vertexArity :: (Ord a, Show a) => PreDecoratedTree a b -> IntSource

The arity of a corolla

vertexMap :: (Ord a, Show a, Ord b, Show b) => (a -> b) -> PreDecoratedTree a c -> PreDecoratedTree b cSource

Apply a function f to all the internal vertex labels of a PreDecoratedTree.

glueTrees :: (Ord a, Show a) => PreDecoratedTree a (PreDecoratedTree a b) -> PreDecoratedTree a bSource

If a tree has trees as labels for its leaves, we can replace the leaves with the roots of those label trees. Thus we may glue together trees, as required by the compositions.

type DecoratedTree a = PreDecoratedTree a IntSource

This is the fundamental datatype of the whole project. Monomials in a free operad are decorated trees, and we build a type for decorated trees here. We require our trees to have Int labels, limiting us to at most 2 147 483 647 leaf labels.

data (Ord a, Show a, TreeOrdering t) => OrderedTree a t Source

Monomial orderings on the free operad requires us to choose an ordering for the trees. These are parametrized by types implementing the type class TreeOrdering, and this is a data type for a tree carrying its comparison type. We call these ordered trees.

Constructors

OT (DecoratedTree a) t 

Instances

(Ord a, Show a, TreeOrdering t) => Eq (OrderedTree a t) 
(Ord a, Show a, TreeOrdering t) => Ord (OrderedTree a t)

Monomial ordering for trees. We require this to be a total well-ordering, compatible with the operadic compositions.

(Ord a, Read a, Read t, Show a, TreeOrdering t) => Read (OrderedTree a t) 
(Ord a, Show a, TreeOrdering t) => Show (OrderedTree a t) 
(Ord a, Show a, TreeOrdering t) => PPrint (OrderedTree a t) 

ot :: (Ord a, Show a, TreeOrdering t) => DecoratedTree a -> OrderedTree a tSource

Building an ordered tree with PathLex ordering from a decorated tree.

dt :: (Ord a, Show a, TreeOrdering t) => OrderedTree a t -> DecoratedTree aSource

Extracting the underlying tree from an ordered tree.

Monomial orderings on the free operad

class (Eq t, Show t) => TreeOrdering t whereSource

The type class that parametrizes types implementing tree orderings.

Methods

treeCompare :: (Ord a, Show a) => t -> DecoratedTree a -> DecoratedTree a -> OrderingSource

comparePathSequence :: (Ord a, Show a) => t -> DecoratedTree a -> ([[a]], Shuffle) -> DecoratedTree a -> ([[a]], Shuffle) -> OrderingSource

ordering :: tSource

pathSequence :: (Ord a, Show a) => DecoratedTree a -> ([[a]], Shuffle)Source

Finding the path sequences. cf. Dotsenko-Khoroshkin.

orderedPathSequence :: (Ord a, Show a) => DecoratedTree a -> ([[a]], Shuffle)Source

Reordering the path sequences to mirror the actual leaf ordering.

reverseOrder :: Ordering -> OrderingSource

Changes direction of an ordering.

data PathPerm Source

Using the path sequence, the leaf orders and order reversal, we can get 8 different orderings from one paradigm. These are given by PathPerm, RPathPerm, PathRPerm, RPathRPerm for the variations giving (possibly reversed) path sequence comparison precedence over (possibly reversed) leaf permutations; additionally, there are PermPath, RPermPath, PermRPath and RPermRPath for the variations with the opposite precedence.

Constructors

PathPerm 

Utility functions on trees

corolla :: (Ord a, Show a) => a -> [Int] -> DecoratedTree aSource

Build a single corolla in a decorated tree. Takes a list for labels for the leaves, and derives the arity of the corolla from those. This, and the composition functions, form the preferred method to construct trees.

leaf :: (Ord a, Show a) => Int -> DecoratedTree aSource

Build a single leaf.

isLeaf :: (Ord a, Show a) => DecoratedTree a -> BoolSource

Check whether a given root is a leaf.

isCorolla :: (Ord a, Show a) => DecoratedTree a -> BoolSource

Check whether a given root is a corolla.

relabelLeaves :: (Ord a, Show a) => DecoratedTree a -> [b] -> PreDecoratedTree a bSource

Change the leaves of a tree to take their values from a given list.

leafOrder :: (Ord a, Show a) => DecoratedTree a -> [Int]Source

Find the permutation the leaf labeling ordains for inputs.

minimalLeaf :: (Ord a, Show a, Ord b) => PreDecoratedTree a b -> bSource

Find the minimal leaf covering any given vertex.

nLeaves :: (Ord a, Show a) => DecoratedTree a -> IntSource

Compute the number of leaves of the entire tree covering a given vertex.

arityDegree :: (Ord a, Show a) => DecoratedTree a -> IntSource

arityDegree is one less than nLeaves.

Shuffles

type Shuffle = [Int]Source

A shuffle is a special kind of sequence of integers.

isSorted :: (Ord a, Show a) => [a] -> BoolSource

We need to recognize sorted sequences of integers.

isShuffle :: Shuffle -> BoolSource

This tests whether a given sequence of integers really is a shuffle.

isShuffleIJ :: Shuffle -> Int -> Int -> BoolSource

This tests whether a given sequence of integers is an (i,j)-shuffle

isShuffleIPQ :: Shuffle -> Int -> Int -> BoolSource

This tests whether a given sequence of integers is admissible for a specific composition operation.

applyPerm :: Show a => Shuffle -> [a] -> [a]Source

This applies the resulting permutation from a shuffle to a set of elements

invApplyPerm :: Shuffle -> [a] -> [a]Source

Apply the permutation inversely to applyPerm.

kSubsets :: Int -> [Int] -> [[Int]]Source

Generate all subsets of length k from a given list.

applyAt :: (a -> a) -> Int -> [a] -> [a]Source

Applies f only at the nth place in a list.

lastNonzero :: Num a => [a] -> IntSource

Picks out the last nonzero entry in a list.

allShPerm :: Int -> [Int] -> [[[Int]]]Source

Generates shuffle permutations by filling buckets.

allShuffles :: Int -> Int -> Int -> [Shuffle]Source

Generates all shuffles from Sh_i(p,q).

Fundamental data types and instances

operationDegree :: (Ord a, Show a) => DecoratedTree a -> IntSource

The number of internal vertices of a tree.

operationDegrees :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> [Int]Source

A list of operation degrees occurring in the terms of the operad element

maxOperationDegree :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> IntSource

The maximal operation degree of an operadic element

isHomogenous :: (Ord a, Show a, TreeOrdering t, Num n) => OperadElement a n t -> BoolSource

Check that an element of a free operad is homogenous

Free operad

Operadic compositions

shuffleCompose :: (Ord a, Show a) => Int -> Shuffle -> DecoratedTree a -> DecoratedTree a -> DecoratedTree aSource

Composition in the shuffle operad

nsCompose :: (Ord a, Show a) => Int -> DecoratedTree a -> DecoratedTree a -> DecoratedTree aSource

Composition in the non-symmetric operad. We compose s o_i t.

symmetricCompose :: (Ord a, Show a) => Int -> Shuffle -> DecoratedTree a -> DecoratedTree a -> DecoratedTree aSource

Composition in the symmetric operad

nsComposeAll :: (Ord a, Show a) => DecoratedTree a -> [DecoratedTree a] -> DecoratedTree aSource

Non-symmetric composition in the g(s;t1,...,tk) style.

checkShuffleAll :: Shuffle -> [Int] -> BoolSource

Verification for a shuffle used for the g(s;t1,..,tk) style composition in the shuffle operad.

isPermutation :: Shuffle -> BoolSource

Sanity check for permutations.

shuffleComposeAll :: (Ord a, Show a) => Shuffle -> DecoratedTree a -> [DecoratedTree a] -> DecoratedTree aSource

Shuffle composition in the g(s;t1,...,tk) style.

symmetricComposeAll :: (Ord a, Show a) => Shuffle -> DecoratedTree a -> [DecoratedTree a] -> DecoratedTree aSource

Symmetric composition in the g(s;t1,...,tk) style.

Divisibility among trees

type Embedding a = DecoratedTree (Maybe a)Source

Data type to move the results of finding an embedding point for a subtree in a larger tree around. The tree is guaranteed to have exactly one corolla tagged Nothing, the subtrees on top of that corolla sorted by minimal covering leaf in the original setting, and the shuffle carried around is guaranteed to restore the original leaf labels before the search.

divides :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree a -> BoolSource

Returns True if there is a subtree of t isomorphic to s, respecting leaf orders.

dividesHigh :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree a -> BoolSource

Returns True if there is a subtree of t isomorphic to s, respecting leaf orders, and not located at the root.

dividesRooted :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree a -> BoolSource

Returns True if there is a rooted subtree of t isomorphic to s, respecting leaf orders.

findAllEmbeddings :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree a -> [Embedding a]Source

Finds all ways to embed s into t respecting leaf orders.

findRootedEmbedding :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree a -> Maybe (Embedding a)Source

Finds all ways to embed s into t, respecting leaf orders and mapping the root of s to the root of t.

planarTree :: (Ord a, Show a) => DecoratedTree a -> BoolSource

Checks a tree for planarity.

dividesDifferent :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree a -> DecoratedTree a -> BoolSource

Returns True if s and t divide u, with different embeddings and t sharing root with u.

flipEither :: Either a a -> Either a aSource

Interchanges Left to Right and Right to Left for types Either a a

stripEither :: Either a a -> aSource

Projects the type Either a a onto the type a in the obvious manner.

flipEitherRoot :: (Ord a, Show a) => PreDecoratedTree (Either a a) b -> PreDecoratedTree (Either a a) bSource

Applies flipEither to the root vertex label of a tree.

fuseTree :: (Ord a, Show a) => DecoratedTree (Either a a) -> [Int] -> DecoratedTree (Either a a)Source

Projects vertex labels and applies leaf labels to a tree with internal labeling in Either a a.

stripTree :: (Ord a, Show a) => DecoratedTree (Either a a) -> DecoratedTree aSource

Strips the Either layer from internal vertex labels

leafOrders :: (Ord a, Show a, Ord b, Show b) => DecoratedTree a -> DecoratedTree b -> [(Int, Int)]Source

Acquires lists for resorting leaf labels according to the algorithm found for constructing small common multiples with minimal work.

findFirstRight :: (Ord a, Show a, Ord b, Show b) => DecoratedTree (Either a b) -> Maybe (DecoratedTree (Either a b))Source

Locates the first vertex tagged with a Right constructor in a tree labeled with Either a b.

maybeLast :: [a] -> Maybe aSource

Equivalent to listToMaybe . reverse

leafLabels :: (Ord a, Show a) => DecoratedTree a -> [Int] -> [Int] -> [[Int]]Source

Recursive algorithm to figure out correct leaf labels for a reconstructed small common multiple of two trees.

findRootedSCM :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree a -> Maybe (DecoratedTree a)Source

Finds rooted small common multiples of two trees.

findNonSymmetricSCM :: (Ord a, Show a) => Int -> DecoratedTree (Either a a) -> DecoratedTree (Either a a) -> [DecoratedTree (Either a a)]Source

Finds structural small common multiples, disregarding leaf labels completely.

findBoundedSCM :: (Ord a, Show a) => Int -> DecoratedTree a -> DecoratedTree a -> [DecoratedTree (Either a a)]Source

Finds small common multiples of two trees bounding internal operation degree.

findAllSCM :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree a -> [DecoratedTree (Either a a)]Source

Finds all small common multiples of two trees.

findAllBoundedSCM :: (Ord a, Show a) => Int -> DecoratedTree a -> DecoratedTree a -> [DecoratedTree (Either a a)]Source

Finds all small common multiples of two trees, bounding the internal operation degree.

scmToEmbedding :: (Ord a, Show a) => DecoratedTree (Either a a) -> DecoratedTree a -> DecoratedTree a -> (Embedding a, Embedding a)Source

Constructs embeddings for s and t in SCM(s,t) and returns these.

rePackLabels :: (Ord a, Show a, Ord b) => PreDecoratedTree a b -> DecoratedTree aSource

Relabels a tree in the right order, but with entries from [1..]

fromJustTree :: (Ord a, Show a) => DecoratedTree (Maybe a) -> Maybe (DecoratedTree a)Source

Removes vertex type encapsulations.

toJustTree :: (Ord a, Show a) => DecoratedTree a -> DecoratedTree (Maybe a)Source

Adds vertex type encapsulations.

equivalentOrders :: [Int] -> [Int] -> BoolSource

Verifies that two integer sequences correspond to the same total ordering of the entries.

subTreeHasNothing :: (Ord a, Show a) => DecoratedTree (Maybe a) -> BoolSource

Returns True if any of the vertices in the given tree has been tagged.

reconstructNode :: (Ord a, Show a) => DecoratedTree a -> Embedding a -> Maybe (DecoratedTree a)Source

The function that mimics resubstitution of a new tree into the hole left by finding embedding, called m_alpha,beta in Dotsenko-Khoroshkin. This version only attempts to resubstitute the tree at the root, bailing out if not possible.

reconstructTree :: (Ord a, Show a) => DecoratedTree a -> Embedding a -> Maybe (DecoratedTree a)Source

The function that mimics resubstitution of a new tree into the hole left by finding embedding, called m_alpha,beta in Dotsenko-Khoroshkin. This version recurses down in the tree in order to find exactly one hole, and substitute the tree sub into it.

Groebner basis methods

applyReconstruction :: (Ord a, Show a, TreeOrdering t, Num n) => Embedding a -> OperadElement a n t -> OperadElement a n tSource

Applies the reconstruction map represented by em to all trees in the operad element op. Any operad element that fails the reconstruction (by having the wrong total arity, for instance) will be silently dropped. We recommend you apply this function only to homogenous operad elements, but will not make that check.

findAllSPolynomials :: (Ord a, Show a, TreeOrdering t, Fractional n) => [OperadElement a n t] -> [OperadElement a n t] -> [OperadElement a n t]Source

Finds all S polynomials for a given list of operad elements.

findInitialSPolynomials :: (Ord a, Show a, TreeOrdering t, Fractional n) => Int -> [OperadElement a n t] -> [OperadElement a n t] -> [OperadElement a n t]Source

Finds all S polynomials for which the operationdegree stays bounded.

findSPolynomials :: (Ord a, Show a, TreeOrdering t, Fractional n) => Int -> OperadElement a n t -> OperadElement a n t -> [OperadElement a n t]Source

Finds all S polynomials for a given pair of operad elements, keeping a bound on operation degree.

findNSInitialSPolynomials :: (Ord a, Show a, TreeOrdering t, Fractional n) => Int -> [OperadElement a n t] -> [OperadElement a n t] -> [OperadElement a n t]Source

Non-symmetric version of findInitialSPolynomials.

findNSSPolynomials :: (Ord a, Show a, TreeOrdering t, Fractional n) => Int -> OperadElement a n t -> OperadElement a n t -> [OperadElement a n t]Source

Non-symmetric version of findSPolynomials.

reduceOE :: (Ord a, Show a, TreeOrdering t, Fractional n) => Embedding a -> OperadElement a n t -> OperadElement a n t -> OperadElement a n tSource

Reduce g with respect to f and the embedding em: lt f -> lt g.

reduceInitial :: (Ord a, Show a, TreeOrdering t, Fractional n) => OperadElement a n t -> [OperadElement a n t] -> OperadElement a n tSource

Reduce the leading monomial of op with respect to gb.

reduceCompletely :: (Ord a, Show a, TreeOrdering t, Fractional n) => OperadElement a n t -> [OperadElement a n t] -> OperadElement a n tSource

Reduce all terms of op with respect to gbn.

stepOperadicBuchberger :: (Ord a, Show a, TreeOrdering t, Fractional n) => [OperadElement a n t] -> [OperadElement a n t] -> [OperadElement a n t]Source

Perform one iteration of the Buchberger algorithm: generate all S-polynomials. Reduce all S-polynomials. Return anything that survived the reduction.

stepInitialOperadicBuchberger :: (Ord a, Show a, TreeOrdering t, Fractional n) => Int -> [OperadElement a n t] -> [OperadElement a n t] -> [OperadElement a n t]Source

Perform one iteration of the Buchberger algorithm: generate all S-polynomials. Reduce all S-polynomials. Return anything that survived the reduction. Keep the occurring operation degrees bounded.

operadicBuchberger :: (Ord a, Show a, TreeOrdering t, Fractional n) => [OperadElement a n t] -> [OperadElement a n t]Source

Perform the entire Buchberger algorithm for a given list of generators. Iteratively run the single iteration from stepOperadicBuchberger until no new elements are generated.

DO NOTE: This is entirely possible to get stuck in an infinite loop. It is not difficult to write down generators such that the resulting Groebner basis is infinite. No checking is performed to catch this kind of condition.

nsOperadicBuchberger :: (Ord a, Show a, TreeOrdering t, Fractional n) => [OperadElement a n t] -> [OperadElement a n t]Source

Non-symmetric version of operadicBuchberger.

streamOperadicBuchberger :: (Ord a, Show a, TreeOrdering t, Fractional n) => Int -> [OperadElement a n t] -> [OperadElement a n t]Source

Perform the entire Buchberger algorithm for a given list of generators. This iteratively runs single iterations from stepOperadicBuchberger until no new elements are generated.

reduceBasis :: (Fractional n, TreeOrdering t, Show a, Ord a) => [OperadElement a n t] -> [OperadElement a n t] -> [OperadElement a n t]Source

Reduces a list of elements with respect to all other elements occurring in that same list.

Low degree bases

allTrees :: (Ord a, Show a) => [DecoratedTree a] -> Int -> [DecoratedTree a]Source

All trees composed from the given generators of operation degree n.

basisElements :: (Ord a, Show a) => [DecoratedTree a] -> [DecoratedTree a] -> Int -> [DecoratedTree a]Source

Generate basis trees for a given Groebner basis for degree maxDegree. divisors is expected to contain the leading monomials in the Groebner basis.

changeOrder :: (Ord a, Show a, TreeOrdering s, TreeOrdering t) => t -> OrderedTree a s -> OrderedTree a tSource

Change the monomial order used for a specific tree. Use this in conjunction with mapMonomials in order to change monomial order for an entire operad element.

m12_3 :: DecoratedTree IntegerSource

The element m2(m2(1,2),3)

m13_2 :: DecoratedTree IntegerSource

The element m2(m2(1,3),2)

m1_23 :: DecoratedTree IntegerSource

The element m2(1,m2(2,3))

m2 :: DecoratedTree IntegerSource

The element m2(1,2)

m3 :: DecoratedTree IntegerSource

The element m3(1,2,3)

yTree :: DecoratedTree IntegerSource

The element m2(m2(1,2),m2(3,4))

lgb :: [OperadElement Integer Rational PathPerm]Source

The list of operad elements consisting of 'm12_3'-'m13_2'-'m1_23'. This generates the ideal of relations for the operad Lie.