pangraph-0.2.1: A set of parsers for graph languages and conversions to graph libaries.

Safe HaskellNone
LanguageHaskell2010

Pangraph

Contents

Description

See Pangraph for the type which provides a guaranteed well-formed graph once constructed. The rest of the modules provides constructors and getters on this type.

Synopsis

Abstract Types

data Pangraph Source #

The Pangraph type is the core intermediate type between abstract representations of graphs.

Instances
Eq Pangraph Source # 
Instance details

Defined in Pangraph

Show Pangraph Source # 
Instance details

Defined in Pangraph

ToGraph Pangraph Source # 
Instance details

Defined in Pangraph

Associated Types

type ToVertex Pangraph :: * #

Methods

toGraph :: Pangraph -> Graph (ToVertex Pangraph) #

foldg :: r -> (ToVertex Pangraph -> r) -> (r -> r -> r) -> (r -> r -> r) -> Pangraph -> r #

isEmpty :: Pangraph -> Bool #

size :: Pangraph -> Int #

hasVertex :: ToVertex Pangraph -> Pangraph -> Bool #

hasEdge :: ToVertex Pangraph -> ToVertex Pangraph -> Pangraph -> Bool #

vertexCount :: Pangraph -> Int #

edgeCount :: Pangraph -> Int #

vertexList :: Pangraph -> [ToVertex Pangraph] #

edgeList :: Pangraph -> [(ToVertex Pangraph, ToVertex Pangraph)] #

vertexSet :: Pangraph -> Set (ToVertex Pangraph) #

vertexIntSet :: Pangraph -> IntSet #

edgeSet :: Pangraph -> Set (ToVertex Pangraph, ToVertex Pangraph) #

preSet :: ToVertex Pangraph -> Pangraph -> Set (ToVertex Pangraph) #

preIntSet :: Int -> Pangraph -> IntSet #

postSet :: ToVertex Pangraph -> Pangraph -> Set (ToVertex Pangraph) #

postIntSet :: Int -> Pangraph -> IntSet #

adjacencyList :: Pangraph -> [(ToVertex Pangraph, [ToVertex Pangraph])] #

adjacencyMap :: Pangraph -> Map (ToVertex Pangraph) (Set (ToVertex Pangraph)) #

adjacencyIntMap :: Pangraph -> IntMap IntSet #

adjacencyMapTranspose :: Pangraph -> Map (ToVertex Pangraph) (Set (ToVertex Pangraph)) #

adjacencyIntMapTranspose :: Pangraph -> IntMap IntSet #

dfsForest :: Pangraph -> Forest (ToVertex Pangraph) #

dfsForestFrom :: [ToVertex Pangraph] -> Pangraph -> Forest (ToVertex Pangraph) #

dfs :: [ToVertex Pangraph] -> Pangraph -> [ToVertex Pangraph] #

reachable :: ToVertex Pangraph -> Pangraph -> [ToVertex Pangraph] #

topSort :: Pangraph -> Maybe [ToVertex Pangraph] #

isAcyclic :: Pangraph -> Bool #

toAdjacencyMap :: Pangraph -> AdjacencyMap (ToVertex Pangraph) #

toAdjacencyMapTranspose :: Pangraph -> AdjacencyMap (ToVertex Pangraph) #

toAdjacencyIntMap :: Pangraph -> AdjacencyIntMap #

toAdjacencyIntMapTranspose :: Pangraph -> AdjacencyIntMap #

isDfsForestOf :: Forest (ToVertex Pangraph) -> Pangraph -> Bool #

isTopSortOf :: [ToVertex Pangraph] -> Pangraph -> Bool #

type ToVertex Pangraph Source # 
Instance details

Defined in Pangraph

data Edge Source #

Edges also reqiure [Attribute] and a tuple of Vertex passed as connections to be constructed with makeEdge

Instances
Eq Edge Source # 
Instance details

Defined in Pangraph

Methods

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

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

Show Edge Source # 
Instance details

Defined in Pangraph

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

data Vertex Source #

A Vertex holds [Attribute] and must have a unique VertexID to be constructed with makeVertex.

Instances
Eq Vertex Source # 
Instance details

Defined in Pangraph

Methods

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

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

Show Vertex Source # 
Instance details

Defined in Pangraph

type Attribute = (Key, Value) Source #

The type alias for storage of fields.

type Key = ByteString Source #

The Key in the tuple that makes up Attribute.

type Value = ByteString Source #

The Value in the tuple that makes up Attribute.

type VertexID = ByteString Source #

A field that is Maybe internally is exposed for lookup.

type EdgeID = Int Source #

A type exposed for lookup in the resulting lists.

Constructors

makePangraph :: [Vertex] -> [Edge] -> Maybe Pangraph Source #

Takes lists of Vertex and Edge to produce 'Just Pangraph' if the graph is correctly formed.

makeEdge :: (VertexID, VertexID) -> [Attribute] -> Edge Source #

Edge constructor

makeVertex :: VertexID -> [Attribute] -> Vertex Source #

Vertex constructor

Pangraph Getters

edgeList :: Pangraph -> [Edge] Source #

Returns the [Edge] from a Pangraph instance

vertexList :: Pangraph -> [Vertex] Source #

Returns the [Vertex] from a Pangraph instance

lookupVertex :: VertexID -> Pangraph -> Maybe Vertex Source #

Lookup of the VertexID in a Pangraph. Complexity: O(log n)

lookupEdge :: EdgeID -> Pangraph -> Maybe Edge Source #

Lookup of the EdgeID in a Pangraph. Complexity: O(log n)

Getters on Vertex and Edge

edgeAttributes :: Edge -> [Attribute] Source #

Returns the [Attribute] of an Edge

vertexAttributes :: Vertex -> [Attribute] Source #

Returns the [Attribute] list of an Edge

edgeEndpoints :: Edge -> (VertexID, VertexID) Source #

Returns the endpoint of tupled Vertex of an Edge

edgeID :: Edge -> Maybe EdgeID Source #

Returns the EdgeID if it has one. Edges are given a new EdgeID when they are passed and retrived from a Pangraph