Commit f178fd98 authored by Jean-Baptiste Mazon's avatar Jean-Baptiste Mazon

add eccentricity

parent 1bc3746a
......@@ -4,6 +4,8 @@ module IGraph.Algorithms.Structure
( -- * Shortest Path Related Functions
shortestPath
, diameter
, eccentricity
-- * Graph Components
, inducedSubgraph
, isConnected
, isStronglyConnected
......@@ -11,6 +13,8 @@ module IGraph.Algorithms.Structure
, isDag
, topSort
, topSortUnsafe
-- * Auxiliary types
, Neimode(IgraphOut,IgraphIn,IgraphAll) -- not IgraphTotal
) where
import Control.Monad
......@@ -88,6 +92,25 @@ diameter graph directed unconn = unsafePerformIO $
, `Bool'
} -> `CInt' void- #}
-- | Eccentricity of some vertices.
eccentricity :: Graph d v e
-> Neimode -- ^ 'IgraphOut' to follow edges' direction,
-- 'IgraphIn' to reverse it, 'IgraphAll' to ignore
-> [Node] -- ^ vertices for which to calculate eccentricity
-> [Double]
eccentricity graph mode vids = unsafePerformIO $
allocaVector $ \res ->
withVerticesList vids $ \vs -> do
igraphEccentricity (_graph graph) res vs mode
toList res
{-# INLINE igraphEccentricity #-}
{#fun igraph_eccentricity as ^
{ `IGraph'
, castPtr `Ptr Vector'
, castPtr %`Ptr VertexSelector'
, `Neimode'
} -> `CInt' void- #}
-- | Creates a subgraph induced by the specified vertices. This function collects
-- the specified vertices and all edges between them to a new graph.
inducedSubgraph :: (Ord v, Serialize v)
......
......@@ -22,6 +22,7 @@ tests = testGroup "Algorithms"
, motifTest
, cliqueTest
, diameterTest
, eccentricityTest
, subGraphs
, decomposeTest
, pagerankTest
......@@ -64,6 +65,16 @@ diameterTest = testGroup "Diameters"
, testCase "ring" $ fst (diameter (ring 10) U False) @?= 5
]
eccentricityTest :: TestTree
eccentricityTest = testGroup "Eccentricity"
[ testCase "clique" $
eccentricity (full @'U 10 False) IgraphAll [0..9] @?= replicate 10 1
, testCase "star" $
eccentricity (star 10) IgraphAll [0..9] @?= (1 : replicate 9 2)
, testCase "ring" $
eccentricity (ring 10) IgraphAll [0..9] @?= replicate 10 5
]
subGraphs :: TestTree
subGraphs = testGroup "generate induced subgraphs"
[ testCase "" $ test case1 ]
......
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