Skip to content

Instantly share code, notes, and snippets.

@m-renaud
Last active February 27, 2016 19:50
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save m-renaud/6712666db195261b10a3 to your computer and use it in GitHub Desktop.
Save m-renaud/6712666db195261b10a3 to your computer and use it in GitHub Desktop.
Generic graphs with type families instead of functional dependencies.
{- | Based on http://www.osl.iu.edu/publications/prints/2005/garcia05:_extended_comparing05.pdf -}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
import Data.Array
----------------------------------------
-- Typeclass definitions.
----------------------------------------
{- | The 'GraphEdge' class is types that can be used as edges in a graph.
It defines an associated 'VertexType', and two function to retrieve the source
vertex and the target vertex.
Minimal complete definition: 'src', 'tgt'.
-}
class GraphEdge e where
type VertexType e :: *
src :: e -> VertexType e
tgt :: e -> VertexType e
{- | The 'IncidenceGraph' class is types that can yield out edges given a
vertex. It defines an assocaited 'EdgeType' for the graph.
We constraint the associated 'EdgeType' to be an instance of 'GraphEdge'.
Minimal complete definition: 'outEdges'.
-}
class (GraphEdge (EdgeType g)) => IncidenceGraph g where
type EdgeType g :: *
outEdges :: VertexType (EdgeType g) -> g -> [EdgeType g]
outDegree :: VertexType (EdgeType g) -> g -> Int
outDegree = (length .) . outEdges
{- | The 'BidirectionalGraph' class extends the 'IncidenceGraph' class and adds
access to the in edges of a vertex.
Minimal complete definition: 'inEdges', 'degree'.
-}
class IncidenceGraph g => BidirectionalGraph g where
inEdges :: VertexType (EdgeType g) -> g -> [EdgeType g]
inDegree :: VertexType (EdgeType g) -> g -> Int
degree :: VertexType (EdgeType g) -> g -> Int
inDegree = (length .) . inEdges
{- | The 'VertexListGraph' class is types that can expose the complete list of
vertices.
Minimal complete definition: 'vertices'.
-}
class VertexListGraph g where
vertices :: g -> [VertexType (EdgeType g)]
numVertices :: g -> Int
numVertices = length . vertices
----------------------------------------
-- Data definitions.
----------------------------------------
data AdjacencyList = AdjacencyList (Array Int [Int]) deriving (Read, Show)
data Vertex = Vertex Int deriving (Eq, Ord, Read, Show)
data Edge = Edge Int Int deriving (Eq, Ord, Read, Show)
----------------------------------------
-- Instances.
----------------------------------------
instance GraphEdge Edge where
type VertexType Edge = Int
src (Edge s _) = s
tgt (Edge _ t) = t
instance IncidenceGraph AdjacencyList where
type EdgeType AdjacencyList = Edge
outEdges v (AdjacencyList adjList) = map (Edge v) outVertices
where outVertices :: [Int]
outVertices = adjList ! v
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment