unordered-graphs-0.1.0: Graph library using unordered-containers

Copyright(c) Ivan Lazar Miljenovic
LicenseMIT
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Data.Graph.Unordered

Contents

Description

Known limitations:

  • Adding edges might not be the same depending on graph construction (if you add then delete a lot of edges, then the next new edge might be higher than expected).

Synopsis

Graph datatype

data Graph et n nl el Source

Instances

(Eq (et n), Eq n, Eq nl, Eq el) => Eq (Graph et n nl el) Source 
(ValidGraph et n, Read n, Read nl, Read el) => Read (Graph et n nl el) Source 
(EdgeType et, Show n, Show nl, Show el) => Show (Graph et n nl el) Source 
(NFData n, NFData (et n), NFData nl, NFData el) => NFData (Graph et n nl el) Source 

type ValidGraph et n = (Hashable n, Eq n, EdgeType et) Source

Edge types

newtype Edge Source

Constructors

Edge 

Fields

unEdge :: Word
 

Instances

Bounded Edge Source 
Enum Edge Source 
Eq Edge Source 
Ord Edge Source 
Read Edge Source 
Show Edge Source 
NFData Edge Source 
Hashable Edge Source 
ToContext (n, nl, AdjLookup (at n) el) Source 
FromContext (n, nl, AdjLookup (at n) el) Source 
Contextual (n, nl, AdjLookup (at n) el) Source 
type CNode (n, nl, AdjLookup (at n) el) = n Source 
type CAType (n, nl, AdjLookup (at n) el) = at Source 
type CNLabel (n, nl, AdjLookup (at n) el) = nl Source 
type CELabel (n, nl, AdjLookup (at n) el) = el Source 

data DirEdge n Source

Constructors

DE 

Fields

fromNode :: !n
 
toNode :: !n
 

Instances

Functor DirEdge Source 
EdgeType DirEdge Source

Note that for loops, the result of otherN will always be a ToNode.

EdgeMergeable DirEdge Source 
Eq n => Eq (DirEdge n) Source 
Ord n => Ord (DirEdge n) Source 
Read n => Read (DirEdge n) Source 
Show n => Show (DirEdge n) Source 
Generic (DirEdge n) Source 
NFData n => NFData (DirEdge n) Source 
type AdjType DirEdge = DirAdj Source 
type Rep (DirEdge n) Source 

class (Functor et, NodeFrom (AdjType et)) => EdgeType et where Source

Associated Types

type AdjType et :: * -> * Source

Methods

mkEdge :: n -> n -> et n Source

otherN :: Eq n => n -> et n -> AdjType et n Source

Assumes n is one of the end points of this edge.

toEdge :: n -> AdjType et n -> et n Source

edgeNodes :: et n -> [n] Source

Returns a list of length 2.

edgeTriple :: (et n, el) -> (n, n, el) Source

Instances

EdgeType UndirEdge Source 
EdgeType DirEdge Source

Note that for loops, the result of otherN will always be a ToNode.

class NodeFrom at where Source

Methods

getNode :: at n -> n Source

data DirAdj n Source

Constructors

ToNode n 
FromNode n 

Instances

newtype Identity a :: * -> *

Identity functor and monad. (a non-strict monad)

Since: 4.8.0.0

Constructors

Identity 

Fields

runIdentity :: a
 

Instances

Monad Identity 
Functor Identity 
MonadFix Identity 
Applicative Identity 
Foldable Identity 
Traversable Identity 
Generic1 Identity 
MonadZip Identity 
NodeFrom Identity Source 
Eq a => Eq (Identity a) 
Data a => Data (Identity a) 
Ord a => Ord (Identity a) 
Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Generic (Identity a) 
NFData a => NFData (Identity a)

Since: 1.4.0.0

type Rep1 Identity = D1 D1Identity (C1 C1_0Identity (S1 S1_0_0Identity Par1)) 
type Rep (Identity a) = D1 D1Identity (C1 C1_0Identity (S1 S1_0_0Identity (Rec0 a))) 

Graph Context

data Context at n nl el Source

Constructors

Ctxt 

Fields

cNode :: !n
 
cLabel :: !nl
 
cAdj :: !(AdjLookup (at n) el)
 

Instances

(Eq n, Eq nl, Eq el, Eq (at n)) => Eq (Context at n nl el) Source 
(Read n, Read nl, Read el, Read (at n)) => Read (Context at n nl el) Source 
(Show n, Show nl, Show el, Show (at n)) => Show (Context at n nl el) Source 
Generic (Context at n nl el) Source 
(NFData n, NFData nl, NFData el, NFData (at n)) => NFData (Context at n nl el) Source 
ToContext (Context at n nl el) Source 
FromContext (Context at n nl el) Source 
Contextual (Context at n nl el) Source 
type Rep (Context at n nl el) Source 
type CNode (Context at n nl el) = n Source 
type CAType (Context at n nl el) = at Source 
type CNLabel (Context at n nl el) = nl Source 
type CELabel (Context at n nl el) = el Source 

type AdjLookup n el = HashMap Edge (n, el) Source

class Contextual ctxt Source

Associated Types

type CNode ctxt :: * Source

type CAType ctxt :: * -> * Source

type CNLabel ctxt :: * Source

type CELabel ctxt :: * Source

Instances

