haggle-0.1.0.0: A graph library offering mutable, immutable, and inductive graphs

Safe HaskellNone
LanguageHaskell2010

Data.Graph.Haggle.Classes

Contents

Synopsis

Basic Types

data Vertex Source #

An abstract representation of a vertex.

Note that the representation is currently exposed. Do not rely on this, as it is subject to change.

Instances
Eq Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

(==) :: Vertex -> Vertex -> Bool #

(/=) :: Vertex -> Vertex -> Bool #

Ord Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Show Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

NFData Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

rnf :: Vertex -> () #

Hashable Vertex Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

hashWithSalt :: Int -> Vertex -> Int #

hash :: Vertex -> Int #

data Edge Source #

An edge between two vertices.

Instances
Eq Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

(==) :: Edge -> Edge -> Bool #

(/=) :: Edge -> Edge -> Bool #

Ord Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

compare :: Edge -> Edge -> Ordering #

(<) :: Edge -> Edge -> Bool #

(<=) :: Edge -> Edge -> Bool #

(>) :: Edge -> Edge -> Bool #

(>=) :: Edge -> Edge -> Bool #

max :: Edge -> Edge -> Edge #

min :: Edge -> Edge -> Edge #

Show Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

NFData Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

rnf :: Edge -> () #

Hashable Edge Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Basic

Methods

hashWithSalt :: Int -> Edge -> Int #

hash :: Edge -> Int #

Mutable Graphs

class MGraph g where Source #

The interface supported by a mutable graph.

Associated Types

type ImmutableGraph g Source #

The type generated by freezeing a mutable graph

Methods

getVertices :: (PrimMonad m, MonadRef m) => g m -> m [Vertex] Source #

List all of the vertices in the graph.

getSuccessors :: (PrimMonad m, MonadRef m) => g m -> Vertex -> m [Vertex] Source #

List the successors for the given Vertex.

getOutEdges :: (PrimMonad m, MonadRef m) => g m -> Vertex -> m [Edge] Source #

Get all of the Edges with the given Vertex as their source.

countVertices :: (PrimMonad m, MonadRef m) => g m -> m Int Source #

Return the number of vertices in the graph

countEdges :: (PrimMonad m, MonadRef m) => g m -> m Int Source #

Return the number of edges in the graph

