Skip to content

Commit

Permalink
Merge pull request #33 from thisiswhereitype/master
Browse files Browse the repository at this point in the history
pangraph-0.2.0
  • Loading branch information
thisiswhereitype authored Sep 13, 2018
2 parents 431c636 + 375d0d3 commit 22315a7
Show file tree
Hide file tree
Showing 19 changed files with 377 additions and 196 deletions.
46 changes: 23 additions & 23 deletions README.md
Original file line number Diff line number Diff line change
@@ -1,48 +1,43 @@
# pangraph [![Build Status](https://travis-ci.org/tuura/pangraph.svg?branch=master)](https://travis-ci.org/tuura/pangraph)

Pangraph is a Haskell library which offers for parsing and serializations for graph files. As well as conversions to other Haskell graph formats. An example format is [GraphML](http://graphml.graphdrawing.org/). A graphml file
Pangraph is a Haskell library which offers parsing and serializations for graph files. As well as conversions to other Haskell graph formats. An example format is [GraphML](http://graphml.graphdrawing.org/). A graphml file
could for example represent the following graph, with vertices from `A` to `E` and connections, the edges, between them.
![a-sample-graph](examples/graphs/network.svg)
Source:
[Mokhov, et al. (2017)](https://github.com/tuura/papers/tree/3460a889ebcf8e21bbde54f9cb7fc3662a6c7ff8/fdl-2017 "Newcastle University")

## Contents
1. [Usage](#usage)
2. [Graph File Support](#graph-file-support)
3. [Library support](#graph-library-support)
2. [Building](#building)
3. [Graph File Support](#graph-file-support)
4. [Library support](#graph-library-support)

## Usage
Pangraph offers an API in the module `Pangraph` for construction and
Pangraph provides an API in the module `Pangraph` for construction and
manipulation of graphs. The parsers in the library use this module to
generate pangraphs. Parsers and serializers are imported from modules
individually. This example shows imports for GraphML.
```haskell
import Pangraph.GraphML.Parser (parse)
import Pangraph.GraphML.Writer (write)
```
Usage of multiple file types in the same module will require qualified imports.
## Examples
See `src/Pangraph/Examples` for further examples.
### Sample Parsing a Graph
Repeated here is code from `src/Pangraph/Examples/Reading.hs`
```haskell
module Pangraph.Examples.Reading where

import Prelude hiding (readFile)

import Data.ByteString (readFile)
Usage of multiple file types in the same module will require
qualified imports. Please see `src/Pangraph/Examples` for further examples.

import Pangraph
import qualified Pangraph.GraphML.Parser as GraphML_P

main :: IO ()
main = do
fileName <- getLine
file <- readFile fileName
print (GraphML_P.parse file)
## Building
```haskell
stack build
stack test
```

## Graph File Support

### [GML](https://en.wikipedia.org/wiki/Graph_Modelling_Language)
GML files are currently:
- Parsing: Ok
- Writing: Ok
Node: See `Pangraph.Gml.*`

### [GraphML](http://graphml.graphdrawing.org/)
GraphML files are currently:
- Parsing: Ok
Expand All @@ -62,3 +57,8 @@ Workcraft files are currently:
Currently implements:
- Convert: `Pangraph.Containers`
- Revert: **Unimplemented**

### [FGL](https://hackage.haskell.org/package/fgl)
Currently implements:
- Convert: `Pangraph.FGL`
- Revert: **Unimplemented**
20 changes: 20 additions & 0 deletions changelog.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
# Changelog

pangraph-0.2.0
* Addition of conversion and revert for FGL.
* Addition of Parser, Serializer and AST for GML.
* Change `Edge` types to now only construct with a `VertexID` type.
* Change `edgeEndpoints` to return VertexID.

pangraph-0.1.2 141360fbc2b6ca232ce91a9b14aa9a626082ba92 08/06/2018
Note: First Hackage release which follows correct cabal versioning increments.
* Addition of Containers (convert).
* Bump to Stack LTS.
* Update to Algebraic Graphs to build with more versions.

pangraph-0.1.1.5 49bc8a38842256b7fb7c285725dcfb6dfb03cfcb 03/02/2018
Note: First hackage release, prior to this on the repo there are many issues with commits.
Note: Commit date earlier.
Note: This list is of all features up to this point.
* Parser and serlizer for subset of Graphml.
* Implementation of Algebraic Graphs.
10 changes: 6 additions & 4 deletions pangraph.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: pangraph
version: 0.1.2
version: 0.2.0
synopsis: A set of parsers for graph languages and conversions to
graph libaries.
description: A package allowing parsing of graph files into graph
Expand All @@ -26,10 +26,12 @@ library
, Pangraph.GraphML.Parser
, Pangraph.GraphML.Writer
, Pangraph.Internal.XMLTemplate
, Pangraph.Internal.HexmlExtra
, Pangraph.Examples.Reading
, Pangraph.Examples.Writing
, Pangraph.Examples.ToContainersGraph
, Pangraph.Examples.SampleGraph
, Pangraph.Internal.ProtoGraph
, Pangraph.Examples.Gml
, Pangraph.Gml.Ast
, Pangraph.Gml.Parser
Expand All @@ -38,13 +40,13 @@ library
, bytestring
, hexml
, containers
, algebraic-graphs == 0.1.1.*
, fgl == 5.6.0.0
, algebraic-graphs
, fgl
, attoparsec
, text
, html-entities
default-language: Haskell2010
GHC-options: -Wall -fwarn-tabs -O2
GHC-options: -Wall -fwarn-tabs

test-suite pangraph-test
type: exitcode-stdio-1.0
Expand Down
79 changes: 43 additions & 36 deletions src/Pangraph.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,17 @@
{-|
Module : Pangraph
Description : Exports the core intermediate type for graph representation.
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.
-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}

module Pangraph (
-- * Abstract Types
Pangraph, Edge, Vertex, Attribute,
Key, Value, VertexID, EdgeID,
Key, Value, VertexID, EdgeID, MalformedEdge,

-- * Constructors
makePangraph, makeEdge, makeVertex,
Expand All @@ -26,20 +33,20 @@ import qualified Algebra.Graph.Class as Alga

-- | The 'Pangraph' type is the core intermediate type between abstract representations of graphs.
data Pangraph = Pangraph
{ vertices' :: Map VertexID Vertex
, edges' :: Map EdgeID Edge
} deriving (Eq)
{ vertices' :: Map VertexID Vertex
, edges' :: Map EdgeID Edge
} deriving (Eq)
-- | A Vertex holds ['Attribute'] and must have a unique 'VertexID' to be constructed with 'makeVertex'.
data Vertex = Vertex
{ vertexID' :: VertexID
, vertexAttributes' :: [Attribute]
} deriving (Eq)
{ vertexID' :: VertexID
, vertexAttributes' :: [Attribute]
} deriving (Eq)
-- | Edges also reqiure ['Attribute'] and a tuple of 'Vertex' passed as connections to be constructed with 'makeEdge'
data Edge = Edge
{ edgeID' :: Maybe EdgeID
, edgeAttributes' :: [Attribute]
, endpoints' :: (Vertex, Vertex)
} deriving (Eq)
{ edgeID' :: Maybe EdgeID
, endpoints' :: (VertexID, VertexID)
, edgeAttributes' :: [Attribute]
} deriving (Eq)

-- | A type exposed for lookup in the resulting lists.
type EdgeID = Int
Expand All @@ -52,49 +59,49 @@ type Key = BS.ByteString
-- | The 'Value' in the tuple that makes up 'Attribute'.
type Value = BS.ByteString

type MalformedEdge = (Edge, (Maybe Vertex, Maybe Vertex))
type MalformedEdge = (Edge, (Maybe VertexID, Maybe VertexID))

instance Show Pangraph where
show p = "makePangraph " ++ show (Map.elems (vertices' p)) ++ " " ++ show (Map.elems (edges' p))
show p = "makePangraph " ++ show (Map.elems (vertices' p)) ++ " " ++ show (Map.elems (edges' p))

instance Show Vertex where
show (Vertex i as) = unwords ["makeVertex", show i, show as]
show (Vertex i as) = unwords ["makeVertex", show i, show as]

instance Show Edge where
show (Edge _ as e) = unwords ["makeEdge", show as, show e]
show (Edge _ e as) = unwords ["makeEdge", show e, show as]

instance Alga.ToGraph Pangraph where
type ToVertex Pangraph = Vertex
toGraph p = Alga.vertices (vertexList p) `Alga.overlay` Alga.edges (map edgeEndpoints $ edgeList p)
type ToVertex Pangraph = VertexID
toGraph p = Alga.vertices (map vertexID . vertexList $ p) `Alga.overlay` Alga.edges (map edgeEndpoints $ edgeList p)

-- * List based constructors

-- | Takes lists of 'Vertex' and 'Edge' to produce 'Just Pangraph' if the graph is correctly formed.
makePangraph :: [Vertex] -> [Edge] -> Maybe Pangraph
makePangraph vs es = case verifyGraph vertexMap es of
[] -> Just $ Pangraph vertexMap edgeMap
_ -> Nothing
where
vertexMap :: Map VertexID Vertex
vertexMap = Map.fromList $ zip (map vertexID vs) vs
edgeMap :: Map EdgeID Edge
edgeMap = Map.fromList indexEdges
indexEdges :: [(EdgeID, Edge)]
indexEdges = map (\ (i, Edge _ as a) -> (i, Edge (Just i) as a )) $ zip [0..] es
[] -> (Just . Pangraph vertexMap) edgeMap
_ -> Nothing
where
vertexMap :: Map VertexID Vertex
vertexMap = Map.fromList $ zip (map vertexID vs) vs
edgeMap :: Map EdgeID Edge
edgeMap = Map.fromList indexEdges
indexEdges :: [(EdgeID, Edge)]
indexEdges = map (\(i, Edge _ a as) -> (i, Edge (Just i) a as )) $ zip [0..] es

verifyGraph :: Map VertexID Vertex -> [Edge] -> [MalformedEdge]
verifyGraph vs = mapMaybe (\e -> lookupEndpoints (e, edgeEndpoints e))
where
lookupEndpoints :: (Edge, (Vertex, Vertex)) -> Maybe MalformedEdge
verifyGraph vs = let
lookupEndpoints :: (Edge, (VertexID, VertexID)) -> Maybe MalformedEdge
lookupEndpoints (e, (v1,v2)) =
case (Map.lookup (vertexID v1) vs, Map.lookup (vertexID v2) vs) of
(Just _ , Just _) -> Nothing
(Nothing, Just _) -> Just (e, (Just v1, Nothing))
(Just _ , Nothing) -> Just (e, (Nothing, Just v2))
(Nothing, Nothing) -> Just (e, (Just v1, Just v2))
case (Map.lookup v1 vs, Map.lookup v2 vs) of
(Just _ , Just _) -> Nothing
(Nothing, Just _) -> Just (e, (Just v1, Nothing))
(Just _ , Nothing) -> Just (e, (Nothing, Just v2))
(Nothing, Nothing) -> Just (e, (Just v1, Just v2))
in mapMaybe (\e -> lookupEndpoints (e, edgeEndpoints e))

-- | Edge constructor
makeEdge :: [Attribute] -> (Vertex, Vertex) -> Edge
makeEdge :: (VertexID, VertexID) -> [Attribute] -> Edge
makeEdge = Edge Nothing

-- | Vertex constructor
Expand Down Expand Up @@ -130,7 +137,7 @@ vertexAttributes :: Vertex -> [Attribute]
vertexAttributes = vertexAttributes'

-- | Returns the endpoint of tupled 'Vertex' of an 'Edge'
edgeEndpoints :: Edge -> (Vertex, Vertex)
edgeEndpoints :: Edge -> (VertexID, VertexID)
edgeEndpoints = endpoints'

-- | Returns the EdgeID if it has one. 'Edge's are given a new 'EdgeID' when they are passed and retrived from a 'Pangraph'
Expand Down
34 changes: 17 additions & 17 deletions src/Pangraph/Containers.hs
Original file line number Diff line number Diff line change
@@ -1,39 +1,39 @@
{-|
Module : Pangraph.Containers
Description : Convert `Pangraph` into a CGraph.Graph
-}
module Pangraph.Containers
( convert
) where

import Pangraph
import qualified Data.Graph as CGraph

import Data.Maybe (fromMaybe)
import Data.List (groupBy, sort)
import Control.Arrow ((***))
import Data.Maybe (fromMaybe)

import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import qualified Data.Graph as CGraph
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map

-- | Transforms a 'Pangraph' in a 'CGraph.Graph'.
-- | Transforms a 'Pangraph' into a 'CGraph.Graph'.
convert :: Pangraph -> (CGraph.Graph, CGraph.Vertex -> (Vertex, VertexID, [VertexID]), VertexID -> Maybe CGraph.Vertex)
convert p = CGraph.graphFromEdges getVertices
where
-- A helper function for getting the IDs of endpoints.
edgeEndpointIDs :: Edge -> (VertexID, VertexID)
edgeEndpointIDs e = (vertexID *** vertexID) $ edgeEndpoints e

convert p = let
-- Create an Edge Map using VertexID grouping edge sources together.
edgeMap :: Map VertexID [VertexID]
edgeMap = (Map.fromList . groupIDs) $ map edgeEndpointIDs $ edgeList p
edgeMap = (Map.fromList . groupIDs . map edgeEndpoints . edgeList) p

-- Lookup the edges for this vertex. Returning empty list on Nothing.
-- Lookup the edges for this vertex. Returning empty list on Nothing. Which means there are no outgoing arcs.
vertexConnections :: Vertex -> [VertexID]
vertexConnections v = fromMaybe [] (Map.lookup (vertexID v) edgeMap)

-- Convert Pangraph Vertex into a form ready to collect Edges from the Pangraph
getVertices :: [(Vertex, VertexID, [VertexID])]
getVertices = map (\v ->(v, vertexID v, vertexConnections v)) $ vertexList p
in CGraph.graphFromEdges getVertices

groupIDs :: [(VertexID, VertexID)] -> [(VertexID, [VertexID])]
groupIDs vs = map (\ts -> (fst $ head ts, map snd ts)) groupedEdges
where
groupIDs endPoints =let
groupedEdges :: [[(VertexID, VertexID)]]
groupedEdges = groupBy (\a b -> fst a == fst b) $ sort vs
groupedEdges = groupBy (\a b -> fst a == fst b) (sort endPoints)
in map (\ts -> (fst $ head ts, map snd ts)) groupedEdges
10 changes: 4 additions & 6 deletions src/Pangraph/Examples/SampleGraph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,17 +5,15 @@ module Pangraph.Examples.SampleGraph
) where

import Pangraph
import Data.Maybe(fromJust)

smallGraph :: Pangraph
smallGraph = case graph of
Just p -> p
Nothing -> error "Small graph literal failed to construct."
smallGraph = fromJust graph
where
graph =
makePangraph
[makeVertex "n0" [("id","n0")]
,makeVertex "n1" [("id","n1")]
,makeVertex "n2" [("id","n2")]]
[makeEdge [("source","n0"),("target","n2")]
(makeVertex "n0" [("id","n0")]
,makeVertex "n2" [("id","n2")])]
[makeEdge ("n0", "n2")
[("source","n0"),("target","n2")]]
Loading

0 comments on commit 22315a7

Please sign in to comment.