Skip to content

Commit e0390f1

Browse files
committed
Run all tests with temporary 'XDG_CACHE_HOME'
This makes sure each test run is independent. Makes the tests * iface-error-test-1 * iface-th-test less flaky locally. Should not have any effect on the CI flakiness issue. --- Fix test cases to work with the temporary `XDG_CACHE_HOME` Some tests were launching additional HLS instances for the tests. Fixed, which should make the test slightly faster.
1 parent e00b5dd commit e0390f1

File tree

4 files changed

+92
-48
lines changed

4 files changed

+92
-48
lines changed

ghcide-test/exe/BootTests.hs

Lines changed: 18 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -27,25 +27,24 @@ tests = testGroup "boot"
2727
let cPath = dir </> "C.hs"
2828
cSource <- liftIO $ readFileUtf8 cPath
2929
-- Dirty the cache
30-
liftIO $ runInDir dir $ do
31-
cDoc <- createDoc cPath "haskell" cSource
32-
-- We send a hover request then wait for either the hover response or
33-
-- `ghcide/reference/ready` notification.
34-
-- Once we receive one of the above, we wait for the other that we
35-
-- haven't received yet.
36-
-- If we don't wait for the `ready` notification it is possible
37-
-- that the `getDefinitions` request/response in the outer ghcide
38-
-- session will find no definitions.
39-
let hoverParams = HoverParams cDoc (Position 4 3) Nothing
40-
hoverRequestId <- sendRequest SMethod_TextDocumentHover hoverParams
41-
let parseReadyMessage = isReferenceReady cPath
42-
let parseHoverResponse = responseForId SMethod_TextDocumentHover hoverRequestId
43-
hoverResponseOrReadyMessage <- skipManyTill anyMessage ((Left <$> parseHoverResponse) <|> (Right <$> parseReadyMessage))
44-
_ <- skipManyTill anyMessage $
45-
case hoverResponseOrReadyMessage of
46-
Left _ -> void parseReadyMessage
47-
Right _ -> void parseHoverResponse
48-
closeDoc cDoc
30+
cDoc <- createDoc cPath "haskell" cSource
31+
-- We send a hover request then wait for either the hover response or
32+
-- `ghcide/reference/ready` notification.
33+
-- Once we receive one of the above, we wait for the other that we
34+
-- haven't received yet.
35+
-- If we don't wait for the `ready` notification it is possible
36+
-- that the `getDefinitions` request/response in the outer ghcide
37+
-- session will find no definitions.
38+
let hoverParams = HoverParams cDoc (Position 4 3) Nothing
39+
hoverRequestId <- sendRequest SMethod_TextDocumentHover hoverParams
40+
let parseReadyMessage = isReferenceReady cPath
41+
let parseHoverResponse = responseForId SMethod_TextDocumentHover hoverRequestId
42+
hoverResponseOrReadyMessage <- skipManyTill anyMessage ((Left <$> parseHoverResponse) <|> (Right <$> parseReadyMessage))
43+
_ <- skipManyTill anyMessage $
44+
case hoverResponseOrReadyMessage of
45+
Left _ -> void parseReadyMessage
46+
Right _ -> void parseHoverResponse
47+
closeDoc cDoc
4948
cdoc <- createDoc cPath "haskell" cSource
5049
locs <- getDefinitions cdoc (Position 7 4)
5150
let floc = mkR 9 0 9 1

ghcide-test/exe/CradleTests.hs

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33

44
module CradleTests (tests) where
55

