diff --git a/CONTRIBUTING.md b/CONTRIBUTING.md index 81ea71849dab7f36732f711a01f670e99cdc60ee..7a7842017c5da4bf9dbdbcecf4c88e765bb1de5d 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 0000000000000000000000000000000000000000..a3143ff9ffd24dd208d692d1005941905fa51f0a --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/ParseErrorProvenance/cabal.out @@ -0,0 +1,10 @@ +# cabal v2-build +Warning: <ROOT>/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 0000000000000000000000000000000000000000..49360b5987290c1b5864de2acebe73db1fae33f7 --- /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 0000000000000000000000000000000000000000..f9c44e63d5bed0d26067cb2d99c756b496ea8620 --- /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 0000000000000000000000000000000000000000..959c40f5660c4c3256fb6b5851381bc58ef877df --- /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 0000000000000000000000000000000000000000..e5291b3adcd89306a83d3a4398a561d05c6c49b1 --- /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 2c3d17e615088022c468c17b58b9c324aea039c3..fb641cad995b810942c31353b90d60ae65df9138 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 0f3383af38a1e5728c7f401d32921221c13fac94..4e31b87d254cd595969b04cf2dc2fa1da5bd8571 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 0000000000000000000000000000000000000000..42ab103128422fe521a9827f294c7851de2b41e2 --- /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\<username>\AppData\Local\Temp\cabal-testsuite-8376 +cabal.test.hs: +C:\Users\<username>\AppData\Local\Temp\cabal-testsuite-8376\errors.expect.txt: removePathForcibly:DeleteFile +"\\\\?\\C:\\Users\\<username>\\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 6455dbb87b1732554fc604ba0d4cf5f992959723..daa5472c9d09ee7358ee76540edf3546a9b06fcb 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\<username>\AppData\Local\Temp\cabal-testsuite-8376\errors.expect.txt: +-- > removePathForcibly:DeleteFile +-- > "\\\\?\\C:\\Users\\<username>\\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 0000000000000000000000000000000000000000..fb7dd8c9ec7b377498d346a823ec575f6aed5c84 --- /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\<username>\AppData\Local\Temp\cabal-testsuite-8376 +cabal.test.hs: +C:\Users\<username>\AppData\Local\Temp\cabal-testsuite-8376\errors.expect.txt: removePathForcibly:DeleteFile +"\\\\?\\C:\\Users\\<username>\\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.