Commit e9db8aad authored by Kai Zhang's avatar Kai Zhang

remove withSystemRandom

parent 69a1f831
name: haskell-igraph name: haskell-igraph
version: 0.7.1 version: 0.7.1.1
synopsis: Haskell interface of the igraph library. synopsis: Haskell interface of the igraph library.
description: igraph<"http://igraph.org/c/"> is a library for creating description: igraph<"http://igraph.org/c/"> is a library for creating
and manipulating large graphs. This package provides the Haskell and manipulating large graphs. This package provides the Haskell
......
module IGraph.Random module IGraph.Random
( Gen ( Gen
, withSystemRandom
, withSeed , withSeed
) where ) where
...@@ -9,9 +8,11 @@ import IGraph.Internal ...@@ -9,9 +8,11 @@ import IGraph.Internal
-- | Random number generator -- | Random number generator
data Gen = Gen data Gen = Gen
{-
withSystemRandom :: (Gen -> IO a) -> IO a withSystemRandom :: (Gen -> IO a) -> IO a
withSystemRandom fun = fun Gen withSystemRandom fun = fun Gen
{-# INLINE withSystemRandom #-} {-# INLINE withSystemRandom #-}
-}
withSeed :: Int -> (Gen -> IO a) -> IO a withSeed :: Int -> (Gen -> IO a) -> IO a
withSeed seed fun = allocaRng $ \rng -> do withSeed seed fun = allocaRng $ \rng -> do
......
...@@ -73,7 +73,7 @@ decomposeTest = testGroup "Decompose" ...@@ -73,7 +73,7 @@ decomposeTest = testGroup "Decompose"
[ testCase "ring" $ edges (head $ decompose $ ring 10) @?= [ testCase "ring" $ edges (head $ decompose $ ring 10) @?=
[(0,1), (1,2), (2,3), (3,4), (4,5), (5,6), (6,7), (7,8), (8,9), (0,9)] [(0,1), (1,2), (2,3), (3,4), (4,5), (5,6), (6,7), (7,8), (8,9), (0,9)]
, testCase "1 component" $ do , testCase "1 component" $ do
gr <- (withSystemRandom $ erdosRenyiGame (GNP 100 (40/100)) False) :: IO (Graph 'U () ()) gr <- (withSeed 1244 $ erdosRenyiGame (GNP 100 (40/100)) False) :: IO (Graph 'U () ())
1 @?= length (decompose gr) 1 @?= length (decompose gr)
, testCase "toy example" $ map (sort . edges) (decompose gr) @?= , testCase "toy example" $ map (sort . edges) (decompose gr) @?=
[ [(0,1), (0,2), (1,2)] [ [(0,1), (0,2), (1,2)]
......
...@@ -88,11 +88,15 @@ nonSimpleGraphTest = testGroup "loops, multiple edges" ...@@ -88,11 +88,15 @@ nonSimpleGraphTest = testGroup "loops, multiple edges"
randomGeneratorTest :: TestTree randomGeneratorTest :: TestTree
randomGeneratorTest = testGroup "random generator" randomGeneratorTest = testGroup "random generator"
[ t1 ] [t1 , t2]
where where
t1 = testCase "random graph" $ do t1 = testCase "random graph" $ do
gr1 <- sort . edges <$> genGr 1244 gr1 <- sort . edges <$> genGr 1244
gr2 <- sort . edges <$> genGr 1244 gr2 <- sort . edges <$> genGr 1244
gr1 @=? gr2 gr1 @=? gr2
t2 = testCase "random graph" $ do
gr1 <- sort . edges <$> genGr 145
gr2 <- sort . edges <$> genGr 24
assertBool "" $ gr1 /= gr2
genGr :: Int -> IO (Graph 'D () ()) genGr :: Int -> IO (Graph 'D () ())
genGr seed = withSeed seed $ erdosRenyiGame (GNP 1000 0.5) False genGr seed = withSeed seed $ erdosRenyiGame (GNP 500 0.5) False
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