module Main where import HGraph.Directed import HGraph.Directed.Connectivity import qualified HGraph.Directed.AdjacencyMap as AM import qualified Data.Set as S import Test.HUnit hiding (Node) import System.Exit (exitFailure, exitSuccess) v1 = 1 :: Int tests = TestList [ TestLabel "Maximal paths 1" $ TestCase ( do let d = addVertex v1 AM.emptyDigraph ps = allMaximalPaths d assertEqual "Paths" [[1]] ps ) , TestLabel "Maximal paths 2" $ TestCase ( do let d = foldr addArc (foldr addVertex AM.emptyDigraph [v1,2]) [(1,2)] ps = allMaximalPaths d assertEqual "Paths" [[1,2]] ps ) , TestLabel "Maximal paths 3" $ TestCase ( do let d = foldr addArc (foldr addVertex AM.emptyDigraph [v1,2,3,4,5]) [(1,2), (2,3), (3,4), (4,5)] ps = allMaximalPaths d assertEqual "Paths" [[1,2,3,4,5]] ps ) , TestLabel "Maximal paths 4" $ TestCase ( do let d = foldr addArc (foldr addVertex AM.emptyDigraph [v1,2,3,4]) $ zip [1,2,3,4] [2,3,4,1] ps = allMaximalPaths d assertEqual "Paths" (S.fromList $ [ arcSet [1,2,3,4,1]]) (S.fromList $ map arcSet ps) ) , TestLabel "Maximal paths 5" $ TestCase ( do let d = foldr addArc (foldr addVertex AM.emptyDigraph [v1,2,3,4,5]) $ zip [1,2,5,5] [5,5,3,4] ps = allMaximalPaths d assertEqual "Paths" (S.fromList [[1,5,3], [2,5,3], [1,5,4], [2,5,4]]) (S.fromList ps) ) , TestLabel "Maximal paths 6" $ TestCase ( do let d = foldr addArc (foldr addVertex AM.emptyDigraph [v1,2,3]) $ [ (v,u) | v <- [1..3] , u <- [1..3] , u /= v ] ps = allMaximalPaths d assertEqual "Paths" (S.fromList $ map arcSet [ [1,2,1], [1,3,1] , [1,2,3,1], [1,3,2,1] , [2,3,2] ] ) (S.fromList $ map arcSet ps) ) , TestLabel "Maximal paths 7" $ TestCase ( do let d = foldr addArc (foldr addVertex AM.emptyDigraph [0,1,2,3,4]) $ [ (0,1), (0,2), (0,4) , (1,0), (2,1), (2,4) , (3,1), (3,2), (3,4) , (4,0) ] ps = allMaximalPaths d assertEqual "Paths" (S.fromList $ map arcSet [ [3,2,4,0,1], [3,4,0,1] , [3,4,0,2,1], [3,1,0,2,4] , [3,2,1,0,4], [3,1,0,4] ] ) (S.fromList $ map arcSet ps) ) ] arcSet p = S.fromList $ zip p $ tail p main = do count <- runTestTT tests if errors count + failures count > 0 then exitFailure else exitSuccess