Skip to content

Commit 25e953d

Browse files
authored
Introduce declarative test project definition for plugin tests (#3767)
* Introduce declarative test project definition Test data is currently often in some 'testdata' directory in 'test/'. It can easily get quite messy with many files. Especially since 'lsp-test' should load only exactly what is needed to speed up tests and avoid test flakiness. A subdirectory per test file is quite overkill and increases the required boilerplate to write tests. Thus, we introduce a declarative test project specification that runs lsp-test in a temporary directory. The first advantage is that we can load only exactly what we need, and create more accurate projects. * Migrate hls-eval-plugin to new FileSystem infrastructure Set ups a test project per file in a temporary directory. Speeds up test cases quite a when no cabal invocation is required or desired. Additionally, reduces flakiness since HLS often loads only a single file then. Proof of concept s.t. other flaky plugin test suites can be migrated later as well.
1 parent 663c0e7 commit 25e953d

File tree

13 files changed

+516
-72
lines changed

13 files changed

+516
-72
lines changed

hls-test-utils/hls-test-utils.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ library
2828
exposed-modules:
2929
Test.Hls
3030
Test.Hls.Util
31+
Test.Hls.FileSystem
3132

3233
hs-source-dirs: src
3334
build-depends:

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

+213-5
Original file line numberDiff line numberDiff line change
@@ -21,15 +21,22 @@ module Test.Hls
2121
defaultTestRunner,
2222
goldenGitDiff,
2323
goldenWithHaskellDoc,
24+
goldenWithHaskellDocInTmpDir,
2425
goldenWithHaskellAndCaps,
26+
goldenWithHaskellAndCapsInTmpDir,
2527
goldenWithCabalDoc,
2628
goldenWithHaskellDocFormatter,
29+
goldenWithHaskellDocFormatterInTmpDir,
2730
goldenWithCabalDocFormatter,
31+
goldenWithCabalDocFormatterInTmpDir,
2832
def,
2933
-- * Running HLS for integration tests
3034
runSessionWithServer,
3135
runSessionWithServerAndCaps,
36+
runSessionWithServerInTmpDir,
37+
runSessionWithServerAndCapsInTmpDir,
3238
runSessionWithServer',
39+
runSessionWithServerInTmpDir',
3340
-- * Helpful re-exports
3441
PluginDescriptor,
3542
IdeState,
@@ -90,11 +97,13 @@ import GHC.Stack (emptyCallStack)
9097
import GHC.TypeLits
9198
import Ide.Logger (Doc, Logger (Logger),
9299
Pretty (pretty),
93-
Priority (Debug),
100+
Priority (..),
94101
Recorder (Recorder, logger_),
95102
WithPriority (WithPriority, priority),
96103
cfilter, cmapWithPrio,
97-
makeDefaultStderrRecorder)
104+
logWith,
105+
makeDefaultStderrRecorder,
106+
(<+>))
98107
import Ide.Types
99108
import Language.LSP.Protocol.Capabilities
100109
import Language.LSP.Protocol.Message
@@ -105,9 +114,12 @@ import System.Directory (getCurrentDirectory,
105114
setCurrentDirectory)
106115
import System.Environment (lookupEnv)
107116
import System.FilePath
117+
import System.IO.Extra (newTempDir, withTempDir)
108118
import System.IO.Unsafe (unsafePerformIO)
109119
import System.Process.Extra (createPipe)
110120
import System.Time.Extra
121+
import qualified Test.Hls.FileSystem as FS
122+
import Test.Hls.FileSystem
111123
import Test.Hls.Util
112124
import Test.Tasty hiding (Timeout)
113125
import Test.Tasty.ExpectedFailure
@@ -116,11 +128,26 @@ import Test.Tasty.HUnit
116128
import Test.Tasty.Ingredients.Rerun
117129
import Test.Tasty.Runners (NumThreads (..))
118130

119-
newtype Log = LogIDEMain IDEMain.Log
131+
data Log
132+
= LogIDEMain IDEMain.Log
133+
| LogTestHarness LogTestHarness
120134

