Safe Haskell | Safe-Infered |
---|
A module providing functions to construct and investigate (small, finite) matroids.
- implies :: Bool -> Bool -> Bool
- exists :: [a] -> Bool
- unique :: [t] -> t
- shortlex :: Ord a => [a] -> [a] -> Ordering
- isShortlex :: Ord a => [[a]] -> Bool
- toShortlex :: Ord a => [[a]] -> [[a]]
- isClutter :: Ord a => [[a]] -> Bool
- deletions :: [a] -> [[a]]
- closedUnderSubsets :: Ord a => [[a]] -> Bool
- data TrieSet a = TS [(a, TrieSet a)]
- tsshow :: Show a => TrieSet a -> [Char]
- tsempty :: TrieSet a
- tsinsert :: Ord a => [a] -> TrieSet a -> TrieSet a
- tsmember :: Eq a => [a] -> TrieSet a -> Bool
- tssubmember :: Ord a => [a] -> TrieSet a -> Bool
- tstolist :: TrieSet a -> [[a]]
- tsfromlist :: Ord a => [[a]] -> TrieSet a
- data Matroid a = M [a] (TrieSet a)
- elements :: Matroid t -> [t]
- indeps :: Ord a => Matroid a -> [[a]]
- isIndependent :: Ord a => Matroid a -> [a] -> Bool
- isDependent :: Ord a => Matroid a -> [a] -> Bool
- isMatroidIndeps :: Ord a => [[a]] -> Bool
- fromIndeps :: Ord a => [a] -> [[a]] -> Matroid a
- fromIndeps1 :: Ord a => [a] -> [[a]] -> Matroid a
- vectorMatroid :: (Eq k, Fractional k) => [[k]] -> Matroid Int
- vectorMatroid' :: (Eq k, Fractional k) => [[k]] -> Matroid Int
- cycleMatroid :: Ord a => [[a]] -> Matroid Int
- cycleMatroid' :: Ord a => [[a]] -> Matroid [a]
- to1n :: Ord a => Matroid a -> Matroid Int
- incidenceGraphB :: Ord a => Matroid a -> Graph (Either a [a])
- incidenceGraphC :: Ord a => Matroid a -> Graph (Either a [a])
- incidenceGraphH :: Ord a => Matroid a -> Graph (Either a [a])
- matroidIsos :: (Ord t3, Ord t2) => Matroid t2 -> Matroid t3 -> [[(t2, t3)]]
- isMatroidIso :: (Ord a, Ord b) => Matroid a -> Matroid b -> Bool
- matroidAuts :: Ord a => Matroid a -> [Permutation a]
- isCircuit :: Ord a => Matroid a -> [a] -> Bool
- circuits :: Ord a => Matroid a -> [[a]]
- isMatroidCircuits :: Ord a => [[a]] -> Bool
- fromCircuits :: Ord a => [a] -> [[a]] -> Matroid a
- isLoop :: Ord a => Matroid a -> a -> Bool
- isParallel :: Ord a => Matroid a -> a -> a -> Bool
- isSimple :: Ord a => Matroid a -> Bool
- isBase :: Ord a => Matroid a -> [a] -> Bool
- bases :: Ord a => Matroid a -> [[a]]
- isMatroidBases :: Ord a => [[a]] -> Bool
- fromBases :: Ord a => [a] -> [[a]] -> Matroid a
- fundamentalCircuit :: Ord a => Matroid a -> [a] -> a -> [a]
- uniformMatroid :: Int -> Int -> Matroid Int
- u :: Int -> Int -> Matroid Int
- restriction1 :: Ord a => Matroid a -> [a] -> Matroid a
- restriction :: Ord a => Matroid a -> [a] -> Matroid a
- rankfun :: Ord a => Matroid a -> [a] -> Int
- rank :: Ord a => Matroid a -> Int
- fromRankfun :: Ord a => [a] -> ([a] -> Int) -> Matroid a
- closure :: Ord a => Matroid a -> [a] -> [a]
- fromClosure :: Ord a => [a] -> ([a] -> [a]) -> Matroid a
- isFlat :: Ord a => Matroid a -> [a] -> Bool
- flats1 :: Ord a => Matroid a -> [[a]]
- coveringFlats :: Ord t => Matroid t -> [t] -> [[t]]
- minimalFlat :: Ord a => Matroid a -> [a]
- flats :: Ord a => Matroid a -> [[a]]
- fromFlats :: Ord a => [[a]] -> Matroid a
- fromFlats' :: Ord a => [[a]] -> Matroid a
- isSpanning :: Ord a => Matroid a -> [a] -> Bool
- isHyperplane :: Ord a => Matroid a -> [a] -> Bool
- hyperplanes1 :: Ord a => Matroid a -> [[a]]
- hyperplanes :: Ord a => Matroid a -> [[a]]
- isMatroidHyperplanes :: Ord a => [a] -> [[a]] -> Bool
- fromHyperplanes1 :: Ord a => [a] -> [[a]] -> Matroid a
- fromHyperplanes :: Ord a => [a] -> [[a]] -> Matroid a
- affineMatroid :: (Eq k, Fractional k) => [[k]] -> Matroid Int
- fromGeoRep :: Ord a => [[a]] -> [[a]] -> [[a]] -> [[a]] -> Matroid a
- minimal :: Ord a => [[a]] -> [[a]]
- simpleFromGeoRep :: Ord a => [[a]] -> [[a]] -> Matroid a
- isSimpleGeoRep :: Ord a => [[a]] -> [[a]] -> Bool
- isCircuitHyperplane :: Ord a => Matroid a -> [a] -> Bool
- circuitHyperplanes :: Ord a => Matroid a -> [[a]]
- relaxation :: Ord a => Matroid a -> [a] -> Matroid a
- ex161 :: Num t => [[t]]
- transversalGraph :: (Enum b1, Num b1) => [[a]] -> [(Either a b, Either a1 b1)]
- partialMatchings :: Ord a => [(a, a)] -> [[(a, a)]]
- transversalMatroid :: Ord a => [a] -> [[a]] -> Matroid a
- dual :: Ord a => Matroid a -> Matroid a
- isCoindependent :: Ord a => Matroid a -> [a] -> Bool
- isCobase :: Ord a => Matroid a -> [a] -> Bool
- isCocircuit :: Ord a => Matroid a -> [a] -> Bool
- cocircuits :: Ord a => Matroid a -> [[a]]
- isColoop :: Ord a => Matroid a -> a -> Bool
- isCoparallel :: Ord a => Matroid a -> a -> a -> Bool
- deletion :: Ord a => Matroid a -> [a] -> Matroid a
- (\\\) :: Ord a => Matroid a -> [a] -> Matroid a
- contraction :: Ord a => Matroid a -> [a] -> Matroid a
- (///) :: Ord a => Matroid a -> [a] -> Matroid a
- isConnected :: Ord a => Matroid a -> Bool
- component :: Ord a => Matroid a -> a -> [a]
- dsum :: (Ord a, Ord b) => Matroid a -> Matroid b -> Matroid (Either a b)
- matroidPG :: (Eq a, Fractional a) => Int -> [a] -> Matroid Int
- matroidAG :: (Eq a, Fractional a) => Int -> [a] -> Matroid Int
- fundamentalCircuitIncidenceMatrix :: (Ord a, Num k) => Matroid a -> [a] -> [[k]]
- fundamentalCircuitIncidenceMatrix' :: (Num t, Ord a) => Matroid a -> [a] -> [[t]]
- fcim :: (Num k, Ord a) => Matroid a -> [a] -> [[k]]
- fcim' :: (Num t, Ord a) => Matroid a -> [a] -> [[t]]
- markNonInitialRCs :: (Eq a, Num a) => [[a]] -> [[ZeroOneStar]]
- substStars :: Num a => [[ZeroOneStar]] -> [a] -> [[[a]]]
- starSubstitutionsV :: Num a => [a] -> [ZeroOneStar] -> [[a]]
- representations1 :: (Fractional a1, Ord a1, Ord a) => [a1] -> Matroid a -> [[[a1]]]
- fcig :: Ord t => Matroid t -> [t] -> [[t]]
- markedfcim :: Ord a => Matroid a -> [a] -> [[ZeroOneStar]]
- representations2 :: (Fractional a1, Ord a1, Ord a) => [a1] -> Matroid a -> [[[a1]]]
- representations :: (Eq fq, Fractional fq, Ord a) => [fq] -> Matroid a -> [[[fq]]]
- isRepresentable :: (Eq fq, Fractional fq, Ord a) => [fq] -> Matroid a -> Bool
- isBinary :: Ord a => Matroid a -> Bool
- isTernary :: Ord a => Matroid a -> Bool
- data LMR a b
- seriesConnection :: (Ord a1, Ord a) => (Matroid a, a) -> (Matroid a1, a1) -> Matroid (LMR a a1)
- parallelConnection :: (Ord a1, Ord a) => (Matroid a, a) -> (Matroid a1, a1) -> Matroid (LMR a a1)
- twoSum :: (Ord a1, Ord a) => (Matroid a, a) -> (Matroid a1, a1) -> Matroid (LMR a a1)
- matroidUnion :: Ord a => Matroid a -> Matroid a -> Matroid a
- f7 :: Matroid Int
- f7m :: Matroid Int
- pappus :: Matroid Int
- nonPappus :: Matroid Int
- desargues :: Matroid Int
- vamosMatroid1 :: (Enum a, Num a, Ord a) => Matroid a
- vamosMatroid :: (Num a, Ord a) => Matroid a
- v8 :: Matroid Int
- p8 :: Matroid Int
- p8' :: (Num a, Ord a) => Matroid a
- p8m :: Matroid Int
- p8mm :: Matroid Int
- wheelGraph :: (Enum a, Num a) => a -> Graph a
- mw4 :: Matroid Int
- w4' :: Matroid Int
- w4 :: (Num a, Ord a) => Matroid a
- isBinary2 :: Ord a => Matroid a -> Bool
- x :: GlexPoly Integer String
- rankPoly1 :: Ord a => Matroid a -> GlexPoly Integer String
- rankPoly :: Ord a => Matroid a -> GlexPoly Integer String
- numBases :: Ord a => Matroid a -> Integer
- numIndeps :: Ord a => Matroid a -> Integer
- numSpanning :: Ord a => Matroid a -> Integer
- indepCounts :: Ord a => Matroid a -> [Int]
- whitney2nd :: Ord a => Matroid a -> [Int]
- whitney1st :: Ord a => Matroid a -> [Int]
Documentation
isShortlex :: Ord a => [[a]] -> BoolSource
toShortlex :: Ord a => [[a]] -> [[a]]Source
closedUnderSubsets :: Ord a => [[a]] -> BoolSource
The data structure that we use to store the bases of the matroid
tssubmember :: Ord a => [a] -> TrieSet a -> BoolSource
tsfromlist :: Ord a => [[a]] -> TrieSet aSource
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).
indeps :: Ord a => Matroid a -> [[a]]Source
Return all the independent sets of a matroid, in shortlex order.
isIndependent :: Ord a => Matroid a -> [a] -> BoolSource
isDependent :: Ord a => Matroid a -> [a] -> BoolSource
isMatroidIndeps :: Ord a => [[a]] -> BoolSource
Are these the independent sets of a matroid? (The sets must individually be ordered.)
fromIndeps :: Ord a => [a] -> [[a]] -> Matroid aSource
Construct a matroid from its elements and its independent sets.
fromIndeps1 :: Ord a => [a] -> [[a]] -> Matroid aSource
vectorMatroid :: (Eq k, Fractional k) => [[k]] -> Matroid IntSource
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 IntSource
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 IntSource
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 IntSource
Given a matroid over an arbitrary type, relabel to obtain a matroid over the integers.
isMatroidIso :: (Ord a, Ord b) => Matroid a -> Matroid b -> BoolSource
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] -> BoolSource
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]] -> BoolSource
Are the given sets the circuits of some matroid?
fromCircuits :: Ord a => [a] -> [[a]] -> Matroid aSource
Reconstruct a matroid from its elements and circuits.
isLoop :: Ord a => Matroid a -> a -> BoolSource
An element e in a matroid M is a loop if {e} is a circuit of M.
isParallel :: Ord a => Matroid a -> a -> a -> BoolSource
Elements f and g in a matroid M are parallel if {f,g} is a circuit of M.
isSimple :: Ord a => Matroid a -> BoolSource
A matroid is simple if it has no loops or parallel elements
isBase :: Ord a => Matroid a -> [a] -> BoolSource
A base or basis in a matroid is a maximal independent set.
isMatroidBases :: Ord a => [[a]] -> BoolSource
Are the given sets the bases of some matroid?
fromBases :: Ord a => [a] -> [[a]] -> Matroid aSource
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 IntSource
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 aSource
restriction :: Ord a => Matroid a -> [a] -> Matroid aSource
The restriction of a matroid to a subset of its elements
rankfun :: Ord a => Matroid a -> [a] -> IntSource
Given a matroid m, rankfun m
is the rank function on subsets of its element set
fromRankfun :: Ord a => [a] -> ([a] -> Int) -> Matroid aSource
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 aSource
Reconstruct a matroid from its elements and closure operator
isFlat :: Ord a => Matroid a -> [a] -> BoolSource
A flat in a matroid is a closed set, that is a set which is equal to its own closure
coveringFlats :: Ord t => Matroid t -> [t] -> [[t]]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 aSource
Reconstruct a matroid from its flats. (The flats must be given in shortlex order.)
fromFlats' :: Ord a => [[a]] -> Matroid aSource
isSpanning :: Ord a => Matroid a -> [a] -> BoolSource
A subset of the elements in a matroid is spanning if its closure is all the elements
isHyperplane :: Ord a => Matroid a -> [a] -> BoolSource
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]] -> BoolSource
fromHyperplanes1 :: Ord a => [a] -> [[a]] -> Matroid aSource
fromHyperplanes :: Ord a => [a] -> [[a]] -> Matroid aSource
Reconstruct a matroid from its elements and hyperplanes
affineMatroid :: (Eq k, Fractional k) => [[k]] -> Matroid IntSource
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 aSource
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.
simpleFromGeoRep :: Ord a => [[a]] -> [[a]] -> Matroid aSource
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]] -> BoolSource
isCircuitHyperplane :: Ord a => Matroid a -> [a] -> BoolSource
circuitHyperplanes :: Ord a => Matroid a -> [[a]]Source
List the circuit-hyperplanes of a matroid.
relaxation :: Ord a => Matroid a -> [a] -> Matroid aSource
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.
partialMatchings :: Ord a => [(a, a)] -> [[(a, a)]]Source
transversalMatroid :: Ord a => [a] -> [[a]] -> Matroid aSource
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.
isCoindependent :: Ord a => Matroid a -> [a] -> BoolSource
isCocircuit :: Ord a => Matroid a -> [a] -> BoolSource
cocircuits :: Ord a => Matroid a -> [[a]]Source
isCoparallel :: Ord a => Matroid a -> a -> a -> BoolSource
contraction :: Ord a => Matroid a -> [a] -> Matroid aSource
isConnected :: Ord a => Matroid a -> BoolSource
A matroid is (2-)connected if, for every pair of distinct elements, there is a circuit containing both
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 IntSource
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 IntSource
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' :: (Num t, Ord a) => Matroid a -> [a] -> [[t]]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 a) => [a1] -> Matroid a -> [[[a1]]]Source
markedfcim :: Ord a => Matroid a -> [a] -> [[ZeroOneStar]]Source
representations2 :: (Fractional a1, Ord a1, Ord a) => [a1] -> Matroid a -> [[[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 -> BoolSource
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 -> BoolSource
A binary matroid is a matroid which is representable over F2
isTernary :: Ord a => Matroid a -> BoolSource
A ternary matroid is a matroid which is representable over F3
seriesConnection :: (Ord a1, Ord a) => (Matroid a, a) -> (Matroid a1, a1) -> Matroid (LMR a a1)Source
parallelConnection :: (Ord a1, Ord a) => (Matroid a, a) -> (Matroid a1, a1) -> Matroid (LMR a a1)Source
vamosMatroid :: (Num a, Ord a) => Matroid aSource
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-- 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 :: (Enum a, Num a) => a -> Graph aSource
rankPoly :: Ord a => Matroid a -> GlexPoly Integer StringSource
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.
numSpanning :: Ord a => Matroid a -> IntegerSource
indepCounts :: Ord a => Matroid a -> [Int]Source
whitney2nd :: Ord a => Matroid a -> [Int]Source
whitney1st :: Ord a => Matroid a -> [Int]Source