Graphalyze-0.7.0.0: Graph-Theoretic Analysis library.Source codeContentsIndex
Data.Graph.Analysis.Types
MaintainerIvan.Miljenovic@gmail.com
Contents
Graph specialization.
Functions on GraphData.
Clustering graphs based on their node labels.
Graph label types.
Description
This module defines the various types and classes utilised by the Graphalyze library.
Synopsis
data GraphData n e = GraphData {
graph :: AGr n e
wantedRootNodes :: NGroup
directedData :: Bool
unusedRelationships :: [Rel n e]
}
type AGr n e = Gr n e
type Rel n e = (n, n, e)
type NGroup = [Node]
type LNGroup a = [LNode a]
wantedRoots :: GraphData n e -> LNGroup n
applyAlg :: (AGr n e -> a) -> GraphData n e -> a
applyDirAlg :: (Bool -> AGr n e -> a) -> GraphData n e -> a
mergeUnused :: (Ord n, Ord e) => GraphData n e -> GraphData n e
removeUnused :: GraphData n e -> GraphData n e
updateGraph :: (AGr a b -> AGr c d) -> GraphData a b -> GraphData c d
updateGraph' :: (Bool -> AGr a b -> AGr c d) -> GraphData a b -> GraphData c d
mapAllNodes :: (Ord a, Ord e, Ord b) => (a -> b) -> GraphData a e -> GraphData b e
mapNodeType :: (Ord a, Ord b, Ord e) => (a -> b) -> (a -> b) -> GraphData a e -> GraphData b e
class ClusterType (Cluster cl) => ClusterLabel cl where
type Cluster cl
type NodeLabel cl
cluster :: cl -> Cluster cl
nodeLabel :: cl -> NodeLabel cl
class Ord c => ClusterType c where
clusterID :: c -> Maybe GraphID
GraphID (Str, Int, Dbl, HTML)
data GenCluster a = GC {
clust :: Int
nLbl :: a
}
data PosLabel a = PLabel {
xPos :: Int
yPos :: Int
pnode :: Node
plabel :: a
}
Graph specialization.
data GraphData n e Source
Represents information about the graph being analysed.
Constructors
GraphData
graph :: AGr n eWe use a graph type with no edge labels.
wantedRootNodes :: NGroupThe expected root nodes in the graph.
directedData :: BoolIs the data this graph represents directed in nature?
unusedRelationships :: [Rel n e]Unused relationships (i.e. not in the actual graph). These are the edges containing nodes not in the graph.
type AGr n e = Gr n eSource
An alias for the type of graph being used by default.
type Rel n e = (n, n, e)Source
A relationship between two nodes with a label.
type NGroup = [Node]Source
A grouping of Nodes.
type LNGroup a = [LNode a]Source
A grouping of LNodes.
Functions on GraphData.
wantedRoots :: GraphData n e -> LNGroup nSource
The expected roots in the data to be analysed.
applyAlg :: (AGr n e -> a) -> GraphData n e -> aSource
Apply an algorithm to the data to be analysed.
applyDirAlg :: (Bool -> AGr n e -> a) -> GraphData n e -> aSource
Apply an algorithm that requires knowledge about whether the graph is directed (True) or undirected (False) to the data to be analysed.
mergeUnused :: (Ord n, Ord e) => GraphData n e -> GraphData n eSource
Merge the unusedRelationships into the graph by adding the appropriate nodes.
removeUnused :: GraphData n e -> GraphData n eSource
Used to set unusedRelationships = []. This is of use when they are unneeded or because there is no sensible mapping function to use when applying a mapping function to the nodes in the graph.
updateGraph :: (AGr a b -> AGr c d) -> GraphData a b -> GraphData c dSource
Replace the current graph by applying a function to it. To ensure type safety, removeUnused is applied.
updateGraph' :: (Bool -> AGr a b -> AGr c d) -> GraphData a b -> GraphData c dSource
Replace the current graph by applying a function to it, where the function depends on whether the graph is directed (True) or undirected (False). To ensure type safety, removeUnused is applied.
mapAllNodes :: (Ord a, Ord e, Ord b) => (a -> b) -> GraphData a e -> GraphData b eSource
Apply a function to all the data points. This might be useful in circumstances where you want to reduce the data type used to a simpler one, etc. The function is also applied to the datums in unusedRelationships.
mapNodeType :: (Ord a, Ord b, Ord e) => (a -> b) -> (a -> b) -> GraphData a e -> GraphData b eSource
Apply the first function to nodes in the graph, and the second function to those unknown datums in unusedRelationships. As a sample reason for this function, it can be used to apply a two-part constructor (e.g. Left and Right from Either) to the nodes such that the wanted and unwanted datums can be differentiated before calling mergeUnused.
Clustering graphs based on their node labels.
class ClusterType (Cluster cl) => ClusterLabel cl whereSource

These types and classes represent useful label types.

The class of outputs of a clustering algorithm. This class is mainly used for visualization purposes, with the Ord instance required for grouping. Instances of this class are intended for use as the label type of graphs.

Associated Types
type Cluster cl Source
type NodeLabel cl Source
Methods
cluster :: cl -> Cluster clSource
The cluster the node label belongs in.
nodeLabel :: cl -> NodeLabel clSource
The actual label.
show/hide Instances
class Ord c => ClusterType c whereSource
A class used to define which types are valid for clusters.
Methods
clusterID :: c -> Maybe GraphIDSource
Create a label for visualisation purposes with the GraphViz library. Default is const Nothing.
show/hide Instances
GraphID (Str, Int, Dbl, HTML)
Graph label types.
data GenCluster a Source
A generic cluster-label type.
Constructors
GC
clust :: Int
nLbl :: a
show/hide Instances
data PosLabel a Source
Label type for storing node positions. Note that this isn't an instance of ClusterLabel since there's no clear indication on which cluster a node belongs to at this stage.
Constructors
PLabel
xPos :: Int
yPos :: Int
pnode :: Node
plabel :: a
show/hide Instances
Eq a => Eq (PosLabel a)
Show a => Show (PosLabel a)
Eq a => Metric (PosLabel a)
Produced by Haddock version 2.4.2