Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- set :: Ord b => [b] -> [b]
- powerset :: [t] -> [[t]]
- data Graph a = G [a] [[a]]
- nf :: Ord a => Graph a -> Graph a
- isSetSystem :: Ord a => [a] -> [[a]] -> Bool
- isGraph :: Ord a => [a] -> [[a]] -> Bool
- graph :: Ord t => ([t], [[t]]) -> Graph t
- toGraph :: Ord a => ([a], [[a]]) -> Graph a
- vertices :: Graph t -> [t]
- edges :: Graph t -> [[t]]
- incidenceMatrix :: (Num t, Eq a) => Graph a -> [[t]]
- fromIncidenceMatrix :: (Ord t, Num t, Num a, Eq a, Enum t) => [[a]] -> Graph t
- adjacencyMatrix :: (Ord a, Num t) => Graph a -> [[t]]
- fromAdjacencyMatrix :: (Num b, Eq b) => [[b]] -> Graph Int
- nullGraph :: Integral t => t -> Graph t
- nullGraph' :: Graph Int
- c :: Integral t => t -> Graph t
- k :: Integral t => t -> Graph t
- kb :: Integral t => t -> t -> Graph t
- kb' :: Integral t => t -> t -> Graph (Either t t)
- q :: Integral t => Int -> Graph t
- q' :: Integral t => Int -> Graph [t]
- tetrahedron :: Graph Integer
- cube :: Graph Integer
- octahedron :: Graph Integer
- dodecahedron :: Graph Integer
- icosahedron :: Graph Integer
- prism :: Int -> Graph (Int, Int)
- to1n :: (Ord t, Ord a, Num t, Enum t) => Graph a -> Graph t
- fromDigits :: Integral a => Graph [a] -> Graph a
- fromBinary :: Integral a => Graph [a] -> Graph a
- petersen :: Graph [Integer]
- complement :: Ord t => Graph t -> Graph t
- restriction :: Eq a => Graph a -> [a] -> Graph a
- inducedSubgraph :: Eq a => Graph a -> [a] -> Graph a
- lineGraph :: (Ord a, Ord t, Num t, Enum t) => Graph a -> Graph t
- lineGraph' :: Ord a => Graph a -> Graph [a]
- cartProd :: (Ord t1, Ord t) => Graph t -> Graph t1 -> Graph (t, t1)
- order :: Graph a -> Int
- size :: Graph t -> Int
- valency :: Eq a => Graph a -> a -> Int
- valencies :: Eq a => Graph a -> [(Int, Int)]
- valencyPartition :: Eq b => Graph b -> [[b]]
- regularParam :: Eq a => Graph a -> Maybe Int
- isRegular :: Eq t => Graph t -> Bool
- isCubic :: Eq t => Graph t -> Bool
- nbrs :: Eq a => Graph a -> a -> [a]
- findPaths :: Eq a => Graph a -> a -> a -> [[a]]
- distance :: Eq a => Graph a -> a -> a -> Int
- diameter :: Ord t => Graph t -> Int
- findCycles :: Eq a => Graph a -> a -> [[a]]
- girth :: Eq t => Graph t -> Int
- distancePartition :: Ord a => Graph a -> a -> [[a]]
- distancePartitionS :: Ord a => [a] -> Set [a] -> a -> [[a]]
- component :: Ord a => Graph a -> a -> [a]
- isConnected :: Ord t => Graph t -> Bool
- components :: Ord a => Graph a -> [[a]]
- j :: Int -> Int -> Int -> Graph [Int]
- kneser :: Int -> Int -> Graph [Int]
- johnson :: Int -> Int -> Graph [Int]
- bipartiteKneser :: Int -> Int -> Graph (Either [Int] [Int])
- desargues1 :: Graph (Either [Int] [Int])
- gp :: Integral a => a -> a -> Graph (Either a a)
- petersen2 :: Graph (Either Integer Integer)
- prism' :: Integral a => a -> Graph (Either a a)
- durer :: Graph (Either Integer Integer)
- mobiusKantor :: Graph (Either Integer Integer)
- dodecahedron2 :: Graph (Either Integer Integer)
- desargues2 :: Graph (Either Integer Integer)
Documentation
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
G [a] [[a]] |
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
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.
incidenceMatrix :: (Num t, Eq a) => Graph a -> [[t]] Source
adjacencyMatrix :: (Ord a, Num t) => Graph a -> [[t]] 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
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
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' :: Ord a => Graph a -> Graph [a] 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)
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
isConnected :: Ord t => Graph t -> Bool Source
Is the graph connected?
components :: Ord a => Graph a -> [[a]] Source