[Git][ghc/ghc][wip/9.12-testsuite-fixes] 7 commits: testsuite: normalise some versions in callstacks
Zubin (@wz1000)
gitlab at gitlab.haskell.org
Mon Nov 11 09:52:09 UTC 2024
Zubin pushed to branch wip/9.12-testsuite-fixes at Glasgow Haskell Compiler / GHC
Commits:
e56ed179 by Zubin Duggal at 2024-11-11T15:16:35+05:30
testsuite: normalise some versions in callstacks
(cherry picked from commit f230e29f30d0c1c566d4dd251807fcab76a2710e)
- - - - -
a28fc903 by Zubin Duggal at 2024-11-11T15:16:35+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests
(cherry picked from commit b19de476bc5ce5c7792e8af1354b94a4286a1a13)
- - - - -
ed16d303 by Zubin Duggal at 2024-11-11T15:16:36+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests
(cherry picked from commit fbf0889eadc410d43dd5c1657e320634b6738fa5)
- - - - -
e45e5836 by Zubin Duggal at 2024-11-11T15:16:36+05:30
haddock: oneshot tests can drop files if they share modtimes. Stop this by
including the filename in the key.
Ideally we would use `ghc -M` output to do a proper toposort
Partially addresses #25372
(cherry picked from commit e78c7ef96e395f1ef41f04790aebecd0409b92b9)
- - - - -
9104e6eb by Zubin Duggal at 2024-11-11T15:16:36+05:30
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences
(cherry picked from commit a79a587e025d42d34bb30e115fc5c7cab6c1e030)
- - - - -
2c31264a by Zubin Duggal at 2024-11-11T15:16:36+05:30
testsuite: normalise windows file seperators
(cherry picked from commit f858875e03b9609656b542aaaaff85ad0a83878a)
- - - - -
2807f91b by Zubin Duggal at 2024-11-11T15:21:30+05:30
testsuite: Also match <VERSION> placeholders when normalising callsites
- - - - -
16 changed files:
- testsuite/driver/testlib.py
- testsuite/tests/backpack/should_compile/all.T
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/all.T
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/gadt/all.T
- testsuite/tests/ghc-api/T20757.stderr
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-e/should_fail/all.T
- testsuite/tests/profiling/should_run/all.T
- utils/haddock/haddock-test/src/Test/Haddock.hs
- utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs
- utils/haddock/html-test/Main.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug548.html
Changes:
=====================================
testsuite/driver/testlib.py
=====================================
@@ -2857,7 +2857,7 @@ def normalise_whitespace(s: str) -> str:
# Merge contiguous whitespace characters into a single space.
return ' '.join(s.split())
-callSite_re = re.compile(r', called at (.+):[\d]+:[\d]+ in [\w\-\.]+:')
+callSite_re = re.compile(r', called at (.+):[\d]+:[\d]+ in [<>\w\-\.]+:')
def normalise_callstacks(s: str) -> str:
opts = getTestOpts()
=====================================
testsuite/tests/backpack/should_compile/all.T
=====================================
@@ -8,7 +8,7 @@ test('bkp11', normal, backpack_compile, [''])
test('bkp12', normal, backpack_compile, [''])
test('bkp14', normal, backpack_compile, [''])
test('bkp15', normal, backpack_compile, [''])
-test('bkp16', normalise_version('base', 'ghc-internal'), backpack_compile, [''])
+test('bkp16', [normalise_version('base', 'ghc-internal')], backpack_compile, ['-fhide-source-paths'])
test('bkp17', normal, backpack_compile, [''])
test('bkp18', normal, backpack_compile, [''])
test('bkp19', normal, backpack_compile, [''])
@@ -60,4 +60,4 @@ test('T13214', normal, backpack_compile, [''])
test('T13250', normal, backpack_compile, [''])
test('T13323', normal, backpack_compile, [''])
test('T20396', normal, backpack_compile, [''])
-test('T23424', [ignore_stdout, ignore_stderr], backpack_compile, ['-ddump-rn-trace -ddump-if-trace -ddump-tc-trace'])
\ No newline at end of file
+test('T23424', [ignore_stdout, ignore_stderr], backpack_compile, ['-ddump-rn-trace -ddump-if-trace -ddump-tc-trace'])
=====================================
testsuite/tests/backpack/should_compile/bkp16.stderr
=====================================
@@ -1,9 +1,9 @@
[1 of 2] Processing p
- [1 of 1] Compiling Int[sig] ( p/Int.hsig, nothing )
+ [1 of 1] Compiling Int[sig]
[2 of 2] Processing q
Instantiating q
[1 of 1] Including p[Int=base-4.20.0.0:GHC.Exts]
Instantiating p[Int=base-4.20.0.0:GHC.Exts]
[1 of 1] Including base-4.20.0.0
- [1 of 1] Compiling Int[sig] ( p/Int.hsig, bkp16.out/p/p-3JmGAx0a1DyKjX6bh7CxGJ/Int.o )
+ [1 of 1] Compiling Int[sig]
[1 of 1] Instantiating p
=====================================
testsuite/tests/backpack/should_fail/all.T
=====================================
@@ -12,9 +12,9 @@ test('bkpfail13', normal, backpack_compile_fail, [''])
test('bkpfail14', normal, backpack_compile_fail, [''])
test('bkpfail15', normal, backpack_compile_fail, [''])
test('bkpfail16', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
-test('bkpfail17', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
+test('bkpfail17', normalise_version('ghc-internal', 'base'), backpack_compile_fail, ['-fhide-source-paths'])
test('bkpfail18', normal, backpack_compile_fail, [''])
-test('bkpfail19', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
+test('bkpfail19', normalise_version('ghc-internal', 'base'), backpack_compile_fail, ['-fhide-source-paths'])
test('bkpfail20', normal, backpack_compile_fail, [''])
test('bkpfail21', normal, backpack_compile_fail, [''])
test('bkpfail22', normal, backpack_compile_fail, [''])
=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -1,10 +1,10 @@
[1 of 2] Processing p
- [1 of 1] Compiling ShouldFail[sig] ( p/ShouldFail.hsig, nothing )
+ [1 of 1] Compiling ShouldFail[sig]
[2 of 2] Processing q
Instantiating q
[1 of 1] Including p[ShouldFail=base-4.20.0.0:Prelude]
Instantiating p[ShouldFail=base-4.20.0.0:Prelude]
- [1 of 1] Compiling ShouldFail[sig] ( p/ShouldFail.hsig, bkpfail17.out/p/p-9R9TTjIBG3MEjwCQffKVYM/ShouldFail.o )
+ [1 of 1] Compiling ShouldFail[sig]
<no location info>: error: [GHC-15843]
• Type constructor ‘Either’ has conflicting definitions in the module
and its hsig file.
=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -1,10 +1,10 @@
[1 of 2] Processing p
- [1 of 1] Compiling ShouldFail[sig] ( p/ShouldFail.hsig, nothing )
+ [1 of 1] Compiling ShouldFail[sig]
[2 of 2] Processing q
Instantiating q
[1 of 1] Including p[ShouldFail=base-4.20.0.0:Data.STRef]
Instantiating p[ShouldFail=base-4.20.0.0:Data.STRef]
- [1 of 1] Compiling ShouldFail[sig] ( p/ShouldFail.hsig, bkpfail19.out/p/p-Gwl8Z2CPH0M7Zi2wPSYSbs/ShouldFail.o )
+ [1 of 1] Compiling ShouldFail[sig]
<no location info>: error: [GHC-12424]
• The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
but the implementing module exports a different identifier ‘GHC.Internal.STRef.newSTRef’
=====================================
testsuite/tests/gadt/all.T
=====================================
@@ -127,7 +127,7 @@ test('T20485', normal, compile, [''])
test('T20485a', normal, compile, [''])
test('T22235', normal, compile, [''])
test('T19847', normal, compile, [''])
-test('T19847a', normal, compile, ['-ddump-types'])
+test('T19847a', normalise_version('base'), compile, ['-ddump-types'])
test('T19847b', normal, compile, [''])
test('T23022', normal, compile, ['-dcore-lint'])
test('T23023', normal, compile_fail, ['-O -dcore-lint']) # todo: move this test?
=====================================
testsuite/tests/ghc-api/T20757.stderr
=====================================
@@ -2,11 +2,11 @@ T20757: Exception:
could not detect mingw toolchain in the following paths: ["/..//mingw","/..//..//mingw","/..//..//..//mingw"]
-Package: ghc-inplace
+Package: ghc-<VERSION>-<HASH>
Module: GHC.Utils.Panic
Type: GhcException
HasCallStack backtrace:
collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:<line>:<column> in <package-id>:GHC.Internal.Exception
toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:<line>:<column> in <package-id>:GHC.Internal.IO
- throwIO, called at compiler/GHC/Utils/Panic.hs:<line>:<column> in <package-id>:GHC.Utils.Panic
+ throwIO, called at compiler/GHC/Utils/Panic.hs:183:23 in ghc-<VERSION>-<HASH>:GHC.Utils.Panic
=====================================
testsuite/tests/ghc-api/all.T
=====================================
@@ -38,7 +38,7 @@ test('T19156', [ extra_run_opts('"' + config.libdir + '"')
],
compile_and_run,
['-package ghc'])
-test('T20757', [unless(opsys('mingw32'), skip), exit_code(1)],
+test('T20757', [unless(opsys('mingw32'), skip), exit_code(1), normalise_version('ghc')],
compile_and_run,
['-package ghc'])
test('PrimOpEffect_Sanity', normal, compile_and_run, ['-Wall -Werror -package ghc'])
=====================================
testsuite/tests/ghc-e/should_fail/all.T
=====================================
@@ -15,6 +15,7 @@ test('ghc-e-fail2', req_interp, makefile_test, ['ghc-e-fail2'])
test('T9930fail',
[extra_files(['T9930']),
when(opsys('mingw32'), skip),
+ normalise_errmsg_fun(lambda s: normalise_version_("ghc")(s).replace('ghc-<VERSION>-<HASH>','ghc')),
# broken for JS until cross-compilers become stage2 compilers (#19174)
# or until we bootstrap with a 9.10 compiler
js_broken(19174)],
@@ -24,7 +25,7 @@ test('T18441fail0', req_interp, makefile_test, ['T18441fail0'])
test('T18441fail1', req_interp, makefile_test, ['T18441fail1'])
-test('T18441fail2', req_interp, makefile_test, ['T18441fail2'])
+test('T18441fail2', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail2'])
test('T18441fail3', [ignore_stderr, exit_code(1)], run_command, ['{compiler} -e ":! abcde"'])
@@ -34,9 +35,9 @@ test('T18441fail5', req_interp, makefile_test, ['T18441fail5'])
test('T18441fail6', req_interp, makefile_test, ['T18441fail6'])
-test('T18441fail7', req_interp, makefile_test, ['T18441fail7'])
+test('T18441fail7', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail7'])
-test('T18441fail8', req_interp, makefile_test, ['T18441fail8'])
+test('T18441fail8', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail8'])
test('T18441fail9', req_interp, makefile_test, ['T18441fail9'])
@@ -60,6 +61,6 @@ test('T18441fail18', req_interp, makefile_test, ['T18441fail18'])
test('T18441fail19', [ignore_stderr, exit_code(1)], run_command, ['{compiler} -e ":cd abcd"'])
-test('T23663', req_interp, makefile_test, ['T23663'])
+test('T23663', [req_interp, normalise_version('ghc')], makefile_test, ['T23663'])
test('T24172', normal, compile_fail, ['-fdiagnostics-color=always'])
=====================================
testsuite/tests/profiling/should_run/all.T
=====================================
@@ -145,11 +145,13 @@ test('T7275', test_opts_dot_prof, makefile_test, [])
test('callstack001',
# unoptimised results are different w.r.t. CAF attribution
[test_opts_dot_prof # produces a different stack
+ ,normalise_fun(lambda s: re.sub(r"(?<!('|‘))\\", '/', s).replace("//","/"))
], compile_and_run,
['-fprof-auto-calls -fno-full-laziness -fno-state-hack'])
test('callstack002',
[ test_opts_dot_prof # produces a different stack
+ , normalise_fun(lambda s: re.sub(r"(?<!('|‘))\\", '/', s))
],
compile_and_run,
['-fprof-auto-calls -fno-full-laziness -fno-state-hack'])
=====================================
utils/haddock/haddock-test/src/Test/Haddock.hs
=====================================
@@ -156,7 +156,7 @@ runHaddock cfg@(Config{..}) = do
files <- filter ((== ".hi") . takeExtension) <$> listDirectory hiDir
-- Use the output order of GHC as a simple dependency order
- filesSorted <- Map.elems . Map.fromList <$> traverse (\file -> (,file) <$> getModificationTime (hiDir </> file)) files
+ filesSorted <- Map.elems . Map.fromList <$> traverse (\file -> (\mt -> ((mt,file),file)) <$> getModificationTime (hiDir </> file)) files
let srcRef = if "--hyperlinked-source" `elem` cfgHaddockArgs then ",src,visible," else ""
loop [] = pure True
loop (file : files) = do
=====================================
utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs
=====================================
@@ -8,6 +8,7 @@ module Test.Haddock.Xhtml
, stripIdsWhen
, stripFooter
, fixAttrValueWhen
+ , stripVersions
) where
{-
@@ -22,7 +23,7 @@ and since the `xhtml` library already handles the pretty-printing aspect,
this would appear to be a reasonable compromise for now.
-}
-import Data.Char (isSpace)
+import Data.Char (isSpace, isAlphaNum)
import Data.List (isPrefixOf, stripPrefix)
-- | Simple wrapper around the pretty-printed HTML source
@@ -142,3 +143,18 @@ stripFooter (Xml body) = Xml (findDiv body)
Just valRest''
| otherwise =
dropToDiv cs
+
+-- | Strip strings of the form <pkg>-<version>-<hash>
+-- to just <pkg>
+stripVersions :: [String] -> Xml -> Xml
+stripVersions xs (Xml body) = Xml $ foldr id body $ map go xs
+ where
+ go pkg "" = ""
+ go pkg body@(x:body') = case stripPrefix pkg body of
+ Just ('-':rest)
+ | (version,'-':rest') <- span (/= '-') rest
+ , all (`elem` ('.':['0'..'9'])) version
+ , let (hash, rest'') = span isAlphaNum rest'
+ -> pkg ++ go pkg rest''
+ _ -> x:go pkg body'
+
=====================================
utils/haddock/html-test/Main.hs
=====================================
@@ -42,7 +42,7 @@ main = do
stripIfRequired :: String -> Xml -> Xml
stripIfRequired mdl =
- stripLinks' . stripFooter
+ stripLinks' . stripFooter . stripVersions ["base"]
where
stripLinks'
| mdl `elem` preserveLinksModules = id
=====================================
utils/haddock/html-test/ref/Bug1004.html
=====================================
@@ -210,7 +210,7 @@
>D1</a
> ('<a href="#" title="GHC.Generics"
>MetaData</a
- > "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" '<a href="#" title="Data.Bool"
+ > "Product" "Data.Functor.Product" "base" '<a href="#" title="Data.Bool"
>False</a
>) (<a href="#" title="GHC.Generics"
>C1</a
@@ -2037,7 +2037,7 @@
>D1</a
> ('<a href="#" title="GHC.Generics"
>MetaData</a
- > "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" '<a href="#" title="Data.Bool"
+ > "Product" "Data.Functor.Product" "base" '<a href="#" title="Data.Bool"
>False</a
>) (<a href="#" title="GHC.Generics"
>C1</a
@@ -2510,7 +2510,7 @@
>D1</a
> ('<a href="#" title="GHC.Generics"
>MetaData</a
- > "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" '<a href="#" title="Data.Bool"
+ > "Product" "Data.Functor.Product" "base" '<a href="#" title="Data.Bool"
>False</a
>) (<a href="#" title="GHC.Generics"
>C1</a
@@ -2604,7 +2604,7 @@
>D1</a
> ('<a href="#" title="GHC.Generics"
>MetaData</a
- > "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" '<a href="#" title="Data.Bool"
+ > "Product" "Data.Functor.Product" "base" '<a href="#" title="Data.Bool"
>False</a
>) (<a href="#" title="GHC.Generics"
>C1</a
=====================================
utils/haddock/html-test/ref/Bug548.html
=====================================
@@ -186,7 +186,7 @@
>D1</a
> ('<a href="#" title="GHC.Generics"
>MetaData</a
- > "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" '<a href="#" title="Data.Bool"
+ > "WrappedArrow" "Control.Applicative" "base" '<a href="#" title="Data.Bool"
>True</a
>) (<a href="#" title="GHC.Generics"
>C1</a
@@ -792,7 +792,7 @@
>D1</a
> ('<a href="#" title="GHC.Generics"
>MetaData</a
- > "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" '<a href="#" title="Data.Bool"
+ > "WrappedArrow" "Control.Applicative" "base" '<a href="#" title="Data.Bool"
>True</a
>) (<a href="#" title="GHC.Generics"
>C1</a
@@ -903,7 +903,7 @@
>D1</a
> ('<a href="#" title="GHC.Generics"
>MetaData</a
- > "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" '<a href="#" title="Data.Bool"
+ > "WrappedArrow" "Control.Applicative" "base" '<a href="#" title="Data.Bool"
>True</a
>) (<a href="#" title="GHC.Generics"
>C1</a
@@ -973,7 +973,7 @@
>D1</a
> ('<a href="#" title="GHC.Generics"
>MetaData</a
- > "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" '<a href="#" title="Data.Bool"
+ > "WrappedArrow" "Control.Applicative" "base" '<a href="#" title="Data.Bool"
>True</a
>) (<a href="#" title="GHC.Generics"
>C1</a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3bb8084feba59fd121925a152726b2eed720f7a7...2807f91bfb0b1e60ea8668622eae344e9ff5d840
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3bb8084feba59fd121925a152726b2eed720f7a7...2807f91bfb0b1e60ea8668622eae344e9ff5d840
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241111/5ff8294c/attachment-0001.html>
More information about the ghc-commits
mailing list