Commit 6e7e8fbf authored by Jean-Baptiste Mazon's avatar Jean-Baptiste Mazon

add density and reciprocity

parent 9beab9e7
......@@ -18,6 +18,9 @@ module IGraph.Algorithms.Structure
, isDag
, topSort
, topSortUnsafe
-- * Other Operations
, density
, reciprocity
-- * Auxiliary types
, Neimode(IgraphOut,IgraphIn,IgraphAll) -- not IgraphTotal
) where
......@@ -248,6 +251,34 @@ topSortUnsafe gr = unsafePerformIO $ allocaVectorN n $ \res -> do
, `Neimode'
} -> `CInt' void- #}
-- | Calculate the density of a graph.
density :: Graph d v e
-> Bool -- ^ whether to include loops
-> Double -- ^ the ratio of edges to possible edges
density gr loops = unsafePerformIO $ alloca $ \res -> do
igraphDensity (_graph gr) res loops
peek res
{-# INLINE igraphDensity #-}
{#fun igraph_density as ^
{ `IGraph'
, castPtr `Ptr Double'
, `Bool'
} -> `CInt' void -#}
-- | Calculates the reciprocity of a directed graph.
reciprocity :: Graph d v e
-> Bool -- ^ whether to ignore loop edges
-> Double -- ^ the proportion of mutual connections
reciprocity gr ignore_loops = unsafePerformIO $ alloca $ \res -> do
igraphReciprocity (_graph gr) res ignore_loops IgraphReciprocityDefault
peek res
{#fun igraph_reciprocity as ^
{ `IGraph'
, castPtr `Ptr Double'
, `Bool'
, `Reciprocity'
} -> `CInt' void -#}
-- Marshaller for those "treat edges as directed" booleans.
dirToBool :: Num n => EdgeType -> n
dirToBool D = cFromBool True
......
......@@ -41,3 +41,6 @@ module IGraph.Internal.Constants where
{#enum igraph_degseq_t as Degseq {underscoreToCase}
deriving (Show, Read, Eq) #}
{#enum igraph_reciprocity_t as Reciprocity {underscoreToCase}
deriving (Show, Read, Eq) #}
......@@ -31,6 +31,8 @@ tests = testGroup "Algorithms"
, bridgeTest
, pagerankTest
, kleinbergTest
, densityTest
, reciprocityTest
]
graphIsomorphism :: TestTree
......@@ -170,6 +172,19 @@ kleinbergTest = testGroup "Kleinberg"
fst (authorityScore (ring 4) False) @?= replicate 4 0.5
]
densityTest :: TestTree
densityTest = testGroup "Density"
[ testCase "clique" $ density (full @'U 16 False) False @?= 1
, testCase "ring" $ density (ring 9) False @?= 1/4
]
reciprocityTest :: TestTree
reciprocityTest = testGroup "Reciprocity"
[ testCase "clique" $ reciprocity (full @'D 10 False) False @?= 1
, testCase "ring" $ reciprocity g False @?= 0
]
where g = fromLabeledEdges @'D [(("a","b"),()),(("b","c"),()),(("c","a"),())]
-- 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