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

+1-1
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

+1-1
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

+1-1
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

+1-1
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

+6-6
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

+9-9
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

+9-9
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

+2-2
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

+4-4
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

+3-3
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)

ghcide/test/exe/FindDefinitionAndHoverTests.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -83,16 +83,16 @@ tests = let
8383
sourceFilePath = T.unpack sourceFileName
8484
sourceFileName = "GotoHover.hs"
8585

86-
mkFindTests tests = testGroup "get"
87-
[ testGroup "definition" $ mapMaybe fst tests
88-
, testGroup "hover" $ mapMaybe snd tests
89-
, testGroup "hover compile" [checkFileCompiles sourceFilePath $
86+
mkFindTests tests = sequentialTestGroup "get" AllFinish
87+
[ sequentialTestGroup "definition" AllFinish $ mapMaybe fst tests
88+
, sequentialTestGroup "hover" AllFinish $ mapMaybe snd tests
89+
, sequentialTestGroup "hover compile" AllFinish [checkFileCompiles sourceFilePath $
9090
expectDiagnostics
9191
[ ( "GotoHover.hs", [(DiagnosticSeverity_Error, (62, 7), "Found hole: _")])
9292
, ( "GotoHover.hs", [(DiagnosticSeverity_Error, (65, 8), "Found hole: _")])
9393
]]
94-
, testGroup "type-definition" typeDefinitionTests
95-
, testGroup "hover-record-dot-syntax" recordDotSyntaxTests ]
94+
, sequentialTestGroup "type-definition" AllFinish typeDefinitionTests
95+
, sequentialTestGroup "hover-record-dot-syntax" AllFinish recordDotSyntaxTests ]
9696

9797
typeDefinitionTests = [ tst (getTypeDefinitions, checkDefs) aaaL14 sourceFilePath (pure tcData) "Saturated data con"
9898
, tst (getTypeDefinitions, checkDefs) aL20 sourceFilePath (pure [ExpectNoDefinitions]) "Polymorphic variable"]

ghcide/test/exe/FuzzySearch.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -18,11 +18,11 @@ import Text.Fuzzy.Parallel
1818

1919
tests :: TestTree
2020
tests =
21-
testGroup
22-
"Fuzzy search"
21+
sequentialTestGroup
22+
"Fuzzy search" AllFinish
2323
[ needDictionary $
24-
testGroup
25-
"match works as expected on the english dictionary"
24+
sequentialTestGroup
25+
"match works as expected on the english dictionary" AllFinish
2626
[ testProperty "for legit words" propLegit,
2727
testProperty "for prefixes" propPrefix,
2828
testProperty "for typos" propTypo

ghcide/test/exe/GarbageCollectionTests.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,8 @@ import Test.Tasty.HUnit
1717
import Text.Printf (printf)
1818

1919
tests :: TestTree
20-
tests = testGroup "garbage collection"
21-
[ testGroup "dirty keys"
20+
tests = sequentialTestGroup "garbage collection" AllFinish
21+
[ sequentialTestGroup "dirty keys" AllFinish
2222
[ testWithDummyPluginEmpty' "are collected" $ \dir -> do
2323
liftIO $ writeFile (dir </> "hie.yaml") "cradle: {direct: {arguments: [A]}}"
2424
doc <- generateGarbage "A" dir

ghcide/test/exe/HaddockTests.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ import Test.Tasty.HUnit
88

99
tests :: TestTree
1010
tests
11-
= testGroup "haddock"
11+
= sequentialTestGroup "haddock" AllFinish
1212
[ testCase "Num" $ checkHaddock
1313
(unlines
1414
[ "However, '(+)' and '(*)' are"

ghcide/test/exe/HieDbRetry.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,8 @@ import Ide.Logger (Recorder (Recorder, logger_),
1414
WithPriority (WithPriority, payload),
1515
cmapWithPrio)
1616
import qualified System.Random as Random
17-
import Test.Tasty (TestTree, testGroup)
17+
import Test.Tasty (DependencyType (AllFinish), TestTree,
18+
sequentialTestGroup)
1819
import Test.Tasty.HUnit (assertFailure, testCase, (@?=))
1920

2021
data Log
@@ -46,7 +47,7 @@ isErrorCall e
4647
| ErrorCall _ <- e = Just e
4748

4849
tests :: TestTree
49-
tests = testGroup "RetryHieDb"
50+
tests = sequentialTestGroup "RetryHieDb" AllFinish
5051
[ testCase "retryOnException throws exception after max retries" $ do
5152
logMsgsVar <- newVar []
5253
let logger = makeLogger logMsgsVar

ghcide/test/exe/HighlightTests.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import Test.Tasty
1515
import Test.Tasty.HUnit
1616

1717
tests :: TestTree
18-
tests = testGroup "highlight"
18+
tests = sequentialTestGroup "highlight" AllFinish
1919
[ testWithDummyPluginEmpty "value" $ do
2020
doc <- createDoc "A.hs" "haskell" source
2121
_ <- waitForDiagnostics

ghcide/test/exe/IfaceTests.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ import Test.Tasty
2323
import Test.Tasty.HUnit
2424

2525
tests :: TestTree
26-
tests = testGroup "Interface loading tests"
26+
tests = sequentialTestGroup "Interface loading tests" AllFinish
2727
[ -- https://github.com/haskell/ghcide/pull/645/
2828
ifaceErrorTest
2929
, ifaceErrorTest2

ghcide/test/exe/InitializeResponseTests.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ tests = withResource acquire release tests where
2626
-- actually does provide! Hopefully this will change ...
2727
tests :: IO (TResponseMessage Method_Initialize) -> TestTree
2828
tests getInitializeResponse =
29-
testGroup "initialize response capabilities"
29+
sequentialTestGroup "initialize response capabilities" AllFinish
3030
[ chk " text doc sync" _textDocumentSync tds
3131
, chk " hover" _hoverProvider (Just $ InR (HoverOptions (Just False)))
3232
, chk " completion" _completionProvider (Just $ CompletionOptions (Just False) (Just ["."]) Nothing (Just True) Nothing)

ghcide/test/exe/Main.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,7 @@ import WatchedFileTests
6868
main :: IO ()
6969
main = do
7070
-- We mess with env vars so run single-threaded.
71-
defaultMainWithRerun $ testGroup "ghcide"
71+
defaultMainWithRerun $ sequentialTestGroup "ghcide" AllFinish
7272
[ OpenCloseTest.tests
7373
, InitializeResponseTests.tests
7474
, CompletionTests.tests

ghcide/test/exe/NonLspCommandLine.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ import Test.Tasty.HUnit
1818

1919
-- A test to ensure that the command line ghcide workflow stays working
2020
tests :: TestTree
21-
tests = testGroup "ghcide command line"
21+
tests = sequentialTestGroup "ghcide command line" AllFinish
2222
[ testCase "works" $ withTempDir $ \dir -> do
2323
ghcide <- locateGhcideExecutable
2424
copyTestDataFiles dir "multi"

ghcide/test/exe/OutlineTests.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -28,8 +28,8 @@ testSymbolsA testName content expectedSymbols =
2828

2929
tests :: TestTree
3030
tests =
31-
testGroup
32-
"outline"
31+
sequentialTestGroup
32+
"outline" AllFinish
3333
[ testSymbolsA
3434
"type class:"
3535
["module A where", "class A a where a :: a -> Bool"]

ghcide/test/exe/PositionMappingTests.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -48,10 +48,10 @@ mkChangeEvent r t = TextDocumentContentChangeEvent $ InL
4848

4949
tests :: TestTree
5050
tests =
51-
testGroup "position mapping"
51+
sequentialTestGroup "position mapping" AllFinish
5252
[
5353
enumMapMappingTest
54-
, testGroup "toCurrent"
54+
, sequentialTestGroup "toCurrent" AllFinish
5555
[ testCase "before" $
5656
toCurrent
5757
(Range (Position 0 1) (Position 0 3))
@@ -98,7 +98,7 @@ tests =
9898
"abc"
9999
(Position 0 1) @?= PositionExact (Position 0 4)
100100
]
101-
, testGroup "fromCurrent"
101+
, sequentialTestGroup "fromCurrent" AllFinish
102102
[ testCase "before" $
103103
fromCurrent
104104
(Range (Position 0 1) (Position 0 3))
@@ -145,7 +145,7 @@ tests =
145145
"abc"
146146
(Position 0 4) @?= PositionExact (Position 0 1)
147147
]
148-
, adjustOption (\(QuickCheckTests i) -> QuickCheckTests (max 1000 i)) $ testGroup "properties"
148+
, adjustOption (\(QuickCheckTests i) -> QuickCheckTests (max 1000 i)) $ sequentialTestGroup "properties" AllFinish
149149
[ testProperty "fromCurrent r t <=< toCurrent r t" $ do
150150
-- Note that it is important to use suchThatMap on all values at once
151151
-- instead of only using it on the position. Otherwise you can get

ghcide/test/exe/Progress.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ import Test.Tasty
1212
import Test.Tasty.HUnit
1313

1414
tests :: TestTree
15-
tests = testGroup "Progress"
15+
tests = sequentialTestGroup "Progress" AllFinish
1616
[ reportProgressTests
1717
]
1818

@@ -22,7 +22,7 @@ data InProgressModel = InProgressModel {
2222
}
2323

2424
reportProgressTests :: TestTree
25-
reportProgressTests = testGroup "recordProgress"
25+
reportProgressTests = sequentialTestGroup "recordProgress" AllFinish
2626
[ test "addNew" addNew
2727
, test "increase" increase
2828
, test "decrease" decrease

ghcide/test/exe/ReferenceTests.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -41,8 +41,8 @@ import Test.Tasty.HUnit
4141

4242

4343
tests :: TestTree
44-
tests = testGroup "references"
45-
[ testGroup "can get references to FOIs"
44+
tests = sequentialTestGroup "references" AllFinish
45+
[ sequentialTestGroup "can get references to FOIs" AllFinish
4646
[ referenceTest "can get references to symbols"
4747
("References.hs", 4, 7)
4848
YesIncludeDeclaration
@@ -111,7 +111,7 @@ tests = testGroup "references"
111111
]
112112
]
113113

114-
, testGroup "can get references to non FOIs"
114+
, sequentialTestGroup "can get references to non FOIs" AllFinish
115115
[ referenceTest "can get references to symbol defined in a module we import"
116116
("References.hs", 22, 4)
117117
YesIncludeDeclaration

0 commit comments

Comments
 (0)