HaskellForMaths-0.4.9: Combinatorics, group theory, commutative algebra, non-commutative algebra

Safe HaskellNone
LanguageHaskell98

Math.Combinatorics.Matroid

Description

A module providing functions to construct and investigate (small, finite) matroids.

Synopsis

Documentation

exists :: Foldable t => t a -> Bool Source #

unique :: [a] -> a Source #

shortlex :: (Foldable t, Ord (t a)) => t a -> t a -> Ordering Source #

isShortlex :: (Foldable t, Ord (t a)) => [t a] -> Bool Source #

toShortlex :: (Ord (t a), Foldable t) => [t a] -> [t a] Source #

isClutter :: Ord a => [[a]] -> Bool Source #

deletions :: [a] -> [[a]] Source #

data TrieSet a Source #

The data structure that we use to store the bases of the matroid

Constructors

TS [(a, TrieSet a)] 
Instances
Functor TrieSet Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

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

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

Eq a => Eq (TrieSet a) Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

(==) :: TrieSet a -> TrieSet a -> Bool #

(/=) :: TrieSet a -> TrieSet a -> Bool #

Ord a => Ord (TrieSet a) Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

compare :: TrieSet a -> TrieSet a -> Ordering #

(<) :: TrieSet a -> TrieSet a -> Bool #

(<=) :: TrieSet a -> TrieSet a -> Bool #

(>) :: TrieSet a -> TrieSet a -> Bool #

(>=) :: TrieSet a -> TrieSet a -> Bool #

max :: TrieSet a -> TrieSet a -> TrieSet a #

min :: TrieSet a -> TrieSet a -> TrieSet a #

Show a => Show (TrieSet a) Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

showsPrec :: Int -> TrieSet a -> ShowS #

show :: TrieSet a -> String #

showList :: [TrieSet a] -> ShowS #

tsshow :: Show a => TrieSet a -> [Char] Source #

tsinsert :: Ord a => [a] -> TrieSet a -> TrieSet a Source #

tsmember :: Eq a => [a] -> TrieSet a -> Bool Source #

tssubmember :: Ord a => [a] -> TrieSet a -> Bool Source #

tstolist :: TrieSet a -> [[a]] Source #

tsfromlist :: (Foldable t, Ord a) => t [a] -> TrieSet a Source #

data Matroid a Source #

A datatype to represent a matroid. M es bs is the matroid whose elements are es, and whose bases are bs. The normal form is for the es to be in order, for each of the bs individually to be in order. (So the TrieSet should have the property that any path from the root to a leaf is strictly increasing).

Constructors

M [a] (TrieSet a) 
Instances
Functor Matroid Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

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

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

Eq a => Eq (Matroid a) Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

(==) :: Matroid a -> Matroid a -> Bool #

(/=) :: Matroid a -> Matroid a -> Bool #

Show a => Show (Matroid a) Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

showsPrec :: Int -> Matroid a -> ShowS #

show :: Matroid a -> String #

showList :: [Matroid a] -> ShowS #

elements :: Matroid t -> [t] Source #

Return the elements over which the matroid is defined.

indeps :: Ord a => Matroid a -> [[a]] Source #

Return all the independent sets of a matroid, in shortlex order.

isIndependent :: Ord a => Matroid a -> [a] -> Bool Source #

isDependent :: Ord a => Matroid a -> [a] -> Bool Source #

isMatroidIndeps :: Ord a => [[a]] -> Bool Source #

Are these the independent sets of a matroid? (The sets must individually be ordered.)

fromIndeps :: Ord a => [a] -> [[a]] -> Matroid a Source #

Construct a matroid from its elements and its independent sets.

fromIndeps1 :: Ord a => [a] -> [[a]] -> Matroid a Source #

vectorMatroid :: (Eq k, Fractional k) => [[k]] -> Matroid Int Source #

Given a matrix, represented as a list of rows, number the columns [1..], and construct the matroid whose independent sets correspond to those sets of columns which are linearly independent (or in case there are repetitions, those multisets of columns which are sets, and which are linearly independent).

vectorMatroid' :: (Eq k, Fractional k) => [[k]] -> Matroid Int Source #

Given a list of vectors (or rows of a matrix), number the vectors (rows) [1..], and construct the matroid whose independent sets correspond to those sets of vectors (rows) which are linearly independent (or in case there are repetitions, those multisets which are sets, and which are linearly independent).

cycleMatroid :: Ord a => [[a]] -> Matroid Int Source #

Given the edges of an undirected graph, number the edges [1..], and construct the matroid whose independent sets correspond to those sets of edges which contain no cycle. The bases therefore correspond to maximal forests within the graph. The edge set is allowed to contain loops or parallel edges.

