{-# LANGUAGE ScopedTypeVariables #-}
module Data.Graph.Connectivity where
import Data.List (foldl')
import Data.Hashable
import qualified Data.Set as S
import Data.Graph.DGraph
import Data.Graph.Types
import Data.Graph.UGraph
areConnected :: forall g v e . (Graph g, Hashable v, Eq v, Ord v)
=> g v e
-> v
-> v
-> Bool
areConnected g fromV toV
| fromV == toV = True
| otherwise = search (fromV : reachableAdjacentVertices g fromV) S.empty toV
where
search :: [v] -> S.Set v -> v -> Bool
search [] _ _ = False
search (v:vs) banned v'
| v `S.member` banned = search vs banned v'
| v == v' = True
| otherwise =
search (v : reachableAdjacentVertices g v) banned' v'
|| search vs banned' v'
where banned' = v `S.insert` banned
areDisconnected :: (Graph g, Hashable v, Eq v, Ord v) => g v e -> v -> v -> Bool
areDisconnected g fromV toV = not $ areConnected g fromV toV
isIsolated :: (Graph g, Hashable v, Eq v) => g v e -> v -> Bool
isIsolated g v = vertexDegree g v == 0
isConnected :: (Graph g, Hashable v, Eq v, Ord v) => g v e -> Bool
isConnected g = go vs True
where
vs = vertices g
go _ False = False
go [] bool = bool
go (v':vs') bool =
go vs' $ foldl' (\b v -> b && areConnected g v v') bool vs
isBridgeless :: (Hashable v, Eq v, Ord v) => UGraph v e -> Bool
isBridgeless g =
foldl' (\b vs -> b && isConnected (removeEdgePair vs g)) True (edgePairs g)
isOrientable :: (Hashable v, Eq v, Ord v) => UGraph v e -> Bool
isOrientable g = isConnected g && isBridgeless g
isWeaklyConnected :: (Hashable v, Eq v, Ord v) => DGraph v e -> Bool
isWeaklyConnected = isConnected . toUndirected
isStronglyConnected :: (Hashable v, Eq v, Ord v) => DGraph v e -> Bool
isStronglyConnected = isConnected