Commit 9beab9e7 authored by Jean-Baptiste Mazon's avatar Jean-Baptiste Mazon

add articulation points and bridges

parent f10801d3
...@@ -12,6 +12,9 @@ module IGraph.Algorithms.Structure ...@@ -12,6 +12,9 @@ module IGraph.Algorithms.Structure
, isConnected , isConnected
, isStronglyConnected , isStronglyConnected
, decompose , decompose
, articulationPoints
, bridges
-- * Topological Sorting, Directed Acyclic Graphs
, isDag , isDag
, topSort , topSort
, topSortUnsafe , topSortUnsafe
...@@ -192,6 +195,27 @@ decompose gr = unsafePerformIO $ allocaVectorPtr $ \ptr -> do ...@@ -192,6 +195,27 @@ decompose gr = unsafePerformIO $ allocaVectorPtr $ \ptr -> do
, `Int' , `Int'
} -> `CInt' void- #} } -> `CInt' void- #}
-- | Find the articulation points in a graph.
articulationPoints :: Graph d v e -> [Node]
articulationPoints gr = unsafePerformIO $ allocaVector $ \res -> do
igraphArticulationPoints (_graph gr) res
toNodes res
{-#INLINE igraphArticulationPoints #-}
{#fun igraph_articulation_points as ^
{ `IGraph'
, castPtr `Ptr Vector'
} -> `CInt' void- #}
-- ^ Find all bridges in a graph.
bridges :: Graph d v e -> [Edge]
bridges gr = unsafePerformIO $ allocaVector $ \res -> do
igraphBridges (_graph gr) res
map (getEdgeByEid gr) <$> toNodes res
{-# INLINE igraphBridges #-}
{#fun igraph_bridges as ^
{ `IGraph'
, castPtr `Ptr Vector'
} -> `CInt' void- #}
-- | Checks whether a graph is a directed acyclic graph (DAG) or not. -- | Checks whether a graph is a directed acyclic graph (DAG) or not.
isDag :: Graph d v e -> Bool isDag :: Graph d v e -> Bool
......
...@@ -27,6 +27,8 @@ tests = testGroup "Algorithms" ...@@ -27,6 +27,8 @@ tests = testGroup "Algorithms"
, radiusTest , radiusTest
, subGraphs , subGraphs
, decomposeTest , decomposeTest
, articulationTest
, bridgeTest
, pagerankTest , pagerankTest
, kleinbergTest , kleinbergTest
] ]
...@@ -124,6 +126,18 @@ decomposeTest = testGroup "Decompose" ...@@ -124,6 +126,18 @@ decomposeTest = testGroup "Decompose"
, (8,9), (9,10) ] , (8,9), (9,10) ]
gr = mkGraph (replicate 11 ()) $ zip es $ repeat () :: Graph 'U () () gr = mkGraph (replicate 11 ()) $ zip es $ repeat () :: Graph 'U () ()
articulationTest :: TestTree
articulationTest = testCase "Articulation points" $
articulationPoints (star 3) @?= [0]
bridgeTest :: TestTree
bridgeTest = testCase "Bridges" $ edgeLab g <$> bridges g @?= ["bridge"]
where g = fromLabeledEdges @'U
[ (("a","b"),"ab") , (("b","c"),"bc") , (("c","a"),"ca")
, (("i","j"),"ij") , (("j","k"),"jk") , (("k","i"),"ki")
, (("a","i"),"bridge")
]
{- {-
communityTest :: TestTree communityTest :: TestTree
communityTest = testGroup "Community" communityTest = testGroup "Community"
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment