Commit b3220726 authored by Kai Zhang's avatar Kai Zhang

add tests

parent 62fb8045
module Test.Basic
( tests
) where
import Test.Tasty
import Test.Tasty.HUnit
import Test.Utils
import System.IO.Unsafe
import Data.List
import IGraph
tests :: TestTree
tests = testGroup "Basic tests"
[ graphCreation
]
graphCreation :: TestTree
graphCreation = testGroup "Graph creation"
[ testCase "" $ assertBool "" $ nNodes simple == 3 && nEdges simple == 3
, testCase "" $ [(0,1),(1,2),(2,0)] @=? (sort $ edges simple)
, testCase "" $ assertBool "" $ nNodes gr == 100 && nEdges gr == 1000
, testCase "" $ edgeList @=? (sort $ edges gr)
]
where
edgeList = sort $ unsafePerformIO $ randEdges 1000 100
gr = mkGraph (100,Nothing) (edgeList, Nothing) :: LGraph D () ()
simple = mkGraph (3,Nothing) ([(0,1),(1,2),(2,0)],Nothing) :: LGraph D () ()
module Test.Utils where
import Control.Monad
import System.Random
import Data.List
randEdges :: Int -- ^ number of edges to generate
-> Int -- ^ number of nodes in the graph
-> IO [(Int, Int)]
randEdges n nd = do
fr <- replicateM (2*n) $ randomRIO (0,nd-1)
to <- replicateM (2*n) $ randomRIO (0,nd-1)
return $ take n $ nub $ filter (uncurry (/=)) $ zip fr to
import qualified Test.Basic as Basic
import Test.Tasty
main :: IO ()
main = defaultMain $ testGroup "Haskell-igraph Tests"
[ Basic.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