cycleMatroid' :: Ord a => [[a]] -> Matroid [a] Source #

to1n :: Ord a => Matroid a -> Matroid Int Source #

Given a matroid over an arbitrary type, relabel to obtain a matroid over the integers.

matroidIsos :: (Ord b2, Ord a) => Matroid a -> Matroid b2 -> [[(a, b2)]] Source #

isMatroidIso :: (Ord a, Ord b) => Matroid a -> Matroid b -> Bool Source #

Are the two matroids isomorphic?

matroidAuts :: Ord a => Matroid a -> [Permutation a] Source #

Return the automorphisms of the matroid.

isCircuit :: Ord a => Matroid a -> [a] -> Bool Source #

A circuit in a matroid is a minimal dependent set.

circuits :: Ord a => Matroid a -> [[a]] Source #

Return all circuits for the given matroid, in shortlex order.

isMatroidCircuits :: Ord a => [[a]] -> Bool Source #

Are the given sets the circuits of some matroid?

fromCircuits :: Ord a => [a] -> [[a]] -> Matroid a Source #

Reconstruct a matroid from its elements and circuits.

isLoop :: Ord a => Matroid a -> a -> Bool Source #

An element e in a matroid M is a loop if {e} is a circuit of M.

isParallel :: Ord a => Matroid a -> a -> a -> Bool Source #

Elements f and g in a matroid M are parallel if {f,g} is a circuit of M.

isSimple :: Ord a => Matroid a -> Bool Source #

A matroid is simple if it has no loops or parallel elements

isBase :: Ord a => Matroid a -> [a] -> Bool Source #

A base or basis in a matroid is a maximal independent set.

bases :: Ord a => Matroid a -> [[a]] Source #

Return all bases for the given matroid

isMatroidBases :: Ord a => [[a]] -> Bool Source #

Are the given sets the bases of some matroid?

fromBases :: Ord a => [a] -> [[a]] -> Matroid a Source #

Reconstruct a matroid from its elements and bases.

fundamentalCircuit :: Ord a => Matroid a -> [a] -> a -> [a] Source #

Given a matroid m, a basis b, and an element e, fundamentalCircuit m b e returns the unique circuit contained in b union {e}, which is called the fundamental circuit of e with respect to b.

u :: Int -> Int -> Matroid Int Source #

The uniform matroid U m n is the matroid whose independent sets are all subsets of [1..n] with m or fewer elements.

restriction1 :: Ord a => Matroid a -> [a] -> Matroid a Source #

restriction :: Ord a => Matroid a -> [a] -> Matroid a Source #

The restriction of a matroid to a subset of its elements

rankfun :: Ord a => Matroid a -> [a] -> Int Source #

Given a matroid m, rankfun m is the rank function on subsets of its element set

rank :: Ord a => Matroid a -> Int Source #

The rank of a matroid is the cardinality of a basis

fromRankfun :: Ord a => [a] -> ([a] -> Int) -> Matroid a Source #

Reconstruct a matroid from its elements and rank function

closure :: Ord a => Matroid a -> [a] -> [a] Source #

Given a matroid m, closure m is the closure operator on subsets of its element set

fromClosure :: Ord a => [a] -> ([a] -> [a]) -> Matroid a Source #

Reconstruct a matroid from its elements and closure operator

isFlat :: Ord a => Matroid a -> [a] -> Bool Source #

A flat in a matroid is a closed set, that is a set which is equal to its own closure

flats1 :: Ord a => Matroid a -> [[a]] Source #

coveringFlats :: Ord a => Matroid a -> [a] -> [[a]] Source #

minimalFlat :: Ord a => Matroid a -> [a] Source #

flats :: Ord a => Matroid a -> [[a]] Source #

The flats of a matroid are its closed sets. They form a lattice under inclusion.

fromFlats :: Ord a => [[a]] -> Matroid a Source #

Reconstruct a matroid from its flats. (The flats must be given in shortlex order.)

fromFlats' :: Ord a => [[a]] -> Matroid a Source #

isSpanning :: Ord a => Matroid a -> [a] -> Bool Source #

A subset of the elements in a matroid is spanning if its closure is all the elements

isHyperplane :: Ord a => Matroid a -> [a] -> Bool Source #

A hyperplane is a flat whose rank is one less than that of the matroid

hyperplanes1 :: Ord a => Matroid a -> [[a]] Source #

hyperplanes :: Ord a => Matroid a -> [[a]] Source #

isMatroidHyperplanes :: Ord a => [a] -> [[a]] -> Bool Source #

fromHyperplanes1 :: Ord a => [a] -> [[a]] -> Matroid a Source #

fromHyperplanes :: Ord a => [a] -> [[a]] -> Matroid a Source #

