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

add averagePathLength, radius

parent f178fd98
...@@ -3,8 +3,10 @@ ...@@ -3,8 +3,10 @@
module IGraph.Algorithms.Structure module IGraph.Algorithms.Structure
( -- * Shortest Path Related Functions ( -- * Shortest Path Related Functions
shortestPath shortestPath
, averagePathLength
, diameter , diameter
, eccentricity , eccentricity
, radius
-- * Graph Components -- * Graph Components
, inducedSubgraph , inducedSubgraph
, isConnected , isConnected
...@@ -69,6 +71,23 @@ shortestPath gr s t getEdgeW = unsafePerformIO $ allocaVector $ \path -> do ...@@ -69,6 +71,23 @@ shortestPath gr s t getEdgeW = unsafePerformIO $ allocaVector $ \path -> do
, `Neimode' , `Neimode'
} -> `CInt' void- #} } -> `CInt' void- #}
-- | Calculates the average shortest path length between all vertex pairs.
averagePathLength :: Graph d v e
-> EdgeType -- ^ whether to consider directed paths
-> Bool -- ^ if unconnected,
-- include only connected pairs (True)
-- or return number if vertices (False)
-> Double
averagePathLength graph directed unconn =
cFloatConv $ igraphAveragePathLength (_graph graph) directed unconn
{-# INLINE igraphAveragePathLength #-}
{#fun pure igraph_average_path_length as ^
{ `IGraph'
, alloca- `CDouble' peek*
, dirToBool `EdgeType'
, `Bool'
} -> `CInt' void- #}
-- | Calculates the diameter of a graph (longest geodesic). -- | Calculates the diameter of a graph (longest geodesic).
diameter :: Graph d v e diameter :: Graph d v e
-> EdgeType -- ^ whether to consider directed paths -> EdgeType -- ^ whether to consider directed paths
...@@ -111,6 +130,19 @@ eccentricity graph mode vids = unsafePerformIO $ ...@@ -111,6 +130,19 @@ eccentricity graph mode vids = unsafePerformIO $
, `Neimode' , `Neimode'
} -> `CInt' void- #} } -> `CInt' void- #}
-- | Radius of a graph.
radius :: Graph d v e
-> Neimode -- ^ 'IgraphOut' to follow edges' direction,
-- 'IgraphIn' to reverse it, 'IgraphAll' to ignore
-> Double
radius graph mode = cFloatConv $ igraphRadius (_graph graph) mode
{-# INLINE igraphRadius #-}
{#fun pure igraph_radius as ^
{ `IGraph'
, alloca- `CDouble' peek*
, `Neimode'
} -> `CInt' void- #}
-- | Creates a subgraph induced by the specified vertices. This function collects -- | Creates a subgraph induced by the specified vertices. This function collects
-- the specified vertices and all edges between them to a new graph. -- the specified vertices and all edges between them to a new graph.
inducedSubgraph :: (Ord v, Serialize v) inducedSubgraph :: (Ord v, Serialize v)
......
...@@ -21,8 +21,10 @@ tests = testGroup "Algorithms" ...@@ -21,8 +21,10 @@ tests = testGroup "Algorithms"
[ graphIsomorphism [ graphIsomorphism
, motifTest , motifTest
, cliqueTest , cliqueTest
, averagePathTest
, diameterTest , diameterTest
, eccentricityTest , eccentricityTest
, radiusTest
, subGraphs , subGraphs
, decomposeTest , decomposeTest
, pagerankTest , pagerankTest
...@@ -58,6 +60,13 @@ cliqueTest = testGroup "Clique" ...@@ -58,6 +60,13 @@ cliqueTest = testGroup "Clique"
[2,3,4], [2,4,5] ] [2,3,4], [2,4,5] ]
c4 = [[1, 2, 3, 4], [1, 2, 4, 5]] c4 = [[1, 2, 3, 4], [1, 2, 4, 5]]
averagePathTest :: TestTree
averagePathTest = testGroup "Average path lengths"
[ testCase "clique" $ averagePathLength (full @'U 10 False) U True @?= 1
, testCase "star" $ averagePathLength (star 10) U True @?~ 1.8
, testCase "ring" $ averagePathLength (ring 11) U True @?= 3
]
diameterTest :: TestTree diameterTest :: TestTree
diameterTest = testGroup "Diameters" diameterTest = testGroup "Diameters"
[ testCase "clique" $ fst (diameter (full @'U 10 False) U True) @?= 1 [ testCase "clique" $ fst (diameter (full @'U 10 False) U True) @?= 1
...@@ -75,6 +84,13 @@ eccentricityTest = testGroup "Eccentricity" ...@@ -75,6 +84,13 @@ eccentricityTest = testGroup "Eccentricity"
eccentricity (ring 10) IgraphAll [0..9] @?= replicate 10 5 eccentricity (ring 10) IgraphAll [0..9] @?= replicate 10 5
] ]
radiusTest :: TestTree
radiusTest = testGroup "Radius"
[ testCase "clique" $ radius (full @'U 10 False) IgraphAll @?= 1
, testCase "star" $ radius (star 10) IgraphAll @?= 1
, testCase "ring" $ radius (ring 10) IgraphAll @?= 5
]
subGraphs :: TestTree subGraphs :: TestTree
subGraphs = testGroup "generate induced subgraphs" subGraphs = testGroup "generate induced subgraphs"
[ testCase "" $ test case1 ] [ testCase "" $ test case1 ]
...@@ -130,3 +146,7 @@ pagerankTest = testGroup "PageRank" ...@@ -130,3 +146,7 @@ pagerankTest = testGroup "PageRank"
ranks = [0.47,0.05,0.05,0.05,0.05,0.05,0.05,0.05,0.05,0.05,0.05] ranks = [0.47,0.05,0.05,0.05,0.05,0.05,0.05,0.05,0.05,0.05,0.05]
ranks' = map ((/100) . fromIntegral . round. (*100)) $ ranks' = map ((/100) . fromIntegral . round. (*100)) $
pagerank gr 0.85 Nothing Nothing pagerank gr 0.85 Nothing Nothing
-- approximate equality helper
(@?~) :: (Ord n,Fractional n) => n -> n -> Assertion
a @?~ b = assertBool "" $ abs (b-a) < 1/65536
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