Skip to content

Commit

Permalink
add test cases for ToySolver.Graph
Browse files Browse the repository at this point in the history
  • Loading branch information
msakai committed Dec 8, 2024
1 parent d6d7cb0 commit f4d04f4
Show file tree
Hide file tree
Showing 3 changed files with 51 additions and 0 deletions.
48 changes: 48 additions & 0 deletions test/Test/Graph.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
{-# OPTIONS_GHC -Wall -fno-warn-orphans #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
module Test.Graph (graphTestGroup) where

import Control.Monad
import Data.Array
import Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
import Test.Tasty
import Test.Tasty.QuickCheck
import Test.Tasty.TH

import ToySolver.Graph.Base


-- ------------------------------------------------------------------------

arbitrarySimpleGraph :: Gen Graph
arbitrarySimpleGraph = do
sized $ \n -> do
m <- choose (0, n*n-1)
fmap (graphFromUnorderedEdges n) $ replicateM m $ do
node1 <- choose (0, n-1)
node2 <- fmap (\i -> (node1 + i) `mod` n) $ choose (1, n-1)
return (node1, node2, ())

vertexes :: EdgeLabeledGraph a -> IntSet
vertexes = IntSet.fromAscList . uncurry enumFromTo . bounds

arbitrarySubset :: IntSet -> Gen IntSet
arbitrarySubset = fmap IntSet.fromAscList . sublistOf . IntSet.toAscList

-- ------------------------------------------------------------------------

prop_indepndent_set_and_clique :: Property
prop_indepndent_set_and_clique =
forAll arbitrarySimpleGraph $ \g ->
forAll (arbitrarySubset (vertexes g)) $ \s -> do
counterexample (show (graphToUnorderedEdges g)) $
s `isIndependentSetOf` g === s `isCliqueOf` complementSimpleGraph g

-- ------------------------------------------------------------------------
-- Test harness

graphTestGroup :: TestTree
graphTestGroup = $(testGroupGenerator)
2 changes: 2 additions & 0 deletions test/TestSuite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import Test.Converter
import Test.CNF
import Test.Delta
import Test.FiniteModelFinder
import Test.Graph
import Test.GraphShortestPath
import Test.HittingSets
import Test.Knapsack
Expand Down Expand Up @@ -49,6 +50,7 @@ main = defaultMain $ testGroup "ToySolver test suite"
, ctTestGroup
, deltaTestGroup
, fmfTestGroup
, graphTestGroup
, graphShortestPathTestGroup
, hittingSetsTestGroup
, knapsackTestGroup
Expand Down
1 change: 1 addition & 0 deletions toysolver.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -896,6 +896,7 @@ Test-suite TestSuite
Test.Converter
Test.Delta
Test.FiniteModelFinder
Test.Graph
Test.GraphShortestPath
Test.HittingSets
Test.Knapsack
Expand Down

0 comments on commit f4d04f4

Please sign in to comment.