Skip to content

Commit

Permalink
Add exhaustive test suite for 'cabal path' cmd
Browse files Browse the repository at this point in the history
We test that each query honours cabal.project files, cli parameters, and
is composable with the other query flags.

We extend the test output normalisers for ghc compiler location and
cabal-install version, as the 'cabal path' command outputs the exact ghc
and ghc-pkg location. In addition, the json output format is versioned
on the cabal-install version.

Currently, we query the cabal-install version on each test normalisation
run. This might be unnecessary expensive, and could be avoided by
introducing a 'cabalProgram' that specifies how the program version can
be found. This way, we can cache the version query.
  • Loading branch information
fendor committed Mar 10, 2024
1 parent 4b95b78 commit 50ba442
Show file tree
Hide file tree
Showing 13 changed files with 638 additions and 13 deletions.
447 changes: 447 additions & 0 deletions cabal-testsuite/PackageTests/Path/All/cabal.out

Large diffs are not rendered by default.

26 changes: 25 additions & 1 deletion cabal-testsuite/PackageTests/Path/All/cabal.test.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,27 @@
import Test.Cabal.Prelude
import Data.List (subsequences)

allOutputFormats =
[ "json"
, "key-value"
]

allFlags =
[ "--compiler-info"
, "--cache-dir"
, "--logs-dir"
, "--store-dir"
, "--config-file"
, "--installdir"
]

main = cabalTest $ do
forM_ allOutputFormats $ \outputFormat -> do
-- Order of flags should not matter, neither does any flag depend on the
-- existence of any other flag.
--
-- 'subsequences' generated "n over k" for k in (1 .. n)
forM_ (subsequences allFlags) $ \flags -> do
cabal "path" $ ["--output-format", outputFormat] <> flags


main = cabalTest . void $ cabal "path" ["-z", "--output-format=key-value"]
6 changes: 6 additions & 0 deletions cabal-testsuite/PackageTests/Path/Compiler/cabal.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
# cabal path
compiler-flavour: ghc
compiler-id: ghc-<GHCVER>
compiler-path: <GHCPATH>
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","compiler":{"flavour":"ghc","id":"ghc-<GHCVER>","path":"<GHCPATH>"}}
6 changes: 6 additions & 0 deletions cabal-testsuite/PackageTests/Path/Compiler/cabal.test.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
import Test.Cabal.Prelude

main = cabalTest $ do
-- Basic output
void $ cabal "path" ["-z", "--output-format=key-value", "--compiler-info"]
void $ cabal "path" ["-z", "--output-format=json", "--compiler-info"]
64 changes: 64 additions & 0 deletions cabal-testsuite/PackageTests/Path/Config/cabal.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
# cabal path
<ROOT>/cabal.dist/home/.cabal/packages
# cabal path
<ROOT>/cabal.dist/home/.cabal/logs
# cabal path
<ROOT>/cabal.dist/home/.cabal/store
# cabal path
<ROOT>/cabal.dist/home/.cabal/config
# cabal path
<ROOT>/cabal.dist/home/.cabal/bin
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","cache-dir":"<ROOT>/cabal.dist/home/.cabal/packages"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","logs-dir":"<ROOT>/cabal.dist/home/.cabal/logs"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","store-dir":"<ROOT>/cabal.dist/home/.cabal/store"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","config-file":"<ROOT>/cabal.dist/home/.cabal/config"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","installdir":"<ROOT>/cabal.dist/home/.cabal/bin"}
# cabal path
test-dir
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","store-dir":"test-dir"}
# cabal path
my-cache-dir
# cabal path
my-logs-dir
# cabal path
my-store-dir
# cabal path
fake-cabal.config
# cabal path
my-installdir
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","cache-dir":"my-cache-dir"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","logs-dir":"my-logs-dir"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","store-dir":"my-store-dir"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","config-file":"fake-cabal.config"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","installdir":"my-installdir"}
# cabal path
my-cache-dir
# cabal path
my-logs-dir
# cabal path
my-store-dir
# cabal path
<ROOT>/cabal.dist/home/.cabal/config
# cabal path
my-installdir
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","cache-dir":"my-cache-dir"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","logs-dir":"my-logs-dir"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","store-dir":"my-store-dir"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","config-file":"<ROOT>/cabal.dist/home/.cabal/config"}
# cabal path
{"cabal-install-version":"<CABAL_INSTALL_VER>","installdir":"my-installdir"}
43 changes: 43 additions & 0 deletions cabal-testsuite/PackageTests/Path/Config/cabal.test.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
import Test.Cabal.Prelude