121135
instance Pretty Log where
122136
pretty = \case
123-
LogIDEMain log -> pretty log
137+
LogIDEMain log -> pretty log
138+
LogTestHarness log -> pretty log
139+
140+
data LogTestHarness
141+
= LogTestDir FilePath
142+
| LogCleanup
143+
| LogNoCleanup
144+
145+
146+
instance Pretty LogTestHarness where
147+
pretty = \case
148+
LogTestDir dir -> "Test Project located in directory:" <+> pretty dir
149+
LogCleanup -> "Cleaned up temporary directory"
150+
LogNoCleanup -> "No cleanup of temporary directory"
124151

125152
-- | Run 'defaultMainWithRerun', limiting each single test case running at most 10 minutes
126153
defaultTestRunner :: TestTree -> IO ()
@@ -145,6 +172,19 @@ goldenWithHaskellDoc
145172
-> TestTree
146173
goldenWithHaskellDoc = goldenWithDoc "haskell"
147174

175+
goldenWithHaskellDocInTmpDir
176+
:: Pretty b
177+
=> Config
178+
-> PluginTestDescriptor b
179+
-> TestName
180+
-> VirtualFileTree
181+
-> FilePath
182+
-> FilePath
183+
-> FilePath
184+
-> (TextDocumentIdentifier -> Session ())
185+
-> TestTree
186+
goldenWithHaskellDocInTmpDir = goldenWithDocInTmpDir "haskell"
187+
148188
goldenWithHaskellAndCaps
149189
:: Pretty b
150190
=> Config
@@ -167,6 +207,28 @@ goldenWithHaskellAndCaps config clientCaps plugin title testDataDir path desc ex
167207
act doc
168208
documentContents doc
169209

210+
goldenWithHaskellAndCapsInTmpDir
211+
:: Pretty b
212+
=> Config
213+
-> ClientCapabilities
214+
-> PluginTestDescriptor b
215+
-> TestName
216+
-> VirtualFileTree
217+
-> FilePath
218+
-> FilePath
219+
-> FilePath
220+
-> (TextDocumentIdentifier -> Session ())
221+
-> TestTree
222+
goldenWithHaskellAndCapsInTmpDir config clientCaps plugin title tree path desc ext act =
223+
goldenGitDiff title (vftOriginalRoot tree </> path <.> desc <.> ext)
224+
$ runSessionWithServerAndCapsInTmpDir config plugin clientCaps tree
225+
$ TL.encodeUtf8 . TL.fromStrict
226+
<$> do
227+
doc <- openDoc (path <.> ext) "haskell"
228+
void waitForBuildQueue
229+
act doc
230+
documentContents doc
231+
170232
goldenWithCabalDoc
171233
:: Pretty b
172234
=> Config
@@ -202,6 +264,28 @@ goldenWithDoc fileType config plugin title testDataDir path desc ext act =
202264
act doc
203265
documentContents doc
204266

267+
goldenWithDocInTmpDir
268+
:: Pretty b
269+
=> T.Text
270+
-> Config
271+
-> PluginTestDescriptor b
272+
-> TestName
273+
-> VirtualFileTree
274+
-> FilePath
275+
-> FilePath
276+
-> FilePath
277+
-> (TextDocumentIdentifier -> Session ())
278+
-> TestTree
279+
goldenWithDocInTmpDir fileType config plugin title tree path desc ext act =
280+
goldenGitDiff title (vftOriginalRoot tree </> path <.> desc <.> ext)
281+
$ runSessionWithServerInTmpDir config plugin tree
282+
$ TL.encodeUtf8 . TL.fromStrict
283+
<$> do
284+
doc <- openDoc (path <.> ext) fileType
285+
void waitForBuildQueue
286+
act doc
287+
documentContents doc
288+
205289
-- ------------------------------------------------------------
206290
-- Helper function for initialising plugins under test
207291
-- ------------------------------------------------------------
@@ -298,6 +382,76 @@ runSessionWithServerAndCaps config plugin caps fp act = do
298382
recorder <- pluginTestRecorder
299383
runSessionWithServer' (plugin recorder) config def caps fp act
300384

