Skip to content

Latest commit

 

History

History
816 lines (522 loc) · 45.4 KB

introductorySession.md

File metadata and controls

816 lines (522 loc) · 45.4 KB

MatroidActivities

A package for working with ordered matroids in Macaulay2.

History

Macaulay2 is an excellent tool to get intuition and refine conjectures when studying algebraic geometry and commutative algebra. I first came to use it when I needed some higher dimensional examples of curious polyhedral subdivisions of a space-tiling zonotopes. Typically when I want to compute polyhedral subdivsions these days I turn to polymake but back then installing polymake on my Mac was beyond me, so out of desperation I turned to the Polyhedra package of Macaulay2 written by René Birkner. The package was intuitive to use and the documentation was excellent (a common feature of Macaulay2 packages). After a couple of weeks running examples, Julian Pfeifle and I found the right formulation for the result that appears as the main theorem in our paper A Polyhedral Proof of the Matrix Theorem.

That project with Julian got me thinking about matroids and I ended up writing some simple scripts in Macaulay2 to facilitate the research that eventually led to the article Internally Perfect Matroids. In some sense, this package can be seen as the companion software to that article.

Much later I found the Matroids package written by Justin Chen's and set about recasting my scripts to fit with the vast amount of work he had done. The result is the package MatroidActivities. It both expands the functionality available for studying (unordered) matroids in Macaulay2 and defines the new class OrderedMatroid for studying matroids endowed with a linear order on the ground set.

Following this link to MatroidActivities one can find the source code and installation protocol. The goals of this post are twofold: to highlight some of the features available with this package and to illustrate these features by working out in detail Example 6 in Internally Perfect Matroids.

The Package

As of March 2017, the current release is MatroidActivities 0.2. The package is still under development. Please get in touch with any comments, feature requests, or bug reports!

MatroidActivities facilitates studying matroids on the Macaulay2 platform in two major ways. First, it extends the functionality of the Matroids package by defining a number of new methods for creating matroids, producing matroid invariants, and testing a given matroid for certain properties. Second, it defines a new class of objects, the OrderedMatroid class, that allows the user to study structures arising from matroids whose ground sets have been endowed with a linear order. Such structures include the broken circuit complex, the Orlik-Solomon algebra, and (of course) internal and external activities.

We will first talk about the new methods available for unordered matroids before turning to those available for ordered matroids.

Computing with Matroids in MatroidActivities

As stated above, MatroidActivities builds upon the Matroids package written by J. Chen. When loading MatroidActivites the Matroids package is automatically loaded (assuming the user has installed it) together with the following Macaulay2 packages: HyperplaneArrangements, Posets, SimplicialComplexes, and Depth.

One aspect of matroids that makes them so ubiquitous in mathematics is the many equivalent ways in which they can be defined: from graphs and matrices, as simplicial complexes, ideals, or posets with certain properties, etc. Using the Matroids package one can define a matroid from a list of bases or circuits, or from a graph or matrix. Using the orderedMatroid method, the MatroidActivities package allows the user to define matroids from these inputs as well as from (central) hyperplane arrangements, (monomial) ideals, and simplicial complexes. For example, below we obtain a(n ordered) matroid from the 2-dimensional braid arrangement.

i1 : H = typeA 2; -- the 2-dimensional braid arrangement

i2 : OM = orderedMatroid H; -- get the associated ordered matroid

i3 : peek OM -- let's have a look under the hood

o3 = OrderedMatroid{cache => CacheTable{...1...}                 }
                matroid => Matroid
                orderedBases => {{0, 1}, {0, 2}, {1, 2}}
                orderedCircuits => {{0, 1, 2}}
                orderedCocircuits => {{0, 1}, {0, 2}, {1, 2}}
                orderedGround => {0, 1, 2}
                Presentations => CacheTable{...2...}

We will talk about the difference between the class of matroids and ordered matroids below, but for now simply notice that the ordered matroid OM is a hash table and one of the keys is matroid. Such a matroid object is always part of the data of an ordered matroid object and it can be retrieved as follows.

i4 : M = OM.matroid; -- an object of type Matroid

i5 : peek M -- matroids are also hash tables; use peek to view keys and values

o5 = Matroid{bases => {set {0, 1}, set {0, 2}, set {1, 2}}}
             cache => CacheTable{...2...}
             ground => set {0, 1, 2}
             groundSet => {| 1  |, | 1  |, | 0  |}
                           | -1 |  | 0  |  | 1  |
                           | 0  |  | -1 |  | -1 |

