Commit d37ff712 authored by Kai Zhang's avatar Kai Zhang

fix triad

parent c6153226
......@@ -80,6 +80,7 @@ test-suite tests
other-modules:
Test.Basic
Test.Structure
Test.Motif
Test.Utils
default-language: Haskell2010
......@@ -87,6 +88,7 @@ test-suite tests
base
, haskell-igraph
, data-ordlist
, matrices
, tasty
, tasty-golden
, tasty-hunit
......
......@@ -9,20 +9,18 @@ import IGraph.Internal.Graph
import IGraph.Internal.Constants
import IGraph.Internal.Initialization
data ErdosRenyiModel = GNP
| GNM
data ErdosRenyiModel = GNP Int Double
| GNM Int Int
erdosRenyiGame :: Graph d
=> ErdosRenyiModel
-> Int -- ^ n
-> Double -- ^ p or m
-> d -- ^ directed
-> Bool -- ^ self-loop
-> IO (LGraph d () ())
erdosRenyiGame model n p_or_m d self = do
gp <- igraphInit >> igraphErdosRenyiGame model' n p_or_m (isD d) self
erdosRenyiGame (GNP n p) d self = do
gp <- igraphInit >> igraphErdosRenyiGame IgraphErdosRenyiGnp n p (isD d) self
unsafeFreeze $ MLGraph gp
erdosRenyiGame (GNM n m) d self = do
gp <- igraphInit >> igraphErdosRenyiGame IgraphErdosRenyiGnm n
(fromIntegral m) (isD d) self
unsafeFreeze $ MLGraph gp
where
model' = case model of
GNP -> IgraphErdosRenyiGnp
GNM -> IgraphErdosRenyiGnm
......@@ -19,7 +19,7 @@ import IGraph.Internal.Data
-- 021C: A->B->C, the directed line.
-- 111D: A<->B<-C.
-- 111U: A<->B->C.
-- 030T: A->B<-C, A->C.
-- 030T: A->B<-C, A->C. Feed forward loop.
-- 030C: A<-B<-C, A->C.
-- 201: A<->B<->C.
-- 120D: A<-B->C, A<->C.
......@@ -28,9 +28,10 @@ import IGraph.Internal.Data
-- 210: A->B<->C, A<->C.
-- 300: A<->B<->C, A<->C, the complete graph.
triad :: [LGraph D () ()]
triad = map make xs
triad = map make edgeList
where
xs = [ []
edgeList =
[ []
, [(0,1)]
, [(0,1), (1,0)]
, [(1,0), (1,2)]
......@@ -45,10 +46,10 @@ triad = map make xs
, [(0,1), (2,1), (0,2), (2,0)]
, [(0,1), (1,2), (0,2), (2,0)]
, [(0,1), (1,2), (2,1), (0,2), (2,0)]
, [(0,1), (1,2), (1,2), (2,1), (0,2), (2,0)]
, [(0,1), (1,0), (1,2), (2,1), (0,2), (2,0)]
]
make :: [(Int, Int)] -> LGraph D () ()
make xs = mkGraph (replicate (length xs) ()) $ zip xs $ repeat ()
make xs = mkGraph (replicate 3 ()) $ zip xs $ repeat ()
triadCensus :: (Hashable v, Eq v, Read v) => LGraph d v e -> [Int]
triadCensus gr = unsafePerformIO $ do
......
module Test.Motif
( tests
) where
import Control.Arrow
import Control.Monad.ST
import Data.List
import qualified Data.Matrix.Unboxed as M
import System.IO.Unsafe
import Test.Tasty
import Test.Tasty.HUnit
import Test.Utils
import IGraph
import IGraph
import IGraph.Motif
tests :: TestTree
tests = testGroup "Network motif"
[ testCase "triad Census" $ M.toLists (M.ident 16 :: M.Matrix Int) @=?
map triadCensus triad ]
import qualified Test.Basic as Basic
import qualified Test.Basic as Basic
import qualified Test.Motif as Motif
import qualified Test.Structure as Structure
import Test.Tasty
import Test.Tasty
main :: IO ()
main = defaultMain $ testGroup "Haskell-igraph Tests"
[ Basic.tests
, Structure.tests
, Motif.tests
]
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