{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.DiGraph
( DiGraph
, DiEdge
, adjacencySets
, vertices
, edges
, adjacents
, incidents
, insertEdge
, fromEdges
, insertVertex
, mapVertices
, union
, transpose
, symmetric
, fromList
, unsafeFromList
, isDiGraph
, isAdjacent
, isRegular
, isSymmetric
, isIrreflexive
, isEdge
, isVertex
, order
, size
, diSize
, symSize
, outDegree
, inDegree
, maxOutDegree
, maxInDegree
, minOutDegree
, minInDegree
, ShortestPathCache
, shortestPathCache
, shortestPath
, shortestPath_
, distance
, distance_
, diameter
, diameter_
, emptyGraph
, singleton
, clique
, pair
, triangle
, cycle
, diCycle
, line
, diLine
, petersonGraph
, twentyChainGraph
, hoffmanSingleton
) where
import Control.Arrow
import Control.DeepSeq
import Control.Monad
import Data.Foldable
import Data.Hashable (Hashable)
import qualified Data.HashMap.Strict as HM
import qualified Data.HashSet as HS
import qualified Data.List as L
import Data.Maybe
import Data.Semigroup
import Data.Traversable
import Data.Tuple
import GHC.Generics
import Numeric.Natural
import Prelude hiding (cycle)
import qualified Data.DiGraph.FloydWarshall as FW
int :: Integral a => Num b => a -> b
int = fromIntegral
{-# INLINE int #-}
type DiEdge a = (a, a)
newtype DiGraph a = DiGraph { unGraph :: HM.HashMap a (HS.HashSet a) }
deriving (Show, Eq, Ord, Generic)
deriving anyclass (NFData, Hashable)
instance (Hashable a, Eq a) => Semigroup (DiGraph a) where
(DiGraph a) <> (DiGraph b) = DiGraph (HM.unionWith (<>) a b)
{-# INLINE (<>) #-}
instance (Hashable a, Eq a) => Monoid (DiGraph a) where
mempty = DiGraph mempty
mappend = (<>)
{-# INLINE mempty #-}
{-# INLINE mappend #-}
isDiGraph :: Eq a => Hashable a => DiGraph a -> Bool
isDiGraph g@(DiGraph m) = HS.null (HS.unions (HM.elems m) `HS.difference` vertices g)
{-# INLINE isDiGraph #-}
adjacencySets :: DiGraph a -> HM.HashMap a (HS.HashSet a)
adjacencySets = unGraph
{-# INLINE adjacencySets #-}
vertices :: DiGraph a -> HS.HashSet a
vertices = HS.fromMap . HM.map (const ()) . unGraph
{-# INLINE vertices #-}
edges :: Eq a => Hashable a => DiGraph a -> HS.HashSet (DiEdge a)
edges = HS.fromList . concatMap (traverse HS.toList) . HM.toList . unGraph
{-# INLINE edges #-}
adjacents :: Eq a => Hashable a => a -> DiGraph a -> HS.HashSet a
adjacents a (DiGraph g) = g HM.! a
{-# INLINE adjacents #-}
incidents :: Eq a => Hashable a => a -> DiGraph a -> [(a, a)]
incidents a g = [ (a, b) | b <- toList (adjacents a g) ]
{-# INLINE incidents #-}
fromList :: Eq a => Hashable a => [(a,[a])] -> DiGraph a
fromList l = foldr insertVertex es (fst <$> l)
where
es = fromEdges [ (a,b) | (a, bs) <- l, b <- bs ]
{-# INLINE fromList #-}
unsafeFromList :: Eq a => Hashable a => [(a,[a])] -> DiGraph a
unsafeFromList = DiGraph . HM.map HS.fromList . HM.fromList
{-# INLINE unsafeFromList #-}
fromEdges :: Eq a => Hashable a => Foldable f => f (a, a) -> DiGraph a
fromEdges = foldr insertEdge mempty
{-# INLINE fromEdges #-}
union :: Eq a => Hashable a => DiGraph a -> DiGraph a -> DiGraph a
union = (<>)
{-# INLINE union #-}
mapVertices :: Eq b => Hashable b => (a -> b) -> DiGraph a -> DiGraph b
mapVertices f = DiGraph . HM.fromList . fmap (f *** HS.map f) . HM.toList . unGraph
{-# INLINE mapVertices #-}
transpose :: Eq a => Hashable a => DiGraph a -> DiGraph a
transpose g = (DiGraph $ mempty <$ unGraph g)
`union` (fromEdges . HS.map swap $ edges g)
symmetric :: Eq a => Hashable a => DiGraph a -> DiGraph a
symmetric g = g <> transpose g
{-# INLINE symmetric #-}
insertEdge :: Eq a => Hashable a => DiEdge a -> DiGraph a -> DiGraph a
insertEdge (a,b) = DiGraph
. HM.insertWith (<>) a [b]
. HM.insertWith (<>) b []
. unGraph
{-# INLINE insertEdge #-}
insertVertex :: Eq a => Hashable a => a -> DiGraph a -> DiGraph a
insertVertex a = DiGraph . HM.insertWith (<>) a [] . unGraph
{-# INLINE insertVertex #-}
order :: DiGraph a -> Natural
order = int . HS.size . vertices
{-# INLINE order #-}
diSize :: Eq a => Hashable a => DiGraph a -> Natural
diSize = int . HS.size . edges
{-# INLINE diSize #-}
size :: Eq a => Hashable a => DiGraph a -> Natural
size = int . HS.size . edges
{-# INLINE size #-}
symSize :: Eq a => Hashable a => DiGraph a -> Natural
symSize g = diSize (symmetric g) `div` 2
{-# INLINE symSize #-}
outDegree :: Eq a => Hashable a => DiGraph a -> a -> Natural
outDegree (DiGraph g) a = int . HS.size $ g HM.! a
{-# INLINE outDegree #-}
maxOutDegree :: Eq a => Hashable a => DiGraph a -> Natural
maxOutDegree g = maximum $ HS.map (outDegree g) (vertices g)
{-# INLINE maxOutDegree #-}
minOutDegree :: Eq a => Hashable a => DiGraph a -> Natural
minOutDegree g = minimum $ HS.map (outDegree g) (vertices g)
{-# INLINE minOutDegree #-}
inDegree :: Eq a => Hashable a => DiGraph a -> a -> Natural
inDegree g = outDegree (transpose g)
{-# INLINE inDegree #-}
maxInDegree :: Eq a => Hashable a => DiGraph a -> Natural
maxInDegree = maxOutDegree . transpose
{-# INLINE maxInDegree #-}
minInDegree :: Eq a => Hashable a => DiGraph a -> Natural
minInDegree = minOutDegree . transpose
{-# INLINE minInDegree #-}
isRegular :: DiGraph a -> Bool
isRegular = (== 1)
. length
. L.group
. fmap (HS.size . snd)
. HM.toList
. unGraph
{-# INLINE isRegular #-}
isSymmetric :: Hashable a => Eq a => DiGraph a -> Bool
isSymmetric g = all checkVertex $ HM.toList $ unGraph g
where
checkVertex (a, e) = all (\x -> isAdjacent x a g) e
{-# INLINE isSymmetric #-}
isIrreflexive :: Eq a => Hashable a => DiGraph a -> Bool
isIrreflexive = not . any (uncurry HS.member) . HM.toList . unGraph
{-# INLINE isIrreflexive #-}
isVertex :: Eq a => Hashable a => a -> DiGraph a -> Bool
isVertex a = HM.member a . unGraph
{-# INLINE isVertex #-}
isEdge :: Eq a => Hashable a => DiEdge a -> DiGraph a -> Bool
isEdge (a, b) = maybe False (HS.member b) . HM.lookup a . unGraph
{-# INLINE isEdge #-}
isAdjacent :: Eq a => Hashable a => a -> a -> DiGraph a -> Bool
isAdjacent = curry isEdge
{-# INLINE isAdjacent #-}
data ShortestPathCache a = ShortestPathCache
{ _spcMatrix :: {-# UNPACK #-} !FW.ShortestPathMatrix
, _spcIndices :: !(HM.HashMap a Int)
, _spcVertices :: !(HM.HashMap Int a)
}
deriving (Show, Eq, Ord, Generic)
deriving anyclass (NFData)
shortestPathCache :: Eq a => Hashable a => DiGraph a -> ShortestPathCache a
shortestPathCache g = ShortestPathCache m vmap rvmap
where
m = FW.floydWarshall $ FW.fromAdjacencySets (unGraph ig)
ig = mapVertices (vmap HM.!) g
vmap = HM.fromList $ zip (HS.toList $ vertices g) [0..]
rvmap = HM.fromList $ zip [0..] (HS.toList $ vertices g)
diameter :: Eq a => Hashable a => DiGraph a -> Maybe Natural
diameter = diameter_ . shortestPathCache
{-# INLINE diameter #-}
diameter_ :: ShortestPathCache a -> Maybe Natural
diameter_ (ShortestPathCache m _ _) = round <$> FW.diameter m
{-# INLINE diameter_ #-}
shortestPath :: Eq a => Hashable a => a -> a -> DiGraph a -> Maybe [a]
shortestPath src trg = shortestPath_ src trg . shortestPathCache
{-# INLINE shortestPath #-}
shortestPath_ :: Eq a => Hashable a => a -> a -> ShortestPathCache a -> Maybe [a]
shortestPath_ src trg (ShortestPathCache c m r)
= fmap ((HM.!) r) <$> FW.shortestPath c (m HM.! src) (m HM.! trg)
{-# INLINE shortestPath_ #-}
distance :: Eq a => Hashable a => a -> a -> DiGraph a -> Maybe Natural
distance src trg = distance_ src trg . shortestPathCache
{-# INLINE distance #-}
distance_ :: Eq a => Hashable a => a -> a -> ShortestPathCache a -> Maybe Natural
distance_ src trg (ShortestPathCache c m _)
= round <$> FW.distance c (m HM.! src) (m HM.! trg)
{-# INLINE distance_ #-}
emptyGraph :: Natural -> DiGraph Int
emptyGraph n = unsafeFromList [ (i, []) | i <- [0 .. int n - 1] ]
clique :: Natural -> DiGraph Int
clique i = unsafeFromList
[ (a, b)
| a <- [0 .. int i - 1]
, let b = [ x | x <- [0 .. int i - 1] , x /= a ]
]
singleton :: DiGraph Int
singleton = clique 1
pair :: DiGraph Int
pair = clique 2
triangle :: DiGraph Int
triangle = clique 3
diCycle :: Natural -> DiGraph Int
diCycle n = unsafeFromList [ (a, [(a + 1) `mod` int n]) | a <- [0 .. int n - 1] ]
cycle :: Natural -> DiGraph Int
cycle = symmetric . diCycle
diLine :: Natural -> DiGraph Int
diLine n = unsafeFromList [ (a, [ a + 1 | a /= int n - 1]) | a <- [0 .. int n - 1] ]
line :: Natural -> DiGraph Int
line = symmetric . diLine
petersonGraph :: DiGraph Int
petersonGraph = DiGraph
[ (0, [2,3,5])
, (1, [3,4,6])
, (2, [4,0,7])
, (3, [0,1,8])
, (4, [1,2,9])
, (5, [0,6,9])
, (6, [1,5,7])
, (7, [2,6,8])
, (8, [3,7,9])
, (9, [4,8,5])
]
twentyChainGraph :: DiGraph Int
twentyChainGraph = pentagram `union` decagon `union` connections
where
pentagram = mapVertices (+ 5) $ pentagon2pentagram $ cycle 5
decagon = mapVertices (+ 10) $ cycle 10
connections = fromEdges $ HS.fromList $ mconcat
[ [(i, x), (x, i)]
| i <- [0..4]
, x <- [i + 5, i + 10, i + 15]
]
pentagon2pentagram = mapVertices $ \case
0 -> 0
1 -> 3
2 -> 1
3 -> 4
4 -> 2
_ -> error "invalid vertex"
hoffmanSingleton :: DiGraph Int
hoffmanSingleton = pentagons `union` pentagrams `union` connections
where
pentagons = mconcat
[ mapVertices (p_off i) $ cycle 5 | i <- [0 .. 4] ]
pentagrams = mconcat
[ mapVertices (q_off i) $ pentagon2pentagram $ cycle 5 | i <- [0 .. 4] ]
p_off h = (+) (25 + 5 * h)
q_off i = (+) (5 * i)
pentagon2pentagram = mapVertices $ \case
0 -> 0
1 -> 3
2 -> 1
3 -> 4
4 -> 2
_ -> error "invalid vertex"
connections = fromEdges $ HS.fromList $ mconcat
[ [(a, b), (b, a)]
| h <- [0 .. 4]
, j <- [0 .. 4]
, let a = p_off h j
, i <- [0 .. 4]
, let b = q_off i ((h * i + j) `mod` 5)
]