main = cabalTest $ do
-- Basic output
void $ cabal "path" ["-z", "--output-format=key-value", "--cache-dir"]
void $ cabal "path" ["-z", "--output-format=key-value", "--logs-dir"]
void $ cabal "path" ["-z", "--output-format=key-value", "--store-dir"]
void $ cabal "path" ["-z", "--output-format=key-value", "--config-file"]
void $ cabal "path" ["-z", "--output-format=key-value", "--installdir"]
-- Works for json, too
void $ cabal "path" ["-z", "--output-format=json", "--cache-dir"]
void $ cabal "path" ["-z", "--output-format=json", "--logs-dir"]
void $ cabal "path" ["-z", "--output-format=json", "--store-dir"]
void $ cabal "path" ["-z", "--output-format=json", "--config-file"]
void $ cabal "path" ["-z", "--output-format=json", "--installdir"]
-- Honours cli overwrites
void $ cabalG ["--store-dir=test-dir"] "path" ["-z", "--output-format=key-value", "--store-dir"]
void $ cabalG ["--store-dir=test-dir"] "path" ["-z", "--output-format=json", "--store-dir"]
-- Honour config file overwrites:
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=key-value", "--cache-dir"]
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=key-value", "--logs-dir"]
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=key-value", "--store-dir"]
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=key-value", "--config-file"]
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=key-value", "--installdir"]

void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=json", "--cache-dir"]
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=json", "--logs-dir"]
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=json", "--store-dir"]
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=json", "--config-file"]
void $ cabalG ["--config-file=fake-cabal.config"] "path" ["-z", "--output-format=json", "--installdir"]

-- Honour cabal.project file
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=key-value", "--cache-dir"]
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=key-value", "--logs-dir"]
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=key-value", "--store-dir"]
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=key-value", "--config-file"]
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=key-value", "--installdir"]
-- Works for json, too
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=json", "--cache-dir"]
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=json", "--logs-dir"]
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=json", "--store-dir"]
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=json", "--config-file"]
void $ cabal "path" ["--project-file=fake.cabal.project", "--output-format=json", "--installdir"]
5 changes: 5 additions & 0 deletions cabal-testsuite/PackageTests/Path/Config/config.cabal
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
cabal-version: 3.0
name: config
version: 0.1

library
11 changes: 11 additions & 0 deletions cabal-testsuite/PackageTests/Path/Config/fake-cabal.config
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
-- this is a test file, dont use it
repository hackage.haskell.org
url: http://hackage.haskell.org/
-- secure: True
-- root-keys:
-- key-threshold: 3

logs-dir: my-logs-dir
store-dir: my-store-dir
remote-repo-cache: my-cache-dir
installdir: my-installdir
6 changes: 6 additions & 0 deletions cabal-testsuite/PackageTests/Path/Config/fake.cabal.project
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
packages: ./

logs-dir: my-logs-dir
store-dir: my-store-dir
remote-repo-cache: my-cache-dir
installdir: my-installdir
2 changes: 0 additions & 2 deletions cabal-testsuite/PackageTests/Path/Single/cabal.out

This file was deleted.

3 changes: 0 additions & 3 deletions cabal-testsuite/PackageTests/Path/Single/cabal.test.hs

This file was deleted.

25 changes: 20 additions & 5 deletions cabal-testsuite/src/Test/Cabal/Monad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -300,9 +300,7 @@ runTestM mode m =
program_db1
verbosity

