Skip to content

Commit

Permalink
Switch ghcide tests to sequential execution
Browse files Browse the repository at this point in the history
  • Loading branch information
dyniec committed Jun 9, 2024
1 parent efe8913 commit 592bcc9
Show file tree
Hide file tree
Showing 29 changed files with 78 additions and 77 deletions.
2 changes: 1 addition & 1 deletion ghcide/test/exe/AsyncTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Test.Tasty.HUnit

-- | Test if ghcide asynchronously handles Commands and user Requests
tests :: TestTree
tests = testGroup "async"
tests = sequentialTestGroup "async" AllFinish
[
testWithDummyPluginEmpty "command" $ do
-- Execute a command that will block forever
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/BootTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Test.Tasty.HUnit


tests :: TestTree
tests = testGroup "boot"
tests = sequentialTestGroup "boot" AllFinish
[ testCase "boot-def-test" $ runWithExtraFiles "boot" $ \dir -> do
let cPath = dir </> "C.hs"
cSource <- liftIO $ readFileUtf8 cPath
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/CPPTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Test.Tasty.HUnit

tests :: TestTree
tests =
testGroup "cpp"
sequentialTestGroup "cpp" AllFinish
[ testCase "cpp-error" $ do
let content =
T.unlines
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/ClientSettingsTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import Test.Hls (testConfigCaps,
import Test.Tasty

tests :: TestTree
tests = testGroup "client settings handling"
tests = sequentialTestGroup "client settings handling" AllFinish
[ testWithDummyPluginEmpty "ghcide restarts shake session on config changes" $ do
setIgnoringLogNotifications False
void $ createDoc "A.hs" "haskell" "module A where"
Expand Down
12 changes: 6 additions & 6 deletions ghcide/test/exe/CodeLensTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ import Test.Tasty
import Test.Tasty.HUnit

tests :: TestTree
tests = testGroup "code lenses"
tests = sequentialTestGroup "code lenses" AllFinish
[ addSigLensesTests
]

Expand Down Expand Up @@ -91,12 +91,12 @@ addSigLensesTests =
, ("notInScopeTest = mkCharType", "notInScopeTest :: String -> Data.Data.DataType")
, ("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")
]
in testGroup
"add signature"
[ testGroup "signatures are correct" [sigSession (T.unpack $ T.replace "\n" "\\n" def) False False "always" "" (def, Just sig) [] | (def, sig) <- cases]
in sequentialTestGroup
"add signature" AllFinish
[ sequentialTestGroup "signatures are correct" AllFinish [sigSession (T.unpack $ T.replace "\n" "\\n" def) False False "always" "" (def, Just sig) [] | (def, sig) <- cases]
, sigSession "exported mode works" False False "exported" "xyz" ("xyz = True", Just "xyz :: Bool") (fst <$> take 3 cases)
, testGroup
"diagnostics mode works"
, sequentialTestGroup
"diagnostics mode works" AllFinish
[ sigSession "with GHC warnings" True True "diagnostics" "" (second Just $ head cases) []
, sigSession "without GHC warnings" False False "diagnostics" "" (second (const Nothing) $ head cases) []
]
Expand Down
18 changes: 9 additions & 9 deletions ghcide/test/exe/CompletionTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,15 +37,15 @@ import Test.Tasty.HUnit

tests :: TestTree
tests
= testGroup "completion"
= sequentialTestGroup "completion" AllFinish
[
testGroup "non local" nonLocalCompletionTests
, testGroup "topLevel" topLevelCompletionTests
, testGroup "local" localCompletionTests
, testGroup "package" packageCompletionTests
, testGroup "project" projectCompletionTests
, testGroup "other" otherCompletionTests
, testGroup "doc" completionDocTests
sequentialTestGroup "non local" AllFinish nonLocalCompletionTests
, sequentialTestGroup "topLevel" AllFinish topLevelCompletionTests
, sequentialTestGroup "local" AllFinish localCompletionTests
, sequentialTestGroup "package" AllFinish packageCompletionTests
, sequentialTestGroup "project" AllFinish projectCompletionTests
, sequentialTestGroup "other" AllFinish otherCompletionTests
, sequentialTestGroup "doc" AllFinish completionDocTests
]

testSessionEmpty :: TestName -> Session () -> TestTree
Expand Down Expand Up @@ -255,7 +255,7 @@ nonLocalCompletionTests =
]
(Position 3 6)
[],
testGroup "ordering"
sequentialTestGroup "ordering" AllFinish
[completionTest "qualified has priority"
["module A where"
,"import qualified Data.ByteString as BS"
Expand Down
18 changes: 9 additions & 9 deletions ghcide/test/exe/CradleTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,20 +35,20 @@ import Test.Tasty.HUnit


tests :: TestTree
tests = testGroup "cradle"
[testGroup "dependencies" [sessionDepsArePickedUp]
,testGroup "ignore-fatal" [ignoreFatalWarning]
,testGroup "loading" [loadCradleOnlyonce, retryFailedCradle]
,testGroup "multi" (multiTests "multi")
tests = sequentialTestGroup "cradle" AllFinish
[sequentialTestGroup "dependencies" AllFinish [sessionDepsArePickedUp]
,sequentialTestGroup "ignore-fatal" AllFinish [ignoreFatalWarning]
,sequentialTestGroup "loading" AllFinish [loadCradleOnlyonce, retryFailedCradle]
,sequentialTestGroup "multi" AllFinish (multiTests "multi")
,ignoreForGhcVersions [GHC92] "multiple units not supported on 9.2"
$ testGroup "multi-unit" (multiTests "multi-unit")
,testGroup "sub-directory" [simpleSubDirectoryTest]
$ sequentialTestGroup "multi-unit" AllFinish (multiTests "multi-unit")
,sequentialTestGroup "sub-directory" AllFinish [simpleSubDirectoryTest]
,ignoreForGhcVersions [GHC92] "multiple units not supported on 9.2"
$ testGroup "multi-unit-rexport" [multiRexportTest]
$ sequentialTestGroup "multi-unit-rexport" AllFinish [multiRexportTest]
]

loadCradleOnlyonce :: TestTree
loadCradleOnlyonce = testGroup "load cradle only once"
loadCradleOnlyonce = sequentialTestGroup "load cradle only once" AllFinish
[ testWithDummyPluginEmpty' "implicit" implicit
, testWithDummyPluginEmpty' "direct" direct
]
Expand Down
4 changes: 2 additions & 2 deletions ghcide/test/exe/DependentFileTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,8 @@ import Test.Hls


tests :: TestTree
tests = testGroup "addDependentFile"
[testGroup "file-changed" [testCase "test" $ runSessionWithTestConfig def
tests = sequentialTestGroup "addDependentFile" AllFinish
[sequentialTestGroup "file-changed" AllFinish [testCase "test" $ runSessionWithTestConfig def
{ testShiftRoot = True
, testDirLocation = Right (mkIdeTestFs [])
, testPluginDescriptor = dummyPlugin
Expand Down
8 changes: 4 additions & 4 deletions ghcide/test/exe/DiagnosticTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ import Test.Tasty
import Test.Tasty.HUnit

tests :: TestTree
tests = testGroup "diagnostics"
tests = sequentialTestGroup "diagnostics" AllFinish
[ testWithDummyPluginEmpty "fix syntax error" $ do
let content = T.unlines [ "module Testing wher" ]
doc <- createDoc "Testing.hs" "haskell" content
Expand Down Expand Up @@ -120,7 +120,7 @@ tests = testGroup "diagnostics"
)
]

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

, testGroup "Cancellation"
, sequentialTestGroup "Cancellation" AllFinish
[ cancellationTestGroup "edit header" editHeader yesSession noParse noTc
, cancellationTestGroup "edit import" editImport noSession yesParse noTc
, cancellationTestGroup "edit body" editBody yesSession yesParse yesTc
Expand Down Expand Up @@ -539,7 +539,7 @@ tests = testGroup "diagnostics"
yesTc = True

cancellationTestGroup :: TestName -> (TextDocumentContentChangeEvent, TextDocumentContentChangeEvent) -> Bool -> Bool -> Bool -> TestTree
cancellationTestGroup name edits sessionDepsOutcome parseOutcome tcOutcome = testGroup name
cancellationTestGroup name edits sessionDepsOutcome parseOutcome tcOutcome = sequentialTestGroup name AllFinish
[ cancellationTemplate edits Nothing
, cancellationTemplate edits $ Just ("GetFileContents", True)
, cancellationTemplate edits $ Just ("GhcSession", True)
Expand Down
6 changes: 3 additions & 3 deletions ghcide/test/exe/ExceptionTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,8 +38,8 @@ import Test.Tasty.HUnit

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

, testGroup "Testing PluginError order..."
, sequentialTestGroup "Testing PluginError order..." AllFinish
[ pluginOrderTestCase "InternalError over InvalidParams" (PluginInternalError "error test") (PluginInvalidParams "error test")
, pluginOrderTestCase "InvalidParams over InvalidUserState" (PluginInvalidParams "error test") (PluginInvalidUserState "error test")
, pluginOrderTestCase "InvalidUserState over RequestRefused" (PluginInvalidUserState "error test") (PluginRequestRefused DisabledGlobally)
Expand Down
12 changes: 6 additions & 6 deletions ghcide/test/exe/FindDefinitionAndHoverTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -83,16 +83,16 @@ tests = let
sourceFilePath = T.unpack sourceFileName
sourceFileName = "GotoHover.hs"

mkFindTests tests = testGroup "get"
[ testGroup "definition" $ mapMaybe fst tests
, testGroup "hover" $ mapMaybe snd tests
, testGroup "hover compile" [checkFileCompiles sourceFilePath $
mkFindTests tests = sequentialTestGroup "get" AllFinish
[ sequentialTestGroup "definition" AllFinish $ mapMaybe fst tests
, sequentialTestGroup "hover" AllFinish $ mapMaybe snd tests
, sequentialTestGroup "hover compile" AllFinish [checkFileCompiles sourceFilePath $
expectDiagnostics
[ ( "GotoHover.hs", [(DiagnosticSeverity_Error, (62, 7), "Found hole: _")])
, ( "GotoHover.hs", [(DiagnosticSeverity_Error, (65, 8), "Found hole: _")])
]]
, testGroup "type-definition" typeDefinitionTests
, testGroup "hover-record-dot-syntax" recordDotSyntaxTests ]
, sequentialTestGroup "type-definition" AllFinish typeDefinitionTests
, sequentialTestGroup "hover-record-dot-syntax" AllFinish recordDotSyntaxTests ]

typeDefinitionTests = [ tst (getTypeDefinitions, checkDefs) aaaL14 sourceFilePath (pure tcData) "Saturated data con"
, tst (getTypeDefinitions, checkDefs) aL20 sourceFilePath (pure [ExpectNoDefinitions]) "Polymorphic variable"]
Expand Down
8 changes: 4 additions & 4 deletions ghcide/test/exe/FuzzySearch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,11 +18,11 @@ import Text.Fuzzy.Parallel

tests :: TestTree
tests =
testGroup
"Fuzzy search"
sequentialTestGroup
"Fuzzy search" AllFinish
[ needDictionary $
testGroup
"match works as expected on the english dictionary"
sequentialTestGroup
"match works as expected on the english dictionary" AllFinish
[ testProperty "for legit words" propLegit,
testProperty "for prefixes" propPrefix,
testProperty "for typos" propTypo
Expand Down
4 changes: 2 additions & 2 deletions ghcide/test/exe/GarbageCollectionTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,8 @@ import Test.Tasty.HUnit
import Text.Printf (printf)

tests :: TestTree
tests = testGroup "garbage collection"
[ testGroup "dirty keys"
tests = sequentialTestGroup "garbage collection" AllFinish
[ sequentialTestGroup "dirty keys" AllFinish
[ testWithDummyPluginEmpty' "are collected" $ \dir -> do
liftIO $ writeFile (dir </> "hie.yaml") "cradle: {direct: {arguments: [A]}}"
doc <- generateGarbage "A" dir
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/HaddockTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Test.Tasty.HUnit

tests :: TestTree
tests
= testGroup "haddock"
= sequentialTestGroup "haddock" AllFinish
[ testCase "Num" $ checkHaddock
(unlines
[ "However, '(+)' and '(*)' are"
Expand Down
5 changes: 3 additions & 2 deletions ghcide/test/exe/HieDbRetry.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ import Ide.Logger (Recorder (Recorder, logger_),
WithPriority (WithPriority, payload),
cmapWithPrio)
import qualified System.Random as Random
import Test.Tasty (TestTree, testGroup)
import Test.Tasty (DependencyType (AllFinish), TestTree,
sequentialTestGroup)
import Test.Tasty.HUnit (assertFailure, testCase, (@?=))

data Log
Expand Down Expand Up @@ -46,7 +47,7 @@ isErrorCall e
| ErrorCall _ <- e = Just e

tests :: TestTree
tests = testGroup "RetryHieDb"
tests = sequentialTestGroup "RetryHieDb" AllFinish
[ testCase "retryOnException throws exception after max retries" $ do
logMsgsVar <- newVar []
let logger = makeLogger logMsgsVar
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/HighlightTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Test.Tasty
import Test.Tasty.HUnit

tests :: TestTree
tests = testGroup "highlight"
tests = sequentialTestGroup "highlight" AllFinish
[ testWithDummyPluginEmpty "value" $ do
doc <- createDoc "A.hs" "haskell" source
_ <- waitForDiagnostics
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/IfaceTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Test.Tasty
import Test.Tasty.HUnit

tests :: TestTree
tests = testGroup "Interface loading tests"
tests = sequentialTestGroup "Interface loading tests" AllFinish
[ -- https://github.com/haskell/ghcide/pull/645/
ifaceErrorTest
, ifaceErrorTest2
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/InitializeResponseTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ tests = withResource acquire release tests where
-- actually does provide! Hopefully this will change ...
tests :: IO (TResponseMessage Method_Initialize) -> TestTree
tests getInitializeResponse =
testGroup "initialize response capabilities"
sequentialTestGroup "initialize response capabilities" AllFinish
[ chk " text doc sync" _textDocumentSync tds
, chk " hover" _hoverProvider (Just $ InR (HoverOptions (Just False)))
, chk " completion" _completionProvider (Just $ CompletionOptions (Just False) (Just ["."]) Nothing (Just True) Nothing)
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ import WatchedFileTests
main :: IO ()
main = do
-- We mess with env vars so run single-threaded.
defaultMainWithRerun $ testGroup "ghcide"
defaultMainWithRerun $ sequentialTestGroup "ghcide" AllFinish
[ OpenCloseTest.tests
, InitializeResponseTests.tests
, CompletionTests.tests
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/NonLspCommandLine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ import Test.Tasty.HUnit

-- A test to ensure that the command line ghcide workflow stays working
tests :: TestTree
tests = testGroup "ghcide command line"
tests = sequentialTestGroup "ghcide command line" AllFinish
[ testCase "works" $ withTempDir $ \dir -> do
ghcide <- locateGhcideExecutable
copyTestDataFiles dir "multi"
Expand Down
4 changes: 2 additions & 2 deletions ghcide/test/exe/OutlineTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,8 +28,8 @@ testSymbolsA testName content expectedSymbols =

tests :: TestTree
tests =
testGroup
"outline"
sequentialTestGroup
"outline" AllFinish
[ testSymbolsA
"type class:"
["module A where", "class A a where a :: a -> Bool"]
Expand Down
8 changes: 4 additions & 4 deletions ghcide/test/exe/PositionMappingTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,10 +48,10 @@ mkChangeEvent r t = TextDocumentContentChangeEvent $ InL

tests :: TestTree
tests =
testGroup "position mapping"
sequentialTestGroup "position mapping" AllFinish
[
enumMapMappingTest
, testGroup "toCurrent"
, sequentialTestGroup "toCurrent" AllFinish
[ testCase "before" $
toCurrent
(Range (Position 0 1) (Position 0 3))
Expand Down Expand Up @@ -98,7 +98,7 @@ tests =
"abc"
(Position 0 1) @?= PositionExact (Position 0 4)
]
, testGroup "fromCurrent"
, sequentialTestGroup "fromCurrent" AllFinish
[ testCase "before" $
fromCurrent
(Range (Position 0 1) (Position 0 3))
Expand Down Expand Up @@ -145,7 +145,7 @@ tests =
"abc"
(Position 0 4) @?= PositionExact (Position 0 1)
]
, adjustOption (\(QuickCheckTests i) -> QuickCheckTests (max 1000 i)) $ testGroup "properties"
, adjustOption (\(QuickCheckTests i) -> QuickCheckTests (max 1000 i)) $ sequentialTestGroup "properties" AllFinish
[ testProperty "fromCurrent r t <=< toCurrent r t" $ do
-- Note that it is important to use suchThatMap on all values at once
-- instead of only using it on the position. Otherwise you can get
Expand Down
4 changes: 2 additions & 2 deletions ghcide/test/exe/Progress.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import Test.Tasty
import Test.Tasty.HUnit

tests :: TestTree
tests = testGroup "Progress"
tests = sequentialTestGroup "Progress" AllFinish
[ reportProgressTests
]

Expand All @@ -22,7 +22,7 @@ data InProgressModel = InProgressModel {
}

reportProgressTests :: TestTree
reportProgressTests = testGroup "recordProgress"
reportProgressTests = sequentialTestGroup "recordProgress" AllFinish
[ test "addNew" addNew
, test "increase" increase
, test "decrease" decrease
Expand Down
6 changes: 3 additions & 3 deletions ghcide/test/exe/ReferenceTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,8 @@ import Test.Tasty.HUnit


tests :: TestTree
tests = testGroup "references"
[ testGroup "can get references to FOIs"
tests = sequentialTestGroup "references" AllFinish
[ sequentialTestGroup "can get references to FOIs" AllFinish
[ referenceTest "can get references to symbols"
("References.hs", 4, 7)
YesIncludeDeclaration
Expand Down Expand Up @@ -111,7 +111,7 @@ tests = testGroup "references"
]
]

, testGroup "can get references to non FOIs"
, sequentialTestGroup "can get references to non FOIs" AllFinish
[ referenceTest "can get references to symbol defined in a module we import"
("References.hs", 22, 4)
YesIncludeDeclaration
Expand Down
Loading

0 comments on commit 592bcc9

Please sign in to comment.