6-
import Config (checkDefs, mkL, runInDir,
6+
import Config (checkDefs, mkL,
77
runWithExtraFiles,
88
testWithDummyPluginEmpty')
99
import Control.Applicative.Combinators
@@ -175,12 +175,9 @@ simpleMultiDefTest variant = ignoreForWindows $ testCase testName $
175175
runWithExtraFiles variant $ \dir -> do
176176
let aPath = dir </> "a/A.hs"
177177
bPath = dir </> "b/B.hs"
178-
adoc <- liftIO $ runInDir dir $ do
179-
aSource <- liftIO $ readFileUtf8 aPath
180-
adoc <- createDoc aPath "haskell" aSource
181-
skipManyTill anyMessage $ isReferenceReady aPath
182-
closeDoc adoc
183-
pure adoc
178+
adoc <- openDoc aPath "haskell"
179+
skipManyTill anyMessage $ isReferenceReady aPath
180+
closeDoc adoc
184181
bSource <- liftIO $ readFileUtf8 bPath
185182
bdoc <- createDoc bPath "haskell" bSource
186183
locs <- getDefinitions bdoc (Position 2 7)

ghcide-test/exe/FindDefinitionAndHoverTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -187,7 +187,7 @@ tests = let
187187
holeL65 = Position 65 8 ; hleInfo2 = [ExpectHoverText ["_ :: a -> Maybe a"]]
188188
cccL17 = Position 17 16 ; docLink = [ExpectHoverTextRegex "\\*Defined in 'GHC.Types'\\* \\*\\(ghc-prim-[0-9.]+\\)\\*\n\n"]
189189
imported = Position 56 13 ; importedSig = getDocUri "Foo.hs" >>= \foo -> return [ExpectHoverText ["foo", "Foo", "Haddock"], mkL foo 5 0 5 3]
190-
reexported = Position 55 14 ; reexportedSig = getDocUri "Bar.hs" >>= \bar -> return [ExpectHoverText ["Bar", "Bar", "Haddock"], if ghcVersion >= GHC94 && ghcVersion < GHC910 then mkL bar 3 5 3 8 else mkL bar 3 0 3 14]
190+
reexported = Position 55 14 ; reexportedSig = getDocUri "Bar.hs" >>= \bar -> return [ExpectHoverText ["Bar", "Bar", "Haddock"], mkL bar 3 0 3 14]
191191
thLocL57 = Position 59 10 ; thLoc = [ExpectHoverText ["Identity"]]
192192
cmtL68 = Position 67 0 ; lackOfdEq = [ExpectHoverExcludeText ["$dEq"]]
193193
import310 = Position 3 10; pkgTxt = [ExpectHoverText ["Data.Text\n\ntext-"]]

hls-test-utils/src/Test/Hls.hs

Lines changed: 69 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -507,32 +507,73 @@ runSessionWithServerInTmpDir config plugin tree act =
507507
{testLspConfig=config, testPluginDescriptor = plugin, testDirLocation=Right tree}
508508
(const act)
509509

510-
runWithLockInTempDir :: VirtualFileTree -> (FileSystem -> IO a) -> IO a
511-
runWithLockInTempDir tree act = withLock lockForTempDirs $ do
510+
-- | Same as 'withTemporaryDataAndCacheDirectory', but materialises the given
511+
-- 'VirtualFileTree' in the temporary directory.
512+
withVfsTestDataDirectory :: VirtualFileTree -> (FileSystem -> IO a) -> IO a
513+
withVfsTestDataDirectory tree act = do
514+
withTemporaryDataAndCacheDirectory $ \tmpRoot -> do
515+
fs <- FS.materialiseVFT tmpRoot tree
516+
act fs
517+
518+
-- | Run an action in a temporary directory.
519+
-- Sets the 'XDG_CACHE_HOME' environment variable to a temporary directory as well.
520+
--
521+
-- This sets up a temporary directory for HLS tests to run.
522+
-- Typically, HLS tests copy their test data into the directory and then launch
523+
-- the HLS session in that directory.
524+
-- This makes sure that the tests are run in isolation, which is good for correctness
525+
-- but also important to have fast tests.
526+
--
527+
-- For improved isolation, we also make sure the 'XDG_CACHE_HOME' environment
528+
-- variable points to a temporary directory. So, we never share interface files
529+
-- or the 'hiedb' across tests.
530+
withTemporaryDataAndCacheDirectory :: (FilePath -> IO a) -> IO a
531+
withTemporaryDataAndCacheDirectory act = withLock lockForTempDirs $ do
512532
testRoot <- setupTestEnvironment
513533
helperRecorder <- hlsHelperTestRecorder
514534
-- Do not clean up the temporary directory if this variable is set to anything but '0'.
515535
-- Aids debugging.
516536
cleanupTempDir <- lookupEnv "HLS_TEST_HARNESS_NO_TESTDIR_CLEANUP"
517537
let runTestInDir action = case cleanupTempDir of
518538
Just val | val /= "0" -> do
519-
(tempDir, _) <- newTempDirWithin testRoot
520-
a <- action tempDir
539+
(tempDir, cacheHome, _) <- setupTemporaryTestDirectories testRoot
540+
a <- withTempCacheHome cacheHome (action tempDir)
521541
logWith helperRecorder Debug LogNoCleanup
522542
pure a
523543

524544
_ -> do
525-
(tempDir, cleanup) <- newTempDirWithin testRoot
526-
a <- action tempDir `finally` cleanup
545+
(tempDir, cacheHome, cleanup) <- setupTemporaryTestDirectories testRoot
546+
a <- withTempCacheHome cacheHome (action tempDir) `finally` cleanup
527547
logWith helperRecorder Debug LogCleanup
528548
pure a
529549
runTestInDir $ \tmpDir' -> do
530550
-- we canonicalize the path, so that we do not need to do
531-
-- cannibalization during the test when we compare two paths
551+
-- canonicalization during the test when we compare two paths
532552
tmpDir <- canonicalizePath tmpDir'
533553
logWith helperRecorder Info $ LogTestDir tmpDir
534-
fs <- FS.materialiseVFT tmpDir tree
535-
act fs
554+
act tmpDir
555+
where
556+
cache_home_var = "XDG_CACHE_HOME"
557+
-- Set the dir for "XDG_CACHE_HOME".
558+
-- When the operation finished, make sure the old value is restored.
559+
withTempCacheHome tempCacheHomeDir act =
560+
bracket
561+
(do
562+
old_cache_home <- lookupEnv cache_home_var
563+
setEnv cache_home_var tempCacheHomeDir
564+
pure old_cache_home)
565+
(\old_cache_home ->
566+
maybe (pure ()) (setEnv cache_home_var) old_cache_home
567+
)
568+
(\_ -> act)
569+
570+
-- Set up a temporary directory for the test files and one for the 'XDG_CACHE_HOME'.
571+
-- The 'XDG_CACHE_HOME' is important for independent test runs, i.e. completely empty
572+
-- caches.
573+
setupTemporaryTestDirectories testRoot = do
574+
(tempTestCaseDir, cleanup1) <- newTempDirWithin testRoot
575+
(tempCacheHomeDir, cleanup2) <- newTempDirWithin testRoot
576+
pure (tempTestCaseDir, tempCacheHomeDir, cleanup1 >> cleanup2)
536577

537578
runSessionWithServer :: Pretty b => Config -> PluginTestDescriptor b -> FilePath -> Session a -> IO a
538579
runSessionWithServer config plugin fp act =
@@ -565,17 +606,11 @@ instance Default (TestConfig b) where
565606
-- It returns the root to the testing directory that tests should use.
566607
-- This directory is not fully cleaned between reruns.
567608
-- However, it is totally safe to delete the directory between runs.
568-
--
569-
-- Additionally, this overwrites the 'XDG_CACHE_HOME' variable to isolate
570-
-- the tests from existing caches. 'hie-bios' and 'ghcide' honour the
571-
-- 'XDG_CACHE_HOME' environment variable and generate their caches there.
572609
setupTestEnvironment :: IO FilePath
573610
setupTestEnvironment = do
574611
tmpDirRoot <- getTemporaryDirectory
575612
let testRoot = tmpDirRoot </> "hls-test-root"
576-
testCacheDir = testRoot </> ".cache"
577-
createDirectoryIfMissing True testCacheDir
578-
setEnv "XDG_CACHE_HOME" testCacheDir
613+
createDirectoryIfMissing True testRoot
579614
pure testRoot
580615

581616
goldenWithHaskellDocFormatter
@@ -692,7 +727,6 @@ lockForTempDirs = unsafePerformIO newLock
692727
data TestConfig b = TestConfig
693728
{
694729
testDirLocation :: Either FilePath VirtualFileTree
695-
-- ^ Client capabilities
696730
-- ^ The file tree to use for the test, either a directory or a virtual file tree
697731
-- if using a virtual file tree,
698732
-- Creates a temporary directory, and materializes the VirtualFileTree
@@ -747,8 +781,20 @@ wrapClientLogger logger = do
747781
return (lspLogRecorder <> logger, cb1)
748782

749783
-- | Host a server, and run a test session on it.
750-
-- For setting custom timeout, set the environment variable 'LSP_TIMEOUT'
751-
-- * LSP_TIMEOUT=10 cabal test
784+
--
785+
-- Environment variables are used to influence logging verbosity, test cleanup and test execution:
786+
--
787+
-- * @LSP_TIMEOUT@: Set a specific test timeout in seconds.
788+
-- * @LSP_TEST_LOG_MESSAGES@: Log the LSP messages between the client and server.
789+
-- * @LSP_TEST_LOG_STDERR@: Log the stderr of the server to the stderr of this process.
790+
-- * @HLS_TEST_HARNESS_STDERR@: Log test setup messages.
791+
--
792+
-- Test specific environment variables:
793+
--
794+
-- * @HLS_TEST_PLUGIN_LOG_STDERR@: Log all messages of the hls plugin under test to stderr.
795+
-- * @HLS_TEST_LOG_STDERR@: Log all HLS messages to stderr.
796+
-- * @HLS_TEST_HARNESS_NO_TESTDIR_CLEANUP@: Don't remove the test directories after test execution.
797+
--
752798
-- For more detail of the test configuration, see 'TestConfig'
753799
runSessionWithTestConfig :: Pretty b => TestConfig b -> (FilePath -> Session a) -> IO a
754800
runSessionWithTestConfig TestConfig{..} session =
@@ -792,8 +838,10 @@ runSessionWithTestConfig TestConfig{..} session =
792838
else f
793839
runSessionInVFS (Left testConfigRoot) act = do
794840
root <- makeAbsolute testConfigRoot
795-
act root
796-
runSessionInVFS (Right vfs) act = runWithLockInTempDir vfs $ \fs -> act (fsRoot fs)
841+
withTemporaryDataAndCacheDirectory (const $ act root)
842+
runSessionInVFS (Right vfs) act =
843+
withVfsTestDataDirectory vfs $ \fs -> do
844+
act (fsRoot fs)
797845
testingArgs prjRoot recorderIde plugins =
798846
let
799847
arguments@Arguments{ argsHlsPlugins, argsIdeOptions, argsLspOptions } = defaultArguments (cmapWithPrio LogIDEMain recorderIde) prjRoot plugins

0 commit comments

Comments
 (0)