Reconstruct a matroid from its elements and hyperplanes

affineMatroid :: (Eq k, Fractional k) => [[k]] -> Matroid Int Source #

Given a list of points in k^n, number the points [1..], and construct the matroid whose independent sets correspond to those sets of points which are affinely independent.

A multiset of points in k^n is said to be affinely dependent if it contains two identical points, or three collinear points, or four coplanar points, or ... - and affinely independent otherwise.

fromGeoRep :: Ord a => [[a]] -> [[a]] -> [[a]] -> [[a]] -> Matroid a Source #

fromGeoRep returns a matroid from a geometric representation consisting of dependent flats of various ranks. Given lists of dependent rank 0 flats (loops), rank 1 flats (points), rank 2 flats (lines) and rank 3 flats (planes), fromGeoRep loops points lines planes returns the matroid having these as dependent flats. Note that if all the elements lie in the same plane, then this should still be listed as an argument.

minimal :: Ord a => [[a]] -> [[a]] Source #

simpleFromGeoRep :: Ord a => [[a]] -> [[a]] -> Matroid a Source #

A simple matroid has no loops or parallel elements, hence its geometric representation has no loops or dependent points. simpleFromGeoRep lines planes returns the simple matroid having these dependent flats.

isSimpleGeoRep :: Ord a => [[a]] -> [[a]] -> Bool Source #

circuitHyperplanes :: Ord a => Matroid a -> [[a]] Source #

List the circuit-hyperplanes of a matroid.

relaxation :: Ord a => Matroid a -> [a] -> Matroid a Source #

Given a matroid m, and a set of elements b which is both a circuit and a hyperplane in m, then relaxation m b is the matroid which is obtained by adding b as a new basis. This corresponds to removing b from the geometric representation of m.

ex161 :: Num a => [[a]] Source #

transversalGraph :: (Num b1, Enum b1) => [[a1]] -> [(Either a1 b2, Either a2 b1)] Source #

partialMatchings :: Ord a => [(a, a)] -> [[(a, a)]] Source #

transversalMatroid :: Ord a => [a] -> [[a]] -> Matroid a Source #

Given a set of elements es, and a sequence as = [a1,...,am] of subsets of es, return the matroid whose independent sets are the partial transversals of the as.

dual :: Ord a => Matroid a -> Matroid a Source #

The dual matroid

isCoindependent :: Ord a => Matroid a -> [a] -> Bool Source #

isCobase :: Ord a => Matroid a -> [a] -> Bool Source #

isCocircuit :: Ord a => Matroid a -> [a] -> Bool Source #

cocircuits :: Ord a => Matroid a -> [[a]] Source #

isColoop :: Ord a => Matroid a -> a -> Bool Source #

isCoparallel :: Ord a => Matroid a -> a -> a -> Bool Source #

deletion :: Ord a => Matroid a -> [a] -> Matroid a Source #

(\\\) :: Ord a => Matroid a -> [a] -> Matroid a Source #

contraction :: Ord a => Matroid a -> [a] -> Matroid a Source #

