Commit 2164c9d2 authored by Kai Zhang's avatar Kai Zhang

minor

parent cefeec0b
...@@ -78,33 +78,33 @@ shortestPath gr s t getEdgeW = unsafePerformIO $ allocaVector $ \path -> do ...@@ -78,33 +78,33 @@ shortestPath gr s t getEdgeW = unsafePerformIO $ allocaVector $ \path -> do
} -> `CInt' void- #} } -> `CInt' void- #}
-- | Calculates the average shortest path length between all vertex pairs. -- | Calculates the average shortest path length between all vertex pairs.
averagePathLength :: Graph d v e averagePathLength :: SingI d
-> EdgeType -- ^ whether to consider directed paths => Graph d v e
-> Bool -- ^ if unconnected, -> Bool -- ^ if unconnected,
-- include only connected pairs (True) -- include only connected pairs (True)
-- or return number if vertices (False) -- or return number if vertices (False)
-> Double -> Double
averagePathLength graph directed unconn = averagePathLength graph unconn =
cFloatConv $ igraphAveragePathLength (_graph graph) directed unconn cFloatConv $ igraphAveragePathLength (_graph graph) (isDirected graph) unconn
{-# INLINE igraphAveragePathLength #-} {-# INLINE igraphAveragePathLength #-}
{#fun pure igraph_average_path_length as ^ {#fun pure igraph_average_path_length as ^
{ `IGraph' { `IGraph'
, alloca- `CDouble' peek* , alloca- `CDouble' peek*
, dirToBool `EdgeType' , `Bool'
, `Bool' , `Bool'
} -> `CInt' void- #} } -> `CInt' void- #}
-- | Calculates the diameter of a graph (longest geodesic). -- | Calculates the diameter of a graph (longest geodesic).
diameter :: Graph d v e diameter :: SingI d
-> EdgeType -- ^ whether to consider directed paths => Graph d v e
-> Bool -- ^ if unconnected, -> Bool -- ^ if unconnected,
-- return largest component diameter (True) -- return largest component diameter (True)
-- or number of vertices (False) -- or number of vertices (False)
-> (Int,[Node]) -> (Int, [Node])
diameter graph directed unconn = unsafePerformIO $ diameter graph unconn = unsafePerformIO $
alloca $ \pres -> alloca $ \pres ->
allocaVector $ \path -> do allocaVector $ \path -> do
igraphDiameter (_graph graph) pres nullPtr nullPtr path directed unconn igraphDiameter (_graph graph) pres nullPtr nullPtr path (isDirected graph) unconn
liftM2 (,) (peekIntConv pres) (toNodes path) liftM2 (,) (peekIntConv pres) (toNodes path)
{-# INLINE igraphDiameter #-} {-# INLINE igraphDiameter #-}
{#fun igraph_diameter as ^ {#fun igraph_diameter as ^
...@@ -113,7 +113,7 @@ diameter graph directed unconn = unsafePerformIO $ ...@@ -113,7 +113,7 @@ diameter graph directed unconn = unsafePerformIO $
, castPtr `Ptr CInt' , castPtr `Ptr CInt'
, castPtr `Ptr CInt' , castPtr `Ptr CInt'
, castPtr `Ptr Vector' , castPtr `Ptr Vector'
, dirToBool `EdgeType' , `Bool'
, `Bool' , `Bool'
} -> `CInt' void- #} } -> `CInt' void- #}
...@@ -277,9 +277,4 @@ reciprocity gr ignore_loops = unsafePerformIO $ alloca $ \res -> do ...@@ -277,9 +277,4 @@ reciprocity gr ignore_loops = unsafePerformIO $ alloca $ \res -> do
, castPtr `Ptr Double' , castPtr `Ptr Double'
, `Bool' , `Bool'
, `Reciprocity' , `Reciprocity'
} -> `CInt' void -#} } -> `CInt' void -#}
\ No newline at end of file
-- Marshaller for those "treat edges as directed" booleans.
dirToBool :: Num n => EdgeType -> n
dirToBool D = cFromBool True
dirToBool U = cFromBool False
...@@ -67,16 +67,16 @@ cliqueTest = testGroup "Clique" ...@@ -67,16 +67,16 @@ cliqueTest = testGroup "Clique"
averagePathTest :: TestTree averagePathTest :: TestTree
averagePathTest = testGroup "Average path lengths" averagePathTest = testGroup "Average path lengths"
[ testCase "clique" $ averagePathLength (full @'U 10 False) U True @?= 1 [ testCase "clique" $ averagePathLength (full @'U 10 False) True @?= 1
, testCase "star" $ averagePathLength (star 10) U True @?~ 1.8 , testCase "star" $ averagePathLength (star 10) True @?~ 1.8
, testCase "ring" $ averagePathLength (ring 11) U True @?= 3 , testCase "ring" $ averagePathLength (ring 11) 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) True) @?= 1
, testCase "star" $ fst (diameter (star 10) D False) @?= 2 , testCase "star" $ fst (diameter (star 10) False) @?= 2
, testCase "ring" $ fst (diameter (ring 10) U False) @?= 5 , testCase "ring" $ fst (diameter (ring 10) False) @?= 5
] ]
eccentricityTest :: TestTree eccentricityTest :: TestTree
......
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