Graphalyze-0.7.0.0: Graph-Theoretic Analysis library.Source codeContentsIndex
Data.Graph.Analysis
MaintainerIvan.Miljenovic@gmail.com
Contents
Re-exporting other modules
Importing data
Result analysis
Description

This is the root module of the Graphalyze library, which aims to provide a way of analysing the relationships inherent in discrete data as a graph.

The original version of this library was written as part of my mathematics honours thesis, Graph-Theoretic Analysis of the Relationships in Discrete Data.

Synopsis
version :: String
module Data.Graph.Analysis.Types
module Data.Graph.Analysis.Utils
module Data.Graph.Analysis.Algorithms
module Data.Graph.Analysis.Visualisation
module Data.Graph.Analysis.Reporting
module Data.Graph.Inductive.Graph
data ImportParams n e = Params {
dataPoints :: [n]
relationships :: [Rel n e]
roots :: [n]
directed :: Bool
}
importData :: (Ord n, Ord e) => ImportParams n e -> GraphData n e
lengthAnalysis :: [[a]] -> (Int, Int, [(Int, [a])])
classifyRoots :: Ord n => GraphData n e -> ([LNode n], [LNode n], [LNode n])
interiorChains :: (Eq n, Eq e) => GraphData n e -> [LNGroup n]
Documentation
version :: StringSource
The library version.
Re-exporting other modules
module Data.Graph.Analysis.Types
module Data.Graph.Analysis.Utils
module Data.Graph.Analysis.Algorithms
module Data.Graph.Analysis.Visualisation
module Data.Graph.Analysis.Reporting
module Data.Graph.Inductive.Graph
Importing data
data ImportParams n e Source
This represents the information that's being passed in that we want to analyse. If the graph is undirected, it is better to list each edge once rather than both directions.
Constructors
Params
dataPoints :: [n]The discrete points.
relationships :: [Rel n e]The relationships between the points.
roots :: [n]The expected roots of the graph. If directed = False, then this is ignored.
directed :: BoolFalse if relationships are symmetric (i.e. an undirected graph).
importData :: (Ord n, Ord e) => ImportParams n e -> GraphData n eSource
Import data into a format suitable for analysis. This function is edge-safe: if any datums are listed in the edges of ImportParams that aren't listed in the data points, then those edges are ignored. Thus, no sanitation of the relationships in ImportParams is necessary. The unused relations are stored in unusedRelationships. Note that it is assumed that all datums in roots are also contained within dataPoints.
Result analysis
Extra functions for data analysis.
lengthAnalysis :: [[a]] -> (Int, Int, [(Int, [a])])Source
Returns the mean and standard deviations of the lengths of the sublists, as well all those lists more than one standard deviation longer than the mean.
classifyRoots :: Ord n => GraphData n e -> ([LNode n], [LNode n], [LNode n])Source

Compare the actual roots in the graph with those that are expected (i.e. those in wantedRoots). Returns (in order):

  • Those roots that are expected (i.e. elements of wantedRoots that are roots).
  • Those roots that are expected but not present (i.e. elements of wantedRoots that aren't roots.
  • Unexpected roots (i.e. those roots that aren't present in wantedRoots).
interiorChains :: (Eq n, Eq e) => GraphData n e -> [LNGroup n]Source
Only return those chains (see chainsIn) where the non-initial nodes are not expected roots.
Produced by Haddock version 2.4.2