{-# LANGUAGE OverloadedStrings #-} module Main where import System.Exit (exitFailure, exitSuccess) import Test.HUnit hiding (Node) import Data.List import Nauty.Digraph6.Internal import qualified Data.Text.Lazy as T testParsing :: AdjacencyMatrix -> T.Text -> IO () testParsing g str = do assertEqual ("parse " ++ T.unpack str) ([Right g]) (parse str) assertEqual ("encode " ++ T.unpack str) str (encode g) tests :: Test tests = TestList [ TestLabel "g = parse $ encode g" $ TestCase ( do -- < 0 >< 1 >< 2 >< 3 >< 4 > -- 001010 000000 000010 010000 000000 -- 10 0 2 16 0 -- I ? @ G ? -- ( 40)( 0)( 144)( 0) testParsing (fromArcList 5 [(0,2), (0,4), (3,1), (3,4)]) "&DI?AO?" -- < 0 > < 1 > < 2 > < 3 > < 4 > < 5 > -- 010001 001000 100000 000011 000000 100000 -- 17 8 32 3 0 32 -- P G _ B ? _ testParsing (fromArcList 6 [(0,1), (1,2), (2,0), (3,4), (3,5), (5,0), (0,5)]) "&EPG_B?_" -- < 0 >< 1 > < 2 >< 3 > < 4 >< 5 > < 6 >< 7 > < 8 > -- 010000 000110 000000 000000 000000 000000 000000 000100 000000 100000 000000 000001 000000 010000 -- 16 6 0 0 0 0 0 4 0 32 0 1 0 16 -- O E ? ? ? ? ? C ? _ ? @ ? O testParsing (fromArcList 9 [(1,1), (0,1), (1,0), (6,0), (8,7), (7,8), (5,0)]) "&HOE?????C?_?@?O" testParsing (fromArcList 3 [(0,1), (1,2), (2,0)]) "&BP_" testParsing (fromArcList 3 [(0,1), (1,2), (0,2)]) "&BX?" testParsing (fromArcList 4 [ (0,1), (0,2), (0,3) , (1,2), (1,3) , (2,3) ]) "&C[p?" ) , TestLabel "g = fromArcList $ toArcList g" $ TestCase ( do let g = fromArcList 3 [(0,1), (1,2), (2,0)] in do assertEqual "" ([(0,1), (1,2), (2,0)]) (sort $ snd $ toArcList g) assertEqual "" (g) (fromArcList 3 $ snd $ toArcList g) let arcList = [(0,1), (0,4), (1,5), (1,6), (2,0), (2,1), (2,5), (2,6), (3,0), (3,1), (3,2), (3,4), (3,5), (4,1), (4,2), (4,5), (5,0), (5,6), (6,0), (6,3), (6,4), (7,0), (7,1), (7,2), (7,3), (7,4), (7,5), (7,6)] g = (fromArcList 8 arcList) in do assertEqual "" (sort $ arcList) (sort $ snd $ toArcList g) assertEqual "" (g) (fromArcList 8 $ snd $ toArcList g) ) ] main :: IO () main = do count <- runTestTT tests if errors count + failures count > 0 then exitFailure else exitSuccess