(///) :: Ord a => Matroid a -> [a] -> Matroid a Source #

isConnected :: Ord a => Matroid a -> Bool Source #

A matroid is (2-)connected if, for every pair of distinct elements, there is a circuit containing both

component :: Ord a => Matroid a -> a -> [a] Source #

dsum :: (Ord a, Ord b) => Matroid a -> Matroid b -> Matroid (Either a b) Source #

The direct sum of two matroids

matroidPG :: (Eq a, Fractional a) => Int -> [a] -> Matroid Int Source #

matroidPG n fq returns the projective geometry PG(n,Fq), where fq is a list of the elements of Fq

matroidAG :: (Eq a, Fractional a) => Int -> [a] -> Matroid Int Source #

matroidAG n fq returns the affine geometry AG(n,Fq), where fq is a list of the elements of Fq

fundamentalCircuitIncidenceMatrix :: (Ord a, Num k) => Matroid a -> [a] -> [[k]] Source #

Given a matroid m, the fundamental-circuit incidence matrix relative to a base b has rows indexed by the elements of b, and columns indexed by the elements not in b. The bi, ej entry is 1 if bi is in the fundamental circuit of ej relative to b, and 0 otherwise.

fundamentalCircuitIncidenceMatrix' :: (Ord a1, Num a2) => Matroid a1 -> [a1] -> [[a2]] Source #

fcim :: (Ord a, Num k) => Matroid a -> [a] -> [[k]] Source #

fcim' :: (Ord a1, Num a2) => Matroid a1 -> [a1] -> [[a2]] Source #

markNonInitialRCs :: (Eq a, Num a) => [[a]] -> [[ZeroOneStar]] Source #

substStars :: Num a => [[ZeroOneStar]] -> [a] -> [[[a]]] Source #

starSubstitutionsV :: Num a => [a] -> [ZeroOneStar] -> [[a]] Source #

representations1 :: (Fractional a1, Ord a1, Ord a2) => [a1] -> Matroid a2 -> [[[a1]]] Source #

fcig :: Ord a => Matroid a -> [a] -> [[a]] Source #

markedfcim :: Ord a => Matroid a -> [a] -> [[ZeroOneStar]] Source #

representations2 :: (Fractional a1, Ord a1, Ord a2) => [a1] -> Matroid a2 -> [[[a1]]] Source #

representations :: (Eq fq, Fractional fq, Ord a) => [fq] -> Matroid a -> [[[fq]]] Source #

Find representations of the matroid m over fq. Specifically, this function will find one representative of each projective equivalence class of representation.

isRepresentable :: (Eq fq, Fractional fq, Ord a) => [fq] -> Matroid a -> Bool Source #

Is the matroid representable over Fq? For example, to find out whether a matroid m is binary, evaluate isRepresentable f2 m.

isBinary :: Ord a => Matroid a -> Bool Source #

A binary matroid is a matroid which is representable over F2

isTernary :: Ord a => Matroid a -> Bool Source #

A ternary matroid is a matroid which is representable over F3

data LMR a b Source #

Constructors

L a 
Mid 
R b 
Instances
(Eq a, Eq b) => Eq (LMR a b) Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

(==) :: LMR a b -> LMR a b -> Bool #

(/=) :: LMR a b -> LMR a b -> Bool #

(Ord a, Ord b) => Ord (LMR a b) Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

compare :: LMR a b -> LMR a b -> Ordering #

(<) :: LMR a b -> LMR a b -> Bool #

(<=) :: LMR a b -> LMR a b -> Bool #

(>) :: LMR a b -> LMR a b -> Bool #

(>=) :: LMR a b -> LMR a b -> Bool #

max :: LMR a b -> LMR a b -> LMR a b #

min :: LMR a b -> LMR a b -> LMR a b #

(Show a, Show b) => Show (LMR a b) Source # 
Instance details

Defined in Math.Combinatorics.Matroid

Methods

showsPrec :: Int -> LMR a b -> ShowS #

show :: LMR a b -> String #

showList :: [LMR a b] -> ShowS #

seriesConnection :: (Ord a1, Ord a2) => (Matroid a1, a1) -> (Matroid a2, a2) -> Matroid (LMR a1 a2) Source #

parallelConnection :: (Ord a1, Ord a2) => (Matroid a1, a1) -> (Matroid a2, a2) -> Matroid (LMR a1 a2) Source #

twoSum :: (Ord a1, Ord a2) => (Matroid a1, a1) -> (Matroid a2, a2) -> Matroid (LMR a1 a2) Source #

f7 :: Matroid Int Source #

The Fano plane F7 = PG(2,F2)

f7m :: Matroid Int Source #

F7-, the relaxation of the Fano plane by removal of a line

pappus :: Matroid Int Source #

The Pappus configuration from projective geometry

nonPappus :: Matroid Int Source #

Relaxation of the Pappus configuration by removal of a line

desargues :: Matroid Int Source #

The Desargues configuration

v8 :: Matroid Int Source #

The Vamos matroid V8. It is not representable over any field.

p8 :: Matroid Int Source #

P8 is a minor-minimal matroid that is not representable over F4, F8, F16, ... . It is Fq-representable if and only if q is not a power of 2.

p8' :: (Ord a, Num a) => Matroid a Source #

p8m :: Matroid Int Source #

P8- is a relaxation of P8. It is Fq-representable if and only if q >= 4.

p8mm :: Matroid Int Source #

P8-- is a relaxation of P8-. It is a minor-minimal matroid that is not representable over F4. It is Fq-representable if and only if q >= 5.

wheelGraph :: (Num a, Enum a) => a -> Graph a Source #

w4 :: (Ord a, Num a) => Matroid a Source #

rankPoly :: Ord a => Matroid a -> GlexPoly Integer String Source #

Given a matroid m over elements es, the rank polynomial is a polynomial r(x,y), which is essentially a generating function for the subsets of es, enumerated by size and rank. It is efficiently calculated using deletion and contraction.

It has the property that r(0,0) is the number of bases in m, r(1,0) is the number of independent sets, r(0,1) is the number of spanning sets. It can also be used to derive the chromatic polynomial of a graph, the weight enumerator of a linear code, and more.

whitney2nd :: Ord a => Matroid a -> [Int] Source #

whitney1st :: Ord a => Matroid a -> [Int] Source #