Skip to content

Commit aeb57a8

Browse files
fendormergify[bot]
andauthored
Introduce common code for Recorders in Plugin Tests (#3347)
* Add generic test plugin recorder initialisation * Migrate some plugins to the new test plugin recorder structure * Introduce improved Test Logging Infrastructure Every plugin should use the new functions. This way, we can guarantee predictable logging behaviour for tests. Most notably, we now have a single control point, for co-log style logging, how to write logs to stderr, and how to write logs for server and plugin at the same time. * HlsPlugins: Make sure every plugin is imported qualified * hls-cabal-plugin: Unify logging infrastructure * hls-cabal-fmt-plugin: Unify logging infrastructure * hls-alternate-number-format-plugin: Unify logging infrastructure * hls-brittany-plugin: Unify logging infrastructure * hls-call-hierarchy-plugin: Unify logging infrastructure * hls-change-type-signature-plugin: Unify logging infrastructure * hls-class-plugin: Unify logging infrastructure * hls-code-range-plugin: Unify logging infrastructure * hls-eval-plugin: Unify logging infrastructure * hls-explicit-fixity-plugin: Unify logging infrastructure * hls-explicit-imports-plugin: Unify logging infrastructure * hls-explicit-record-fields-plugin: Unify logging infrastructure * hls-floskell-plugin: Unify logging infrastructure * hls-fourmolu-plugin: Unify logging infrastructure * hls-gadt-plugin: Unify logging infrastructure * hls-haddock-comments-plugin: Unify logging infrastructure * hls-hlint-plugin: Unify logging infrastructure * hls-module-name-plugin: Unify logging infrastructure * hls-ormolu-plugin: Unify logging infrastructure * hls-pragmas-plugin: Unify logging infrastructure * hls-qualify-imported-names-plugin: Unify logging infrastructure * hls-refactor-plugin: Unify logging infrastructure * hls-refine-imports-plugin: Unify logging infrastructure * hls-rename-plugin: Unify logging infrastructure * hls-splice-plugin: Unify logging infrastructure * hls-stan-plugin: Unify logging infrastructure * hls-stylish-haskell-plugin: Unify logging infrastructure * hls-tactics-plugin: Unify logging infrastructure Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 9e5fc88 commit aeb57a8

File tree

41 files changed

+331
-233
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

41 files changed

+331
-233
lines changed

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

Lines changed: 146 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -20,21 +20,35 @@ module Test.Hls
2020
goldenWithHaskellDocFormatter,
2121
goldenWithCabalDocFormatter,
2222
def,
23+
-- * Running HLS for integration tests
2324
runSessionWithServer,
25+
runSessionWithServerAndCaps,
2426
runSessionWithServerFormatter,
2527
runSessionWithCabalServerFormatter,
2628
runSessionWithServer',
27-
waitForProgressDone,
28-
waitForAllProgressDone,
29+
-- * Helpful re-exports
2930
PluginDescriptor,
3031
IdeState,
32+
-- * Assertion helper functions
33+
waitForProgressDone,
34+
waitForAllProgressDone,
3135
waitForBuildQueue,
3236
waitForTypecheck,
3337
waitForAction,
3438
sendConfigurationChanged,
3539
getLastBuildKeys,
3640
waitForKickDone,
3741
waitForKickStart,
42+
-- * Plugin descriptor helper functions for tests
43+
PluginTestDescriptor,
44+
pluginTestRecorder,
45+
mkPluginTestDescriptor,
46+
mkPluginTestDescriptor',
47+
-- * Re-export logger types
48+
-- Avoids slightly annoying ghcide imports when they are unnecessary.
49+
WithPriority(..),
50+
Recorder,
51+
Priority(..),
3852
)
3953
where
4054

