@@ -21,15 +21,22 @@ module Test.Hls
21
21
defaultTestRunner ,
22
22
goldenGitDiff ,
23
23
goldenWithHaskellDoc ,
24
+ goldenWithHaskellDocInTmpDir ,
24
25
goldenWithHaskellAndCaps ,
26
+ goldenWithHaskellAndCapsInTmpDir ,
25
27
goldenWithCabalDoc ,
26
28
goldenWithHaskellDocFormatter ,
29
+ goldenWithHaskellDocFormatterInTmpDir ,
27
30
goldenWithCabalDocFormatter ,
31
+ goldenWithCabalDocFormatterInTmpDir ,
28
32
def ,
29
33
-- * Running HLS for integration tests
30
34
runSessionWithServer ,
31
35
runSessionWithServerAndCaps ,
36
+ runSessionWithServerInTmpDir ,
37
+ runSessionWithServerAndCapsInTmpDir ,
32
38
runSessionWithServer' ,
39
+ runSessionWithServerInTmpDir' ,
33
40
-- * Helpful re-exports
34
41
PluginDescriptor ,
35
42
IdeState ,
@@ -90,11 +97,13 @@ import GHC.Stack (emptyCallStack)
90
97
import GHC.TypeLits
91
98
import Ide.Logger (Doc , Logger (Logger ),
92
99
Pretty (pretty ),
93
- Priority (Debug ),
100
+ Priority (.. ),
94
101
Recorder (Recorder , logger_ ),
95
102
WithPriority (WithPriority , priority ),
96
103
cfilter , cmapWithPrio ,
97
- makeDefaultStderrRecorder )
104
+ logWith ,
105
+ makeDefaultStderrRecorder ,
106
+ (<+>) )
98
107
import Ide.Types
99
108
import Language.LSP.Protocol.Capabilities
100
109
import Language.LSP.Protocol.Message
@@ -105,9 +114,12 @@ import System.Directory (getCurrentDirectory,
105
114
setCurrentDirectory )
106
115
import System.Environment (lookupEnv )
107
116
import System.FilePath
117
+ import System.IO.Extra (newTempDir , withTempDir )
108
118
import System.IO.Unsafe (unsafePerformIO )
109
119
import System.Process.Extra (createPipe )
110
120
import System.Time.Extra
121
+ import qualified Test.Hls.FileSystem as FS
122
+ import Test.Hls.FileSystem
111
123
import Test.Hls.Util
112
124
import Test.Tasty hiding (Timeout )
113
125
import Test.Tasty.ExpectedFailure
@@ -116,11 +128,26 @@ import Test.Tasty.HUnit
116
128
import Test.Tasty.Ingredients.Rerun
117
129
import Test.Tasty.Runners (NumThreads (.. ))
118
130
119
- newtype Log = LogIDEMain IDEMain. Log
131
+ data Log
132
+ = LogIDEMain IDEMain. Log
133
+ | LogTestHarness LogTestHarness
120
134
121
135
instance Pretty Log where
122
136
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"
124
151
125
152
-- | Run 'defaultMainWithRerun', limiting each single test case running at most 10 minutes
126
153
defaultTestRunner :: TestTree -> IO ()
@@ -145,6 +172,19 @@ goldenWithHaskellDoc
145
172
-> TestTree
146
173
goldenWithHaskellDoc = goldenWithDoc " haskell"
147
174
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
+
148
188
goldenWithHaskellAndCaps
149
189
:: Pretty b
150
190
=> Config
@@ -167,6 +207,28 @@ goldenWithHaskellAndCaps config clientCaps plugin title testDataDir path desc ex
167
207
act doc
168
208
documentContents doc
169
209
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
+
170
232
goldenWithCabalDoc
171
233
:: Pretty b
172
234
=> Config
@@ -202,6 +264,28 @@ goldenWithDoc fileType config plugin title testDataDir path desc ext act =
202
264
act doc
203
265
documentContents doc
204
266
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
+
205
289
-- ------------------------------------------------------------
206
290
-- Helper function for initialising plugins under test
207
291
-- ------------------------------------------------------------
@@ -298,6 +382,76 @@ runSessionWithServerAndCaps config plugin caps fp act = do
298
382
recorder <- pluginTestRecorder
299
383
runSessionWithServer' (plugin recorder) config def caps fp act
300
384
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
+
301
455
goldenWithHaskellDocFormatter
302
456
:: Pretty b
303
457
=> Config
@@ -346,6 +500,54 @@ goldenWithCabalDocFormatter config plugin formatter conf title testDataDir path
346
500
act doc
347
501
documentContents doc
348
502
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
+
349
551
-- | Restore cwd after running an action
350
552
keepCurrentDirectory :: IO a -> IO a
351
553
keepCurrentDirectory = bracket getCurrentDirectory setCurrentDirectory . const
@@ -355,6 +557,12 @@ keepCurrentDirectory = bracket getCurrentDirectory setCurrentDirectory . const
355
557
lock :: Lock
356
558
lock = unsafePerformIO newLock
357
559
560
+
561
+ {-# NOINLINE lockForTempDirs #-}
562
+ -- | Never run in parallel
563
+ lockForTempDirs :: Lock
564
+ lockForTempDirs = unsafePerformIO newLock
565
+
358
566
-- | Host a server, and run a test session on it
359
567
-- Note: cwd will be shifted into @root@ in @Session a@
360
568
runSessionWithServer' ::
@@ -371,7 +579,7 @@ runSessionWithServer' ::
371
579
FilePath ->
372
580
Session a ->
373
581
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
375
583
(inR, inW) <- createPipe
376
584
(outR, outW) <- createPipe
377
585
0 commit comments