Skip to content

Commit 592bcc9

Browse files
committed
Switch ghcide tests to sequential execution
1 parent efe8913 commit 592bcc9

29 files changed

+78
-77
lines changed

ghcide/test/exe/AsyncTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ import Test.Tasty.HUnit
2323

2424
-- | Test if ghcide asynchronously handles Commands and user Requests
2525
tests :: TestTree
26-
tests = testGroup "async"
26+
tests = sequentialTestGroup "async" AllFinish
2727
[
2828
testWithDummyPluginEmpty "command" $ do
2929
-- Execute a command that will block forever

ghcide/test/exe/BootTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ import Test.Tasty.HUnit
2323

2424

2525
tests :: TestTree
26-
tests = testGroup "boot"
26+
tests = sequentialTestGroup "boot" AllFinish
2727
[ testCase "boot-def-test" $ runWithExtraFiles "boot" $ \dir -> do
2828
let cPath = dir </> "C.hs"
2929
cSource <- liftIO $ readFileUtf8 cPath

ghcide/test/exe/CPPTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import Test.Tasty.HUnit
1515

1616
tests :: TestTree
1717
tests =
18-
testGroup "cpp"
18+
sequentialTestGroup "cpp" AllFinish
1919
[ testCase "cpp-error" $ do
2020
let content =
2121
T.unlines

ghcide/test/exe/ClientSettingsTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ import Test.Hls (testConfigCaps,
2121
import Test.Tasty
2222

2323
tests :: TestTree
24-
tests = testGroup "client settings handling"
24+
tests = sequentialTestGroup "client settings handling" AllFinish
2525
[ testWithDummyPluginEmpty "ghcide restarts shake session on config changes" $ do
2626
setIgnoringLogNotifications False
2727
void $ createDoc "A.hs" "haskell" "module A where"

ghcide/test/exe/CodeLensTests.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ import Test.Tasty
2424
import Test.Tasty.HUnit
2525

2626
tests :: TestTree
27-
tests = testGroup "code lenses"
27+
tests = sequentialTestGroup "code lenses" AllFinish
2828
[ addSigLensesTests
2929
]
3030

@@ -91,12 +91,12 @@ addSigLensesTests =
9191
, ("notInScopeTest = mkCharType", "notInScopeTest :: String -> Data.Data.DataType")
9292
, ("aVeryLongSignature a b c d e f g h i j k l m n = a && b && c && d && e && f && g && h && i && j && k && l && m && n", "aVeryLongSignature :: Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool")
9393
]
94-
in testGroup
95-
"add signature"
96-
[ testGroup "signatures are correct" [sigSession (T.unpack $ T.replace "\n" "\\n" def) False False "always" "" (def, Just sig) [] | (def, sig) <- cases]
94+
in sequentialTestGroup
95+
"add signature" AllFinish
96+
[ sequentialTestGroup "signatures are correct" AllFinish [sigSession (T.unpack $ T.replace "\n" "\\n" def) False False "always" "" (def, Just sig) [] | (def, sig) <- cases]
9797
, sigSession "exported mode works" False False "exported" "xyz" ("xyz = True", Just "xyz :: Bool") (fst <$> take 3 cases)
98-
, testGroup
99-
"diagnostics mode works"
98+
, sequentialTestGroup
99+
"diagnostics mode works" AllFinish
100100
[ sigSession "with GHC warnings" True True "diagnostics" "" (second Just $ head cases) []
101101
, sigSession "without GHC warnings" False False "diagnostics" "" (second (const Nothing) $ head cases) []
102102
]

ghcide/test/exe/CompletionTests.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -37,15 +37,15 @@ import Test.Tasty.HUnit
3737

3838
tests :: TestTree
3939
tests
40-
= testGroup "completion"
40+
= sequentialTestGroup "completion" AllFinish
4141
[
42-
testGroup "non local" nonLocalCompletionTests
43-
, testGroup "topLevel" topLevelCompletionTests
44-
, testGroup "local" localCompletionTests
45-
, testGroup "package" packageCompletionTests
46-
, testGroup "project" projectCompletionTests
47-
, testGroup "other" otherCompletionTests
48-
, testGroup "doc" completionDocTests
42+
sequentialTestGroup "non local" AllFinish nonLocalCompletionTests
43+
, sequentialTestGroup "topLevel" AllFinish topLevelCompletionTests
44+
, sequentialTestGroup "local" AllFinish localCompletionTests
45+
, sequentialTestGroup "package" AllFinish packageCompletionTests
46+
, sequentialTestGroup "project" AllFinish projectCompletionTests
47+
, sequentialTestGroup "other" AllFinish otherCompletionTests
48+
, sequentialTestGroup "doc" AllFinish completionDocTests
4949
]
5050

5151
testSessionEmpty :: TestName -> Session () -> TestTree
@@ -255,7 +255,7 @@ nonLocalCompletionTests =
255255
]
256256
(Position 3 6)
257257
[],
258-
testGroup "ordering"
258+
sequentialTestGroup "ordering" AllFinish
259259
[completionTest "qualified has priority"
260260
["module A where"
261261
,"import qualified Data.ByteString as BS"

ghcide/test/exe/CradleTests.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -35,20 +35,20 @@ import Test.Tasty.HUnit
3535

3636

3737
tests :: TestTree
38-
tests = testGroup "cradle"
39-
[testGroup "dependencies" [sessionDepsArePickedUp]
40-
,testGroup "ignore-fatal" [ignoreFatalWarning]
41-
,testGroup "loading" [loadCradleOnlyonce, retryFailedCradle]
42-
,testGroup "multi" (multiTests "multi")
38+
tests = sequentialTestGroup "cradle" AllFinish
39+
[sequentialTestGroup "dependencies" AllFinish [sessionDepsArePickedUp]
40+
,sequentialTestGroup "ignore-fatal" AllFinish [ignoreFatalWarning]
41+
,sequentialTestGroup "loading" AllFinish [loadCradleOnlyonce, retryFailedCradle]
42+
,sequentialTestGroup "multi" AllFinish (multiTests "multi")
4343
,ignoreForGhcVersions [GHC92] "multiple units not supported on 9.2"
44-
$ testGroup "multi-unit" (multiTests "multi-unit")
45-
,testGroup "sub-directory" [simpleSubDirectoryTest]
44+
$ sequentialTestGroup "multi-unit" AllFinish (multiTests "multi-unit")
45+
,sequentialTestGroup "sub-directory" AllFinish [simpleSubDirectoryTest]
4646
,ignoreForGhcVersions [GHC92] "multiple units not supported on 9.2"
47-
$ testGroup "multi-unit-rexport" [multiRexportTest]
47+
$ sequentialTestGroup "multi-unit-rexport" AllFinish [multiRexportTest]
4848
]
4949

5050
loadCradleOnlyonce :: TestTree
51-
loadCradleOnlyonce = testGroup "load cradle only once"
51+
loadCradleOnlyonce = sequentialTestGroup "load cradle only once" AllFinish
5252
[ testWithDummyPluginEmpty' "implicit" implicit
5353
, testWithDummyPluginEmpty' "direct" direct
5454
]

ghcide/test/exe/DependentFileTest.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,8 +18,8 @@ import Test.Hls
1818

1919

2020
tests :: TestTree
21-
tests = testGroup "addDependentFile"
22-
[testGroup "file-changed" [testCase "test" $ runSessionWithTestConfig def
21+
tests = sequentialTestGroup "addDependentFile" AllFinish
22+
[sequentialTestGroup "file-changed" AllFinish [testCase "test" $ runSessionWithTestConfig def
2323
{ testShiftRoot = True
2424
, testDirLocation = Right (mkIdeTestFs [])
2525
, testPluginDescriptor = dummyPlugin

ghcide/test/exe/DiagnosticTests.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ import Test.Tasty
4444
import Test.Tasty.HUnit
4545

4646
tests :: TestTree
47-
tests = testGroup "diagnostics"
47+
tests = sequentialTestGroup "diagnostics" AllFinish
4848
[ testWithDummyPluginEmpty "fix syntax error" $ do
4949
let content = T.unlines [ "module Testing wher" ]
5050
doc <- createDoc "Testing.hs" "haskell" content
@@ -120,7 +120,7 @@ tests = testGroup "diagnostics"
120120
)
121121
]
122122

123-
, testGroup "deferral" $
123+
, sequentialTestGroup "deferral" AllFinish $
124124
let sourceA a = T.unlines
125125
[ "module A where"
126126
, "a :: Int"
@@ -505,7 +505,7 @@ tests = testGroup "diagnostics"
505505
[ "module Foo() where" , "import MissingModule" ] ]
506506
expectDiagnostics [("Foo.hs", [(DiagnosticSeverity_Error, (1,7), "Could not find module 'MissingModule'")])]
507507

508-
, testGroup "Cancellation"
508+
, sequentialTestGroup "Cancellation" AllFinish
509509
[ cancellationTestGroup "edit header" editHeader yesSession noParse noTc
510510
, cancellationTestGroup "edit import" editImport noSession yesParse noTc
511511
, cancellationTestGroup "edit body" editBody yesSession yesParse yesTc
@@ -539,7 +539,7 @@ tests = testGroup "diagnostics"
539539
yesTc = True
540540

541541
cancellationTestGroup :: TestName -> (TextDocumentContentChangeEvent, TextDocumentContentChangeEvent) -> Bool -> Bool -> Bool -> TestTree
542-
cancellationTestGroup name edits sessionDepsOutcome parseOutcome tcOutcome = testGroup name
542+
cancellationTestGroup name edits sessionDepsOutcome parseOutcome tcOutcome = sequentialTestGroup name AllFinish
543543
[ cancellationTemplate edits Nothing
544544
, cancellationTemplate edits $ Just ("GetFileContents", True)
545545
, cancellationTemplate edits $ Just ("GhcSession", True)

ghcide/test/exe/ExceptionTests.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -38,8 +38,8 @@ import Test.Tasty.HUnit
3838

3939
tests :: TestTree
4040
tests = do
41-
testGroup "Exceptions and PluginError" [
42-
testGroup "Testing that IO Exceptions are caught in..."
41+
sequentialTestGroup "Exceptions and PluginError" AllFinish [
42+
sequentialTestGroup "Testing that IO Exceptions are caught in..." AllFinish
4343
[ testCase "PluginHandlers" $ do
4444
let pluginId = "plugin-handler-exception"
4545
plugins :: Recorder (WithPriority Log) -> IdePlugins IdeState
@@ -110,7 +110,7 @@ tests = do
110110
pure ()
111111
_ -> liftIO $ assertFailure $ "We should have had an empty list" <> show lens]
112112

113-
, testGroup "Testing PluginError order..."
113+
, sequentialTestGroup "Testing PluginError order..." AllFinish
114114
[ pluginOrderTestCase "InternalError over InvalidParams" (PluginInternalError "error test") (PluginInvalidParams "error test")
115115
, pluginOrderTestCase "InvalidParams over InvalidUserState" (PluginInvalidParams "error test") (PluginInvalidUserState "error test")
116116
, pluginOrderTestCase "InvalidUserState over RequestRefused" (PluginInvalidUserState "error test") (PluginRequestRefused DisabledGlobally)

0 commit comments

Comments
 (0)