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

Safe HaskellNone
LanguageHaskell98

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 Source # 
Instance details

Defined in Math.Combinatorics.Graph

Methods

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

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

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

Defined in Math.Combinatorics.Graph

Methods

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

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

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

Defined in Math.Combinatorics.Graph

Methods

compare :: Graph a -> Graph a -> Ordering #

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

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

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

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

max :: Graph a -> Graph a -> Graph a #

min :: Graph a -> Graph a -> Graph a #

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

Defined in Math.Combinatorics.Graph

Methods

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

show :: Graph a -> String #

showList :: [Graph a] -> ShowS #

nf :: Ord a => Graph a -> Graph a Source #

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

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

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

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

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 a Source #

vertices :: Graph a -> [a] Source #

edges :: Graph a -> [[a]] Source #

incidenceMatrix :: (Eq a1, Num a2) => Graph a1 -> [[a2]] Source #

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

adjacencyMatrix :: (Num a2, Ord a1) => Graph a1 -> [[a2]] Source #

fromAdjacencyMatrix :: (Eq a, Num a) => [[a]] -> Graph Int Source #

nullGraph :: Integral t => t -> Graph t Source #

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

nullGraph' :: Graph Int Source #

The null graph, with no vertices or edges

c :: Integral t => t -> Graph t Source #

c n is the cyclic graph on n vertices

k :: Integral t => t -> Graph t Source #

k n is the complete graph on n vertices

kb :: Integral t => t -> t -> Graph t Source #

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 t Source #

q k is the graph of the k-cube

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

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

fromDigits :: Integral a => Graph [a] -> Graph a Source #

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 a Source #

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.

complement :: Ord t => Graph t -> Graph t Source #

restriction :: Eq a => Graph a -> [a] -> Graph a Source #

The restriction of a graph to a subset of the vertices

inducedSubgraph :: Eq a => Graph a -> [a] -> Graph a Source #

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

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

cartProd :: (Ord a1, Ord a2) => Graph a2 -> Graph a1 -> Graph (a2, a1) Source #

valency :: Eq a => Graph a -> a -> Int Source #

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

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

isRegular :: Eq t => Graph t -> Bool Source #

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

isCubic :: Eq t => Graph t -> Bool Source #

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 -> Int Source #

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 -> Int Source #

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 -> Int Source #

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 #

distancePartitionS :: Ord a => [a] -> Set [a] -> a -> [[a]] Source #

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

isConnected :: Ord t => Graph t -> Bool Source #

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 between disjoint subsets

gp :: Integral b => b -> b -> Graph (Either b b) Source #

prism' :: Integral b => b -> Graph (Either b b) Source #