Graphalyze-0.1: 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
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
nlmap :: DynGraph gr => (LNode a -> c) -> gr a b -> gr c b
dotizeGraph :: (DynGraph gr, Ord b) => gr a b -> gr (AttributeNode a) (AttributeEdge b)
toPosGraph :: (DynGraph gr, Ord b) => gr a b -> gr (PosLabel a) b
getPositions :: (DynGraph gr, Ord b) => gr a b -> [PosLabel a]
createLookup :: [[Node]] -> IntMap Int
setCluster :: DynGraph gr => IntMap Int -> gr a b -> gr (GenCluster a) b
assignCluster :: ClusterLabel a c => LNode a -> NodeCluster c a
single :: [a] -> Bool
longerThan :: Int -> [a] -> Bool
longest :: [[a]] -> [a]
groupElems :: Ord b => (a -> b) -> [a] -> [(b, [a])]
sortMinMax :: Ord a => [a] -> ([a], a, a)
blockPrint :: Show a => [a] -> String
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
sq :: Num a => a -> a
fI :: Num a => Int -> a
Graph functions
Data extraction
node :: LNode a -> NodeSource

Extracting data from graphs.

The node number of an LNode.

label :: LNode a -> aSource
The label of an LNode
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.
Graph manipulation
pathValues :: LPath a -> [LNode a]Source

Manipulating graphs.

Extract the actual LNodes from an LPath.

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.
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.
Graph layout
These next two are re-exported from Data.GraphViz
dotizeGraph :: (DynGraph gr, Ord b) => gr a b -> gr (AttributeNode a) (AttributeEdge b)Source

Spatial positioning of graphs. Use the graphToGraph function in Data.GraphViz to determine potential graph layouts.

Pass the plain graph through graphToGraph. This is an IO action, however since the state doesn't change it's safe to use unsafePerformIO to convert this to a normal function.

toPosGraph :: (DynGraph gr, Ord b) => gr a b -> gr (PosLabel a) bSource
Convert the graph into one with positions stored in the node labels.
getPositions :: (DynGraph gr, Ord b) => gr a b -> [PosLabel a]Source
Returns the positions of the nodes in the graph, as found using Graphviz.
Cluster functions
createLookup :: [[Node]] -> IntMap IntSource

Cluster utility functions.

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.
assignCluster :: ClusterLabel a c => LNode a -> NodeCluster c aSource
A function to convert an LNode to the required NodeCluster for use with the Graphviz library.
List functions
single :: [a] -> BoolSource

List utility functions.

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.
longest :: [[a]] -> [a]Source
Returns the longest list in a list of lists.
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.
blockPrint :: Show a => [a] -> StringSource
Attempt to convert a list of elements into a square format in as much of a square shape as possible.
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

Statistics functions.

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

Other utility functions.

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.
sq :: Num a => a -> aSource
Squaring a number.
fI :: Num a => Int -> aSource
Shorthand for fromIntegral
Produced by Haddock version 2.3.0