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

Safe HaskellSafe-Infered

Math.Combinatorics.Graph

Description

A module defining a polymorphic data type for (simple, undirected) graphs, together with constructions of some common families of graphs, new from old constructions, and calculation of simple properties of graphs.

Synopsis

Documentation

set :: Ord b => [b] -> [b]Source

powerset :: [a] -> [[a]]Source

data Graph a Source

Datatype for graphs, represented as a list of vertices and a list of edges. For most purposes, graphs are required to be in normal form. A graph G vs es is in normal form if (i) vs is in ascending order without duplicates, (ii) es is in ascending order without duplicates, (iii) each e in es is a 2-element list [x,y], x<y

Constructors

G [a] [[a]] 

Instances

Functor Graph 
Eq a => Eq (Graph a) 
Ord a => Ord (Graph a) 
Show a => Show (Graph a) 

nf :: Ord a => Graph a -> Graph aSource

Convert a graph to normal form. The input is assumed to be a valid graph apart from order

isSetSystem :: Ord a => [a] -> [[a]] -> BoolSource

isGraph :: Ord a => [a] -> [[a]] -> BoolSource

graph :: Ord t => ([t], [[t]]) -> Graph tSource

Safe constructor for graph from lists of vertices and edges. graph (vs,es) checks that vs and es are valid before returning the graph.

toGraph :: Ord a => ([a], [[a]]) -> Graph aSource

vertices :: Graph t -> [t]Source

edges :: Graph t -> [[t]]Source

incidenceMatrix :: (Eq a, Num t) => Graph a -> [[t]]Source

fromIncidenceMatrix :: (Enum t, Eq a, Num a, Num t, Ord t) => [[a]] -> Graph tSource

adjacencyMatrix :: (Num t, Ord a) => Graph a -> [[t]]Source

fromAdjacencyMatrix :: (Eq b, Num b) => [[b]] -> Graph IntSource

nullGraph :: Integral t => t -> Graph tSource

The null graph on n vertices is the graph with no edges

nullGraph' :: Graph IntSource

The null graph, with no vertices or edges

c :: Integral t => t -> Graph tSource

c n is the cyclic graph on n vertices

k :: Integral t => t -> Graph tSource

k n is the complete graph on n vertices

kb :: Integral t => t -> t -> Graph tSource

kb m n is the complete bipartite graph on m and n vertices

kb' :: Integral t => t -> t -> Graph (Either t t)Source

kb' m n is the complete bipartite graph on m left and n right vertices

q :: Integral t => Int -> Graph tSource

q k is the graph of the k-cube

q' :: Integral t => Int -> Graph [t]Source

to1n :: (Enum t, Num t, Ord t, Ord a) => Graph a -> Graph tSource

fromDigits :: Integral a => Graph [a] -> Graph aSource

Given a graph with vertices which are lists of small integers, eg [1,2,3], return a graph with vertices which are the numbers obtained by interpreting these as digits, eg 123. The caller is responsible for ensuring that this makes sense (eg that the small integers are all < 10)

fromBinary :: Integral a => Graph [a] -> Graph aSource

Given a graph with vertices which are lists of 0s and 1s, return a graph with vertices which are the numbers obtained by interpreting these as binary digits. For example, [1,1,0] -> 6.

restriction :: Eq a => Graph a -> [a] -> Graph aSource

The restriction of a graph to a subset of the vertices

inducedSubgraph :: Eq a => Graph a -> [a] -> Graph aSource

lineGraph :: (Enum t, Num t, Ord a, Ord t) => Graph a -> Graph tSource

lineGraph' :: Ord a => Graph a -> Graph [a]Source

valency :: Eq a => Graph a -> a -> IntSource

valencies :: Eq a => Graph a -> [(Int, Int)]Source

valencyPartition :: Eq b => Graph b -> [[b]]Source

isRegular :: Eq t => Graph t -> BoolSource

A graph is regular if all vertices have the same valency (degree)

isCubic :: Eq t => Graph t -> BoolSource

A 3-regular graph is called a cubic graph

nbrs :: Eq a => Graph a -> a -> [a]Source

findPaths :: Eq a => Graph a -> a -> a -> [[a]]Source

distance :: Eq a => Graph a -> a -> a -> IntSource

Within a graph G, the distance d(u,v) between vertices u, v is length of the shortest path from u to v

diameter :: Ord t => Graph t -> IntSource

The diameter of a graph is maximum distance between two distinct vertices

findCycles :: Eq a => Graph a -> a -> [[a]]Source

girth :: Eq t => Graph t -> IntSource

The girth of a graph is the size of the smallest cycle that it contains. Note: If the graph contains no cycles, we return -1, representing infinity.

distancePartition :: Ord a => Graph a -> a -> [[a]]Source

component :: Ord a => Graph a -> a -> [a]Source

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

Is the graph connected?

components :: Ord a => Graph a -> [[a]]Source

j :: Int -> Int -> Int -> Graph [Int]Source

kneser :: Int -> Int -> Graph [Int]Source

kneser n k returns the kneser graph KG n,k - whose vertices are the k-element subsets of [1..n], with edges joining disjoint subsets

gp :: Integral a => a -> a -> Graph (Either a a)Source

prism :: Integral a => a -> Graph (Either a a)Source