ghcLocation <- case lookupProgramByName "ghc" program_db2 of
Nothing -> fail "runTestM.lookupProgramByName: No location for 'ghc' was found"
Just ghcProg -> pure $ programPath ghcProg
(configuredGhcProg, _) <- requireProgram verbosity ghcProgram program_db2

program_db3 <-
reconfigurePrograms verbosity
Expand All @@ -325,7 +323,7 @@ runTestM mode m =
testProgramDb = program_db,
testPlatform = platform,
testCompiler = comp,
testCompilerPath = ghcLocation,
testCompilerPath = programPath configuredGhcProg,
testPackageDBStack = db_stack,
testVerbosity = verbosity,
testMtimeChangeDelay = Nothing,
Expand Down Expand Up @@ -530,6 +528,16 @@ mkNormalizerEnv = do

canonicalizedTestTmpDir <- liftIO $ canonicalizePath (testTmpDir env)

-- 'cabal' is configured in the package-db, but doesn't specify how to find the program version
-- Thus we find the program location, if it exists, and query for the program version for
-- output normalisation.
cabalVersionM <- do
cabalProgM <- needProgramM "cabal"
case cabalProgM of
Nothing -> pure Nothing
Just cabalProg -> do
liftIO (findProgramVersion "--numeric-version" id (testVerbosity env) (programPath cabalProg))

return NormalizerEnv {
normalizerRoot
= addTrailingPathSeparator (testSourceDir env),
Expand All @@ -548,7 +556,9 @@ mkNormalizerEnv = do
normalizerPlatform
= testPlatform env,
normalizerCabalVersion
= cabalVersionLibrary
= cabalVersionLibrary,
normalizerCabalInstallVersion
= cabalVersionM
}

cabalVersionLibrary :: Version
Expand All @@ -561,6 +571,11 @@ requireProgramM program = do
requireProgram (testVerbosity env) program (testProgramDb env)
return configured_program

needProgramM :: String -> TestM (Maybe ConfiguredProgram)
needProgramM program = do
env <- getTestEnv
return $ lookupProgramByName program (testProgramDb env)

programPathM :: Program -> TestM FilePath
programPathM program = do
fmap programPath (requireProgramM program)
Expand Down
7 changes: 5 additions & 2 deletions cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,20 +63,22 @@ normalizeOutput nenv =
"<GHCVER>"
else id)
. normalizeBuildInfoJson
. normalizePathCmdOutput
. maybe id normalizePathCmdOutput (normalizerCabalInstallVersion nenv)
-- hackage-security locks occur non-deterministically
. resub "(Released|Acquired|Waiting) .*hackage-security-lock\n" ""
where
packageIdRegex pid =
resub (posixRegexEscape (display pid) ++ "(-[A-Za-z0-9.-]+)?")
(prettyShow (packageName pid) ++ "-<VERSION>")

normalizePathCmdOutput =
normalizePathCmdOutput cabalInstallVersion =
-- clear the ghc path out of all supported output formats
resub ("compiler-path: " <> posixRegexEscape (normalizerGhcPath nenv))
"compiler-path: <GHCPATH>"
. resub ("\"compiler-path\"\\s*:\\s*\"" <> posixRegexEscape (normalizerGhcPath nenv) <> "\"")
"\"compiler-path\": \"<GHCPATH>\""
. resub (display cabalInstallVersion)
"<CABAL_INSTALL_VER>"

-- 'build-info.json' contains a plethora of host system specific information.
--
Expand Down Expand Up @@ -116,6 +118,7 @@ data NormalizerEnv = NormalizerEnv
, normalizerKnownPackages :: [PackageId]
, normalizerPlatform :: Platform
, normalizerCabalVersion :: Version
, normalizerCabalInstallVersion :: Maybe Version
}

posixSpecialChars :: [Char]
Expand Down

0 comments on commit 50ba442

Please sign in to comment.