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

Safe HaskellSafe-Infered

Math.Combinatorics.GraphAuts

Synopsis

Documentation

isVertexTransitive :: Ord t => Graph t -> BoolSource

A graph is vertex-transitive if its automorphism group acts transitively on the vertices. Thus, given any two distinct vertices, there is an automorphism mapping one to the other.

isEdgeTransitive :: Ord t => Graph t -> BoolSource

A graph is edge-transitive if its automorphism group acts transitively on the edges. Thus, given any two distinct edges, there is an automorphism mapping one to the other.

(->^) :: Ord b => [b] -> Permutation b -> [b]Source

isArcTransitive :: Ord t => Graph t -> BoolSource

A graph is arc-transitive (or flag-transitive) if its automorphism group acts transitively on arcs. (An arc is an ordered pair of adjacent vertices.)

findArcs :: (Eq a1, Eq a, Num a) => Graph a1 -> a1 -> a -> [[a1]]Source

isnArcTransitive :: Ord t => Int -> Graph t -> BoolSource

A graph is n-arc-transitive is its automorphism group is transitive on n-arcs. (An n-arc is an ordered sequence (v0,...,vn) of adjacent vertices, with crossings allowed but not doubling back.)

isDistanceTransitive :: Ord t => Graph t -> BoolSource

A graph is distance transitive if given any two ordered pairs of vertices (u,u') and (v,v') with d(u,u') == d(v,v'), there is an automorphism of the graph that takes (u,u') to (v,v')

refine :: Ord a => [[a]] -> [[a]] -> [[a]]Source

refine' :: Ord a => [[a]] -> [[a]] -> [[a]]Source

adjLists :: Ord a => Graph a -> Map a [a]Source

toEquitable :: Ord t => Graph t -> [[t]] -> [[t]]Source

toEquitable2 :: Ord a => Map a [a] -> [[a]] -> [[a]] -> ([[a]], [[a]])Source

splitNumNbrs :: (Ord b, Ord a) => Map b [a] -> ([a], [a]) -> ([b], [b]) -> Maybe [([b], [b])]Source

graphAuts :: Ord a => Graph a -> [Permutation a]Source

Given a graph g, graphAuts g returns generators for the automorphism group of g. If g is connected, then the generators will be a strong generating set.

dfsEquitable :: Ord k => (Map k [[k]], Set [k], Map k [k]) -> [(k, k)] -> [[k]] -> [[k]] -> [Permutation k]Source

incidenceAuts :: (Ord p, Ord b) => Graph (Either p b) -> [Permutation p]Source

Given the incidence graph of an incidence structure between points and blocks (for example, a set system), incidenceAuts g returns generators for the automorphism group of the incidence structure. The generators are represented as permutations of the points. The incidence graph should be represented with the points on the left and the blocks on the right. If the incidence graph is connected, then the generators will be a strong generating set.

graphIsos :: (Ord t, Ord t1) => Graph t -> Graph t1 -> [[(t, t1)]]Source

graphIsosCon :: (Ord t, Ord t1) => Graph t -> Graph t1 -> [[(t, t1)]]Source

isGraphIso :: (Ord a, Ord b) => Graph a -> Graph b -> BoolSource

Are the two graphs isomorphic?

isIso :: (Ord t1, Ord t) => Graph t -> Graph t1 -> BoolSource

incidenceIsos :: (Ord t2, Ord t, Ord t3, Ord t1) => Graph (Either t2 t) -> Graph (Either t3 t1) -> [[(t2, t3)]]Source

incidenceIsosCon :: (Ord t2, Ord t, Ord t3, Ord t1) => Graph (Either t2 t) -> Graph (Either t3 t1) -> [[(t2, t3)]]Source

isIncidenceIso :: (Ord p1, Ord b1, Ord p2, Ord b2) => Graph (Either p1 b1) -> Graph (Either p2 b2) -> BoolSource

Are the two incidence structures represented by these incidence graphs isomorphic?