checkEdgeExists :: (PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m Bool Source #

Edge existence test; this has a default implementation, but can be overridden if an implementation can support a better-than-linear version.

freeze :: (PrimMonad m, MonadRef m) => g m -> m (ImmutableGraph g) Source #

Freeze the mutable graph into an immutable graph.

Instances
MGraph MDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Associated Types

type ImmutableGraph MDigraph :: Type Source #

MGraph MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Associated Types

type ImmutableGraph MBiDigraph :: Type Source #

MGraph MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

Associated Types

type ImmutableGraph MSimpleBiDigraph :: Type Source #

MGraph g => MGraph (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type ImmutableGraph (VertexLabeledMGraph g nl) :: Type Source #

MGraph g => MGraph (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type ImmutableGraph (EdgeLabeledMGraph g el) :: Type Source #

MGraph g => MGraph (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type ImmutableGraph (LabeledMGraph g nl el) :: Type Source #

Methods

getVertices :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m [Vertex] Source #

getSuccessors :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Vertex] Source #

getOutEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Edge] Source #

countVertices :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m Int Source #

countEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m Int Source #

checkEdgeExists :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> Vertex -> m Bool Source #

freeze :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> m (ImmutableGraph (LabeledMGraph g nl el)) Source #

class MGraph g => MAddEdge g where Source #

Methods

addEdge :: (PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m (Maybe Edge) Source #

Add a new Edge to the graph from src to dst. If either the source or destination is not in the graph, returns Nothing. Otherwise, the Edge reference is returned.

Instances
MAddEdge MDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Methods

addEdge :: (PrimMonad m, MonadRef m) => MDigraph m -> Vertex -> Vertex -> m (Maybe Edge) Source #

MAddEdge MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Methods

addEdge :: (PrimMonad m, MonadRef m) => MBiDigraph m -> Vertex -> Vertex -> m (Maybe Edge) Source #

MAddEdge MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

MAddEdge g => MAddEdge (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Methods

addEdge :: (PrimMonad m, MonadRef m) => VertexLabeledMGraph g nl m -> Vertex -> Vertex -> m (Maybe Edge) Source #

class MGraph g => MAddVertex g where Source #

Methods

addVertex :: (PrimMonad m, MonadRef m) => g m -> m Vertex Source #

Add a new Vertex to the graph, returning its handle.

class MGraph g => MRemovable g where Source #

An interface for graphs that allow vertex and edge removal. Note that implementations are not required to reclaim storage from removed vertices (just make them inaccessible).

Methods

removeVertex :: (PrimMonad m, MonadRef m) => g m -> Vertex -> m () Source #

removeEdgesBetween :: (PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> m () Source #

removeEdge :: (PrimMonad m, MonadRef m) => g m -> Edge -> m () Source #

class MGraph g => MBidirectional g where Source #

An interface for graphs that support looking at predecessor (incoming edges) efficiently.

Methods

getPredecessors :: (PrimMonad m, MonadRef m) => g m -> Vertex -> m [Vertex] Source #

getInEdges :: (PrimMonad m, MonadRef m) => g m -> Vertex -> m [Edge] Source #

Instances
MBidirectional MBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

MBidirectional MSimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

MBidirectional g => MBidirectional (VertexLabeledMGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

MBidirectional g => MBidirectional (EdgeLabeledMGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

MBidirectional g => MBidirectional (LabeledMGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Methods

getPredecessors :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Vertex] Source #

getInEdges :: (PrimMonad m, MonadRef m) => LabeledMGraph g nl el m -> Vertex -> m [Edge] Source #

class MGraph g => MLabeledEdge g where Source #

Minimal complete definition

unsafeGetEdgeLabel, addLabeledEdge

Associated Types

type MEdgeLabel g Source #

Methods

getEdgeLabel :: (PrimMonad m, MonadRef m) => g m -> Edge -> m (Maybe (MEdgeLabel g)) Source #

unsafeGetEdgeLabel :: (PrimMonad m, MonadRef m) => g m -> Edge -> m (MEdgeLabel g) Source #

addLabeledEdge :: (PrimMonad m, MonadRef m) => g m -> Vertex -> Vertex -> MEdgeLabel g -> m (Maybe Edge) Source #

class MGraph g => MLabeledVertex g where Source #

Minimal complete definition

getVertexLabel, addLabeledVertex

Associated Types

type MVertexLabel g Source #

Immutable Graphs

class Graph g where Source #

The basic interface of immutable graphs.

Minimal complete definition

vertices, edges, successors, outEdges, maxVertexId, isEmpty

Methods

vertices :: g -> [Vertex] Source #

edges :: g -> [Edge] Source #

successors :: g -> Vertex -> [Vertex] Source #

outEdges :: g -> Vertex -> [Edge] Source #

maxVertexId :: g -> Int Source #

isEmpty :: g -> Bool Source #

edgesBetween :: g -> Vertex -> Vertex -> [Edge] Source #

This has a default implementation in terms of outEdges, but is part of the class so that instances can offer a more efficient implementation when possible.

Instances
Graph Digraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Graph BiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Graph SimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

Graph (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

Graph g => Graph (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Graph g => Graph (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Graph g => Graph (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

class Graph g => Thawable g where Source #

Associated Types

type MutableGraph g :: (* -> *) -> * Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => g -> m (MutableGraph g m) Source #

Instances
Thawable Digraph Source # 
Instance details

Defined in Data.Graph.Haggle.Digraph

Associated Types

type MutableGraph Digraph :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => Digraph -> m (MutableGraph Digraph m) Source #

Thawable BiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.BiDigraph

Associated Types

type MutableGraph BiDigraph :: (Type -> Type) -> Type Source #

Thawable SimpleBiDigraph Source # 
Instance details

Defined in Data.Graph.Haggle.SimpleBiDigraph

Associated Types

type MutableGraph SimpleBiDigraph :: (Type -> Type) -> Type Source #

Thawable g => Thawable (VertexLabeledGraph g nl) Source # 
Instance details

Defined in Data.Graph.Haggle.VertexLabelAdapter

Associated Types

type MutableGraph (VertexLabeledGraph g nl) :: (Type -> Type) -> Type Source #

Thawable g => Thawable (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type MutableGraph (EdgeLabeledGraph g el) :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => EdgeLabeledGraph g el -> m (MutableGraph (EdgeLabeledGraph g el) m) Source #

Thawable g => Thawable (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type MutableGraph (LabeledGraph g nl el) :: (Type -> Type) -> Type Source #

Methods

thaw :: (PrimMonad m, MonadRef m) => LabeledGraph g nl el -> m (MutableGraph (LabeledGraph g nl el) m) Source #

class Graph g => Bidirectional g where Source #

The interface for immutable graphs with efficient access to incoming edges.

Methods

predecessors :: g -> Vertex -> [Vertex] Source #

inEdges :: g -> Vertex -> [Edge] Source #

class Graph g => HasEdgeLabel g where Source #

The interface for immutable graphs with labeled edges.

Minimal complete definition

edgeLabel, labeledEdges

Associated Types

type EdgeLabel g Source #

Instances
HasEdgeLabel (PatriciaTree nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.PatriciaTree

Associated Types

type EdgeLabel (PatriciaTree nl el) :: Type Source #

Graph g => HasEdgeLabel (EdgeLabeledGraph g el) Source # 
Instance details

Defined in Data.Graph.Haggle.EdgeLabelAdapter

Associated Types

type EdgeLabel (EdgeLabeledGraph g el) :: Type Source #

Graph g => HasEdgeLabel (LabeledGraph g nl el) Source # 
Instance details

Defined in Data.Graph.Haggle.Internal.Adapter

Associated Types

type EdgeLabel (LabeledGraph g nl el) :: Type Source #

class Graph g => HasVertexLabel g where Source #

The interface for immutable graphs with labeled vertices.

Associated Types

type VertexLabel g Source #

class (HasEdgeLabel g, Bidirectional g) => BidirectionalEdgeLabel g where Source #

Minimal complete definition

Nothing

Methods

labeledInEdges :: g -> Vertex -> [(Edge, EdgeLabel g)] Source #

Inductive Graphs

class (Graph g, HasEdgeLabel g, HasVertexLabel g) => InductiveGraph g where Source #

Methods

emptyGraph :: g Source #

The empty inductive graph

match :: g -> Vertex -> Maybe (Context g, g) Source #

The call

let (c, g') = match g v

decomposes the graph into the Context c of v and the rest of the graph g'.

context :: g -> Vertex -> Maybe (Context g) Source #

Return the context of a Vertex

insertLabeledVertex :: g -> VertexLabel g -> (Vertex, g) Source #

Insert a new labeled Vertex into the graph.

insertLabeledEdge :: g -> Vertex -> Vertex -> EdgeLabel g -> Maybe (Edge, g) Source #

Must return Nothing if either the source or destination Vertex is not in the graph. Also returns Nothing if the edge already exists and the underlying graph does not support parallel edges.

Otherwise return the inserted Edge and updated graph.

deleteEdge :: g -> Edge -> g Source #

Delete the given Edge. In a multigraph, this lets you remove a single parallel edge between two vertices.

deleteEdgesBetween :: g -> Vertex -> Vertex -> g Source #

Delete all edges between a pair of vertices.

replaceLabeledEdge :: g -> Vertex -> Vertex -> EdgeLabel g -> Maybe (Edge, g) Source #

Like insertLabeledEdge, but overwrite any existing edges. Equivalent to:

let g' = deleteEdgesBetween g v1 v2
in insertLabeledEdge g v1 v2 lbl

deleteVertex :: g -> Vertex -> g Source #

Remove a Vertex from the graph

data Context g Source #

Contexts represent the "context" of a Vertex, which includes the incoming edges of the Vertex, the label of the Vertex, and the outgoing edges of the Vertex.

Constructors

Context [(EdgeLabel g, Vertex)] (VertexLabel g) [(EdgeLabel g, Vertex)]