385+
runSessionWithServerInTmpDir :: Pretty b => Config -> PluginTestDescriptor b -> VirtualFileTree -> Session a -> IO a
386+
runSessionWithServerInTmpDir config plugin tree act = do
387+
recorder <- pluginTestRecorder
388+
runSessionWithServerInTmpDir' (plugin recorder) config def fullCaps tree act
389+
390+
runSessionWithServerAndCapsInTmpDir :: Pretty b => Config -> PluginTestDescriptor b -> ClientCapabilities -> VirtualFileTree -> Session a -> IO a
391+
runSessionWithServerAndCapsInTmpDir config plugin caps tree act = do
392+
recorder <- pluginTestRecorder
393+
runSessionWithServerInTmpDir' (plugin recorder) config def caps tree act
394+
395+
-- | Host a server, and run a test session on it.
396+
--
397+
-- Creates a temporary directory, and materializes the VirtualFileTree
398+
-- in the temporary directory.
399+
--
400+
-- To debug test cases and verify the file system is correctly set up,
401+
-- you should set the environment variable 'HLS_TEST_HARNESS_NO_TESTDIR_CLEANUP=1'.
402+
-- Further, we log the temporary directory location on startup. To view
403+
-- the logs, set the environment variable 'HLS_TEST_HARNESS_STDERR=1'.
404+
--
405+
-- Example invocation to debug test cases:
406+
--
407+
-- @
408+
-- HLS_TEST_HARNESS_NO_TESTDIR_CLEANUP=1 HLS_TEST_HARNESS_STDERR=1 cabal test <plugin-name>
409+
-- @
410+
--
411+
-- Don't forget to use 'TASTY_PATTERN' to debug only a subset of tests.
412+
--
413+
-- For plugin test logs, look at the documentation of 'mkPluginTestDescriptor'.
414+
--
415+
-- Note: cwd will be shifted into a temporary directory in @Session a@
416+
runSessionWithServerInTmpDir' ::
417+
-- | Plugins to load on the server.
418+
--
419+
-- For improved logging, make sure these plugins have been initalised with
420+
-- the recorder produced by @pluginTestRecorder@.
421+
IdePlugins IdeState ->
422+
-- | lsp config for the server
423+
Config ->
424+
-- | config for the test session
425+
SessionConfig ->
426+
ClientCapabilities ->
427+
VirtualFileTree ->
428+
Session a ->
429+
IO a
430+
runSessionWithServerInTmpDir' plugins conf sessConf caps tree act = withLock lockForTempDirs $ do
431+
(recorder, _) <- initialiseTestRecorder
432+
["LSP_TEST_LOG_STDERR", "HLS_TEST_HARNESS_STDERR", "HLS_TEST_LOG_STDERR"]
433+
434+
-- Do not clean up the temporary directory if this variable is set to anything but '0'.
435+
-- Aids debugging.
436+
cleanupTempDir <- lookupEnv "HLS_TEST_HARNESS_NO_TESTDIR_CLEANUP"
437+
let runTestInDir = case cleanupTempDir of
438+
Just val
439+
| val /= "0" -> \action -> do
440+
(tempDir, _) <- newTempDir
441+
a <- action tempDir
442+
logWith recorder Debug $ LogNoCleanup
443+
pure a
444+
445+
_ -> \action -> do
446+
a <- withTempDir action
447+
logWith recorder Debug $ LogCleanup
448+
pure a
449+
450+
runTestInDir $ \tmpDir -> do
451+
logWith recorder Info $ LogTestDir tmpDir
452+
_fs <- FS.materialiseVFT tmpDir tree
453+
runSessionWithServer' plugins conf sessConf caps tmpDir act
454+
301455
goldenWithHaskellDocFormatter
302456
:: Pretty b
303457
=> Config
@@ -346,6 +500,54 @@ goldenWithCabalDocFormatter config plugin formatter conf title testDataDir path
346500
act doc
347501
documentContents doc
348502

