module ConfigTest where import Config import Data.Functor.Identity (Identity(..)) import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (Assertion, (@?=), assertFailure, testCase) import Options.Applicative (ParserResult(..), defaultPrefs, execParserPure) test_optionParser :: TestTree test_optionParser = testGroup "Option Parser" [ testCase "defaults" $ [] `shouldParseTo` Config (i False) (i False) (i ".") (i ".") , testCase "dir only" $ ["here"] `shouldParseTo` Config (i False) (i False) (i "here") (i "here") , testCase "custom output dir" $ ["-o", "there", "here"] `shouldParseTo` Config (i False) (i False) (i "there") (i "here") , testCase "force" $ ["-f", "here"] `shouldParseTo` Config (i True) (i False) (i "here") (i "here") , testCase "verbose" $ ["-v"] `shouldParseTo` Config (i False) (i True) (i ".") (i ".") ] where i = Identity shouldParseTo :: [String] -> Config Identity -> Assertion args `shouldParseTo` c = case checkConfig <$> execParserPure defaultPrefs configParserInfo args of Success p -> p @?= Just c _ -> assertFailure "Parse failure"