config test

This commit is contained in:
Lei Zhu 2023-07-22 17:46:23 +08:00
parent 16c7ecabe2
commit dc1a813305
4 changed files with 40 additions and 1 deletions

View File

@ -52,6 +52,7 @@ data ConfigCommand
| SetConfig String (Maybe String) | SetConfig String (Maybe String)
| InitConfig | InitConfig
| AddReleaseChannel Bool URI | AddReleaseChannel Bool URI
deriving (Eq, Show)

View File

@ -420,6 +420,7 @@ test-suite ghcup-optparse-test
Utils Utils
OtherCommandTest OtherCommandTest
ChangeLogTest ChangeLogTest
ConfigTest
default-language: Haskell2010 default-language: Haskell2010
ghc-options: -Wall ghc-options: -Wall
build-depends: base, ghcup, ghcup-optparse, tasty, tasty-hunit, optparse-applicative, versions, text build-depends: base, ghcup, ghcup-optparse, tasty, tasty-hunit, optparse-applicative, versions, text, uri-bytestring

View File

@ -0,0 +1,34 @@
{-# LANGUAGE QuasiQuotes #-}
module ConfigTest where
import Test.Tasty
import Test.Tasty.HUnit
import GHCup.OptParse
import Utils
import Control.Monad.IO.Class
import URI.ByteString.QQ
configTests :: TestTree
configTests = testGroup "config" $ map (uncurry check) checkList
where
check :: String -> ConfigCommand -> TestTree
check args expected = testCase args $ do
res <- configParseWith (words args)
liftIO $ res @?= expected
checkList :: [(String, ConfigCommand)]
checkList =
[ ("config", ShowConfig)
, ("config init", InitConfig)
, ("config show", ShowConfig)
, ("config add-release-channel https://raw.githubusercontent.com/haskell/ghcup-metadata/master/ghcup-prereleases-0.0.7.yaml"
, AddReleaseChannel False [uri|https://raw.githubusercontent.com/haskell/ghcup-metadata/master/ghcup-prereleases-0.0.7.yaml|]
)
, ("config set cache true", SetConfig "cache" (Just "true"))
]
configParseWith :: [String] -> IO ConfigCommand
configParseWith args = do
Config a <- parseWith args
pure a

View File

@ -1,12 +1,15 @@
module Main where module Main where
import Test.Tasty import Test.Tasty
import qualified SetTest import qualified SetTest
import qualified OtherCommandTest import qualified OtherCommandTest
import qualified ChangeLogTest import qualified ChangeLogTest
import qualified ConfigTest
main :: IO () main :: IO ()
main = defaultMain $ testGroup "ghcup" main = defaultMain $ testGroup "ghcup"
[ SetTest.setTests [ SetTest.setTests
, OtherCommandTest.otherCommandTests , OtherCommandTest.otherCommandTests
, ChangeLogTest.changeLogTests , ChangeLogTest.changeLogTests
, ConfigTest.configTests
] ]