From d0bd687a23672fd420fdb25eb11824d1741ff1d8 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Tue, 17 Dec 2024 09:27:14 -0500 Subject: [PATCH 1/4] Use OS-specific splitPath before comparing projects - Manually replace path separators before anything else - Use pathSeparator instead of literal char - Use isPathSeparator predicate --- .../Solver/Types/ProjectConfigPath.hs | 26 +++++++++++++++++-- 1 file changed, 24 insertions(+), 2 deletions(-) diff --git a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs index a1709a0cf9f..17543b5f2de 100644 --- a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs +++ b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs @@ -32,13 +32,17 @@ import Data.Coerce (coerce) import Data.List.NonEmpty ((<|)) import Network.URI (parseURI, parseAbsoluteURI) import System.Directory -import System.FilePath +import System.FilePath hiding (splitPath) +import qualified System.FilePath as FP (splitPath) +import qualified System.FilePath.Posix as Posix +import qualified System.FilePath.Windows as Windows import qualified Data.List.NonEmpty as NE import Distribution.Solver.Modular.Version (VR) import Distribution.Pretty (prettyShow) import Distribution.Utils.String (trim) import Text.PrettyPrint import Distribution.Simple.Utils (ordNub) +import Distribution.System (OS(Windows), buildOS) -- | Path to a configuration file, either a singleton project root, or a longer -- list representing a path to an import. The path is a non-empty list that we @@ -61,6 +65,14 @@ newtype ProjectConfigPath = ProjectConfigPath (NonEmpty FilePath) -- The project itself, a single element root path, compared to any of the -- configuration paths it imports, should always sort first. Comparing one -- project root path against another is done lexically. +-- +-- For comparison purposes, path separators are normalized to the @buildOS@ +-- platform's path separator. +-- +-- >>> let abFwd = ProjectConfigPath $ "a/b.config" :| [] +-- >>> let abBwd = ProjectConfigPath $ "a\\b.config" :| [] +-- >>> compare abFwd abBwd +-- EQ instance Ord ProjectConfigPath where compare pa@(ProjectConfigPath (NE.toList -> as)) pb@(ProjectConfigPath (NE.toList -> bs)) = case (as, bs) of @@ -69,7 +81,7 @@ instance Ord ProjectConfigPath where -- this though, do a comparison anyway when both sides have length -- 1. The root path, the project itself, should always be the first -- path in a sorted listing. - ([a], [b]) -> compare a b + ([a], [b]) -> compare (splitPath a) (splitPath b) ([_], _) -> LT (_, [_]) -> GT @@ -83,6 +95,16 @@ instance Ord ProjectConfigPath where P.<> compare (length aPaths) (length bPaths) P.<> compare aPaths bPaths where + splitPath = FP.splitPath . normSep where + normSep p = + if buildOS == Windows + then + Windows.joinPath $ Windows.splitDirectories + [if Posix.isPathSeparator c then Windows.pathSeparator else c| c <- p] + else + Posix.joinPath $ Posix.splitDirectories + [if Windows.isPathSeparator c then Posix.pathSeparator else c| c <- p] + aPaths = splitPath <$> as bPaths = splitPath <$> bs aImporters = snd $ unconsProjectConfigPath pa From 30f5d3f2162ce36ae63527de9d08efdc6a4f5647 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Wed, 1 Jan 2025 08:05:12 -0500 Subject: [PATCH 2/4] Needle in haystack multiline expectations - Add else.project test - Use normalizeWindowsOutput - Add a changelog entry - Update expectation - Use concatOutput on needle - Include output - Align lines - Show modified output - Apply concatOutput to the needle - Show start and end of lines with ASCII ^ and $h - Can't print pilcrow so use grep char for marking end of line - Marking the start of line distinguishes "expected" intro from its content too, same for "output" - Use \n in multiline string expectation - Add NeedleHaystack - Add expectNeedleInHaystack field to NeedleHaystack - Remove 3 assert*Contains functions - Add TxContains record - Apply the txBwd transformations before display - Add displayHaystack field - Switch to using as the marker - Sort language pragmas - Use ++ rather than cons with reversals - Rerun ParseErrorProvenance test - Add doctests for single line strings - Read exected multiline string from file - Use lineBreaksToSpaces - Add module Test.Cabal.NeedleHaystack - Redo ConditionalAndImport with multiline expectations - Add test of string expectation start and end marking - Rename encodeLf and decodeLfMarkLines - Rename original concatOutput to lineBreaksToSpaces - Add assertOutputContainsWrapped - Use multiline and wrapped assertions - DedupUsingConfigFromComplex multiline assertion - Remove redundant tests that fail on Windows - Use normalizeWindowsOutput in ConditionalAndImport - Forward conversion applied twice by mistake - Easier diff when assertOn follows assertOutputContains - Add readVerbatimFile - Have readVerbatimFile read contents strictly - Add normalizePathSeparator - Don't modify path separator for URIs - Don't normalize path with anything URI-like - Normalize expected output - Rename to normalizePathSeparators - Add an explicit export list to NeedleHaystack - Drop unlines . lines added trailing newline - Show example of normalizePathSeparators - Use local unsnoc definition to avoid CPP - Define local unlines - Satisfy fix-whitespace - Don't use - Rename to delimitLines - Rename the changelog with *.md extension - Add a section on cabal-testsuite changes - Rename the function to readFileVerbatim - Add to contributing and cabal-testsuite's readme - Use setup for the noun - Typo s/displaying/display - Typo "can easier" - Use unsnoc from Cabal-syntax Utils.Generic - Add a note [Multiline Needles] - Remove doctests available elsewhere - Substitute encodeLf for concatOutput for assertOutputMatches --- CONTRIBUTING.md | 9 +- .../ParseErrorProvenance/cabal.out | 10 + .../ParseErrorProvenance/cabal.test.hs | 24 ++ .../ParseErrorProvenance/dir-else/else.config | 4 + .../ParseErrorProvenance/else.project | 1 + .../ParseErrorProvenance/msg.expect.txt | 5 + cabal-testsuite/README.md | 4 + cabal-testsuite/cabal-testsuite.cabal | 2 + .../src/Test/Cabal/NeedleHaystack.hs | 277 ++++++++++++++++++ cabal-testsuite/src/Test/Cabal/Prelude.hs | 80 +++-- changelog.d/pr-10646.md | 209 +++++++++++++ 11 files changed, 604 insertions(+), 21 deletions(-) create mode 100644 cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.out create mode 100644 cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.test.hs create mode 100644 cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/dir-else/else.config create mode 100644 cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/else.project create mode 100644 cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/msg.expect.txt create mode 100644 cabal-testsuite/src/Test/Cabal/NeedleHaystack.hs create mode 100644 changelog.d/pr-10646.md diff --git a/CONTRIBUTING.md b/CONTRIBUTING.md index 81ea71849da..7a7842017c5 100644 --- a/CONTRIBUTING.md +++ b/CONTRIBUTING.md @@ -395,9 +395,12 @@ description: { } ``` -Changelogs may also be written in "markdown-frontmatter" format. This is useful if your -description contains braces, which must be escaped with backslashes in `.cabal` file -format. The front matter is in YAML syntax, not `.cabal` file syntax, and the file +Changelogs may also be written in "markdown-frontmatter" format. This is useful +if your description contains braces, which must be escaped with backslashes in +`.cabal` file format. Another benefit of using an `.md` extension with your +changelog is that it will be checked for typos. + +The front matter is in YAML syntax, not `.cabal` file syntax, and the file _must_ begin with a line containing only hyphens. ```markdown diff --git a/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.out b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.out new file mode 100644 index 00000000000..a3143ff9ffd --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.out @@ -0,0 +1,10 @@ +# cabal v2-build +Warning: /else.project, else.project: Unrecognized section '_' on line 3 +# Multiline string marking: +# ^When using configuration from:$ +# ^ - else.project$ +# ^ - dir-else/else.config$ +# ^The following errors occurred:$ +# ^ - The package location 'no-pkg-here' does not exist.$ +# Pseudo multiline string marking: +# ^When using configuration from: - else.project - dir-else/else.config The following errors occurred: - The package location 'no-pkg-here' does not exist.$ diff --git a/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.test.hs new file mode 100644 index 00000000000..49360b59872 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.test.hs @@ -0,0 +1,24 @@ +import Test.Cabal.Prelude +import System.Directory + +main = cabalTest . recordMode RecordMarked $ do + let log = recordHeader . pure + + outElse <- fails $ cabal' "v2-build" [ "all", "--dry-run", "--project-file=else.project" ] + + msg <- readFileVerbatim "msg.expect.txt" + let msgSingle = lineBreaksToSpaces msg + + log "Multiline string marking:" + mapM_ log (lines . delimitLines $ encodeLf msg) + + log "Pseudo multiline string marking:" + mapM_ log (lines . delimitLines $ encodeLf msgSingle) + + assertOn multilineNeedleHaystack msg outElse + assertOn multilineNeedleHaystack{expectNeedleInHaystack = False} msgSingle outElse + + assertOutputContains msg outElse + assertOutputDoesNotContain msgSingle outElse + + return () diff --git a/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/dir-else/else.config b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/dir-else/else.config new file mode 100644 index 00000000000..f9c44e63d5b --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/dir-else/else.config @@ -0,0 +1,4 @@ +if false +else + _ + packages: no-pkg-here diff --git a/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/else.project b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/else.project new file mode 100644 index 00000000000..959c40f5660 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/else.project @@ -0,0 +1 @@ +import: dir-else/else.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/msg.expect.txt b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/msg.expect.txt new file mode 100644 index 00000000000..e5291b3adcd --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/msg.expect.txt @@ -0,0 +1,5 @@ +When using configuration from: + - else.project + - dir-else/else.config +The following errors occurred: + - The package location 'no-pkg-here' does not exist. diff --git a/cabal-testsuite/README.md b/cabal-testsuite/README.md index 2c3d17e6150..fb641cad995 100644 --- a/cabal-testsuite/README.md +++ b/cabal-testsuite/README.md @@ -218,6 +218,10 @@ variants of a command (e.g., `cabal'` rather than `cabal`) and use `assertOutputContains`. Note that this will search over BOTH stdout and stderr. +For convenience, paste expected multiline string values verbatim into a text +file and read these with `readFileVerbatim`. The suggested extension for these +files are `.expect.txt`. + **How do I skip running a test in some environments?** Use the `skipIf` and `skipUnless` combinators. Useful parameters to test these with include `hasSharedLibraries`, `hasProfiledLibraries`, diff --git a/cabal-testsuite/cabal-testsuite.cabal b/cabal-testsuite/cabal-testsuite.cabal index 0f3383af38a..4e31b87d254 100644 --- a/cabal-testsuite/cabal-testsuite.cabal +++ b/cabal-testsuite/cabal-testsuite.cabal @@ -45,6 +45,7 @@ library Test.Cabal.CheckArMetadata Test.Cabal.DecodeShowBuildInfo Test.Cabal.Monad + Test.Cabal.NeedleHaystack Test.Cabal.OutputNormalizer Test.Cabal.Plan Test.Cabal.Prelude @@ -71,6 +72,7 @@ library , exceptions ^>= 0.10.0 , filepath ^>= 1.3.0.1 || ^>= 1.4.0.0 || ^>= 1.5.0.0 , Glob ^>= 0.10.2 + , network-uri >= 2.6.0.2 && < 2.7 , network-wait ^>= 0.1.2.0 || ^>= 0.2.0.0 , optparse-applicative ^>= 0.14.3.0 || ^>=0.15.1.0 || ^>=0.16.0.0 || ^>= 0.17.0.0 || ^>= 0.18.1.0 , process ^>= 1.2.1.0 || ^>= 1.4.2.0 || ^>= 1.6.1.0 diff --git a/cabal-testsuite/src/Test/Cabal/NeedleHaystack.hs b/cabal-testsuite/src/Test/Cabal/NeedleHaystack.hs new file mode 100644 index 00000000000..42ab1031284 --- /dev/null +++ b/cabal-testsuite/src/Test/Cabal/NeedleHaystack.hs @@ -0,0 +1,277 @@ +{-# LANGUAGE MultiWayIf #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE ViewPatterns #-} + +-- | Functions for searching for a needle in a haystack, with transformations +-- for the strings to search in and the search strings such as re-encoding line +-- breaks or delimiting lines. Both LF and CRLF line breaks are recognized. +module Test.Cabal.NeedleHaystack + ( TxContains(..) + , txContainsId + , NeedleHaystack(..) + , symNeedleHaystack + , multilineNeedleHaystack + , needleHaystack + , lineBreaksToSpaces + , normalizePathSeparators + , encodeLf + , delimitLines + ) where + +import Prelude hiding (unlines) +import qualified Prelude (unlines) +import Data.List (tails) +import Data.Maybe (isJust) +import Distribution.System +import Distribution.Utils.Generic (unsnoc) +import Data.List (isPrefixOf) +import qualified System.FilePath.Posix as Posix +import qualified System.FilePath.Windows as Windows +import Network.URI (parseURI) + +{- +Note [Multiline Needles] +~~~~~~~~~~~~~~~~~~~~~~~~ + +How we search for multiline strings in output that varies by platform. + +Reading Expected Multiline Strings Verbatim +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +With @ghc-9.12.1@ adding @-XMultilineStrings@, writing multiline string +expectations for @cabal-testsuite/PackageTests/**/*.test.hs@ test scripts might +be have been easier but for a catch. We run these tests with older @GHC@ +versions so would need to use @-XCPP@ for those versions and the C preprocessor +does not play nicely with string gaps. While it is possible to encode a +multiline string as a single line with embedded LF characters or by breaking the +line up arbitrarily and using @++@ concatenation or by calling unlines on a list +of lines, string gaps are the multiline strings of Haskell prior to +@-XMultilineStrings@. + +To avoid these problems and for the convenience of pasting the expected value +verbatim into a file, @readFileVerbatim@ can read the expected multiline output +for tests from a text file. This has the same implementation as @readFile@ from +the @strict-io@ package to avoid problems at cleanup. + +Warning: Windows file locking hack: hit the retry limit 3 while trying to remove +C:\Users\\AppData\Local\Temp\cabal-testsuite-8376 +cabal.test.hs: +C:\Users\\AppData\Local\Temp\cabal-testsuite-8376\errors.expect.txt: removePathForcibly:DeleteFile +"\\\\?\\C:\\Users\\\\AppData\\Local\\Temp\\cabal-testsuite-8376\\errors.expect.txt": +permission denied (The process cannot access the file because it is being used by another process.) + +The other process accessing the file is @C:\WINDOWS\System32\svchost.exe@ +running a @QueryDirectory@ event and this problem only occurs when the test +fails. + +Hidden Actual Value Modification +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +The @assertOutputContains@ function was modifying the actual value (the test +output) with @concatOutput@ before checking if it contained the expected value. +This function, now renamed as @lineBreaksToSpaces@, would remove CR values and +convert LF values to spaces. + +With this setup, false positives were possible. An expected value using string +gaps and spaces would match a @concatOutput@ modified actual value of +"foo_bar_baz", where '_' was any of space, LF or CRLF in the unmodified actual +value. The latter two are false positive matches. + +> let expect = "foo \ +> \bar \ +> \baz" + +False negatives were also possible. An expected value set up using string gaps +with LF characters or with @-XMultilineStrings@ wouldn't match an actual value +of "foo_bar_baz", where '_' was either LF or CRLF because these characters had +been replaced by spaces in the actual value, modified before the comparison. + +> let expect = "foo\n\ +> \bar\n\ +> \baz" + +> {-# LANGUAGE MultilineStrings #-} +> +> let expect = """ +> foo +> bar +> baz +> """ + +We had these problems: + +1. The actual value was changed before comparison and this change was not visible. +2. The expected value was not changed in the same way as the actual value. This + made it possible for equal values to become unequal (false negatives) and for + unequal values to become equal (false positives). + +Explicit Changes and Visible Line Delimiters +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +To fix these problems, an added @assertOn@ function takes a @NeedleHaystack@ +configuration for how the search is made, what to expect (to find the expected +value or not) and how to display the expected and actual values. + +A pilcrow ¶ is often used to visibly display line endings but our terminal +output is restricted to ASCII so lines are delimited between @^@ and @$@ +markers. The needle (the expected output fragment) is shown annotated this way +and the haystack (the actual output) can optionally be shown this way too. + +This is still a lenient match, allowing LF to match CRLF, but @encodeLf@ doesn't +replace LF with spaces like @concatOutput@ (@lineBreaksToSpaces@) did: + +If you choose to display the actual value by setting +@NeedleHaystack{displayHaystack = True}@ then its lines will be delimited. + +With @assertOn@, supplying string transformation to both the needle and haystack +before comparison and before display can help find out why an expected value is +or isn't found in the test output. +-} + +-- | Transformations for the search strings and the text to search in. +data TxContains = + TxContains + { + -- | Reverse conversion for display, applied to the forward converted value. + txBwd :: (String -> String), + -- | Forward conversion for comparison. + txFwd :: (String -> String) + } + +-- | Identity transformation for the search strings and the text to search in, +-- leaves them unchanged. +txContainsId :: TxContains +txContainsId = TxContains id id + +-- | Conversions of the needle and haystack strings, the seach string and the +-- text to search in. +data NeedleHaystack = + NeedleHaystack + { + expectNeedleInHaystack :: Bool, + displayHaystack :: Bool, + txNeedle :: TxContains, + txHaystack :: TxContains + } + +-- | Symmetric needle and haystack functions, the same conversion for each going +-- forward and the same coversion for each going backward. +symNeedleHaystack :: (String -> String) -> (String -> String) -> NeedleHaystack +symNeedleHaystack bwd fwd = let tx = TxContains bwd fwd in NeedleHaystack True False tx tx + +-- | Multiline needle and haystack functions with symmetric conversions. Going +-- forward converts line breaks to @"\\n"@. Going backward adds visible +-- delimiters to lines. +multilineNeedleHaystack :: NeedleHaystack +multilineNeedleHaystack = symNeedleHaystack delimitLines encodeLf + +-- | Minimal set up for finding the needle in the haystack. Doesn't change the +-- strings and doesn't display the haystack in any assertion failure message. +needleHaystack :: NeedleHaystack +needleHaystack = NeedleHaystack True False txContainsId txContainsId + +-- | Replace line breaks with spaces, correctly handling @"\\r\\n"@. +-- +-- >>> lineBreaksToSpaces "foo\nbar\r\nbaz" +-- "foo bar baz" +-- +-- >>> lineBreaksToSpaces "foo\nbar\r\nbaz\n" +-- "foo bar baz" +-- +-- >>> lineBreaksToSpaces "\nfoo\nbar\r\nbaz\n" +-- " foo bar baz" +lineBreaksToSpaces :: String -> String +lineBreaksToSpaces = unwords . lines . filter ((/=) '\r') + +-- | Replaces path separators found with those of the current OS, URL-like paths +-- excluded. +-- +-- > buildOS == Linux; normalizePathSeparators "foo\bar\baz" => "foo/bar/baz" +-- > buildOS == Windows; normalizePathSeparators "foo/bar/baz" => "foo\bar\baz" +normalizePathSeparators :: String -> String +normalizePathSeparators = + unlines . map normalizePathSeparator . lines + where + normalizePathSeparator p = + if | any (isJust . parseURI) (tails p) -> p + | buildOS == Windows -> + [if Posix.isPathSeparator c then Windows.pathSeparator else c| c <- p] + | otherwise -> + [if Windows.isPathSeparator c then Posix.pathSeparator else c| c <- p] + +-- | @unlines@ from base will add a trailing newline if there isn't one already +-- but this one doesn't +-- +-- >>> lines "abc" +-- ["abc"] +-- +-- >>> Data.List.unlines $ lines "abc" +-- "abc\n" +-- +-- >>> unlines $ lines "abc" +-- "abc" +unlines :: [String] -> String +unlines = maybe "" fst . unsnoc . Prelude.unlines + +-- | Replace line CRLF line breaks with LF line breaks. +-- +-- >>> encodeLf "foo\nbar\r\nbaz" +-- "foo\nbar\nbaz" +-- +-- >>> encodeLf "foo\nbar\r\nbaz\n" +-- "foo\nbar\nbaz\n" +-- +-- >>> encodeLf "\nfoo\nbar\r\nbaz\n" +-- "\nfoo\nbar\nbaz\n" +-- +-- >>> encodeLf "\n\n\n" +-- "\n\n\n" +encodeLf :: String -> String +encodeLf = filter (/= '\r') + +-- | Mark lines with visible delimiters, @^@ at the start and @$@ at the end. +-- +-- >>> delimitLines "" +-- "^$" +-- +-- >>> delimitLines "\n" +-- "^$\n" +-- +-- >>> delimitLines "\n\n" +-- "^$\n^$\n" +-- +-- >>> delimitLines "\n\n\n" +-- "^$\n^$\n^$\n" +-- +-- >>> delimitLines $ encodeLf "foo\nbar\r\nbaz" +-- "^foo$\n^bar$\n^baz$" +-- +-- >>> delimitLines $ encodeLf "foo\nbar\r\nbaz\n" +-- "^foo$\n^bar$\n^baz$\n" +-- +-- >>> delimitLines $ encodeLf "\nfoo\nbar\r\nbaz\n" +-- "^$\n^foo$\n^bar$\n^baz$\n" +delimitLines:: String -> String +delimitLines "" = "^$" +delimitLines "\n" = "^$\n" +delimitLines ('\n' : xs) = "^$\n" ++ delimitLines xs +delimitLines output = fixupStart . fixupEnd $ + foldr + (\c acc -> c : + if | "\n" == acc -> "$\n" + |("\n" `isPrefixOf` acc) -> "$\n^" ++ drop 1 acc + | otherwise -> acc + ) + "" + output + where + fixupStart :: String -> String + fixupStart s@[] = s + fixupStart s@('^' : _) = s + fixupStart s = '^' : s + + fixupEnd :: String -> String + fixupEnd s@[] = s + fixupEnd s@(reverse -> '$' : _) = s + fixupEnd s@(reverse -> '\n' : '$' : _) = s + fixupEnd s = s ++ "$" diff --git a/cabal-testsuite/src/Test/Cabal/Prelude.hs b/cabal-testsuite/src/Test/Cabal/Prelude.hs index 6455dbb87b1..daa5472c9d0 100644 --- a/cabal-testsuite/src/Test/Cabal/Prelude.hs +++ b/cabal-testsuite/src/Test/Cabal/Prelude.hs @@ -1,14 +1,17 @@ -{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NondecreasingIndentation #-} -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE CPP #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE ViewPatterns #-} -- | Generally useful definitions that we expect most test scripts -- to use. module Test.Cabal.Prelude ( module Test.Cabal.Prelude, module Test.Cabal.Monad, + module Test.Cabal.NeedleHaystack, module Test.Cabal.Run, module System.FilePath, module Distribution.Utils.Path, @@ -18,6 +21,7 @@ module Test.Cabal.Prelude ( module Distribution.Simple.Program, ) where +import Test.Cabal.NeedleHaystack import Test.Cabal.Script import Test.Cabal.Run import Test.Cabal.Monad @@ -800,31 +804,46 @@ recordMode mode = withReaderT (\env -> env { testRecordUserMode = Just mode }) +-- See Note [Multiline Needles] assertOutputContains :: MonadIO m => WithCallStack (String -> Result -> m ()) -assertOutputContains needle result = - withFrozenCallStack $ - unless (needle `isInfixOf` concatOutput output) $ - assertFailure $ " expected: " ++ needle - where output = resultOutput result +assertOutputContains = assertOn + needleHaystack + {txHaystack = TxContains{txBwd = delimitLines, txFwd = encodeLf}} assertOutputDoesNotContain :: MonadIO m => WithCallStack (String -> Result -> m ()) -assertOutputDoesNotContain needle result = +assertOutputDoesNotContain = assertOn + needleHaystack + { expectNeedleInHaystack = False + , txHaystack = TxContains{txBwd = delimitLines, txFwd = encodeLf} + } + +-- See Note [Multiline Needles] +assertOn :: MonadIO m => WithCallStack (NeedleHaystack -> String -> Result -> m ()) +assertOn NeedleHaystack{..} (txFwd txNeedle -> needle) (txFwd txHaystack. resultOutput -> output) = withFrozenCallStack $ - when (needle `isInfixOf` concatOutput output) $ - assertFailure $ "unexpected: " ++ needle - where output = resultOutput result + if expectNeedleInHaystack + then unless (needle `isInfixOf` output) + $ assertFailure $ "expected:\n" ++ (txBwd txNeedle needle) ++ + if displayHaystack + then "\nin output:\n" ++ (txBwd txHaystack output) + else "" + else when (needle `isInfixOf` output) + $ assertFailure $ "unexpected:\n" ++ (txBwd txNeedle needle) ++ + if displayHaystack + then "\nin output:\n" ++ (txBwd txHaystack output) + else "" assertOutputMatches :: MonadIO m => WithCallStack (String -> Result -> m ()) assertOutputMatches regex result = withFrozenCallStack $ - unless (concatOutput output =~ regex) $ + unless (encodeLf output =~ regex) $ assertFailure $ "expected regex match: " ++ regex where output = resultOutput result assertOutputDoesNotMatch :: MonadIO m => WithCallStack (String -> Result -> m ()) assertOutputDoesNotMatch regex result = withFrozenCallStack $ - when (concatOutput output =~ regex) $ + when (encodeLf output =~ regex) $ assertFailure $ "unexpected regex match: " ++ regex where output = resultOutput result @@ -880,10 +899,6 @@ assertNoFileContains paths needle = \path -> assertFileDoesNotContain path needle --- | Replace line breaks with spaces, correctly handling "\r\n". -concatOutput :: String -> String -concatOutput = unwords . lines . filter ((/=) '\r') - -- | The directory where script build artifacts are expected to be cached getScriptCacheDirectory :: FilePath -> TestM FilePath getScriptCacheDirectory script = do @@ -1274,3 +1289,32 @@ findDependencyInStore pkgName = do [] -> error $ "Could not find " <> pkgName' <> " when searching for " <> pkgName' <> " in\n" <> show packageDirs (dir:_) -> dir pure (storeDir storeDirForGhcVersion libDir) + +-- | It can be easier to paste expected output verbatim into a text file, +-- especially if it is a multiline string, rather than encoding it as a multiline +-- string in Haskell source code. +-- +-- With `-XMultilineStrings` triple quoted strings with line breaks will be +-- easier to write in source code but then this will only work with ghc-9.12.1 +-- and later, in which case we'd have to use CPP with test scripts to support +-- older GHC versions. CPP doesn't play nicely with multiline strings using +-- string gaps. None of our test script import other modules. That might be a +-- way to avoid CPP in a module that uses multiline strings. +-- +-- In summary, it is easier to read multiline strings from a file. That is what +-- this function facilitates. +-- +-- The contents of the file are read strictly to avoid problems seen on Windows +-- deleting the file: +-- +-- > cabal.test.hs: +-- > C:\Users\\AppData\Local\Temp\cabal-testsuite-8376\errors.expect.txt: +-- > removePathForcibly:DeleteFile +-- > "\\\\?\\C:\\Users\\\\AppData\\Local\\Temp\\cabal-testsuite-8376\\errors.expect.txt": +-- > permission denied (The process cannot access the file because it is being +-- > used by another process.) +readFileVerbatim :: FilePath -> TestM String +readFileVerbatim filename = do + testDir <- testCurrentDir <$> getTestEnv + s <- liftIO . readFile $ testDir filename + length s `seq` return s diff --git a/changelog.d/pr-10646.md b/changelog.d/pr-10646.md new file mode 100644 index 00000000000..fb7dd8c9ec7 --- /dev/null +++ b/changelog.d/pr-10646.md @@ -0,0 +1,209 @@ +--- +synopsis: Configuration messages without duplicates +packages: [cabal-install-solver] +prs: 10646 +issues: 10645 +--- + +The "using configuration from" message no longer has duplicates on Windows when +a `cabal.project` uses forward slashes for its imports but the message reports +the same import again with backslashes. + +```diff +$ cat cabal.project +import: dir-a/b.config + +$ cabal build all --dry-run +... +When using configuration from: +- - dir-a/b.config + - dir-a\b.config + - cabal.project +``` + +## Changed `Ord ProjectConfigPath` Instance + +For comparison purposes, path separators are normalized to the `buildOS` +platform's path separator. + +```haskell +-- >>> let abFwd = ProjectConfigPath $ "a/b.config" :| [] +-- >>> let abBwd = ProjectConfigPath $ "a\\b.config" :| [] +-- >>> compare abFwd abBwd +-- EQ +``` + +## Changes in `cabal-testsuite` + +### Reading Expected Multiline Strings Verbatim + +With `ghc-9.12.1` adding `-XMultilineStrings`, writing multiline string +expectations for `cabal-testsuite/PackageTests/**/*.test.hs` test scripts might +be have been easier but for a catch. We run these tests with older `GHC` +versions so would need to use `-XCPP` for those versions and the C preprocessor +does not play nicely with string gaps. While it is possible to encode a +multiline string as a single line with embedded LF characters or by breaking the +line up arbitrarily and using `++` concatenation or by calling unlines on a list +of lines, string gaps are the multiline strings of Haskell prior to +`-XMultilineStrings`. + +To avoid these problems and for the convenience of pasting the expected value +verbatim into a file, `readFileVerbatim` can read the expected multiline output +for tests from a text file. This has the same implementation as `readFile` from +the `strict-io` package to avoid problems at cleanup. + +``` +Warning: Windows file locking hack: hit the retry limit 3 while trying to remove +C:\Users\\AppData\Local\Temp\cabal-testsuite-8376 +cabal.test.hs: +C:\Users\\AppData\Local\Temp\cabal-testsuite-8376\errors.expect.txt: removePathForcibly:DeleteFile +"\\\\?\\C:\\Users\\\\AppData\\Local\\Temp\\cabal-testsuite-8376\\errors.expect.txt": +permission denied (The process cannot access the file because it is being used by another process.) +``` + +The other process accessing the file is `C:\WINDOWS\System32\svchost.exe` +running a `QueryDirectory` event and this problem only occurs when the test +fails. + +### Hidden Actual Value Modification + +The `assertOutputContains` function was modifying the actual value (the test +output) with `concatOutput` before checking if it contained the expected value. +This function, now renamed as `lineBreaksToSpaces`, would remove CR values and +convert LF values to spaces. + +```haskell +-- | Replace line breaks with spaces, correctly handling @"\\r\\n"@. +-- +-- >>> lineBreaksToSpaces "foo\nbar\r\nbaz" +-- "foo bar baz" +-- +-- >>> lineBreaksToSpaces "foo\nbar\r\nbaz\n" +-- "foo bar baz" +-- +-- >>> lineBreaksToSpaces "\nfoo\nbar\r\nbaz\n" +-- " foo bar baz" +lineBreaksToSpaces :: String -> String +``` + +With this setup, false positives were possible. An expected value using string +gaps and spaces would match a `concatOutput` modified actual value of +"foo_bar_baz", where '_' was any of space, LF or CRLF in the unmodified actual +value. The latter two are false positive matches. + +```haskell +let expect = "foo \ + \bar \ + \baz" +``` + +False negatives were also possible. An expected value set up using string gaps +with LF characters or with `-XMultilineStrings` wouldn't match an actual value +of "foo_bar_baz", where '_' was either LF or CRLF because these characters had +been replaced by spaces in the actual value, modified before the comparison. + +```haskell +let expect = "foo\n\ + \bar\n\ + \baz" +``` + +```haskell +{-# LANGUAGE MultilineStrings #-} + +let expect = """ + foo + bar + baz + """ +``` + +We had these problems: + +1. The actual value was changed before comparison and this change was not visible. +2. The expected value was not changed in the same way as the actual value. This + made it possible for equal values to become unequal (false negatives) and for + unequal values to become equal (false positives). + +### Explicit Changes and Visible Line Delimiters + +To fix these problems, an added `assertOn` function takes a `NeedleHaystack` +configuration for how the search is made, what to expect (to find the expected +value or not) and how to display the expected and actual values. + +A pilcrow ¶ is often used to visibly display line endings but our terminal +output is restricted to ASCII so lines are delimited between `^` and `$` +markers. The needle (the expected output fragment) is shown annotated this way +and the haystack (the actual output) can optionally be shown this way too. + +We can now implement `assertOutputContains` by calling `assertOn`: + +```diff + assertOutputContains :: MonadIO m => WithCallStack (String -> Result -> m ()) +- assertOutputContains needle result = +- withFrozenCallStack $ +- unless (needle `isInfixOf` (concatOutput output)) $ +- assertFailure $ " expected: " ++ needle +- where output = resultOutput result ++ assertOutputContains = assertOn ++ needleHaystack ++ {txHaystack = ++ TxContains ++ { txBwd = delimitLines ++ , txFwd = encodeLf ++ } ++ } +``` + +This is still a lenient match, allowing LF to match CRLF, but `encodeLf` doesn't +replace LF with spaces like `concatOutput` (`lineBreaksToSpaces`) did: + +```haskell +-- | Replace line CRLF line breaks with LF line breaks. +-- +-- >>> encodeLf "foo\nbar\r\nbaz" +-- "foo\nbar\nbaz" +-- +-- >>> encodeLf "foo\nbar\r\nbaz\n" +-- "foo\nbar\nbaz\n" +-- +-- >>> encodeLf "\nfoo\nbar\r\nbaz\n" +-- "\nfoo\nbar\nbaz\n" +-- +-- >>> encodeLf "\n\n\n" +-- "\n\n\n" +encodeLf :: String -> String +``` + +If you choose to display the actual value by setting +`NeedleHaystack{displayHaystack = True}` then its lines will be delimited. + +```haskell +-- | Mark lines with visible delimiters, @^@ at the start and @$@ at the end. +-- +-- >>> delimitLines "" +-- "^$" +-- +-- >>> delimitLines "\n" +-- "^$\n" +-- +-- >>> delimitLines "\n\n" +-- "^$\n^$\n" +-- +-- >>> delimitLines "\n\n\n" +-- "^$\n^$\n^$\n" +-- +-- >>> delimitLines $ encodeLf "foo\nbar\r\nbaz" +-- "^foo$\n^bar$\n^baz$" +-- +-- >>> delimitLines $ encodeLf "foo\nbar\r\nbaz\n" +-- "^foo$\n^bar$\n^baz$\n" +-- +-- >>> delimitLines $ encodeLf "\nfoo\nbar\r\nbaz\n" +-- "^$\n^foo$\n^bar$\n^baz$\n" +delimitLines:: String -> String +``` + +With `assertOn`, supplying string transformation to both the needle and haystack +before comparison and before display can help find out why an expected value is +or isn't found in the test output. From 484ac9cb04b290c54facbc1c035c30b0ddc6628a Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Wed, 1 Jan 2025 08:03:39 -0500 Subject: [PATCH 3/4] Fix up existing tests with multiline expectations --- .../BuildDeps/InternalLibrary2/setup.test.hs | 2 +- .../BuildDeps/InternalLibrary3/setup.test.hs | 2 +- .../PackageTests/CheckSetup/setup.test.hs | 8 +- .../ConditionalAndImport/cabal.test.hs | 195 ++++++++---------- .../PackageTests/NewBuild/T4288/cabal.test.hs | 10 +- .../DedupUsingConfigFromComplex/cabal.out | 5 +- .../DedupUsingConfigFromComplex/cabal.test.hs | 15 +- ...endency-for-library-and-build-tool.test.hs | 18 +- 8 files changed, 119 insertions(+), 136 deletions(-) diff --git a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary2/setup.test.hs b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary2/setup.test.hs index e36e33823d2..6b6da17f116 100644 --- a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary2/setup.test.hs +++ b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary2/setup.test.hs @@ -6,4 +6,4 @@ main = setupAndCabalTest . withPackageDb $ do assertEqual ("executable should have linked with the internal library") ("foo foo myLibFunc internal") - (concatOutput (resultOutput r)) + (lineBreaksToSpaces $ resultOutput r) diff --git a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary3/setup.test.hs b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary3/setup.test.hs index 549e8bf8bb4..ac05c394383 100644 --- a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary3/setup.test.hs +++ b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary3/setup.test.hs @@ -8,4 +8,4 @@ main = setupAndCabalTest . withPackageDb $ do assertEqual ("executable should have linked with the internal library") ("foo foo myLibFunc internal") - (concatOutput (resultOutput r)) + (lineBreaksToSpaces $ resultOutput r) diff --git a/cabal-testsuite/PackageTests/CheckSetup/setup.test.hs b/cabal-testsuite/PackageTests/CheckSetup/setup.test.hs index 96ed4395785..67997e7e21b 100644 --- a/cabal-testsuite/PackageTests/CheckSetup/setup.test.hs +++ b/cabal-testsuite/PackageTests/CheckSetup/setup.test.hs @@ -13,8 +13,12 @@ main = cabalTest $ do "The dependency 'setup-depends: 'base' does not specify " ++ "an upper bound on the version number" + -- Replace line breaks with spaces in the haystack so that we can search + -- for a string that wraps lines. + let lineBreakBlind = needleHaystack{txHaystack = txContainsId{txFwd = lineBreaksToSpaces}} + -- Asserts for the desired check messages after configure. - assertOutputContains libError1 checkResult - assertOutputContains libError2 checkResult + assertOn lineBreakBlind libError1 checkResult + assertOn lineBreakBlind libError2 checkResult return () diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs index 67118d362c0..d0abb33de2d 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs @@ -1,7 +1,6 @@ import Test.Cabal.Prelude - -normalizeWindowsOutput :: String -> String -normalizeWindowsOutput = if isWindows then map (\x -> case x of '/' -> '\\'; _ -> x) else id +import Test.Cabal.OutputNormalizer +import Data.Function ((&)) main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do let log = recordHeader . pure @@ -111,89 +110,65 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- hops/hops-9.config (no further imports so not cyclical) log "checking that imports work skipping into a subfolder and then back out again and again" hopping <- cabal' "v2-build" [ "--project-file=hops-0.project" ] - assertOutputContains "Configuration is affected by the following files" hopping - assertOutputContains "- hops-0.project" hopping - - assertOutputContains - (normalizeWindowsOutput "- hops-2.config \ - \ imported by: hops/hops-1.config \ - \ imported by: hops-0.project") - hopping - - assertOutputContains - (normalizeWindowsOutput "- hops-4.config \ - \ imported by: hops/hops-3.config \ - \ imported by: hops-2.config \ - \ imported by: hops/hops-1.config \ - \ imported by: hops-0.project") - hopping - - assertOutputContains - (normalizeWindowsOutput "- hops-6.config \ - \ imported by: hops/hops-5.config \ - \ imported by: hops-4.config \ - \ imported by: hops/hops-3.config \ - \ imported by: hops-2.config \ - \ imported by: hops/hops-1.config \ - \ imported by: hops-0.project") - hopping - - assertOutputContains - (normalizeWindowsOutput "- hops-8.config \ - \ imported by: hops/hops-7.config \ - \ imported by: hops-6.config \ - \ imported by: hops/hops-5.config \ - \ imported by: hops-4.config \ - \ imported by: hops/hops-3.config \ - \ imported by: hops-2.config \ - \ imported by: hops/hops-1.config \ - \ imported by: hops-0.project") - hopping - assertOutputContains - (normalizeWindowsOutput "- hops/hops-1.config \ - \ imported by: hops-0.project") - hopping - - assertOutputContains - (normalizeWindowsOutput "- hops/hops-3.config \ - \ imported by: hops-2.config \ - \ imported by: hops/hops-1.config \ - \ imported by: hops-0.project") - hopping - - assertOutputContains - (normalizeWindowsOutput "- hops/hops-5.config \ - \ imported by: hops-4.config \ - \ imported by: hops/hops-3.config \ - \ imported by: hops-2.config \ - \ imported by: hops/hops-1.config \ - \ imported by: hops-0.project") - hopping - - assertOutputContains - (normalizeWindowsOutput "- hops/hops-7.config \ - \ imported by: hops-6.config \ - \ imported by: hops/hops-5.config \ - \ imported by: hops-4.config \ - \ imported by: hops/hops-3.config \ - \ imported by: hops-2.config \ - \ imported by: hops/hops-1.config \ - \ imported by: hops-0.project") - hopping - - assertOutputContains - (normalizeWindowsOutput "- hops/hops-9.config \ - \ imported by: hops-8.config \ - \ imported by: hops/hops-7.config \ - \ imported by: hops-6.config \ - \ imported by: hops/hops-5.config \ - \ imported by: hops-4.config \ - \ imported by: hops/hops-3.config \ - \ imported by: hops-2.config \ - \ imported by: hops/hops-1.config \ - \ imported by: hops-0.project") - hopping + "Configuration is affected by the following files:\n\ + \- hops-0.project\n\ + \- hops-2.config\n\ + \ imported by: hops/hops-1.config\n\ + \ imported by: hops-0.project\n\ + \- hops-4.config\n\ + \ imported by: hops/hops-3.config\n\ + \ imported by: hops-2.config\n\ + \ imported by: hops/hops-1.config\n\ + \ imported by: hops-0.project\n\ + \- hops-6.config\n\ + \ imported by: hops/hops-5.config\n\ + \ imported by: hops-4.config\n\ + \ imported by: hops/hops-3.config\n\ + \ imported by: hops-2.config\n\ + \ imported by: hops/hops-1.config\n\ + \ imported by: hops-0.project\n\ + \- hops-8.config\n\ + \ imported by: hops/hops-7.config\n\ + \ imported by: hops-6.config\n\ + \ imported by: hops/hops-5.config\n\ + \ imported by: hops-4.config\n\ + \ imported by: hops/hops-3.config\n\ + \ imported by: hops-2.config\n\ + \ imported by: hops/hops-1.config\n\ + \ imported by: hops-0.project\n\ + \- hops/hops-1.config\n\ + \ imported by: hops-0.project\n\ + \- hops/hops-3.config\n\ + \ imported by: hops-2.config\n\ + \ imported by: hops/hops-1.config\n\ + \ imported by: hops-0.project\n\ + \- hops/hops-5.config\n\ + \ imported by: hops-4.config\n\ + \ imported by: hops/hops-3.config\n\ + \ imported by: hops-2.config\n\ + \ imported by: hops/hops-1.config\n\ + \ imported by: hops-0.project\n\ + \- hops/hops-7.config\n\ + \ imported by: hops-6.config\n\ + \ imported by: hops/hops-5.config\n\ + \ imported by: hops-4.config\n\ + \ imported by: hops/hops-3.config\n\ + \ imported by: hops-2.config\n\ + \ imported by: hops/hops-1.config\n\ + \ imported by: hops-0.project\n\ + \- hops/hops-9.config\n\ + \ imported by: hops-8.config\n\ + \ imported by: hops/hops-7.config\n\ + \ imported by: hops-6.config\n\ + \ imported by: hops/hops-5.config\n\ + \ imported by: hops-4.config\n\ + \ imported by: hops/hops-3.config\n\ + \ imported by: hops-2.config\n\ + \ imported by: hops/hops-1.config\n\ + \ imported by: hops-0.project" + & normalizeWindowsOutput + & flip (assertOn multilineNeedleHaystack) hopping -- The project is named oops as it is like hops but has conflicting constraints. -- +-- oops-0.project @@ -208,22 +183,25 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- oops/oops-9.config (has conflicting constraints) log "checking conflicting constraints skipping into a subfolder and then back out again and again" oopsing <- fails $ cabal' "v2-build" [ "all", "--project-file=oops-0.project" ] - assertOutputContains "rejecting: hashable-1.4.2.0" oopsing - assertOutputContains "rejecting: hashable-1.4.3.0" oopsing - assertOutputContains "(constraint from oops-0.project requires ==1.4.3.0)" oopsing - assertOutputContains - (normalizeWindowsOutput " (constraint from oops/oops-9.config requires ==1.4.2.0) \ - \ imported by: oops-8.config \ - \ imported by: oops/oops-7.config \ - \ imported by: oops-6.config \ - \ imported by: oops/oops-5.config \ - \ imported by: oops-4.config \ - \ imported by: oops/oops-3.config \ - \ imported by: oops-2.config \ - \ imported by: oops/oops-1.config \ - \ imported by: oops-0.project") - oopsing + "Could not resolve dependencies:\n\ + \[__0] trying: oops-0.1 (user goal)\n\ + \[__1] next goal: hashable (dependency of oops)\n\ + \[__1] rejecting: hashable-1.4.3.0\n\ + \ (constraint from oops/oops-9.config requires ==1.4.2.0)\n\ + \ imported by: oops-8.config\n\ + \ imported by: oops/oops-7.config\n\ + \ imported by: oops-6.config\n\ + \ imported by: oops/oops-5.config\n\ + \ imported by: oops-4.config\n\ + \ imported by: oops/oops-3.config\n\ + \ imported by: oops-2.config\n\ + \ imported by: oops/oops-1.config\n\ + \ imported by: oops-0.project\n\ + \[__1] rejecting: hashable-1.4.2.0\n\ + \ (constraint from oops-0.project requires ==1.4.3.0)" + & normalizeWindowsOutput + & flip (assertOn multilineNeedleHaystack) oopsing -- The project is named yops as it is like hops but with y's for forks. -- +-- yops-0.project @@ -264,13 +242,14 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do log "checking that missing package message lists configuration provenance" missing <- fails $ cabal' "v2-build" [ "--project-file=cabal-missing-package.project" ] - assertOutputContains - (normalizeWindowsOutput "When using configuration from: \ - \ - cabal-missing-package.project \ - \ - missing/pkgs.config \ - \ - missing/pkgs/default.config \ - \The following errors occurred: \ - \ - The package location 'pkg-doesnt-exist' does not exist.") - missing + + "When using configuration from:\n\ + \ - cabal-missing-package.project\n\ + \ - missing/pkgs.config\n\ + \ - missing/pkgs/default.config\n\ + \The following errors occurred:\n\ + \ - The package location 'pkg-doesnt-exist' does not exist." + & normalizeWindowsOutput + & flip (assertOn multilineNeedleHaystack) missing return () diff --git a/cabal-testsuite/PackageTests/NewBuild/T4288/cabal.test.hs b/cabal-testsuite/PackageTests/NewBuild/T4288/cabal.test.hs index 3e3b8de853e..3313f596546 100644 --- a/cabal-testsuite/PackageTests/NewBuild/T4288/cabal.test.hs +++ b/cabal-testsuite/PackageTests/NewBuild/T4288/cabal.test.hs @@ -1,4 +1,5 @@ import Test.Cabal.Prelude +import Data.Function ((&)) -- This test is similar to the simplified example in issue #4288. The package's -- setup script only depends on base and setup-helper. setup-helper exposes a @@ -10,8 +11,7 @@ main = cabalTest $ do skipUnless "no v2-build compatible boot-Cabal" =<< hasNewBuildCompatBootCabal r <- recordMode DoNotRecord $ cabal' "v2-build" ["T4288"] assertOutputContains "This is setup-helper-1.0." r - assertOutputContains - ("In order, the following will be built: " - ++ " - setup-helper-1.0 (lib:setup-helper) (first run) " - ++ " - T4288-1.0 (lib:T4288) (first run)") - r + "In order, the following will be built:\n\ + \ - setup-helper-1.0 (lib:setup-helper) (first run)\n\ + \ - T4288-1.0 (lib:T4288) (first run)" + & flip (assertOn multilineNeedleHaystack) r diff --git a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.out b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.out index 437612a2eca..43a3f25acc2 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.out +++ b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.out @@ -1,3 +1,4 @@ -# checking "using config from message" with URI imports +# check "using config from message" with URI imports # cabal v2-build -# checking that package directories and locations are reported in order +# check project configuration with URI imports is listed in full and +# check package directories and locations are reported in order diff --git a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.test.hs index e354b356d7f..0c65ff68c60 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.test.hs @@ -1,4 +1,5 @@ import Test.Cabal.Prelude +import Data.Function ((&)) main = cabalTest . recordMode RecordMarked $ do let log = recordHeader . pure @@ -31,12 +32,12 @@ main = cabalTest . recordMode RecordMarked $ do out log "checking that package directories and locations are reported in order" - assertOutputContains - "The following errors occurred: \ - \ - The package directory 'no-pkg-1' does not contain any .cabal file. \ - \ - The package location 'no-pkg-2-dir' does not exist. \ - \ - The package directory 'no-pkg-3' does not contain any .cabal file. \ - \ - The package location 'no-pkg-4-dir' does not exist." - out + + "The following errors occurred:\n\ + \ - The package directory 'no-pkg-1' does not contain any .cabal file.\n\ + \ - The package location 'no-pkg-2-dir' does not exist.\n\ + \ - The package directory 'no-pkg-3' does not contain any .cabal file.\n\ + \ - The package location 'no-pkg-4-dir' does not exist." + & flip (assertOn multilineNeedleHaystack) out return () diff --git a/cabal-testsuite/PackageTests/Regression/T5409/use-different-versions-of-dependency-for-library-and-build-tool.test.hs b/cabal-testsuite/PackageTests/Regression/T5409/use-different-versions-of-dependency-for-library-and-build-tool.test.hs index 2a3eb3c093c..4bbb8b91a9b 100644 --- a/cabal-testsuite/PackageTests/Regression/T5409/use-different-versions-of-dependency-for-library-and-build-tool.test.hs +++ b/cabal-testsuite/PackageTests/Regression/T5409/use-different-versions-of-dependency-for-library-and-build-tool.test.hs @@ -1,4 +1,5 @@ import Test.Cabal.Prelude +import Data.Function ((&)) -- The local package, pkg-1.0, depends on build-tool-pkg-1 as a library and -- build-tool-pkg-2 as a build-tool. This test checks that cabal uses the @@ -16,16 +17,13 @@ main = cabalTest $ withShorterPathForNewBuildStore $ do r1 <- recordMode DoNotRecord $ cabal' "v2-build" ["pkg:my-exe"] - let msg = concat - [ "In order, the following will be built:" - , " - build-tool-pkg-1 (lib) (requires build)" - , " - build-tool-pkg-2 (lib) (requires build)" - , " - build-tool-pkg-2 (exe:build-tool-exe) (requires build)" - , " - pkg-1.0 (exe:my-exe) (first run)" - ] + "In order, the following will be built:\n\ + \ - build-tool-pkg-1 (lib) (requires build)\n\ + \ - build-tool-pkg-2 (lib) (requires build)\n\ + \ - build-tool-pkg-2 (exe:build-tool-exe) (requires build)\n\ + \ - pkg-1.0 (exe:my-exe) (first run)" + & flip (assertOn multilineNeedleHaystack) r1 - assertOutputContains msg r1 withPlan $ do r2 <- runPlanExe' "pkg" "my-exe" [] - assertOutputContains - "build-tool library version: 1, build-tool exe version: 2" r2 + assertOn multilineNeedleHaystack "build-tool library version: 1,\nbuild-tool exe version: 2" r2 From 32b820bbb3dd884b551a5d56229b341cde55d9d0 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Wed, 1 Jan 2025 08:03:21 -0500 Subject: [PATCH 4/4] Add verbatim *.expect.txt expectations - Add oops.expect.txt - Add cabal-missing-package.expect.txt - Add hops.expect.txt - Add DedupUsingConfigFromComplex/errors.expect.txt - Add using configuration from to errors.expect.txt --- .../cabal-missing-package.expect.txt | 6 ++ .../ConditionalAndImport/cabal.test.hs | 93 ++----------------- .../ConditionalAndImport/hops.expect.txt | 56 +++++++++++ .../ConditionalAndImport/oops.expect.txt | 16 ++++ .../DedupUsingConfigFromComplex/cabal.test.hs | 37 +------- .../errors.expect.txt | 19 ++++ 6 files changed, 110 insertions(+), 117 deletions(-) create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/cabal-missing-package.expect.txt create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/hops.expect.txt create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops.expect.txt create mode 100644 cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/errors.expect.txt diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal-missing-package.expect.txt b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal-missing-package.expect.txt new file mode 100644 index 00000000000..f81a82a6c73 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal-missing-package.expect.txt @@ -0,0 +1,6 @@ +When using configuration from: + - cabal-missing-package.project + - missing/pkgs.config + - missing/pkgs/default.config +The following errors occurred: + - The package location 'pkg-doesnt-exist' does not exist. diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs index d0abb33de2d..681865df2e5 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs @@ -1,6 +1,7 @@ import Test.Cabal.Prelude import Test.Cabal.OutputNormalizer import Data.Function ((&)) +import Data.Functor ((<&>)) main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do let log = recordHeader . pure @@ -78,7 +79,7 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- etc log "checking that cyclical check catches a same file name that imports itself" cyclical4a <- fails $ cabal' "v2-build" [ "--project-file=cyclical-same-filename-out-out-self.project" ] - assertOutputContains (normalizeWindowsOutput "cyclical import of same-filename/cyclical-same-filename-out-out-self.config") cyclical4a + assertOutputContains (normalizePathSeparators "cyclical import of same-filename/cyclical-same-filename-out-out-self.config") cyclical4a -- +-- cyclical-same-filename-out-out-backback.project -- +-- cyclical-same-filename-out-out-backback.config @@ -111,64 +112,8 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do log "checking that imports work skipping into a subfolder and then back out again and again" hopping <- cabal' "v2-build" [ "--project-file=hops-0.project" ] - "Configuration is affected by the following files:\n\ - \- hops-0.project\n\ - \- hops-2.config\n\ - \ imported by: hops/hops-1.config\n\ - \ imported by: hops-0.project\n\ - \- hops-4.config\n\ - \ imported by: hops/hops-3.config\n\ - \ imported by: hops-2.config\n\ - \ imported by: hops/hops-1.config\n\ - \ imported by: hops-0.project\n\ - \- hops-6.config\n\ - \ imported by: hops/hops-5.config\n\ - \ imported by: hops-4.config\n\ - \ imported by: hops/hops-3.config\n\ - \ imported by: hops-2.config\n\ - \ imported by: hops/hops-1.config\n\ - \ imported by: hops-0.project\n\ - \- hops-8.config\n\ - \ imported by: hops/hops-7.config\n\ - \ imported by: hops-6.config\n\ - \ imported by: hops/hops-5.config\n\ - \ imported by: hops-4.config\n\ - \ imported by: hops/hops-3.config\n\ - \ imported by: hops-2.config\n\ - \ imported by: hops/hops-1.config\n\ - \ imported by: hops-0.project\n\ - \- hops/hops-1.config\n\ - \ imported by: hops-0.project\n\ - \- hops/hops-3.config\n\ - \ imported by: hops-2.config\n\ - \ imported by: hops/hops-1.config\n\ - \ imported by: hops-0.project\n\ - \- hops/hops-5.config\n\ - \ imported by: hops-4.config\n\ - \ imported by: hops/hops-3.config\n\ - \ imported by: hops-2.config\n\ - \ imported by: hops/hops-1.config\n\ - \ imported by: hops-0.project\n\ - \- hops/hops-7.config\n\ - \ imported by: hops-6.config\n\ - \ imported by: hops/hops-5.config\n\ - \ imported by: hops-4.config\n\ - \ imported by: hops/hops-3.config\n\ - \ imported by: hops-2.config\n\ - \ imported by: hops/hops-1.config\n\ - \ imported by: hops-0.project\n\ - \- hops/hops-9.config\n\ - \ imported by: hops-8.config\n\ - \ imported by: hops/hops-7.config\n\ - \ imported by: hops-6.config\n\ - \ imported by: hops/hops-5.config\n\ - \ imported by: hops-4.config\n\ - \ imported by: hops/hops-3.config\n\ - \ imported by: hops-2.config\n\ - \ imported by: hops/hops-1.config\n\ - \ imported by: hops-0.project" - & normalizeWindowsOutput - & flip (assertOn multilineNeedleHaystack) hopping + readFileVerbatim "hops.expect.txt" >>= + flip (assertOn multilineNeedleHaystack) hopping . normalizePathSeparators -- The project is named oops as it is like hops but has conflicting constraints. -- +-- oops-0.project @@ -184,24 +129,8 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do log "checking conflicting constraints skipping into a subfolder and then back out again and again" oopsing <- fails $ cabal' "v2-build" [ "all", "--project-file=oops-0.project" ] - "Could not resolve dependencies:\n\ - \[__0] trying: oops-0.1 (user goal)\n\ - \[__1] next goal: hashable (dependency of oops)\n\ - \[__1] rejecting: hashable-1.4.3.0\n\ - \ (constraint from oops/oops-9.config requires ==1.4.2.0)\n\ - \ imported by: oops-8.config\n\ - \ imported by: oops/oops-7.config\n\ - \ imported by: oops-6.config\n\ - \ imported by: oops/oops-5.config\n\ - \ imported by: oops-4.config\n\ - \ imported by: oops/oops-3.config\n\ - \ imported by: oops-2.config\n\ - \ imported by: oops/oops-1.config\n\ - \ imported by: oops-0.project\n\ - \[__1] rejecting: hashable-1.4.2.0\n\ - \ (constraint from oops-0.project requires ==1.4.3.0)" - & normalizeWindowsOutput - & flip (assertOn multilineNeedleHaystack) oopsing + readFileVerbatim "oops.expect.txt" + >>= flip (assertOn multilineNeedleHaystack) oopsing . normalizePathSeparators -- The project is named yops as it is like hops but with y's for forks. -- +-- yops-0.project @@ -243,13 +172,7 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do log "checking that missing package message lists configuration provenance" missing <- fails $ cabal' "v2-build" [ "--project-file=cabal-missing-package.project" ] - "When using configuration from:\n\ - \ - cabal-missing-package.project\n\ - \ - missing/pkgs.config\n\ - \ - missing/pkgs/default.config\n\ - \The following errors occurred:\n\ - \ - The package location 'pkg-doesnt-exist' does not exist." - & normalizeWindowsOutput - & flip (assertOn multilineNeedleHaystack) missing + readFileVerbatim "cabal-missing-package.expect.txt" + >>= flip (assertOn multilineNeedleHaystack) missing . normalizePathSeparators return () diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/hops.expect.txt b/cabal-testsuite/PackageTests/ConditionalAndImport/hops.expect.txt new file mode 100644 index 00000000000..bf3ea9bc001 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/hops.expect.txt @@ -0,0 +1,56 @@ +Configuration is affected by the following files: +- hops-0.project +- hops-2.config + imported by: hops/hops-1.config + imported by: hops-0.project +- hops-4.config + imported by: hops/hops-3.config + imported by: hops-2.config + imported by: hops/hops-1.config + imported by: hops-0.project +- hops-6.config + imported by: hops/hops-5.config + imported by: hops-4.config + imported by: hops/hops-3.config + imported by: hops-2.config + imported by: hops/hops-1.config + imported by: hops-0.project +- hops-8.config + imported by: hops/hops-7.config + imported by: hops-6.config + imported by: hops/hops-5.config + imported by: hops-4.config + imported by: hops/hops-3.config + imported by: hops-2.config + imported by: hops/hops-1.config + imported by: hops-0.project +- hops/hops-1.config + imported by: hops-0.project +- hops/hops-3.config + imported by: hops-2.config + imported by: hops/hops-1.config + imported by: hops-0.project +- hops/hops-5.config + imported by: hops-4.config + imported by: hops/hops-3.config + imported by: hops-2.config + imported by: hops/hops-1.config + imported by: hops-0.project +- hops/hops-7.config + imported by: hops-6.config + imported by: hops/hops-5.config + imported by: hops-4.config + imported by: hops/hops-3.config + imported by: hops-2.config + imported by: hops/hops-1.config + imported by: hops-0.project +- hops/hops-9.config + imported by: hops-8.config + imported by: hops/hops-7.config + imported by: hops-6.config + imported by: hops/hops-5.config + imported by: hops-4.config + imported by: hops/hops-3.config + imported by: hops-2.config + imported by: hops/hops-1.config + imported by: hops-0.project diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops.expect.txt b/cabal-testsuite/PackageTests/ConditionalAndImport/oops.expect.txt new file mode 100644 index 00000000000..88c23627575 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops.expect.txt @@ -0,0 +1,16 @@ +Could not resolve dependencies: +[__0] trying: oops-0.1 (user goal) +[__1] next goal: hashable (dependency of oops) +[__1] rejecting: hashable-1.4.3.0 + (constraint from oops/oops-9.config requires ==1.4.2.0) + imported by: oops-8.config + imported by: oops/oops-7.config + imported by: oops-6.config + imported by: oops/oops-5.config + imported by: oops-4.config + imported by: oops/oops-3.config + imported by: oops-2.config + imported by: oops/oops-1.config + imported by: oops-0.project +[__1] rejecting: hashable-1.4.2.0 + (constraint from oops-0.project requires ==1.4.3.0) diff --git a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.test.hs index 0c65ff68c60..e1419fb2467 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/cabal.test.hs @@ -4,40 +4,13 @@ import Data.Function ((&)) main = cabalTest . recordMode RecordMarked $ do let log = recordHeader . pure - log "checking \"using config from message\" with URI imports" + log "check \"using config from message\" with URI imports" out <- fails $ cabal' "v2-build" [ "all", "--dry-run", "--project-file=no-pkgs.project" ] - -- Use assertRegex when the output is tainted by the temp directory, like - -- this: - -- - -- When using configuration from: - -- - /tmp/cabal-testsuite-282695/cabal.project - -- - /tmp/cabal-testsuite-282695/2.config etc - assertRegex - "Project configuration with URI imports is listed in full" - "When using configuration from:(\n|\r\n) \ - \ .*no-pkgs\\.project(\n|\r\n) \ - \ .*0\\.config(\n|\r\n) \ - \ .*2\\.config(\n|\r\n) \ - \ .*4\\.config(\n|\r\n) \ - \ .*6\\.config(\n|\r\n) \ - \ .*8\\.config(\n|\r\n) \ - \ .*1\\.config(\n|\r\n) \ - \ .*3\\.config(\n|\r\n) \ - \ .*5\\.config(\n|\r\n) \ - \ .*7\\.config(\n|\r\n) \ - \ .*9\\.config(\n|\r\n) \ - \ .*with-ghc\\.config(\n|\r\n) \ - \ .*https://www.stackage.org/lts-21.25/cabal.config(\n|\r\n)" - out + log "check project configuration with URI imports is listed in full and" + log "check package directories and locations are reported in order" - log "checking that package directories and locations are reported in order" - - "The following errors occurred:\n\ - \ - The package directory 'no-pkg-1' does not contain any .cabal file.\n\ - \ - The package location 'no-pkg-2-dir' does not exist.\n\ - \ - The package directory 'no-pkg-3' does not contain any .cabal file.\n\ - \ - The package location 'no-pkg-4-dir' does not exist." - & flip (assertOn multilineNeedleHaystack) out + readFileVerbatim "errors.expect.txt" + >>= flip (assertOn multilineNeedleHaystack) out . normalizePathSeparators return () diff --git a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/errors.expect.txt b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/errors.expect.txt new file mode 100644 index 00000000000..93907eea807 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromComplex/errors.expect.txt @@ -0,0 +1,19 @@ +When using configuration from: + - no-pkgs.project + - 0.config + - 2.config + - 4.config + - 6.config + - 8.config + - cfg/1.config + - cfg/3.config + - cfg/5.config + - cfg/7.config + - cfg/9.config + - with-ghc.config + - https://www.stackage.org/lts-21.25/cabal.config +The following errors occurred: + - The package directory 'no-pkg-1' does not contain any .cabal file. + - The package location 'no-pkg-2-dir' does not exist. + - The package directory 'no-pkg-3' does not contain any .cabal file. + - The package location 'no-pkg-4-dir' does not exist.