Generally speaking, a matroid is represented in Macaulay2 as a hash table with four keys:

  • bases: a list of (unordered) sets consisting of the bases of the matroid;
  • ground: a set of integers representing the indices of the ground set;
  • groundSet: the ground set of the matroid represented as a list of objects (integers, edges of a graph, or columns of a matrix);
  • cache: a place to store data computed about the matroid for quick recall later.

The above example will serve as a running example while we discuss the methods for the matroid class. We see that the matroid M is a rank two matroid on 3 elements with three bases and that was defined by the columns of matrix. We can also see that the cache has two items in it already. We can view them and use them as in the next example.

i6 : peek M.cache  -- viewing the cache

o6 = CacheTable{circuits => {set {0, 1, 2}}}
             nonbases => {}

i7 : M.cache.circuits -- getting a value from the cache

o7 = {set {0, 1, 2}}

o7 : List

Algebraic Constructions with Unordered Matroids

Now that we know the basics of how a matroid is structured in Macaulay2, let's try out some of the methods available in MatroidActivities. As Macaulay2 is designed to study commutative algebra, it is natural to encode matroids as algebraic objects. One such object is the face ideal of the independence complex of a matroid, which is the ideal generated by the circuits of the matroid. We compute the independence complex of a matroid as follows.

i8 : C = matroidIndependenceComplex M

o8 = | x_1x_2 x_0x_2 x_0x_1 |

o8 : SimplicialComplex

Note that the monomials in o8 are the facets of the independence complex, and that they correspond to the bases of M. When the independence complex of a matroid is computed its value is stored (together with its defining ideal) in the cache.

i9 : peek M.cache

o9 = CacheTable{CircuitIdeal => monomialIdeal(x x x )          }
                         	                   0 1 2
            circuits => {set {0, 1, 2}}
            IndependenceComplex => | x_1x_2 x_0x_2 x_0x_1 |
            nonbases => {}

Now any of Macaulay2 methods available for ideals and rings can be used to study our matroid. For example, it is well-known that the face ring of a matroid is Cohen-Macaulay. Let's confirm this for our example.

i10 : I = M.cache.CircuitIdeal

o10 = monomialIdeal(x x x )
                     0 1 2

o10 : MonomialIdeal of QQ[x , x , x ]
                           0   1   2

i11 : isCM (ring I /I)

o11 = true

Two important invariants of a matroid are the f- and h-vectors of its independence complex. In this software, the f-vector is encoded as a hash table and the h-vector as a polynomial.

i12 : matroidFVector M

o12 = HashTable{-1 => 1}
                0 => 3
                1 => 3

o12 : HashTable

i13 : matroidHPolynomial M

       2
o13 = q  + q + 1

o13 : ZZ[q]

Another useful algebraic construction is the Chow ring of a matroid which is a quotient of QQ[xF] with one variable for every nonempty proper flat.

i14 : matroidChowIdeal M

o14 = ideal (0, x   x   , x   x   , x   x   , 0, x    - x   , x    - x   , - x    + x   , x    - x   , - x    + x   , - x    + x   )
                 {0} {1}   {0} {2}   {1} {2}      {0}    {1}   {0}    {2}     {0}    {1}   {1}    {2}     {0}    {2}     {1}    {2}

o14 : Ideal of QQ[x   , x   , x   ]
                   {0}   {1}   {2}

i15 : matroidChowRing M

                                                        QQ[x   , x   , x   ]
                                                            {0}   {1}   {2}
o15 = ------------------------------------------------------------------------------------------------------------------------
      (0, x   x   , x   x   , x   x   , 0, x    - x   , x    - x   , - x    + x   , x    - x   , - x    + x   , - x    + x   )
           {0} {1}   {0} {2}   {1} {2}      {0}    {1}   {0}    {2}     {0}    {1}   {1}    {2}     {0}    {2}     {1}    {2}

o15 : QuotientRing

In a recent paper, Adiprasito, Huh, and Katz used the Chow ring to prove two long-standing conjectures: for a simple matroid, both the f-vector of the independence complex and the h-polynomial of Orlik-Solomon algebra of a (simple) matroid are unimodal. We can confirm these facts by inspection for our toy example.

