module Main where import HGraph.Undirected.AdjacencyMap import HGraph.Undirected.Solvers.Treedepth import qualified Data.Map as M import Data.List import Test.HUnit hiding (Node) import System.Exit (exitFailure, exitSuccess) tests = TestList [ TestLabel "No edges 1" $ TestCase ( do let g = addVertex emptyGraph 1 td = optimalDecomposition g assertEqual "TD" Decomposition{ ancestor = M.empty , children = M.empty , roots = [1] , depth = 1 } td ) , TestLabel "No edges 2" $ TestCase ( do let g = foldr (flip addVertex) emptyGraph [1,2,3,4,5,6] td = optimalDecomposition g assertEqual "TD" Decomposition{ ancestor = M.empty , children = M.empty , roots = [1,2,3,4,5,6] , depth = 1 } td{roots = sort $ roots td} ) , TestLabel "Path 1" $ TestCase ( do let g = addEdge (foldr (flip addVertex) emptyGraph [1,2]) (1,2) td = optimalDecomposition g assertEqual (show td) 2 (depth td) assertBool (show td) $ isDecomposition g td ) , TestLabel "Path 2" $ TestCase ( do let g = foldr (flip addEdge) (foldr (flip addVertex) emptyGraph [1,2,3,4,5,6]) [(1,2), (2,3), (3,4), (4,5), (5,6)] td = optimalDecomposition g assertEqual (show td) 3 (depth td) assertBool (show td) $ isDecomposition g td ) , TestLabel "Cycle 1" $ TestCase ( do let g = foldr (flip addEdge) (foldr (flip addVertex) emptyGraph [1,2,3,4,5,6]) [(1,2), (2,3), (3,4), (4,5), (5,6), (6,1)] td = optimalDecomposition g assertEqual (show td) 4 (depth td) assertBool (show td) $ isDecomposition g td ) ] main = do count <- runTestTT tests if errors count + failures count > 0 then exitFailure else exitSuccess