Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Graph (fgl) functions.
Synopsis
- lbl_to_fgl :: Graph gr => Lbl v e -> gr v e
- lbl_to_fgl_gr :: Lbl v e -> Gr v e
- fgl_to_lbl :: Graph gr => gr v e -> Lbl v e
- g_degree :: Gr v e -> Int
- g_partition :: Gr v e -> [Gr v e]
- g_node_lookup :: (Eq v, Graph gr) => gr v e -> v -> Maybe Node
- g_node_lookup_err :: (Eq v, Graph gr) => gr v e -> v -> Node
- ug_node_set_impl :: (Eq v, DynGraph gr) => gr v e -> [v] -> [Node]
- type G_Node_Sel_f v e = Gr v e -> Node -> [Node]
- ml_from_list :: MonadPlus m => [t] -> m t
- g_hamiltonian_path_ml :: (MonadPlus m, MonadLogic m) => G_Node_Sel_f v e -> Gr v e -> Node -> m [Node]
- ug_hamiltonian_path_ml_0 :: (MonadPlus m, MonadLogic m) => Gr v e -> m [Node]
- type Edge v = (v, v)
- type Edge_Lbl v l = (Edge v, l)
- g_from_edges_l :: (Eq v, Ord v) => [Edge_Lbl v e] -> Gr v e
- g_from_edges :: Ord v => [Edge v] -> Gr v ()
- e_label_seq :: [Edge v] -> [Edge_Lbl v Int]
- e_normalise_l :: Ord v => Edge_Lbl v l -> Edge_Lbl v l
- e_collate_l :: Ord v => [Edge_Lbl v l] -> [Edge_Lbl v [l]]
- e_collate_normalised_l :: Ord v => [Edge_Lbl v l] -> [Edge_Lbl v [l]]
- e_univ_select_edges :: (t -> t -> Bool) -> [t] -> [Edge t]
- e_univ_select_u_edges :: Ord t => (t -> t -> Bool) -> [t] -> [Edge t]
- e_path_to_edges :: [t] -> [Edge t]
- e_undirected_eq :: Eq t => Edge t -> Edge t -> Bool
- elem_by :: (p -> q -> Bool) -> p -> [q] -> Bool
- e_is_path :: Eq t => [Edge t] -> [t] -> Bool
- pathTree :: DynGraph g => Decomp g a b -> [[Node]]
- makeLeaf :: Context a b -> Context a b
Documentation
lbl_to_fgl_gr :: Lbl v e -> Gr v e Source #
Type-specialised.
g_partition :: Gr v e -> [Gr v e] Source #
subgraph
of each of components
.
g_node_lookup :: (Eq v, Graph gr) => gr v e -> v -> Maybe Node Source #
Find first Node
with given label.
ug_node_set_impl :: (Eq v, DynGraph gr) => gr v e -> [v] -> [Node] Source #
Set of nodes with given labels, plus all neighbours of these nodes. (impl = implications)
Hamiltonian
type G_Node_Sel_f v e = Gr v e -> Node -> [Node] Source #
Node select function, ie. given a graph g and a node n select a set of related nodes from g
g_hamiltonian_path_ml :: (MonadPlus m, MonadLogic m) => G_Node_Sel_f v e -> Gr v e -> Node -> m [Node] Source #
ug_hamiltonian_path_ml_0 :: (MonadPlus m, MonadLogic m) => Gr v e -> m [Node] Source #
g_hamiltonian_path_ml
of neighbors
starting at first node.
map (L.observeAll . ug_hamiltonian_path_ml_0) (g_partition gr)
G (from edges)
g_from_edges_l :: (Eq v, Ord v) => [Edge_Lbl v e] -> Gr v e Source #
Generate a graph given a set of labelled edges.
g_from_edges :: Ord v => [Edge v] -> Gr v () Source #
Variant that supplies ()
as the (constant) edge label.
let g = G.mkGraph [(0,'a'),(1,'b'),(2,'c')] [(0,1,()),(1,2,())] in g_from_edges_ul [('a','b'),('b','c')] == g
Edges
e_normalise_l :: Ord v => Edge_Lbl v l -> Edge_Lbl v l Source #
Normalised undirected labeled edge (ie. order nodes).
e_collate_l :: Ord v => [Edge_Lbl v l] -> [Edge_Lbl v [l]] Source #
Collate labels for edges that are otherwise equal.
e_univ_select_edges :: (t -> t -> Bool) -> [t] -> [Edge t] Source #
Apply predicate to universe of possible edges.
e_univ_select_u_edges :: Ord t => (t -> t -> Bool) -> [t] -> [Edge t] Source #
Consider only edges (p,q) where p < q.
e_path_to_edges :: [t] -> [Edge t] Source #
Sequence of connected vertices to edges.
e_path_to_edges "abcd" == [('a','b'),('b','c'),('c','d')]
e_is_path :: Eq t => [Edge t] -> [t] -> Bool Source #
Is the sequence of vertices a path at the graph, ie. are all adjacencies in the sequence edges.