@@ -43,6 +57,7 @@ import Control.Concurrent.Async (async, cancel, wait)
4357
import Control.Concurrent.Extra
4458
import Control.Exception.Base
4559
import Control.Monad (guard, unless, void)
60+
import Control.Monad.Extra (forM)
4661
import Control.Monad.IO.Class
4762
import Data.Aeson (Result (Success),
4863
Value (Null), fromJSON,
@@ -62,7 +77,7 @@ import qualified Development.IDE.Main as IDEMain
6277
import Development.IDE.Plugin.Test (TestRequest (GetBuildKeysBuilt, WaitForIdeRule, WaitForShakeQueue),
6378
WaitForIdeRuleResult (ideResultSuccess))
6479
import qualified Development.IDE.Plugin.Test as Test
65-
import Development.IDE.Types.Logger (Logger (Logger),
80+
import Development.IDE.Types.Logger (Doc, Logger (Logger),
6681
Pretty (pretty),
6782
Priority (Debug),
6883
Recorder (Recorder, logger_),
@@ -117,7 +132,8 @@ goldenGitDiff :: TestName -> FilePath -> IO ByteString -> TestTree
117132
goldenGitDiff name = goldenVsStringDiff name gitDiff
118133

119134
goldenWithHaskellDoc
120-
:: PluginDescriptor IdeState
135+
:: Pretty b
136+
=> PluginTestDescriptor b
121137
-> TestName
122138
-> FilePath
123139
-> FilePath
@@ -128,7 +144,8 @@ goldenWithHaskellDoc
128144
goldenWithHaskellDoc = goldenWithDoc "haskell"
129145

130146
goldenWithCabalDoc
131-
:: PluginDescriptor IdeState
147+
:: Pretty b
148+
=> PluginTestDescriptor b
132149
-> TestName
133150
-> FilePath
134151
-> FilePath
@@ -139,8 +156,9 @@ goldenWithCabalDoc
139156
goldenWithCabalDoc = goldenWithDoc "cabal"
140157

141158
goldenWithDoc
142-
:: T.Text
143-
-> PluginDescriptor IdeState
159+
:: Pretty b
160+
=> T.Text
161+
-> PluginTestDescriptor b
144162
-> TestName
145163
-> FilePath
146164
-> FilePath
@@ -158,23 +176,119 @@ goldenWithDoc fileType plugin title testDataDir path desc ext act =
158176
act doc
159177
documentContents doc
160178

179+
-- ------------------------------------------------------------
180+
-- Helper function for initialising plugins under test
181+
-- ------------------------------------------------------------
182+
183+
-- | Plugin under test where a fitting recorder is injected.
184+
type PluginTestDescriptor b = Recorder (WithPriority b) -> PluginDescriptor IdeState
185+
186+
-- | Wrap a plugin you want to test, and inject a fitting recorder as required.
187+
--
188+
-- If you want to write the logs to stderr, run your tests with
189+
-- "HLS_TEST_PLUGIN_LOG_STDERR=1", e.g.
190+
--
191+
-- @
192+
-- HLS_TEST_PLUGIN_LOG_STDERR=1 cabal test <test-suite-of-plugin>
193+
-- @
194+
--
195+
--
196+
-- To write all logs to stderr, including logs of the server, use:
197+
--
198+
-- @
199+
-- HLS_TEST_LOG_STDERR=1 cabal test <test-suite-of-plugin>
200+
-- @
201+
mkPluginTestDescriptor
202+
:: (Recorder (WithPriority b) -> PluginId -> PluginDescriptor IdeState)
203+
-> PluginId
204+
-> PluginTestDescriptor b
205+
mkPluginTestDescriptor pluginDesc plId recorder = pluginDesc recorder plId
206+
207+
-- | Wrap a plugin you want to test.
208+
--
209+
-- Ideally, try to migrate this plugin to co-log logger style architecture.
210+
-- Therefore, you should prefer 'mkPluginTestDescriptor' to this if possible.
211+
mkPluginTestDescriptor'
212+
:: (PluginId -> PluginDescriptor IdeState)
213+
-> PluginId
214+
-> PluginTestDescriptor b
215+
mkPluginTestDescriptor' pluginDesc plId _recorder = pluginDesc plId
216+
217+
-- | Initialise a recorder that can be instructed to write to stderr by
218+
-- setting the environment variable "HLS_TEST_PLUGIN_LOG_STDERR=1" before
219+
-- running the tests.
220+
--
221+
-- On the cli, use for example:
222+
--
223+
-- @
224+
-- HLS_TEST_PLUGIN_LOG_STDERR=1 cabal test <test-suite-of-plugin>
225+
-- @
226+
--
227+
-- To write all logs to stderr, including logs of the server, use:
228+
--
229+
-- @
230+
-- HLS_TEST_LOG_STDERR=1 cabal test <test-suite-of-plugin>
231+
-- @
232+
pluginTestRecorder :: Pretty a => IO (Recorder (WithPriority a))
233+
pluginTestRecorder = do
234+
(recorder, _) <- initialiseTestRecorder ["HLS_TEST_PLUGIN_LOG_STDERR", "HLS_TEST_LOG_STDERR"]
235+
pure recorder
236+
237+
-- | Generic recorder initialisation for plugins and the HLS server for test-cases.
238+
--
239+
-- The created recorder writes to stderr if any of the given environment variables
240+
-- have been set to a value different to @0@.
241+
-- We allow multiple values, to make it possible to define a single environment variable
242+
-- that instructs all recorders in the test-suite to write to stderr.
243+
--
244+
-- We have to return the base logger function for HLS server logging initialisation.
245+
-- See 'runSessionWithServer'' for details.
246+
initialiseTestRecorder :: Pretty a => [String] -> IO (Recorder (WithPriority a), WithPriority (Doc ann) -> IO ())
247+
initialiseTestRecorder envVars = do
248+
docWithPriorityRecorder <- makeDefaultStderrRecorder Nothing Debug
249+
-- There are potentially multiple environment variables that enable this logger
250+
definedEnvVars <- forM envVars (\var -> fromMaybe "0" <$> lookupEnv var)
251+
let logStdErr = any (/= "0") definedEnvVars
252+
253+
docWithFilteredPriorityRecorder =
254+
if logStdErr then cfilter (\WithPriority{ priority } -> priority >= Debug) docWithPriorityRecorder
255+
else mempty
256+
257+
Recorder {logger_} = docWithFilteredPriorityRecorder
258+
259+
pure (cmapWithPrio pretty docWithFilteredPriorityRecorder, logger_)
161260

162-
runSessionWithServer :: PluginDescriptor IdeState -> FilePath -> Session a -> IO a
163-
runSessionWithServer plugin = runSessionWithServer' [plugin] def def fullCaps
261+
-- ------------------------------------------------------------
262+
-- Run an HLS server testing a specific plugin
263+
-- ------------------------------------------------------------
164264

165-
runSessionWithServerFormatter :: PluginDescriptor IdeState -> String -> PluginConfig -> FilePath -> Session a -> IO a
166-
runSessionWithServerFormatter plugin formatter conf =
265+
runSessionWithServer :: Pretty b => PluginTestDescriptor b -> FilePath -> Session a -> IO a
266+
runSessionWithServer plugin fp act = do
267+
recorder <- pluginTestRecorder
268+
runSessionWithServer' [plugin recorder] def def fullCaps fp act
269+
270+
runSessionWithServerAndCaps :: Pretty b => PluginTestDescriptor b -> ClientCapabilities -> FilePath -> Session a -> IO a
271+
runSessionWithServerAndCaps plugin caps fp act = do
272+
recorder <- pluginTestRecorder
273+
runSessionWithServer' [plugin recorder] def def caps fp act
274+
275+
runSessionWithServerFormatter :: Pretty b => PluginTestDescriptor b -> String -> PluginConfig -> FilePath -> Session a -> IO a
276+
runSessionWithServerFormatter plugin formatter conf fp act = do
277+
recorder <- pluginTestRecorder
167278
runSessionWithServer'
168-
[plugin]
279+
[plugin recorder]
169280
def
170281
{ formattingProvider = T.pack formatter
171282
, plugins = M.singleton (T.pack formatter) conf
172283
}
173284
def
174285
fullCaps
286+
fp
287+
act
175288

176289
goldenWithHaskellDocFormatter
177-
:: PluginDescriptor IdeState -- ^ Formatter plugin to be used
290+
:: Pretty b
291+
=> PluginTestDescriptor b -- ^ Formatter plugin to be used
178292
-> String -- ^ Name of the formatter to be used
179293
-> PluginConfig
180294
-> TestName -- ^ Title of the test
@@ -195,7 +309,8 @@ goldenWithHaskellDocFormatter plugin formatter conf title testDataDir path desc
195309
documentContents doc
196310

197311
goldenWithCabalDocFormatter
198-
:: PluginDescriptor IdeState -- ^ Formatter plugin to be used
312+
:: Pretty b
313+
=> PluginTestDescriptor b -- ^ Formatter plugin to be used
199314
-> String -- ^ Name of the formatter to be used
200315
-> PluginConfig
201316
-> TestName -- ^ Title of the test
@@ -215,16 +330,18 @@ goldenWithCabalDocFormatter plugin formatter conf title testDataDir path desc ex
215330
act doc
216331
documentContents doc
217332

218-
runSessionWithCabalServerFormatter :: PluginDescriptor IdeState -> String -> PluginConfig -> FilePath -> Session a -> IO a
219-
runSessionWithCabalServerFormatter plugin formatter conf =
333+
runSessionWithCabalServerFormatter :: Pretty b => PluginTestDescriptor b -> String -> PluginConfig -> FilePath -> Session a -> IO a
334+
runSessionWithCabalServerFormatter plugin formatter conf fp act = do
335+
recorder <- pluginTestRecorder
220336
runSessionWithServer'
221-
[plugin]
337+
[plugin recorder]
222338
def
223339
{ cabalFormattingProvider = T.pack formatter
224340
, plugins = M.singleton (T.pack formatter) conf
225341
}
226342
def
227343
fullCaps
344+
fp act
228345

229346
-- | Restore cwd after running an action
230347
keepCurrentDirectory :: IO a -> IO a
@@ -235,11 +352,13 @@ keepCurrentDirectory = bracket getCurrentDirectory setCurrentDirectory . const
235352
lock :: Lock
236353
lock = unsafePerformIO newLock
237354

238-
239355
-- | Host a server, and run a test session on it
240356
-- Note: cwd will be shifted into @root@ in @Session a@
241357
runSessionWithServer' ::
242-
-- | plugins to load on the server
358+
-- | Plugins to load on the server.
359+
--
360+
-- For improved logging, make sure these plugins have been initalised with
361+
-- the recorder produced by @pluginTestRecorder@.
243362
[PluginDescriptor IdeState] ->
244363
-- | lsp config for the server
245364
Config ->
@@ -253,20 +372,19 @@ runSessionWithServer' plugins conf sconf caps root s = withLock lock $ keepCurre
253372
(inR, inW) <- createPipe
254373
(outR, outW) <- createPipe
255374

256-
docWithPriorityRecorder <- makeDefaultStderrRecorder Nothing Debug
257-
258-
logStdErr <- fromMaybe "0" <$> lookupEnv "LSP_TEST_LOG_STDERR"
375+
-- Allow three environment variables, because "LSP_TEST_LOG_STDERR" has been used before,
376+
-- (thus, backwards compatibility) and "HLS_TEST_SERVER_LOG_STDERR" because it
377+
-- uses a more descriptive name.
378+
-- It is also in better accordance with 'pluginTestRecorder' which uses "HLS_TEST_PLUGIN_LOG_STDERR".
379+
-- At last, "HLS_TEST_LOG_STDERR" is intended to enable all logging for the server and the plugins
380+
-- under test.
381+
(recorder, logger_) <- initialiseTestRecorder
382+
["LSP_TEST_LOG_STDERR", "HLS_TEST_SERVER_LOG_STDERR", "HLS_TEST_LOG_STDERR"]
259383

260384
let
261-
docWithFilteredPriorityRecorder@Recorder{ logger_ } =
262-
if logStdErr == "0" then mempty
263-
else cfilter (\WithPriority{ priority } -> priority >= Debug) docWithPriorityRecorder
264-
265385
-- exists until old logging style is phased out
266386
logger = Logger $ \p m -> logger_ (WithPriority p emptyCallStack (pretty m))
267387

268-
recorder = cmapWithPrio pretty docWithFilteredPriorityRecorder
269-
270388
arguments@Arguments{ argsHlsPlugins, argsIdeOptions, argsLogger } = defaultArguments (cmapWithPrio LogIDEMain recorder) logger
271389

272390
hlsPlugins =

plugins/hls-alternate-number-format-plugin/test/Main.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,8 +19,8 @@ import Text.Regex.TDFA ((=~))
1919
main :: IO ()
2020
main = defaultTestRunner test
2121

22-
alternateNumberFormatPlugin :: PluginDescriptor IdeState
23-
alternateNumberFormatPlugin = AlternateNumberFormat.descriptor mempty "alternateNumberFormat"
22+
alternateNumberFormatPlugin :: PluginTestDescriptor AlternateNumberFormat.Log
23+
alternateNumberFormatPlugin = mkPluginTestDescriptor AlternateNumberFormat.descriptor "alternateNumberFormat"
2424

2525
-- NOTE: For whatever reason, this plugin does not play nice with creating Code Actions on time.
2626
-- As a result tests will mostly pass if `import Prelude` is added at the top. We (mostly fendor) surmise this has something

plugins/hls-brittany-plugin/test/Main.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,8 +10,8 @@ import Test.Hls
1010
main :: IO ()
1111
main = defaultTestRunner tests
1212

13-
brittanyPlugin :: PluginDescriptor IdeState
14-
brittanyPlugin = Brittany.descriptor "brittany"
13+
brittanyPlugin :: PluginTestDescriptor ()
14+
brittanyPlugin = mkPluginTestDescriptor' Brittany.descriptor "brittany"
1515

1616
tests :: TestTree
1717
tests = testGroup "brittany"

plugins/hls-cabal-fmt-plugin/test/Main.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -30,8 +30,8 @@ main = do
3030
foundCabalFmt <- isCabalFmtFound
3131
defaultTestRunner (tests foundCabalFmt)
3232

33-
cabalFmtPlugin :: PluginDescriptor IdeState
34-
cabalFmtPlugin = CabalFmt.descriptor mempty "cabal-fmt"
33+
cabalFmtPlugin :: PluginTestDescriptor CabalFmt.Log
34+
cabalFmtPlugin = mkPluginTestDescriptor CabalFmt.descriptor "cabal-fmt"
3535

3636
tests :: CabalFmtFound -> TestTree
3737
tests found = testGroup "cabal-fmt"

0 commit comments

Comments
 (0)