Contextual (n, nl, [(n, [el])]) Source 
Contextual (n, nl, AdjLookup (at n) el) Source 
Contextual (Context at n nl el) Source 

type ValidContext et n nl el ctxt = (Contextual ctxt, n ~ CNode ctxt, AdjType et ~ CAType ctxt, nl ~ CNLabel ctxt, el ~ CELabel ctxt) Source

class Contextual ctxt => FromContext ctxt where Source

Methods

fromContext :: Context (CAType ctxt) (CNode ctxt) (CNLabel ctxt) (CELabel ctxt) -> ctxt Source

Instances

Ord n => FromContext (n, nl, [(n, [el])]) Source 
FromContext (n, nl, AdjLookup (at n) el) Source 
FromContext (Context at n nl el) Source 

class Contextual ctxt => ToContext ctxt where Source

Methods

toContext :: ctxt -> Context (CAType ctxt) (CNode ctxt) (CNLabel ctxt) (CELabel ctxt) Source

Instances

ToContext (n, nl, AdjLookup (at n) el) Source 
ToContext (Context at n nl el) Source 

Graph functions

Graph Information

isEmpty :: Graph et n nl el -> Bool Source

Node information

order :: Graph et n nl el -> Int Source

Number of nodes

hasNode :: ValidGraph et n => Graph et n nl el -> n -> Bool Source

ninfo :: ValidGraph et n => Graph et n nl el -> n -> Maybe ([Edge], nl) Source

nodes :: Graph et n nl el -> [n] Source

nodeDetails :: Graph et n nl el -> [(n, ([Edge], nl))] Source

lnodes :: Graph et n nl el -> [(n, nl)] Source

nlab :: ValidGraph et n => Graph et n nl el -> n -> Maybe nl Source

neighbours :: ValidGraph et n => Graph et n nl el -> n -> [n] Source

Edge information

size :: Graph et n nl el -> Int Source

Number of edges

hasEdge :: ValidGraph et n => Graph et n nl el -> Edge -> Bool Source

einfo :: ValidGraph et n => Graph et n nl el -> Edge -> Maybe (et n, el) Source

edges :: Graph et n nl el -> [Edge] Source

edgeDetails :: Graph et n nl el -> [(Edge, (et n, el))] Source

ledges :: Graph et n nl el -> [(Edge, el)] Source

elab :: ValidGraph et n => Graph et n nl el -> Edge -> Maybe el Source

edgePairs :: EdgeType et => Graph et n nl el -> [(n, n)] Source

ledgePairs :: EdgeType et => Graph et n nl el -> [(n, n, el)] Source

Graph construction

empty :: Graph et n nl el Source

mkGraph :: ValidGraph et n => [(n, nl)] -> [(n, n, el)] -> Graph et n nl el Source

Assumes all nodes are in the node list.

buildGr :: ValidGraph et n => [Context (AdjType et) n nl el] -> Graph et n nl el Source

Assumes the Contexts describe a graph in total, with the outermost one first (i.e. buildGr (c:cs) == c merge buildGr cs).

insNode :: ValidGraph et n => n -> nl -> Graph et n nl el -> Graph et n nl el Source

insEdge :: ValidGraph et n => (n, n, el) -> Graph et n nl el -> (Edge, Graph et n nl el) Source

Merging

type Mergeable et n nl el ctxt = (ValidGraph et n, ToContext ctxt, ValidContext et n nl el ctxt) Source

merge :: ValidGraph et n => Context (AdjType et) n nl el -> Graph et n nl el -> Graph et n nl el Source

mergeAs :: Mergeable et n nl el ctxt => ctxt -> Graph et n nl el -> Graph et n nl el Source

Graph deconstruction

delNode :: ValidGraph et n => n -> Graph et n nl el -> Graph et n nl el Source

delEdge :: ValidGraph et n => Edge -> Graph et n nl el -> Graph et n nl el Source

delEdgeLabel :: (ValidGraph et n, Eq el) => (n, n, el) -> Graph et n nl el -> Graph et n nl el Source

delEdgesBetween :: ValidGraph et n => n -> n -> Graph et n nl el -> Graph et n nl el Source

Matching

type Matchable et n nl el ctxt = (ValidGraph et n, FromContext ctxt, ValidContext et n nl el ctxt) Source

match :: ValidGraph et n => n -> Graph et n nl el -> Maybe (Context (AdjType et) n nl el, Graph et n nl el) Source

Note that for any loops, the resultant edge will only appear once in the output cAdj field.

matchAs :: Matchable et n nl el ctxt => n -> Graph et n nl el -> Maybe (ctxt, Graph et n nl el) Source

matchAny :: ValidGraph et n => Graph et n nl el -> Maybe (Context (AdjType et) n nl el, Graph et n nl el) Source

matchAnyAs :: Matchable et n nl el ctxt => Graph et n nl el -> Maybe (ctxt, Graph et n nl el) Source

Manipulation

nmap :: ValidGraph et n => (nl -> nl') -> Graph et n nl el -> Graph et n nl' el Source

nmapFor :: ValidGraph et n => (nl -> nl) -> Graph et n nl el -> n -> Graph et n nl el Source

emap :: ValidGraph et n => (el -> el') -> Graph et n nl el -> Graph et n nl el' Source

emapFor :: ValidGraph et n => (el -> el) -> Graph et n nl el -> Edge -> Graph et n nl el Source