Graphalyze-0.14.1.1: Graph-Theoretic Analysis library.

Copyright(c) Ivan Lazar Miljenovic 2009
License2-Clause BSD
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell98

Data.Graph.Analysis.Utils

Contents

Description

This module defines various utility functions used throughout.

Synopsis

Graph functions

Data extraction

Extracting data from graphs.

node :: LNode a -> Node Source

The node number of an LNode.

label :: LNode a -> a Source

The label of an LNode.

labels :: Graph g => g a b -> [a] Source

The labels of all nodes in a tree.

edge :: LEdge b -> Edge Source

Extract the Edge from the LEdge.

eLabel :: LEdge b -> b Source

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.

addLabels' :: (Ord a, Graph g) => g a b -> Set Node -> Set (LNode a) Source

Obtain the labels for a Set of Nodes. It is assumed that each Node is indeed present in the given graph.

getLabels :: Graph g => g a b -> [Node] -> [a] Source

Obtain the labels for a list of Nodes. It is assumed that each Node is indeed present in the given graph.

getLabels' :: (Ord a, Graph g) => g a b -> Set Node -> Set 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 b Source

Make the graph undirected, i.e. for every edge from A to B, there exists an edge from B to A. The provided function 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 b Source

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 b Source

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 Int Source

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 b Source

Map over the labels on the nodes, using the node values as well.

delLNodes :: DynGraph gr => LNGroup a -> gr a b -> gr a b Source

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) b Source

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 Int Source

Create a cluster-lookup IntMap.

setCluster :: DynGraph gr => IntMap Int -> gr a b -> gr (GenCluster a) b Source

Used when the clusters are assigned in a lookup IntMap instance.

reCluster :: DynGraph g => g (GenCluster a) b -> g (GenCluster a) b Source

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) b Source

Change the cluster values using the given lookup IntMap.

clusterCount :: Graph g => g (GenCluster a) b -> IntMap Int Source

Create an IntMap of the size of each cluster.

List functions

List utility functions.

single :: [a] -> Bool Source

Return true if and only if the list contains a single element.

longerThan :: Int -> [a] -> Bool Source

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] -> Double Source

An efficient mean function by Don Stewart, available from: http://cgi.cse.unsw.edu.au/~dons/blog/2008/05/16#fast

statistics Source

Arguments

:: [Double] 
-> (Double, Double)

(Mean, Standard Deviation)

Calculate the mean and standard deviation of a list of elements.

statistics' Source

Arguments

:: [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 -> a Source

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 b Source

Find the fixed point of a graph transformation function.

fixPointBy :: (a -> a -> Bool) -> (a -> a) -> a -> a Source

Find the fixed point of a function with the given initial value, using the given equality function.