Skip to content

Commit 61fd5c4

Browse files
soulomoonfendor
andauthored
[Migrate diagnosticTests] part of #4173 Migrate ghcide tests to hls test utils (#4207)
* [x] migrate diagnosticTests, figure out how to pass `--test-no-kick`. * [x] migrate openCloseTests * [x] Lift a few functions from ghcide-test-utils to hls-test-utils * [x] fixed `deeply nested cyclic module dependency` * [x] modify `runSessionWithServer'` and ghcIde arguments to admit additional a switch for `no-kick`. --------- Co-authored-by: fendor <[email protected]>
1 parent 23005f8 commit 61fd5c4

File tree

17 files changed

+198
-186
lines changed

17 files changed

+198
-186
lines changed

Diff for: ghcide/exe/Main.hs

-5
Original file line numberDiff line numberDiff line change
@@ -124,12 +124,7 @@ main = withTelemetryRecorder $ \telemetryRecorder -> do
124124
, IDEMain.argsHlsPlugins = IDEMain.argsHlsPlugins arguments <> pluginDescToIdePlugins [lspRecorderPlugin]
125125

126126
, IDEMain.argsRules = do
127-
-- install the main and ghcide-plugin rules
128127
mainRule (cmapWithPrio LogRules recorder) def
129-
-- install the kick action, which triggers a typecheck on every
130-
-- Shake database restart, i.e. on every user edit.
131-
unless argsDisableKick $
132-
action kick
133128

134129
, IDEMain.argsThreads = case argsThreads of 0 -> Nothing ; i -> Just (fromIntegral i)
135130

Diff for: ghcide/src/Development/IDE/Main.hs

+10-2
Original file line numberDiff line numberDiff line change
@@ -223,13 +223,14 @@ data Arguments = Arguments
223223
, argsHandleOut :: IO Handle
224224
, argsThreads :: Maybe Natural
225225
, argsMonitoring :: IO Monitoring
226+
, argsDisableKick :: Bool -- ^ flag to disable kick used for testing
226227
}
227228

228229
defaultArguments :: Recorder (WithPriority Log) -> IdePlugins IdeState -> Arguments
229230
defaultArguments recorder plugins = Arguments
230231
{ argsProjectRoot = Nothing
231232
, argCommand = LSP
232-
, argsRules = mainRule (cmapWithPrio LogRules recorder) def >> action kick
233+
, argsRules = mainRule (cmapWithPrio LogRules recorder) def
233234
, argsGhcidePlugin = mempty
234235
, argsHlsPlugins = pluginDescToIdePlugins (GhcIde.descriptors (cmapWithPrio LogGhcIde recorder)) <> plugins
235236
, argsSessionLoadingOptions = def
@@ -258,6 +259,7 @@ defaultArguments recorder plugins = Arguments
258259
putStr " " >> hFlush stdout
259260
return newStdout
260261
, argsMonitoring = OpenTelemetry.monitoring
262+
, argsDisableKick = False
261263
}
262264

263265

@@ -293,7 +295,13 @@ defaultMain recorder Arguments{..} = withHeapStats (cmapWithPrio LogHeapStats re
293295
plugins = hlsPlugin <> argsGhcidePlugin
294296
options = argsLspOptions { LSP.optExecuteCommandCommands = LSP.optExecuteCommandCommands argsLspOptions <> Just hlsCommands }
295297
argsParseConfig = getConfigFromNotification argsHlsPlugins
296-
rules = argsRules >> pluginRules plugins
298+
rules = do
299+
argsRules
300+
unless argsDisableKick $ action kick
301+
pluginRules plugins
302+
-- install the main and ghcide-plugin rules
303+
-- install the kick action, which triggers a typecheck on every
304+
-- Shake database restart, i.e. on every user edit.
297305

298306
debouncer <- argsDebouncer
299307
inH <- argsHandleIn

Diff for: ghcide/test/exe/ClientSettingsTests.hs

+1
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ import Language.LSP.Protocol.Types hiding
1414
SemanticTokensEdit (..),
1515
mkRange)
1616
import Language.LSP.Test
17+
import Test.Hls (waitForProgressDone)
1718
import Test.Tasty
1819
import TestUtils
1920

Diff for: ghcide/test/exe/CodeLensTests.hs

+1
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ import Language.LSP.Protocol.Types hiding
1818
SemanticTokensEdit (..),
1919
mkRange)
2020
import Language.LSP.Test
21+
import Test.Hls (waitForProgressDone)
2122
import Test.Tasty
2223
import Test.Tasty.HUnit
2324
import TestUtils

Diff for: ghcide/test/exe/CompletionTests.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -49,10 +49,10 @@ tests
4949
]
5050

5151
testSessionEmpty :: TestName -> Session () -> TestTree
52-
testSessionEmpty name = testCase name . runWithDummyPlugin (mkIdeTestFs [FS.directCradle ["A.hs"]])
52+
testSessionEmpty name = testWithDummyPlugin name (mkIdeTestFs [FS.directCradle ["A.hs"]])
5353