503+
goldenWithHaskellDocFormatterInTmpDir
504+
:: Pretty b
505+
=> Config
506+
-> PluginTestDescriptor b -- ^ Formatter plugin to be used
507+
-> String -- ^ Name of the formatter to be used
508+
-> PluginConfig
509+
-> TestName -- ^ Title of the test
510+
-> VirtualFileTree -- ^ Virtual representation of the test project
511+
-> FilePath -- ^ Path to the testdata to be used within the directory
512+
-> FilePath -- ^ Additional suffix to be appended to the output file
513+
-> FilePath -- ^ Extension of the output file
514+
-> (TextDocumentIdentifier -> Session ())
515+
-> TestTree
516+
goldenWithHaskellDocFormatterInTmpDir config plugin formatter conf title tree path desc ext act =
517+
let config' = config { formattingProvider = T.pack formatter , plugins = M.singleton (PluginId $ T.pack formatter) conf }
518+
in goldenGitDiff title (vftOriginalRoot tree </> path <.> desc <.> ext)
519+
$ runSessionWithServerInTmpDir config' plugin tree
520+
$ TL.encodeUtf8 . TL.fromStrict
521+
<$> do
522+
doc <- openDoc (path <.> ext) "haskell"
523+
void waitForBuildQueue
524+
act doc
525+
documentContents doc
526+
527+
goldenWithCabalDocFormatterInTmpDir
528+
:: Pretty b
529+
=> Config
530+
-> PluginTestDescriptor b -- ^ Formatter plugin to be used
531+
-> String -- ^ Name of the formatter to be used
532+
-> PluginConfig
533+
-> TestName -- ^ Title of the test
534+
-> VirtualFileTree -- ^ Virtual representation of the test project
535+
-> FilePath -- ^ Path to the testdata to be used within the directory
536+
-> FilePath -- ^ Additional suffix to be appended to the output file
537+
-> FilePath -- ^ Extension of the output file
538+
-> (TextDocumentIdentifier -> Session ())
539+
-> TestTree
540+
goldenWithCabalDocFormatterInTmpDir config plugin formatter conf title tree path desc ext act =
541+
let config' = config { cabalFormattingProvider = T.pack formatter , plugins = M.singleton (PluginId $ T.pack formatter) conf }
542+
in goldenGitDiff title (vftOriginalRoot tree </> path <.> desc <.> ext)
543+
$ runSessionWithServerInTmpDir config' plugin tree
544+
$ TL.encodeUtf8 . TL.fromStrict
545+
<$> do
546+
doc <- openDoc (path <.> ext) "cabal"
547+
void waitForBuildQueue
548+
act doc
549+
documentContents doc
550+
349551
-- | Restore cwd after running an action
350552
keepCurrentDirectory :: IO a -> IO a
351553
keepCurrentDirectory = bracket getCurrentDirectory setCurrentDirectory . const
@@ -355,6 +557,12 @@ keepCurrentDirectory = bracket getCurrentDirectory setCurrentDirectory . const
355557
lock :: Lock
356558
lock = unsafePerformIO newLock
357559

560+
561+
{-# NOINLINE lockForTempDirs #-}
562+
-- | Never run in parallel
563+
lockForTempDirs :: Lock
564+
lockForTempDirs = unsafePerformIO newLock
565+
358566
-- | Host a server, and run a test session on it
359567
-- Note: cwd will be shifted into @root@ in @Session a@
360568
runSessionWithServer' ::
@@ -371,7 +579,7 @@ runSessionWithServer' ::
371579
FilePath ->
372580
Session a ->
373581
IO a
374-
runSessionWithServer' plugins conf sconf caps root s = withLock lock $ keepCurrentDirectory $ do
582+
runSessionWithServer' plugins conf sconf caps root s = withLock lock $ keepCurrentDirectory $ do
375583
(inR, inW) <- createPipe
376584
(outR, outW) <- createPipe
377585

0 commit comments

Comments
 (0)