@@ -53,7 +53,7 @@ import Development.IDE.Test (Cursor,
5353 getInterfaceFilesDir ,
5454 waitForAction ,
5555 getStoredKeys ,
56- waitForTypecheck , waitForGC )
56+ waitForTypecheck , waitForGC , configureCheckProject )
5757import Development.IDE.Test.Runfiles
5858import qualified Development.IDE.Types.Diagnostics as Diagnostics
5959import Development.IDE.Types.Location
@@ -427,10 +427,7 @@ diagnosticTests = testGroup "diagnostics"
427427 liftIO $ writeFile (path </> " hie.yaml" ) cradle
428428 _ <- createDoc " ModuleD.hs" " haskell" contentD
429429 expectDiagnostics
430- [ ( " ModuleA.hs"
431- , [(DsError , (1 , 7 ), " Cyclic module dependency between ModuleA, ModuleB" )]
432- )
433- , ( " ModuleB.hs"
430+ [ ( " ModuleB.hs"
434431 , [(DsError , (1 , 7 ), " Cyclic module dependency between ModuleA, ModuleB" )]
435432 )
436433 ]
@@ -1603,10 +1600,7 @@ extendImportTests = testGroup "extend import actions"
16031600 codeActionTitle CodeAction {_title= x} = x
16041601
16051602 template setUpModules moduleUnderTest range expectedTitles expectedContentB = do
1606- sendNotification SWorkspaceDidChangeConfiguration
1607- (DidChangeConfigurationParams $ toJSON
1608- def{checkProject = overrideCheckProject})
1609-
1603+ configureCheckProject overrideCheckProject
16101604
16111605 mapM_ (\ x -> createDoc (fst x) " haskell" (snd x)) setUpModules
16121606 docB <- createDoc (fst moduleUnderTest) " haskell" (snd moduleUnderTest)
@@ -1783,6 +1777,7 @@ suggestImportTests = testGroup "suggest import actions"
17831777 test = test' False
17841778 wantWait = test' True True
17851779 test' waitForCheckProject wanted imps def other newImp = testSessionWithExtraFiles " hover" (T. unpack def) $ \ dir -> do
1780+ configureCheckProject waitForCheckProject
17861781 let before = T. unlines $ " module A where" : [" import " <> x | x <- imps] ++ def : other
17871782 after = T. unlines $ " module A where" : [" import " <> x | x <- imps] ++ [newImp] ++ def : other
17881783 cradle = " cradle: {direct: {arguments: [-hide-all-packages, -package, base, -package, text, -package-env, -, A, Bar, Foo, B]}}"
@@ -5325,6 +5320,7 @@ ifaceTHTest = testCase "iface-th-test" $ runWithExtraFiles "TH" $ \dir -> do
53255320
53265321ifaceErrorTest :: TestTree
53275322ifaceErrorTest = testCase " iface-error-test-1" $ runWithExtraFiles " recomp" $ \ dir -> do
5323+ configureCheckProject True
53285324 let bPath = dir </> " B.hs"
53295325 pPath = dir </> " P.hs"
53305326
@@ -5689,6 +5685,8 @@ getReferences' (file, l, c) includeDeclaration = do
56895685
56905686referenceTestSession :: String -> FilePath -> [FilePath ] -> (FilePath -> Session () ) -> TestTree
56915687referenceTestSession name thisDoc docs' f = testSessionWithExtraFiles " references" name $ \ dir -> do
5688+ -- needed to build whole project indexing
5689+ configureCheckProject True
56925690 let docs = map (dir </> ) $ delete thisDoc $ nubOrd docs'
56935691 -- Initial Index
56945692 docid <- openDoc thisDoc " haskell"
@@ -5819,7 +5817,9 @@ runInDir' dir startExeIn startSessionIn extraOptions s = do
58195817 -- Only sets HOME if it wasn't already set.
58205818 setEnv " HOME" " /homeless-shelter" False
58215819 conf <- getConfigFromEnv
5822- runSessionWithConfig conf cmd lspTestCaps projDir s
5820+ runSessionWithConfig conf cmd lspTestCaps projDir $ do
5821+ configureCheckProject False
5822+ s
58235823
58245824getConfigFromEnv :: IO SessionConfig
58255825getConfigFromEnv = do
0 commit comments