Graphalyze-0.8.0.0: Graph-Theoretic Analysis library.Source codeContentsIndex
Data.Graph.Analysis.Utils
MaintainerIvan.Miljenovic@gmail.com
Contents
Graph functions
Data extraction
Graph manipulation
Graph layout
Cluster functions
List functions
Statistics functions
Other functions
Description
This module defines various utility functions used throughout.
Synopsis
node :: LNode a -> Node
label :: LNode a -> a
labels :: Graph g => g a b -> [a]
edge :: LEdge b -> Edge
eLabel :: LEdge b -> b
addLabels :: Graph g => g a b -> [Node] -> [LNode a]
filterNodes :: Graph g => (g a b -> LNode a -> Bool) -> g a b -> [LNode a]
filterNodes' :: Graph g => (g a b -> Node -> Bool) -> g a b -> [Node]
pathValues :: LPath a -> [LNode a]
undir :: (Eq b, DynGraph gr) => gr a b -> gr a b
oneWay :: (DynGraph g, Eq b) => g a b -> g a b
mkSimple :: DynGraph gr => gr a b -> gr a b
compact :: DynGraph gr => gr a b -> gr a [b]
compact' :: DynGraph gr => gr a b -> gr a Int
compactSame :: Ord b => DynGraph gr => gr a b -> gr a (Int, b)
nlmap :: DynGraph gr => (LNode a -> c) -> gr a b -> gr c b
delLNodes :: DynGraph gr => LNGroup a -> gr a b -> gr a b
toPosGraph :: (DynGraph gr, Ord b) => Bool -> gr a b -> gr (PosLabel a) b
getPositions :: (DynGraph gr, Ord b) => Bool -> gr a b -> [PosLabel a]
createLookup :: [[Node]] -> IntMap Int
setCluster :: DynGraph gr => IntMap Int -> gr a b -> gr (GenCluster a) b
reCluster :: DynGraph g => g (GenCluster a) b -> g (GenCluster a) b
reClusterBy :: DynGraph g => IntMap Int -> g (GenCluster a) b -> g (GenCluster a) b
clusterCount :: Graph g => g (GenCluster a) b -> IntMap Int
single :: [a] -> Bool
longerThan :: Int -> [a] -> Bool
addLengths :: [[a]] -> [(Int, [a])]
longest :: [[a]] -> [a]
lengthSort :: [[a]] -> [[a]]
groupElems :: Ord b => (a -> b) -> [a] -> [(b, [a])]
sortMinMax :: Ord a => [a] -> ([a], a, a)
shuffle :: RandomGen g => g -> [a] -> ([a], g)
mean :: [Double] -> Double
statistics :: [Double] -> (Double, Double)
statistics' :: [Int] -> (Int, Int)
fixPoint :: Eq a => (a -> a) -> a -> a
fixPointGraphs :: (Eq a, Eq b, Graph g) => (g a b -> g a b) -> g a b -> g a b
fixPointBy :: (a -> a -> Bool) -> (a -> a) -> a -> a
Graph functions
Data extraction
Extracting data from graphs.
node :: LNode a -> NodeSource
The node number of an LNode.
label :: LNode a -> aSource
The label of an LNode.
labels :: Graph g => g a b -> [a]Source
The labels of all nodes in a tree.
edge :: LEdge b -> EdgeSource
Extract the Edge from the LEdge.
eLabel :: LEdge b -> bSource
The label of an LEdge.
addLabels :: Graph g => g a b -> [Node] -> [LNode a]Source
Obtain the labels for a list of Nodes. It is assumed that each Node is indeed present in the given graph.
filterNodes :: Graph g => (g a b -> LNode a -> Bool) -> g a b -> [LNode a]Source
Find all the labelled nodes in the graph that match the given predicate.
filterNodes' :: Graph g => (g a b -> Node -> Bool) -> g a b -> [Node]Source
Find all the nodes in the graph that match the given predicate.
pathValues :: LPath a -> [LNode a]Source
Extract the actual LNodes from an LPath.
Graph manipulation
undir :: (Eq b, DynGraph gr) => gr a b -> gr a bSource
Make the graph undirected, i.e. for every edge from A to B, there exists an edge from B to A. The provided function Data.Graph.Inductive.Basic.undir duplicates loops as well, which isn't wanted. It is assumed that no edges are already duplicates [i.e. if there exists an edge (n1,n2), then there doesn't exist (n2,n1)]. This function also preserves edge labels: if two edges exist between two nodes with different edge labels, then both edges will be duplicated.
oneWay :: (DynGraph g, Eq b) => g a b -> g a bSource
This is a pseudo-inverse of undir: any edges that are both successor and predecessor become successor edges only.
mkSimple :: DynGraph gr => gr a b -> gr a bSource
Makes the graph a simple one, by removing all duplicate edges and loops. The edges removed if duplicates exist are arbitrary.
compact :: DynGraph gr => gr a b -> gr a [b]Source
Adjoin duplicate edges by grouping the labels together.
compact' :: DynGraph gr => gr a b -> gr a IntSource
Compact the graph by counting how many multiple edges there are (considering only the two nodes and not the labels).
compactSame :: Ord b => DynGraph gr => gr a b -> gr a (Int, b)Source
Compact the graph by adjoining identical duplicate edges.
nlmap :: DynGraph gr => (LNode a -> c) -> gr a b -> gr c bSource
Map over the labels on the nodes, using the node values as well.
delLNodes :: DynGraph gr => LNGroup a -> gr a b -> gr a bSource
Delete these labelled nodes from the graph.
Graph layout
Spatial positioning of graphs. Use the dotizeGraph function in Data.GraphViz to determine potential graph layouts.
toPosGraph :: (DynGraph gr, Ord b) => Bool -> gr a b -> gr (PosLabel a) bSource
Convert the graph into one with positions stored in the node labels. The Bool parameter denotes if the graph is directed or not.
getPositions :: (DynGraph gr, Ord b) => Bool -> gr a b -> [PosLabel a]Source
Returns the positions of the nodes in the graph, as found using Graphviz. The Bool parameter denotes if the graph is directed or not.
Cluster functions
Cluster utility functions.
createLookup :: [[Node]] -> IntMap IntSource
Create a cluster-lookup IntMap.
setCluster :: DynGraph gr => IntMap Int -> gr a b -> gr (GenCluster a) bSource
Used when the clusters are assigned in a lookup IntMap instance.
reCluster :: DynGraph g => g (GenCluster a) b -> g (GenCluster a) bSource
Change the cluster values in the graph by having the largest cluster have the smallest cluster label.
reClusterBy :: DynGraph g => IntMap Int -> g (GenCluster a) b -> g (GenCluster a) bSource
Change the cluster values using the given lookup IntMap.
clusterCount :: Graph g => g (GenCluster a) b -> IntMap IntSource
Create an IntMap of the size of each cluster.
List functions
List utility functions.
single :: [a] -> BoolSource
Return true if and only if the list contains a single element.
longerThan :: Int -> [a] -> BoolSource
If we need to only tell if the list contains more than n elements, there's no need to find its length.
addLengths :: [[a]] -> [(Int, [a])]Source
Add the length of each sublist.
longest :: [[a]] -> [a]Source
Returns the longest list in a list of lists.
lengthSort :: [[a]] -> [[a]]Source
groupElems :: Ord b => (a -> b) -> [a] -> [(b, [a])]Source
Group elements by the given grouping function.
sortMinMax :: Ord a => [a] -> ([a], a, a)Source
Returns the unique elements of the list in ascending order, as well as the minimum and maximum elements.
shuffle :: RandomGen g => g -> [a] -> ([a], g)Source
Shuffle a list of elements. This isn't the most efficient version, but should serve for small lists. Adapted from: http://www.cse.unsw.edu.au/~tsewell/shuffle.html The adaptation mainly involved altering the code so that the new random seed is also returned.
Statistics functions
mean :: [Double] -> DoubleSource
An efficient mean function by Don Stewart, available from: http://cgi.cse.unsw.edu.au/~dons/blog/2008/05/16#fast
statisticsSource
:: [Double]
-> (Double, Double)(Mean, Standard Deviation)
Calculate the mean and standard deviation of a list of elements.
statistics'Source
:: [Int]
-> (Int, Int)(Mean, Standard Deviation)
Calculate the mean and standard deviation of a list of Int values.
Other functions
fixPoint :: Eq a => (a -> a) -> a -> aSource
Find the fixed point of a function with the given initial value.
fixPointGraphs :: (Eq a, Eq b, Graph g) => (g a b -> g a b) -> g a b -> g a bSource
Find the fixed point of a graph transformation function.
fixPointBy :: (a -> a -> Bool) -> (a -> a) -> a -> aSource
Find the fixed point of a function with the given initial value, using the given equality function.
Produced by Haddock version 2.4.2