graphs-0.7.1: A simple monadic graph library

Copyright(C) 2011 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitytype families
Safe HaskellSafe
LanguageHaskell98

Data.Graph.Class

Description

 

Documentation

class (Monad g, Eq (Vertex g), Eq (Edge g)) => Graph g where Source #

Minimal complete definition

vertexMap, edgeMap

Associated Types

type Vertex g :: * Source #

type Edge g :: * Source #

Methods

vertexMap :: a -> g (VertexMap g a) Source #

edgeMap :: a -> g (EdgeMap g a) Source #

Instances

Graph Identity Source #

The empty graph

Associated Types

type Vertex (Identity :: * -> *) :: * Source #

type Edge (Identity :: * -> *) :: * Source #

Graph g => Graph (MaybeT g) Source # 

Associated Types

type Vertex (MaybeT g :: * -> *) :: * Source #

type Edge (MaybeT g :: * -> *) :: * Source #

Methods

vertexMap :: a -> MaybeT g (VertexMap (MaybeT g) a) Source #

edgeMap :: a -> MaybeT g (EdgeMap (MaybeT g) a) Source #

Graph g => Graph (Dual g) Source # 

Associated Types

type Vertex (Dual g :: * -> *) :: * Source #

type Edge (Dual g :: * -> *) :: * Source #

Methods

vertexMap :: a -> Dual g (VertexMap (Dual g) a) Source #

edgeMap :: a -> Dual g (EdgeMap (Dual g) a) Source #

Ord i => Graph (AdjacencyList i) Source # 

Associated Types

type Vertex (AdjacencyList i :: * -> *) :: * Source #

type Edge (AdjacencyList i :: * -> *) :: * Source #

(Graph g, Monoid m) => Graph (WriterT m g) Source # 

Associated Types

type Vertex (WriterT m g :: * -> *) :: * Source #

type Edge (WriterT m g :: * -> *) :: * Source #

Methods

vertexMap :: a -> WriterT m g (VertexMap (WriterT m g) a) Source #

edgeMap :: a -> WriterT m g (EdgeMap (WriterT m g) a) Source #

(Graph g, Monoid m) => Graph (WriterT m g) Source # 

Associated Types

type Vertex (WriterT m g :: * -> *) :: * Source #

type Edge (WriterT m g :: * -> *) :: * Source #

Methods

vertexMap :: a -> WriterT m g (VertexMap (WriterT m g) a) Source #

edgeMap :: a -> WriterT m g (EdgeMap (WriterT m g) a) Source #

Graph g => Graph (StateT s g) Source # 

Associated Types

type Vertex (StateT s g :: * -> *) :: * Source #

type Edge (StateT s g :: * -> *) :: * Source #

Methods

vertexMap :: a -> StateT s g (VertexMap (StateT s g) a) Source #

edgeMap :: a -> StateT s g (EdgeMap (StateT s g) a) Source #

Graph g => Graph (StateT s g) Source # 

Associated Types

type Vertex (StateT s g :: * -> *) :: * Source #

type Edge (StateT s g :: * -> *) :: * Source #

Methods

vertexMap :: a -> StateT s g (VertexMap (StateT s g) a) Source #

edgeMap :: a -> StateT s g (EdgeMap (StateT s g) a) Source #

Graph g => Graph (IdentityT * g) Source # 

Associated Types

type Vertex (IdentityT * g :: * -> *) :: * Source #

type Edge (IdentityT * g :: * -> *) :: * Source #

(Graph g, Error e) => Graph (ErrorT e g) Source # 

Associated Types

type Vertex (ErrorT e g :: * -> *) :: * Source #

type Edge (ErrorT e g :: * -> *) :: * Source #

Methods

vertexMap :: a -> ErrorT e g (VertexMap (ErrorT e g) a) Source #

edgeMap :: a -> ErrorT e g (EdgeMap (ErrorT e g) a) Source #

Ord i => Graph (AdjacencyMatrix arr i) Source # 

Associated Types

type Vertex (AdjacencyMatrix arr i :: * -> *) :: * Source #

type Edge (AdjacencyMatrix arr i :: * -> *) :: * Source #

Graph g => Graph (ReaderT * m g) Source # 

Associated Types

type Vertex (ReaderT * m g :: * -> *) :: * Source #

type Edge (ReaderT * m g :: * -> *) :: * Source #

Methods

vertexMap :: a -> ReaderT * m g (VertexMap (ReaderT * m g) a) Source #

edgeMap :: a -> ReaderT * m g (EdgeMap (ReaderT * m g) a) Source #

(Graph g, Monoid w) => Graph (RWST r w s g) Source # 

Associated Types

type Vertex (RWST r w s g :: * -> *) :: * Source #

type Edge (RWST r w s g :: * -> *) :: * Source #

Methods

vertexMap :: a -> RWST r w s g (VertexMap (RWST r w s g) a) Source #

edgeMap :: a -> RWST r w s g (EdgeMap (RWST r w s g) a) Source #

(Graph g, Monoid w) => Graph (RWST r w s g) Source # 

Associated Types

type Vertex (RWST r w s g :: * -> *) :: * Source #

type Edge (RWST r w s g :: * -> *) :: * Source #

Methods

vertexMap :: a -> RWST r w s g (VertexMap (RWST r w s g) a) Source #

edgeMap :: a -> RWST r w s g (EdgeMap (RWST r w s g) a) Source #

liftVertexMap :: (MonadTrans t, Graph (t g), Graph g, Vertex (t g) ~ Vertex g) => a -> t g (VertexMap (t g) a) Source #

liftEdgeMap :: (MonadTrans t, Graph (t g), Graph g, Edge (t g) ~ Edge g) => a -> t g (EdgeMap (t g) a) Source #