@@ -95,7 +95,7 @@ import System.Process.Extra (CreateProcess (cwd),
9595import Test.QuickCheck
9696-- import Test.QuickCheck.Instances ()
9797import Control.Concurrent.Async
98- import Control.Lens (to , (^.) )
98+ import Control.Lens (to , (^.) , (.~) )
9999import Control.Monad.Extra (whenJust )
100100import Data.Function ((&) )
101101import Data.IORef
@@ -133,6 +133,7 @@ import Test.Tasty.Ingredients.Rerun
133133import Test.Tasty.QuickCheck
134134import Text.Printf (printf )
135135import Text.Regex.TDFA ((=~) )
136+ import Language.LSP.Types.Lens (workspace , didChangeWatchedFiles )
136137
137138data Log
138139 = LogGhcIde Ghcide. Log
@@ -421,9 +422,12 @@ diagnosticTests = testGroup "diagnostics"
421422 let contentA = T. unlines [ " module ModuleA where" ]
422423 _ <- createDoc " ModuleA.hs" " haskell" contentA
423424 expectDiagnostics [(" ModuleB.hs" , [] )]
424- , ignoreTestBecause " Flaky #2831" $ testSessionWait " add missing module (non workspace)" $ do
425- -- need to canonicalize in Mac Os
426- tmpDir <- liftIO $ canonicalizePath =<< getTemporaryDirectory
425+ , testCase " add missing module (non workspace)" $
426+ -- By default lsp-test sends FileWatched notifications for all files, which we don't want
427+ -- as non workspace modules will not be watched by the LSP server.
428+ -- To work around this, we tell lsp-test that our client doesn't have the
429+ -- FileWatched capability, which is enough to disable the notifications
430+ withTempDir $ \ tmpDir -> runInDir'' lspTestCapsNoFileWatches tmpDir " ." " ." [] $ do
427431 let contentB = T. unlines
428432 [ " module ModuleB where"
429433 , " import ModuleA ()"
@@ -6306,7 +6310,18 @@ withLongTimeout = bracket_ (setEnv "LSP_TIMEOUT" "120" True) (unsetEnv "LSP_TIME
63066310
63076311-- | Takes a directory as well as relative paths to where we should launch the executable as well as the session root.
63086312runInDir' :: FilePath -> FilePath -> FilePath -> [String ] -> Session a -> IO a
6309- runInDir' dir startExeIn startSessionIn extraOptions s = do
6313+ runInDir' = runInDir'' lspTestCaps
6314+
6315+ runInDir''
6316+ :: ClientCapabilities
6317+ -> FilePath
6318+ -> FilePath
6319+ -> FilePath
6320+ -> [String ]
6321+ -> Session b
6322+ -> IO b
6323+ runInDir'' lspCaps dir startExeIn startSessionIn extraOptions s = do
6324+
63106325 ghcideExe <- locateGhcideExecutable
63116326 let startDir = dir </> startExeIn
63126327 let projDir = dir </> startSessionIn
@@ -6326,10 +6341,11 @@ runInDir' dir startExeIn startSessionIn extraOptions s = do
63266341 -- Only sets HOME if it wasn't already set.
63276342 setEnv " HOME" " /homeless-shelter" False
63286343 conf <- getConfigFromEnv
6329- runSessionWithConfig conf cmd lspTestCaps projDir $ do
6344+ runSessionWithConfig conf cmd lspCaps projDir $ do
63306345 configureCheckProject False
63316346 s
63326347
6348+
63336349getConfigFromEnv :: IO SessionConfig
63346350getConfigFromEnv = do
63356351 logColor <- fromMaybe True <$> checkEnv " LSP_TEST_LOG_COLOR"
@@ -6347,6 +6363,9 @@ getConfigFromEnv = do
63476363lspTestCaps :: ClientCapabilities
63486364lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities (Just True ) Nothing Nothing }
63496365
6366+ lspTestCapsNoFileWatches :: ClientCapabilities
6367+ lspTestCapsNoFileWatches = lspTestCaps & workspace . Lens. _Just . didChangeWatchedFiles .~ Nothing
6368+
63506369openTestDataDoc :: FilePath -> Session TextDocumentIdentifier
63516370openTestDataDoc path = do
63526371 source <- liftIO $ readFileUtf8 $ " test/data" </> path
0 commit comments