@@ -53,7 +53,7 @@ import Development.IDE.Test (Cursor,
53
53
getInterfaceFilesDir ,
54
54
waitForAction ,
55
55
getStoredKeys ,
56
- waitForTypecheck , waitForGC )
56
+ waitForTypecheck , waitForGC , configureCheckProject )
57
57
import Development.IDE.Test.Runfiles
58
58
import qualified Development.IDE.Types.Diagnostics as Diagnostics
59
59
import Development.IDE.Types.Location
@@ -427,10 +427,7 @@ diagnosticTests = testGroup "diagnostics"
427
427
liftIO $ writeFile (path </> " hie.yaml" ) cradle
428
428
_ <- createDoc " ModuleD.hs" " haskell" contentD
429
429
expectDiagnostics
430
- [ ( " ModuleA.hs"
431
- , [(DsError , (1 , 7 ), " Cyclic module dependency between ModuleA, ModuleB" )]
432
- )
433
- , ( " ModuleB.hs"
430
+ [ ( " ModuleB.hs"
434
431
, [(DsError , (1 , 7 ), " Cyclic module dependency between ModuleA, ModuleB" )]
435
432
)
436
433
]
@@ -1603,10 +1600,7 @@ extendImportTests = testGroup "extend import actions"
1603
1600
codeActionTitle CodeAction {_title= x} = x
1604
1601
1605
1602
template setUpModules moduleUnderTest range expectedTitles expectedContentB = do
1606
- sendNotification SWorkspaceDidChangeConfiguration
1607
- (DidChangeConfigurationParams $ toJSON
1608
- def{checkProject = overrideCheckProject})
1609
-
1603
+ configureCheckProject overrideCheckProject
1610
1604
1611
1605
mapM_ (\ x -> createDoc (fst x) " haskell" (snd x)) setUpModules
1612
1606
docB <- createDoc (fst moduleUnderTest) " haskell" (snd moduleUnderTest)
@@ -1783,6 +1777,7 @@ suggestImportTests = testGroup "suggest import actions"
1783
1777
test = test' False
1784
1778
wantWait = test' True True
1785
1779
test' waitForCheckProject wanted imps def other newImp = testSessionWithExtraFiles " hover" (T. unpack def) $ \ dir -> do
1780
+ configureCheckProject waitForCheckProject
1786
1781
let before = T. unlines $ " module A where" : [" import " <> x | x <- imps] ++ def : other
1787
1782
after = T. unlines $ " module A where" : [" import " <> x | x <- imps] ++ [newImp] ++ def : other
1788
1783
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
5325
5320
5326
5321
ifaceErrorTest :: TestTree
5327
5322
ifaceErrorTest = testCase " iface-error-test-1" $ runWithExtraFiles " recomp" $ \ dir -> do
5323
+ configureCheckProject True
5328
5324
let bPath = dir </> " B.hs"
5329
5325
pPath = dir </> " P.hs"
5330
5326
@@ -5689,6 +5685,8 @@ getReferences' (file, l, c) includeDeclaration = do
5689
5685
5690
5686
referenceTestSession :: String -> FilePath -> [FilePath ] -> (FilePath -> Session () ) -> TestTree
5691
5687
referenceTestSession name thisDoc docs' f = testSessionWithExtraFiles " references" name $ \ dir -> do
5688
+ -- needed to build whole project indexing
5689
+ configureCheckProject True
5692
5690
let docs = map (dir </> ) $ delete thisDoc $ nubOrd docs'
5693
5691
-- Initial Index
5694
5692
docid <- openDoc thisDoc " haskell"
@@ -5819,7 +5817,9 @@ runInDir' dir startExeIn startSessionIn extraOptions s = do
5819
5817
-- Only sets HOME if it wasn't already set.
5820
5818
setEnv " HOME" " /homeless-shelter" False
5821
5819
conf <- getConfigFromEnv
5822
- runSessionWithConfig conf cmd lspTestCaps projDir s
5820
+ runSessionWithConfig conf cmd lspTestCaps projDir $ do
5821
+ configureCheckProject False
5822
+ s
5823
5823
5824
5824
getConfigFromEnv :: IO SessionConfig
5825
5825
getConfigFromEnv = do
0 commit comments