{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Graph.Types
(
Graph(..)
, IsEdge(..)
, Edge(..)
, Arc(..)
, (<->)
, (-->)
, Weighted(..)
, Labeled(..)
, tripleToPair
, pairToTriple
, tripleOriginVertex
, tripleDestVertex
, tripleAttribute
) where
import Control.Applicative ((<*>))
import Data.Functor ((<$>))
import Data.List (foldl')
import GHC.Float (float2Double)
import GHC.Generics (Generic)
import Control.DeepSeq
import Data.Hashable
import Test.QuickCheck
class Graph g where
empty :: (Hashable v) => g v e
order :: g v e -> Int
size :: (Hashable v, Eq v) => g v e -> Int
size = length . edgePairs
density :: (Hashable v, Eq v) => g v e -> Double
density g = (2 * (e - n + 1)) / (n * (n - 3) + 2)
where
n = fromIntegral $ order g
e = fromIntegral $ size g
vertices :: g v e -> [v]
edgeTriples :: (Hashable v, Eq v) => g v e -> [(v, v, e)]
edgePairs :: (Hashable v, Eq v) => g v e -> [(v, v)]
edgePairs g = tripleToPair <$> edgeTriples g
containsVertex :: (Hashable v, Eq v) => g v e -> v -> Bool
areAdjacent :: (Hashable v, Eq v) => g v e -> v -> v -> Bool
areAdjacent g v1 v2 = containsEdgePair g (v1, v2) || containsEdgePair g (v2, v1)
adjacentVertices :: (Hashable v, Eq v) => g v e -> v -> [v]
adjacentVertices g v = tripleDestVertex <$> adjacentVertices' g v
adjacentVertices' :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)]
reachableAdjacentVertices :: (Hashable v, Eq v) => g v e -> v -> [v]
reachableAdjacentVertices g v = tripleDestVertex <$> reachableAdjacentVertices' g v
reachableAdjacentVertices' :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)]
vertexDegree :: (Hashable v, Eq v) => g v e -> v -> Int
degrees :: (Hashable v, Eq v) => g v e -> [Int]
degrees g = vertexDegree g <$> vertices g
maxDegree :: (Hashable v, Eq v) => g v e -> Int
maxDegree = maximum . degrees
minDegree :: (Hashable v, Eq v) => g v e -> Int
minDegree = minimum . degrees
avgDegree :: (Hashable v, Eq v) => g v e -> Double
avgDegree g = fromIntegral (2 * size g) / fromIntegral (order g)
insertVertex :: (Hashable v, Eq v) => v -> g v e -> g v e
insertVertices :: (Hashable v, Eq v) => [v] -> g v e -> g v e
insertVertices vs g = foldl' (flip insertVertex) g vs
containsEdgePair :: (Hashable v, Eq v) => g v e -> (v, v) -> Bool
incidentEdgeTriples :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)]
incidentEdgePairs :: (Hashable v, Eq v) => g v e -> v -> [(v, v)]
incidentEdgePairs g v = tripleToPair <$> incidentEdgeTriples g v
edgeTriple :: (Hashable v, Eq v) => g v e -> v -> v -> Maybe (v, v, e)
insertEdgeTriple :: (Hashable v, Eq v) => (v, v, e) -> g v e -> g v e
insertEdgeTriples :: (Hashable v, Eq v) => [(v, v, e)] -> g v e -> g v e
insertEdgeTriples es g = foldl' (flip insertEdgeTriple) g es
insertEdgePair :: (Hashable v, Eq v) => (v, v) -> g v () -> g v ()
insertEdgePair (v1, v2) = insertEdgeTriple (v1, v2, ())
insertEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> g v () -> g v ()
insertEdgePairs es g = foldl' (flip insertEdgePair) g es
removeVertex :: (Hashable v, Eq v) => v -> g v e -> g v e
removeVertices :: (Hashable v, Eq v) => [v] -> g v e -> g v e
removeVertices vs g = foldl' (flip removeVertex) g vs
removeEdgePair :: (Hashable v, Eq v) => (v, v) -> g v e -> g v e
removeEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> g v e -> g v e
removeEdgePairs es g = foldl' (flip removeEdgePair) g es
removeEdgePairAndVertices :: (Hashable v, Eq v) => (v, v) -> g v e -> g v e
removeEdgePairAndVertices (v1, v2) g =
removeVertex v2 $ removeVertex v1 $ removeEdgePair (v1, v2) g
isolatedVertices :: (Hashable v, Eq v) => g v e -> [v]
isolatedVertices g = filter (\v -> vertexDegree g v == 0) $ vertices g
isSimple :: (Hashable v, Eq v) => g v e -> Bool
union :: (Hashable v, Eq v) => g v e -> g v e -> g v e
intersection :: (Hashable v, Eq v, Eq e) => g v e -> g v e -> g v e
toList :: (Hashable v, Eq v) => g v e -> [(v, [(v, e)])]
fromList :: (Hashable v, Eq v) => [(v, [(v, e)])] -> g v e
fromList links = go links empty
where
go [] g = g
go ((v, es):rest) g = go
rest $
foldr
(\(v', e) g' -> insertEdgeTriple (v, v', e) g')
(insertVertex v g)
es
fromAdjacencyMatrix :: [[Int]] -> Maybe (g Int ())
class IsEdge e where
originVertex :: e v a -> v
destinationVertex :: e v a -> v
attribute :: e v a -> a
toPair :: e v a -> (v, v)
fromPair :: (v, v) -> e v ()
toTriple :: e v a -> (v, v, a)
fromTriple :: (v, v, a) -> e v a
isLoop :: (Eq v) => e v a -> Bool
data Edge v e = Edge v v e
deriving (Show, Read, Ord, Generic)
data Arc v e = Arc v v e
deriving (Show, Read, Ord, Generic)
(<->) :: (Hashable v) => v -> v -> Edge v ()
(<->) v1 v2 = Edge v1 v2 ()
(-->) :: (Hashable v) => v -> v -> Arc v ()
(-->) v1 v2 = Arc v1 v2 ()
instance (NFData v, NFData e) => NFData (Edge v e)
instance (NFData v, NFData e) => NFData (Arc v e)
instance IsEdge Edge where
originVertex (Edge v _ _) = v
destinationVertex (Edge _ v _) = v
attribute (Edge _ _ e) = e
toPair (Edge v1 v2 _) = (v1, v2)
fromPair (v1, v2) = Edge v1 v2 ()
toTriple (Edge v1 v2 e) = (v1, v2, e)
fromTriple (v1, v2, e) = Edge v1 v2 e
isLoop (Edge v1 v2 _) = v1 == v2
instance IsEdge Arc where
originVertex (Arc v _ _) = v
destinationVertex (Arc _ v _) = v
attribute (Arc _ _ e) = e
toPair (Arc fromV toV _) = (fromV, toV)
fromPair (fromV, toV) = Arc fromV toV ()
toTriple (Arc fromV toV e) = (fromV, toV, e)
fromTriple (fromV, toV, e) = Arc fromV toV e
isLoop (Arc v1 v2 _) = v1 == v2
class Weighted e where
weight :: e -> Double
class Labeled e where
label :: e -> String
instance Weighted Int where
weight = fromIntegral
instance Weighted Float where
weight = float2Double
instance Weighted Double where
weight = id
instance Labeled String where
label = id
instance Weighted (Double, String) where
weight = fst
instance Labeled (Double, String) where
label = snd
instance (Arbitrary v, Arbitrary e, Num v, Ord v) => Arbitrary (Edge v e) where
arbitrary = arbitraryEdge Edge
instance (Arbitrary v, Arbitrary e, Num v, Ord v) => Arbitrary (Arc v e) where
arbitrary = arbitraryEdge Arc
instance Functor (Edge v) where
fmap f (Edge v1 v2 e) = Edge v1 v2 $ f e
instance Functor (Arc v) where
fmap f (Arc v1 v2 e) = Arc v1 v2 $ f e
arbitraryEdge :: (Arbitrary v, Arbitrary e, Ord v, Num v)
=> (v -> v -> e -> edge) -> Gen edge
arbitraryEdge edgeType = edgeType <$> vert <*> vert <*> arbitrary
where vert = getPositive <$> arbitrary
instance (Eq v, Eq a) => Eq (Edge v a) where
(Edge v1 v2 a) == (Edge v1' v2' a') =
(a == a')
&& (v1 == v1' && v2 == v2')
|| (v1 == v2' && v2 == v1')
instance (Eq v, Eq a) => Eq (Arc v a) where
(Arc v1 v2 a) == (Arc v1' v2' a') = (a == a') && (v1 == v1' && v2 == v2')
tripleToPair :: (a, b, c) -> (a, b)
tripleToPair (a, b, _) = (a, b)
pairToTriple :: (a, b) -> (a, b, ())
pairToTriple (a, b) = (a, b, ())
tripleOriginVertex :: (v, v, e) -> v
tripleOriginVertex (v, _, _) = v
tripleDestVertex :: (v, v, e) -> v
tripleDestVertex (_, v, _) = v
tripleAttribute :: (v, v, e) -> e
tripleAttribute (_, _, e) = e