5454
testSessionEmptyWithCradle :: TestName -> T.Text -> Session () -> TestTree
55-
testSessionEmptyWithCradle name cradle = testCase name . runWithDummyPlugin (mkIdeTestFs [file "hie.yaml" (text cradle)])
55+
testSessionEmptyWithCradle name cradle = testWithDummyPlugin name (mkIdeTestFs [file "hie.yaml" (text cradle)])
5656

5757
testSessionSingleFile :: TestName -> FilePath -> T.Text -> Session () -> TestTree
5858
testSessionSingleFile testName fp txt session =

Diff for: ghcide/test/exe/Config.hs

+39-11
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,37 @@
11
{-# LANGUAGE PatternSynonyms #-}
22

3-
module Config where
4-
3+
module Config(
4+
-- * basic config for ghcIde testing
5+
mkIdeTestFs
6+
, dummyPlugin
7+
8+
-- * runners for testing with dummy plugin
9+
, runWithDummyPlugin
10+
, testWithDummyPlugin
11+
, testWithDummyPluginEmpty
12+
, testWithDummyPlugin'
13+
, testWithDummyPluginEmpty'
14+
, testWithDummyPluginAndCap'
15+
, runWithExtraFiles
16+
, testWithExtraFiles
17+
18+
-- * utilities for testing definition and hover
19+
, Expect(..)
20+
, pattern R
21+
, mkR
22+
, checkDefs
23+
, mkL
24+
, lspTestCaps
25+
, lspTestCapsNoFileWatches
26+
) where
27+
28+
import Control.Lens.Setter ((.~))
529
import Data.Foldable (traverse_)
30+
import Data.Function ((&))
631
import qualified Data.Text as T
732
import Development.IDE.Test (canonicalizeUri)
833
import Ide.Types (defaultPluginDescriptor)
34+
import qualified Language.LSP.Protocol.Lens as L
935
import Language.LSP.Protocol.Types (Null (..))
1036
import System.FilePath ((</>))
1137
import Test.Hls
@@ -28,22 +54,18 @@ runWithDummyPlugin = runSessionWithServerInTmpDir def dummyPlugin
2854
runWithDummyPlugin' :: FS.VirtualFileTree -> (FileSystem -> Session a) -> IO a
2955
runWithDummyPlugin' = runSessionWithServerInTmpDirCont' def dummyPlugin
3056

31-
runWithDummyPluginAndCap :: ClientCapabilities -> Session () -> IO ()
32-
runWithDummyPluginAndCap cap = runSessionWithServerAndCapsInTmpDir def dummyPlugin cap (mkIdeTestFs [])
57+
runWithDummyPluginAndCap' :: ClientCapabilities -> (FileSystem -> Session ()) -> IO ()
58+
runWithDummyPluginAndCap' cap = runSessionWithServerAndCapsInTmpDirCont def dummyPlugin cap (mkIdeTestFs [])
3359

34-
testWithDummyPluginAndCap :: String -> ClientCapabilities -> Session () -> TestTree
35-
testWithDummyPluginAndCap caseName cap = testCase caseName . runWithDummyPluginAndCap cap
60+
testWithDummyPluginAndCap' :: String -> ClientCapabilities -> (FileSystem -> Session ()) -> TestTree
61+
testWithDummyPluginAndCap' caseName cap = testCase caseName . runWithDummyPluginAndCap' cap
3662

37-
-- testSessionWithCorePlugin ::(TestRunner cont ()) => TestName -> FS.VirtualFileTree -> cont -> TestTree
3863
testWithDummyPlugin :: String -> FS.VirtualFileTree -> Session () -> TestTree
39-
testWithDummyPlugin caseName vfs = testCase caseName . runWithDummyPlugin vfs
64+
testWithDummyPlugin caseName vfs = testWithDummyPlugin' caseName vfs . const
4065

4166
testWithDummyPlugin' :: String -> FS.VirtualFileTree -> (FileSystem -> Session ()) -> TestTree
4267
testWithDummyPlugin' caseName vfs = testCase caseName . runWithDummyPlugin' vfs
4368

44-
runWithDummyPluginEmpty :: Session a -> IO a
45-
runWithDummyPluginEmpty = runWithDummyPlugin $ mkIdeTestFs []
46-
4769
testWithDummyPluginEmpty :: String -> Session () -> TestTree
4870
testWithDummyPluginEmpty caseName = testWithDummyPlugin caseName $ mkIdeTestFs []
4971

@@ -114,3 +136,9 @@ defToLocation (InL (Definition (InL l))) = [l]
114136
defToLocation (InL (Definition (InR ls))) = ls
115137
defToLocation (InR (InL defLink)) = (\(DefinitionLink LocationLink{_targetUri,_targetRange}) -> Location _targetUri _targetRange) <$> defLink
116138
defToLocation (InR (InR Null)) = []
139+
140+
lspTestCaps :: ClientCapabilities
141+
lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities (Just True) Nothing Nothing }
142+
143+
lspTestCapsNoFileWatches :: ClientCapabilities
144+
lspTestCapsNoFileWatches = lspTestCaps & L.workspace . traverse . L.didChangeWatchedFiles .~ Nothing

0 commit comments

Comments
 (0)