i16 : print values matroidFVector M -- the f-vector `reversed'
{3, 3, 1}

i17 : A = matroidOrlikSolomon orderedMatroid M; -- Orlik-Solomon algebra only accepts ordered matroids as input

i18 : print numerator reduceHilbert hilbertSeries A
           2
1 + 3T + 2T

By a classic result the last polynomial is essentially the characteristic polynomial of the matroid.

i19 : matroidCharacteristicPolynomial M

                2
o19 = 2 - 3T + T

o19 : ZZ[T]

The beta invariant of a matroid is an evaluation of the derivative of the characteristic polynomial. It gives information about the connectedness of a matroid and is computed as follows.

i20 : betaInvariant M

o20 = 1

Combinatorial Constructions with Unordered Matroids

In MatroidActivities many of the algebraic constructions are considered as such since computing them using the algebraic methods in Macaulay2 leads to clean code and fast algorithms. Of course, from a theoretical standpoint many of them are purely combinatorial. For example, in this package the characteristic polynomial of a matroid is computed as a transformation of the Hilbert series of the Orlik-Solomon algebra. We could get the same result by computing the characteristic polynomial of the lattice of flats of a matroid, but this turns out to be much slower.

i21 : time matroidCharacteristicPolynomial M
     -- used 0.000092 seconds

                2
o21 = 2 - 3T + T

o21 : ZZ[T]

i22 : time characteristicPolynomial latticeOfFlats (M, Reduced => false)
     -- used 0.002077 seconds

       2
o22 = q  - 3q + 2

o22 : ZZ[q]

Nonetheless it is worth noting that both the lattice of flats and the Tutte polynomial of a matroid can be computed.

Tests for Unordered Matroids

There are a number of methods included with MatroidActivities for testing if a matroid belongs to a certain class. In Version 0.2 one can test if a matroid is simple, binary, ternary, regular, graphic, cographic, or paving. Once such a test has been run, its value is stored in the matroid cache. We will confirm that our running example is a regular matroid. Before we run the test, let's look in on the cache.

i23 : peek M.cache

o23 = CacheTable{CircuitIdeal => monomialIdeal(x x x )          }
                                                0 1 2
                 circuits => {set {0, 1, 2}}
                 IndependenceComplex => | x_1x_2 x_0x_2 x_0x_1 |
                 LatticeOfFlats => Relation Matrix: | 1 0 0 |
                                                    | 0 1 0 |
                                                    | 0 0 1 |
                 nonbases => {}

To check if M is regular we use the method isRegularMatroid.

i24 : isRegularMatroid M

o24 = true

i25 : peek M.cache

o25 = CacheTable{CircuitIdeal => monomialIdeal(x x x )          }
                                                0 1 2
                 circuits => {set {0, 1, 2}}
                 IndependenceComplex => | x_1x_2 x_0x_2 x_0x_1 |
                 IsBinaryMatroid => true
                 IsRegularMatroid => true
                 IsRepresentableMatroid => true
                 IsTernaryMatroid => true
                 LatticeOfFlats => Relation Matrix: | 1 0 0 |
                                                    | 0 1 0 |
                                                    | 0 0 1 |
                 nonbases => {}

Note that the cache is now much more populated. This is because a matroid is regular if and only if it is binary and ternary, so the method adds the results of these subtests to the cache. Also, a matroid is regular if and only if it is representable over any field. The value of the key IsRepresentableMatroid captures this fact though there is no attempt to actually produce a representation.

Now we turn from computing with objects in the Matroid class to computing with those in the OrderedMatroid class.

Computing with Ordered Matroids in MatroidActivities

We will now work with our small example viewed as an ordered matroid object instead of a matroid object. First we clear our previously defined symbols and redefine the hyperplane arrangement.

i26 : clearAll -- deletes from memory all previously defined user symbols

i27 : H = typeA 2; -- construct the 2-dim braid arrangement again

To construct an ordered matroid from a hyperplane arrangement (or a matroid, matrix, graph, etc.), call orderedMatroid on the pair (X, L) where X is an object of the appropriate type and L is a list giving the desired permutation of the ground set.

i28 : OM = orderedMatroid (H, {2,0,1}); -- make the ordered matroid with 2 < 0 < 1

The result is an object of class OrderedMatroid. Objects in this class are hash tables, so we use peek to look at the data they contain.

i29 : peek OM -- view the hash table representing the ordered matroid

o29 = OrderedMatroid{cache => CacheTable{...1...}                 }
                 matroid => Matroid
                 orderedBases => {{2, 0}, {2, 1}, {0, 1}}
                 orderedCircuits => {{2, 0, 1}}
                 orderedCocircuits => {{2, 0}, {2, 1}, {0, 1}}
                 orderedGround => {2, 0, 1}
                 Presentations => CacheTable{...2...}

Five of the keys in this hash table are self-explanatory.

  • matroid: the underlying matroid of the ordered matroid
  • orderedGround: the linear ordering on the (indices of) the ground set of the matroid;
  • orderedBases: the bases of the matroid ordered lexicographically using orderedGround;
  • orderedCircuits: the circuits of the matroid ordered lexicographically using orderedGround;
  • orderedCocircuits: the cocircuits of the matroid ordered lexicographically using orderedGround.

Now we look at the remaining keys. Presentations is a cache table which stores objects representing the given matroid in various classes. Our example came from a central hyperplane arrangement, so we should expect to see that arrangement in the table.

i30 : peek OM.Presentations

o30 = CacheTable{CentralArrangement => {x  - x , x  - x , x  - x }}
                                         1    2   1    3   2    3
                 Matrix => | 1  1  0  |
                           | -1 0  1  |
                           | 0  -1 -1 |

Indeed, OM.Presentations.CentralArrangement exists in the table. Moreover, we have a matrix representation of OM that was made behind the scenes when we created the ordered matroid from the hyperplane arrangement. The keys that can possibly appear in the Presentations cache are

Matrix, Graph, CentralArrangement, SimplicialComplex, CircuitIdeal.

Finally, the cache key in an ordered matroid is a place to store data computed about the ordered matroid for quick access later. In our little example we have

i31 : peek OM.cache

o31 = CacheTable{isRepresentableMatroid => true}

A word of warning: Recall that a matroid is representable if it has a presentation as the columns of a matrix over a field. The key isRepresentableMatroid only indicates that, in the process of working with the matroid, some matrix presentation over a field has been computed.

Let's now turn to the algebraic constructions for ordered matroids provided by the MatroidActivities package.

Algebraic Constructions with Ordered Matroids

As for any matroid object, we can compute the independence complex of an ordered matroid.

i32 : C = matroidIndependenceComplex OM

o32 = | x_0x_1 x_2x_1 x_2x_0 |

o32 : SimplicialComplex

This simplicial complex is different than the one computed in i8, but only in a slightly subtle way. The monomial orders on the underlying rings are affected by the order in which the variables are presented. For the example from i8 the variables are ordered with respect to the natural order.

i33 : gens ring matroidIndependenceComplex OM.matroid

o33 = {x , x , x }
        0   1   2

On the other hand, the order of the variables in the underlying ring of the complex C in i32 respects the linear order on the ground set of the ordered matroid OM.

i34 : gens ring C

o34 = {x , x , x }
        2   0   1

A second ring one can construct from an ordered matroid is the Orlik-Solomon algebra. We have already used this construction above in i17. Now let's take a look more closely. To create the Orlik-Solomon algebra of an ordered matroid use matroidOrlikSolomon.

i35 : A = matroidOrlikSolomon OM;

This algebra is a quotient of the exterior algebra over the vector space generated by the flats of the matroid. As such, it is a skew-commutative (rather than commutative) algebra. We can see this as well as other structural properties by looking at the options of A.

i36 : options A

o36 = OptionTable{Constants => false                     }
                  DegreeLift => null
                  DegreeMap => null
                  DegreeRank => 1
                  Degrees => {{1}, {1}, {1}}
                  Global => true
                  Heft => {1}
                  Inverses => false
                  Join => null
                  Local => false
                  MonomialOrder => {MonomialSize => 32  }
                                   {Weights => {0, 1, 2}}
                                   {Weights => {1, 1, 1}}
                                   {Lex => 3            }
                                   {Position => Up      }
                  SkewCommutative => {0, 1, 2}
                  Variables => {e , e , e }
                                 2   0   1
                  WeylAlgebra => {}

o36 : OptionTable

A second simplicial complex associated to any ordered matroid is the (no) broken circuit complex. It is a subcomplex of the independence complex and may be computed using the brokenCircuitComplex method.

i37 : NBC = brokenCircuitComplex OM

o37 = | x_2x_1 x_2x_0 |

o37 : SimplicialComplex

For our small example, the broken circuit complex has two of the three (facets corresponding to) bases of OM as facets. The third basis x0x1 is not a facet of the broken circuit complex because it is a broken circuit with respect to the ordering 2 < 0 < 1.

The faces of the broken circuit complex of a matroid are a basis for the Orlik-Solomon algebra. To confirm this let's compute a basis of A.

i38 : basis A

o38 = | 1 e_2 e_2e_0 e_2e_1 e_0 e_1 |

              1       6
o38 : Matrix A  <--- A

Note that the monomials in the matrix above correspond to the faces of NBC.

Combinatorial Constructions with Ordered Matroids

In this section we turn to the methods included in MatroidActivities that allow us to study internal and external activities in ordered matroids. We encourage the reader unfamiliar with these notions to consult Section 2 of Las Vergnas' paper.

By matroid duality internal and external activities are equivalent, so we will focus our attention here on internal activity. For the most part, every method available for computing internal activities has a counterpart for computing directly with external activities.

Given an ordered matroid M on the ground set E and a subset A of E, an element e is internally active with respect to A if e is in A and there is a cocircuit C* contained in E - A + e such that e is the least element of C*. If e is in A and is not internally active, then it is called internally passive.

Let's compute the internally active elements with respect to every subset of our running example. First let's view the ordered cocircuits.

i41 : OM.orderedCocircuits

o41 = {{2, 0}, {2, 1}, {0, 1}}

o41 : List

Now we make a hash table whose keys are the subsets of the ordered ground set and whose values are the internally active elements.

i42 : hashTable apply (subsets OM.orderedGround, s -> s => internallyActiveElements (OM,s))

o42 = HashTable{{} => {}        }
                {2} => {2}
                {0} => {0}
                {1} => {}
                {2, 0} => {2, 0}
                {2, 1} => {2}
                {0, 1} => {}
                {2, 0, 1} => {}

o42 : HashTable

It is crucial to realize that internal activities depend on the ground set. For example, if we change the ordering of OM to the natural ordering 0<1<2 we obtain the following.

i43 : OM' = (orderedMatroid (OM.matroid, {0,1,2}));

i44 : OM'.orderedCocircuits

o44 = {{0, 1}, {0, 2}, {1, 2}}

o44 : List

i45 : hashTable apply (subsets OM'.orderedGround, s -> s => internallyActiveElements (OM',s))

o45 = HashTable{{} => {}        }
                {0} => {0}
                {1} => {1}
                {2} => {}
                {0, 1} => {0, 1}
                {0, 2} => {0}
                {1, 2} => {}
                {0, 1, 2} => {}

o45 : HashTable

When restricted to the bases of an ordered matroid the definition of internal activity can be restated as follows. An element e in a basis B is internally active if there is no lexicographically smaller basis (with respect to the linear order on the ground set) that contains B - e. The internal order of an ordered matroid M is the poset P on the basis of M where two basis B,B' of M satisfy B ≤ B' if every internally passive element of B is internally passive in B'. The internal order of an ordered matroid can be computed using the method internalOrder which in turn uses methods from the Posets package written by Kristine Fisher, Andrew Hoefel, Manoj Kummini, Stephen Sturgeon, and Josephine Yu.

i46 : internalOrder OM

o46 = Relation Matrix: | 1 1 1 |
                       | 0 1 1 |
                       | 0 0 1 |

o46 : Poset

We have noted that internal activity depends on the linear ordering of the ground set of the matroid. We should suspect that the internal order does as well. Let's count the number of isomorphism classes of internal orders of our running example as the linear order of the ground set varies over all permutations.

i47 : # removeIsomorphicPosets apply (permutations 3, p -> internalOrder orderedMatroid (OM.matroid, p))

o47 = 1

The fact that there one isomorphism class for our toy example is a fluke arising from the fact that the underlying matroid has exactly one cycle and so its internal order is a chain (for any ordering of its ground set). A more interesting example is provided by the cycle matroid of the complete graph on four vertices.

i48 : M = matroid completeGraph 4;

i49 : PP = removeIsomorphicPosets apply (permutations 6, p -> internalOrder orderedMatroid (M, p));

i50 = #PP

o50 = 3

This shows that, in general, the internal order of an ordered matroid is not an invariant of the underlying (unordered) matroid. On the other hand, there are properties of the internal order that are invariant under changes in the ordering on the ground set. The first is that the internal order is always a graded poset. Let's check this for all of the internal orders arising from K4.

i51 : all (PP, P -> isGraded P)

o51 = true

The second important invariant property is that the internal order becomes a lattice once an artificial top element is added.

i52 : all (PP, P -> isLattice adjoinMax (P))

o52 = true

The third invariant property we will discuss is the rank generating function of the internal order. For any linear order of the ground set of a matroid, the rank generating function of the internal order is the h-polynomial of the matroid.

i53 : matroidHPolynomial M

        3     2
o53 = 6q  + 6q  + 3q + 1

i54 : apply (PP, P -> rankGeneratingFunction P)

              3     2
o54 = Tally{6q  + 6q  + 3q + 1 => 3}

We will investigate further this connection between the h-polynomial of a matroid and the rank generating function of the internal order in the final section below.

It is often useful to visualize a poset via its Hasse diagram. The Posets package has a method for visualizing an arbitrary poset in a LaTeX file. We have modified this method slightly to beautify the output for internal orders. The output of texInternalOrder can be cut and pasted directly into a LaTex file and the Hasse diagram will be rendered as long as \usepackage{Tikz} is included in the preamble.

i55 : texInternalOrder internalOrder orderedMatroid M

\tikzstyle{every node} = [draw = black, fill = white, rectangle, inner sep = 1pt]
\begin{tikzpicture}[scale = 1]
    \node (0) at (-0+0,0)    {\scriptsize_{{}^{}_{012}}_};
    \node (1) at (-1.5+0,1.33333)    {\scriptsize_{{4}^{}_{01}}_};
    \node (2) at (-1.5+1.5,1.33333)    {\scriptsize_{{5}^{}_{01}}_};
    \node (3) at (-1.5+3,1.33333)    {\scriptsize_{{3}^{}_{02}}_};
    \node (9) at (-3.75+0,2.66667)    {\scriptsize_{{4}^{2}_{1}}_};
    \node (4) at (-3.75+1.5,2.66667)    {\scriptsize_{{5}^{2}_{0}}_};
    \node (7) at (-3.75+3,2.66667)    {\scriptsize_{{45}^{}_{0}}_};
    \node (8) at (-3.75+4.5,2.66667)    {\scriptsize_{{3}^{1}_{2}}_};
    \node (5) at (-3.75+6,2.66667)    {\scriptsize_{{34}^{}_{0}}_};
    \node (6) at (-3.75+7.5,2.66667)    {\scriptsize_{{35}^{}_{0}}_};
    \node (12) at (-3.75+0,4)    {\scriptsize_{{45}^{1}_{}}_};
    \node (15) at (-3.75+1.5,4)    {\scriptsize_{{45}^{2}_{}}_};
    \node (13) at (-3.75+3,4)    {\scriptsize_{{34}^{2}_{}}_};
    \node (10) at (-3.75+4.5,4)    {\scriptsize_{{34}^{1}_{}}_};
    \node (14) at (-3.75+6,4)    {\scriptsize_{{35}^{2}_{}}_};
    \node (11) at (-3.75+7.5,4)    {\scriptsize_{{35}^{1}_{}}_};
  \foreach \to/\from in {0/1, 0/2, 0/3, 1/9, 1/5, 1/7, 2/4, 2/6, 2/7, 3/8, 3/5, 3/6, 4/14, 4/15, 5/13, 5/10, 6/14, 6/11, 7/12, 7/15, 8/10, 8/11, 9/13, 9/15}
  \draw [-] (\to)--(\from);
\end{tikzpicture}

In the rendered poset a bases B is given as a triple _B = S T A where A is the set of internally active elements of B and the sets S and T are as follows. Let B_0 be the lexicographically least basis of the ordered matroid. Then T (respectively, S) is the set of internally passive elements of B that are (not) in B_0. In the above example the lexicographically least basis is B_0 = {0,1,2}. So the basis {0,2,5} is has A = {0}, T = {2} and S= {5}. We will use such decompositions of bases in what follows to define internally perfect bases and matroids.

Note: A LaTeX file containing Hasse diagrams of a representative for each of the three isomorphism classes of internal orders of K4 can be found here.

Tests for Ordered Matroids

Let M be an ordered matroid and B = STA be a basis, where S,T, and A are as in the previous section. Then B is called an f-principal basis if there is an element f in E such that S = {f}.

There are some bases of every ordered matroid that can be written as the join (in the internal order) of f-principal bases in a unique way. Such bases are called (internally) perfect bases. For example, every f-principal basis is trivially perfect, as are those bases of the form B = STA where T is the empty set. A basis that can be written as the join of f-principal bases in more than one way is called an abundant basis, while a basis that cannot be written as the join of f-principal bases is deficient. The method basisType allows one to test whether a basis is perfect, abundant, or deficient.

Let's check how many bases of each type the ordered matroid K4 with the natural ordering has.

i56 : OM = orderedMatroid M;

i57 : tally apply (OM.orderedBases, B -> basisType (OM,B))

o57 = Tally{abundant => 1 }
            deficient => 1
            perfect => 14

o57 : Tally

So the complete graph on four vertices with the natural ordering on the edges furnishes an example in which all three basis types appear. A LaTeX file containing Hasse diagrams of a representative for each isomorphism class of internal orders of K4 can be found here. In the next section we discuss ordered matroids which have only internally perfect bases. Such ordered matroids are called internally perfect matroids and were introduced in the article Internally Perfect Matroids. One can test if an ordered matroid is internally perfect using the method isInternallyPerfect.

i58 : isInternallyPerfect OM

o58 = false

i59 : isInternallyPerfect orderedMatroid completeGraph 3

o59 = true

Internally Perfect Matroids and Stanley's Conjecture

In the previous section we saw how to compute basis types of an ordered matroid and that the bases of some matroids are all internally perfect. In this section we briefly discuss Stanley's Conjecture on the h-vectors of matroids and its connection with internally perfect matroids. Finally we use the methods in MatroidActivities to exhibit an example of an internally perfect matroid that is not in any of the classes of matroids for which Stanley's Conjecture was previously known to hold.

Stanley's Conjecture

In a 1977 paper, Richard Stanley showed that the h-polynomial of a matroid is an O-sequence and conjectured that it is a pure O-sequence. In other words the conjecture states that for any matroid M there exists a collection of monomials M such that

  1. if m in M and m' divides m, then m' \in M,
  2. the maximal elements of M (with respect to divisibility) all have the same total degree, and
  3. the number of elements of M with total degree i equals the coefficient on qi in the h-polynomial of the matroid M.

Such a collection of monomials is called a pure multicomplex.

Stanley's Conjecture has spurred a great deal of research concerning h-polynomials of matroids and O-sequences. It is known to hold for a rank r matroid M on n elements with c coloops if any of the following conditions hold:

  • M is paving;
  • hs (M) ≤ 5, where s = r - c is the degree of the h-polynomial;
  • M* is graphic;
  • M* is transversal;
  • M* has no more than n - r + 2 parallel classes;
  • n ≤ 9 or n-r ≤ 2;
  • r ≤ 4; or
  • M is internally perfect for some ordering of the ground set.

Let us call a matroid interesting if it is internally perfect but is not in any of the other classes listed above. The goal of the remainder of this section is to work out Example 6 from Internally Perfect Matroids which shows that interesting matroids do exist.

An Interesting Internally Perfect Matroid

Let N be the ordered vector matroid given by the columns of the following matrix:

i60 : mat = sub(matrix {{2, 1, 3, -1, -1, 0, -1, -1, 0, 3}, {1, 1, 1, 1, 1, 1, 0, 0, 1, 1}, {0, 0, 0, 0, 0, -1, 1, 1, -1, 0}}, QQ)

o60 = | 2 1 3 -1 -1 0  -1 -1 0  3 |
      | 1 1 1 1  1  1  0  0  1  1 |
      | 0 0 0 0  0  -1 1  1  -1 0 |

               3        10
o60 : Matrix QQ  <--- QQ

i61 : N = orderedMatroid mat;

We are interested in the dual to the matroid N, but we point out that N is an internally perfect matroid with respect to, for example, the order

{0, 3, 5, 1, 2, 4, 6, 7, 8, 9 }.

We will show that the dual matroid M = N* is interesting, that is, that it is internally perfect (and hence satisfies Stanley's Conjecture) and that it is not in any of the classes of matroids for which Stanley's Conjecture was previously known to hold. First we create M and check that it is internally perfect with respect to the natural order on the ground set.

i62 : M = orderedMatroid dualMatroid N.matroid;

i63 : isInternallyPerfect M

o63 = true

By the general theory for internally perfect matroids, it follows that the matroid M satisfies Stanley's Conjecture since its internal order is isomorphic to a pure multicomplex (ordered by divisibility). We will now produce such a multicomplex. First consider the six maximal elements in the Hasse diagram of the internal order of M.

internal order

Since each of the maximal bases is internally perfect, there is a unique way to write each as a join of f-principal bases. We have

  • B1 = 7891346 = 7134625 v 8012346 v 9013456

  • B2 = 7891345 = 7012345 v 8134526 v 9013456

  • B3 = 7892346 = 7346025 v 8012346 v 9203456

  • B4 = 7892345 = 7012345 v 8345026 v 9203456

  • B5 = 7891246 = 7460125 v 8012346 v 9123456

  • B6 = 7891245 = 7012345 v 8450126 v 9123456

Notice that each internally passive element of a maximal basis occurs exactly once in the decomposition as joins of f-principal bases.

We now produce a pure multicomplex whose O-sequence is precisely the h-vector of M. First we define a polynomial ring with variables indexed by those elements of the ground set of M that are not in the lexicographically smallest basis.

i64 : R = ZZ[x_7,x_8,x_9];

For a basis B = STA and an f in S let Bf be the f-principal basis occurring in the decomposition of B as a join of f-principal bases. For an f-principal basis of M define the map µ into the polynomial ring R via

µ(Bf) = x|IP(Bf)|.

Since every basis of M has a unique decomposition into a join of f-principal bases this map extends uniquely to a map on the bases of M. In our example the maximal bases are mapped to monomials as follows.

  • B1 goes to x75 x8 x9,

  • B2 goes to x7 x85 x9,

  • B3 goes to x74 x8 x92,

  • B4 goes to x7 x84 x92,

  • B5 goes to x73 x8 x93,

  • B6 goes to x7 x83 x93.

We store these monomials as a list.

i65: maxMonomials = {x_7^5*x_8^1*x_9^1, x_7^1*x_8^5*x_9^1, x_7^4*x_8^1*x_9^2, x_7^1*x_8^4*x_9^2, x_7^3*x_8^1*x_9^3, x_7^1*x_8^3*x_9^3};

To create a multicomplex where these monomials are the maximal elements, we use the divisorPoset method from the Posets package. This creates a principal multicomplex from each of our maximal monomials. We then take the union of all of these to obtain our multicomplex.

i66 : multicomplex = fold (union, apply (maxMonomials, m -> divisorPoset m))

Using this variation of this clever TikZ gadget by Jang Soo Kim we have a way to visualize the resulting multicomplex.

This multicomplex is pure since its maximal elements all have total degree 7. Let's check that it has the correct O-sequence using the rankGeneratingFunction method from the Posets package.

i67 : rankGeneratingFunction multicomplex

         7      6      5      4      3     2
o67 = 6q  + 14q  + 15q  + 13q  + 10q  + 6q  + 3q + 1

o67 : ZZ[q]

i68 : matroidHPolynomial M

         7      6      5      4      3     2
o68 = 6q  + 14q  + 15q  + 13q  + 10q  + 6q  + 3q + 1

o68 : ZZ[q]

As the O-sequence of the pure multicomplex and the h-polynomial of the matroid coincide, we have verified that the matroid M satisfies Stanley's Conjecture.

We now turn to showing that the matroid M is not in any of the classes of matroids for which Stanley's Conjecture was previously known to hold.

To see that M is not paving we use the method isPavingMatroid.

i69 : isPavingMatroid M

o69 = false

Indeed M is a rank seven matroid with two circuits of size four.

i70 : tally apply (M.orderedCircuits, C -> #C)

o70 = Tally{4 => 2}
            6 => 2
            7 => 4

We can check that the last nonzero entry of the h-vector of M is larger than five by inspecting the matroidHPolynomial of M.

i71 : matroidHPolynomial M

        7      6      5      4      3     2
o71 = 6q  + 14q  + 15q  + 13q  + 10q  + 6q  + 3q + 1

o71 : ZZ[q]

Next we want to see that the dual of M is not a graphic matroid. One can do this either by inspecting the matrix mat above and finding a U(2,4) minor or by using the test isCographicMatroid.

i72 : isCographicMatroid M
Isomorphism: matroids are equal
Contract set {2, 3, 4, 6, 8}, delete set {4}

o72 = false

It is well-known that a matroid is not transversal if it has as a minor the graphic matroid G on [3] with two edges between every pair of vertices. It's easy to see that the minor N - \{0,1,9} is isomorphic to G as removing the corresponding columns f_ris in _matand leaves us with the signed vertex-edge incidence matrix of G.

i73 : mat_{3,4,5,6,7,8}

o73 = | -1 -1 0  -1 -1 0  |
      | 1  1  1  0  0  1  |
      | 0  0  -1 1  1  -1 |

So N is not transversal, as claimed.

Next we need to see that N has at least 10 - 7 + 1 = 4 parallel classes. This can be done either by inspection or by using the parallelClasses method.

i74 : # parallelClasses N

o74 = 6

Finally, since M is a rank 7 matroid on 10 elements, it satisfies the remaining properties in the list. So we have shown that the class of internally perfect matroids constitutes a proper extension of the matroids for which Stanley's Conjecture is known to hold.