hmt-0.16: Haskell Music Theory

Safe HaskellNone
LanguageHaskell98

Music.Theory.Graph.FGL

Contents

Description

Graph (fgl) functions.

Synopsis

Documentation

g_degree :: Gr v e -> Int Source #

Synonym for noNodes.

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.

g_node_lookup_err :: (Eq v, Graph gr) => gr v e -> v -> Node Source #

Erroring variant.

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 #

g_hamiltonian_path_ml :: MonadLogic m => G_NODE_SEL_F v e -> Gr v e -> Node -> m [Node] Source #

Use sel_f of pre for directed graphs and neighbors for undirected.

G (from edges)

type EDGE v = (v, v) Source #

Edge, no label.

type GRAPH v = [EDGE v] Source #

Graph as set of edges.

type EDGE_L v l = (EDGE v, l) Source #

Edge, with label.

type GRAPH_L v l = [EDGE_L v l] Source #

Graph as set of labeled edges.

g_from_edges_l :: (Eq v, Ord v) => GRAPH_L v e -> Gr v e Source #

Generate a graph given a set of labelled edges.

g_from_edges :: Ord v => GRAPH 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_label_seq :: [EDGE v] -> [EDGE_L v Int] Source #

Label sequence of edges starting at one.

e_normalise_l :: Ord v => EDGE_L v l -> EDGE_L v l Source #

Normalised undirected labeled edge (ie. order nodes).

e_collate_l :: Ord v => [EDGE_L v l] -> [EDGE_L 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_undirected_eq :: Eq t => EDGE t -> EDGE t -> Bool Source #

Undirected edge equality.

elem_by :: (p -> q -> Bool) -> p -> [q] -> Bool Source #

e_is_path :: Eq t => GRAPH t -> [t] -> Bool Source #

Is the sequence of vertices a path at the graph, ie. are all adjacencies in the sequence edges.