Skip to content

Commit ba4bdb2

Browse files
authored
Send WorkDoneProgressEnd only when work is done (#649)
* send WorkDoneProgressEnd only when work done * Progress reporting now spans over multiple overlapping kicks * Repurpose benchmark experiments as tests Fixes #650 * use stack to fetch from Hackage * benchmark tests run with the same lsp-test config as other tests * Fix stack cradle in benchmark * Make stack unpack --silent * Fix issues in "code actions after edit" experiment - Repeated breaking edits make ghc run out of suggestions - Diagnostics seem to come and go in-between edits, which leads to a timing issue when asking for code actions. The fix is to wait for diagnostics to be present before asking for code actions * Fix stack.yaml generation in example project * Fix getDefinition in GHC 8.4 Did it break before 0.2.0 or after? * better naming for the progress event TVar * stop progress reporting in shakeShut haskell/ghcide#649 (comment) * hlint
1 parent 5b8d7fa commit ba4bdb2

File tree

10 files changed

+300
-179
lines changed

10 files changed

+300
-179
lines changed

bench/README.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
This folder contains two Haskell programs that work together to simplify the
55
performance analysis of ghcide:
66

7-
- `Main.hs` - a standalone benchmark suite. Run with `stack bench`
7+
- `exe/Main.hs` - a standalone benchmark suite. Run with `stack bench`
88
- `hist/Main.hs` - a Shake script for running the benchmark suite over a set of commits.
99
- Run with `stack exec benchHist`,
1010
- Requires a `ghcide-bench` binary in the PATH,

bench/exe/Main.hs

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
{- An automated benchmark built around the simple experiment described in:
2+
3+
> https://neilmitchell.blogspot.com/2020/05/fixing-space-leaks-in-ghcide.html
4+
5+
As an example project, it unpacks Cabal-3.2.0.0 in the local filesystem and
6+
loads the module 'Distribution.Simple'. The rationale for this choice is:
7+
8+
- It's convenient to download with `cabal unpack Cabal-3.2.0.0`
9+
- It has very few dependencies, and all are already needed to build ghcide
10+
- Distribution.Simple has 235 transitive module dependencies, so non trivial
11+
12+
The experiments are sequences of lsp commands scripted using lsp-test.
13+
A more refined approach would be to record and replay real IDE interactions,
14+
once the replay functionality is available in lsp-test.
15+
A more declarative approach would be to reuse ide-debug-driver:
16+
17+
> https://github.com/digital-asset/daml/blob/master/compiler/damlc/ide-debug-driver/README.md
18+
19+
The result of an experiment is a total duration in seconds after a preset
20+
number of iterations. There is ample room for improvement:
21+
- Statistical analysis to detect outliers and auto infer the number of iterations needed
22+
- GC stats analysis (currently -S is printed as part of the experiment)
23+
- Analyisis of performance over the commit history of the project
24+
25+
How to run:
26+
1. `cabal bench`
27+
2. `cabal exec cabal run ghcide-bench -- -- ghcide-bench-options`
28+
29+
Note that the package database influences the response times of certain actions,
30+
e.g. code actions, and therefore the two methods above do not necessarily
31+
produce the same results.
32+
33+
-}
34+
35+
{-# LANGUAGE ImplicitParams #-}
36+
37+
import Control.Exception.Safe
38+
import Experiments
39+
import Options.Applicative
40+
41+
main :: IO ()
42+
main = do
43+
config <- execParser $ info (configP <**> helper) fullDesc
44+
let ?config = config
45+
46+
output "starting test"
47+
48+
cleanUp <- setup
49+
50+
runBenchmarks experiments `finally` cleanUp
File renamed without changes.

bench/Main.hs renamed to bench/lib/Experiments.hs

Lines changed: 114 additions & 105 deletions
Original file line numberDiff line numberDiff line change
@@ -2,45 +2,26 @@
22
{-# LANGUAGE ExistentialQuantification #-}
33
{-# LANGUAGE ImplicitParams #-}
44

5-
{- An automated benchmark built around the simple experiment described in:
6-
7-
> https://neilmitchell.blogspot.com/2020/05/fixing-space-leaks-in-ghcide.html
8-
9-
As an example project, it unpacks Cabal-3.2.0.0 in the local filesystem and
10-
loads the module 'Distribution.Simple'. The rationale for this choice is:
11-
12-
- It's convenient to download with `cabal unpack Cabal-3.2.0.0`
13-
- It has very few dependencies, and all are already needed to build ghcide
14-
- Distribution.Simple has 235 transitive module dependencies, so non trivial
15-
16-
The experiments are sequences of lsp commands scripted using lsp-test.
17-
A more refined approach would be to record and replay real IDE interactions,
18-
once the replay functionality is available in lsp-test.
19-
A more declarative approach would be to reuse ide-debug-driver:
20-
21-
> https://github.com/digital-asset/daml/blob/master/compiler/damlc/ide-debug-driver/README.md
22-
23-
The result of an experiment is a total duration in seconds after a preset
24-
number of iterations. There is ample room for improvement:
25-
- Statistical analysis to detect outliers and auto infer the number of iterations needed
26-
- GC stats analysis (currently -S is printed as part of the experiment)
27-
- Analyisis of performance over the commit history of the project
28-
29-
How to run:
30-
1. `cabal bench`
31-
2. `cabal exec cabal run ghcide-bench -- -- ghcide-bench-options`
32-
33-
Note that the package database influences the response times of certain actions,
34-
e.g. code actions, and therefore the two methods above do not necessarily
35-
produce the same results.
36-
37-
-}
38-
5+
module Experiments
6+
( Bench(..)
7+
, BenchRun(..)
8+
, Config(..)
9+
, Verbosity(..)
10+
, CabalStack(..)
11+
, experiments
12+
, configP
13+
, defConfig
14+
, output
15+
, setup
16+
, runBench
17+
, runBenchmarks
18+
) where
3919
import Control.Applicative.Combinators (skipManyTill)
4020
import Control.Concurrent
4121
import Control.Exception.Safe
4222
import Control.Monad.Extra
4323
import Control.Monad.IO.Class
24+
import Data.Char (isDigit)
4425
import Data.List
4526
import Data.Maybe
4627
import Data.Version
@@ -54,7 +35,7 @@ import System.FilePath ((</>))
5435
import System.Process
5536
import System.Time.Extra
5637
import Text.ParserCombinators.ReadP (readP_to_S)
57-
import Data.Char (isDigit)
38+
import System.Environment.Blank (getEnv)
5839

5940
-- Points to a string in the target file,
6041
-- convenient for hygienic edits
@@ -82,16 +63,8 @@ breakingEdit =
8263
identifierP :: Position
8364
identifierP = Position 853 12
8465

85-
main :: IO ()
86-
main = do
87-
config <- execParser $ info (configP <**> helper) fullDesc
88-
let ?config = config
89-
90-
output "starting test"
91-
92-
cleanUp <- setup
93-
94-
runBenchmarks
66+
experiments :: [Bench]
67+
experiments =
9568
[ ---------------------------------------------------------------------------------------
9669
bench "hover" 10 $ \doc ->
9770
isJust <$> getHover doc identifierP,
@@ -131,12 +104,19 @@ main = do
131104
not . null <$> getCodeActions doc (Range p p)
132105
),
133106
---------------------------------------------------------------------------------------
134-
bench "code actions after edit" 10 $ \doc -> do
135-
changeDoc doc [breakingEdit]
136-
void (skipManyTill anyMessage message :: Session WorkDoneProgressEndNotification)
137-
not . null <$> getCodeActions doc (Range identifierP identifierP)
107+
benchWithSetup
108+
"code actions after edit"
109+
10
110+
( \doc -> do
111+
changeDoc doc [breakingEdit]
112+
return identifierP
113+
)
114+
( \p doc -> do
115+
changeDoc doc [hygienicEdit]
116+
whileM (null <$> waitForDiagnostics)
117+
not . null <$> getCodeActions doc (Range p p)
118+
)
138119
]
139-
`finally` cleanUp
140120

141121
---------------------------------------------------------------------------------------------
142122

@@ -165,7 +145,7 @@ data Config = Config
165145
-- For some reason, the Shake profile files are truncated and won't load
166146
shakeProfiling :: !(Maybe FilePath),
167147
outputCSV :: !FilePath,
168-
cradle :: !Cradle,
148+
buildTool :: !CabalStack,
169149
rtsOptions :: ![String],
170150
matches :: ![String],
171151
repetitions :: Maybe Natural,
@@ -175,11 +155,14 @@ data Config = Config
175155
}
176156
deriving (Eq, Show)
177157

158+
defConfig :: Config
159+
Success defConfig = execParserPure defaultPrefs (info configP fullDesc) []
160+
178161
quiet, verbose :: Config -> Bool
179162
verbose = (== All) . verbosity
180163
quiet = (== Quiet) . verbosity
181164

182-
data Cradle = Cabal | Stack
165+
data CabalStack = Cabal | Stack
183166
deriving (Eq, Show)
184167

185168
type HasConfig = (?config :: Config)
@@ -193,7 +176,7 @@ configP =
193176
)
194177
<*> optional (strOption (long "shake-profiling" <> metavar "PATH"))
195178
<*> strOption (long "csv" <> metavar "PATH" <> value "results.csv" <> showDefault)
196-
<*> flag Cabal Stack (long "stack" <> help "Use a stack cradle")
179+
<*> flag Cabal Stack (long "stack" <> help "Use stack (by default cabal is used)")
197180
<*> many (strOption (long "rts" <> help "additional RTS options for ghcide"))
198181
<*> many (strOption (short 's' <> long "select" <> help "select which benchmarks to run"))
199182
<*> optional (option auto (long "samples" <> metavar "NAT" <> help "override sampling count"))
@@ -231,26 +214,29 @@ select Bench {name, enabled} =
231214
mm = matches ?config
232215

233216
benchWithSetup ::
234-
HasConfig =>
235217
String ->
236218
Natural ->
237219
(TextDocumentIdentifier -> Session p) ->
238220
(p -> Experiment) ->
239221
Bench
240-
benchWithSetup name defSamples benchSetup experiment = Bench {..}
222+
benchWithSetup name samples benchSetup experiment = Bench {..}
241223
where
242224
enabled = True
243-
samples = fromMaybe defSamples (repetitions ?config)
244225

245-
bench :: HasConfig => String -> Natural -> Experiment -> Bench
226+
bench :: String -> Natural -> Experiment -> Bench
246227
bench name defSamples userExperiment =
247228
benchWithSetup name defSamples (const $ pure ()) experiment
248229
where
249230
experiment () = userExperiment
250231

251232
runBenchmarks :: HasConfig => [Bench] -> IO ()
252-
runBenchmarks (filter select -> benchmarks) = do
253-
results <- forM benchmarks $ \b -> (b,) <$> runBench b
233+
runBenchmarks allBenchmarks = do
234+
let benchmarks = [ b{samples = fromMaybe (samples b) (repetitions ?config) }
235+
| b <- allBenchmarks
236+
, select b ]
237+
results <- forM benchmarks $ \b@Bench{name} ->
238+
let run dir = runSessionWithConfig conf (cmd name dir) lspTestCaps dir
239+
in (b,) <$> runBench run b
254240

255241
-- output raw data as CSV
256242
let headers = ["name", "success", "samples", "startup", "setup", "experiment", "maxResidency"]
@@ -288,6 +274,33 @@ runBenchmarks (filter select -> benchmarks) = do
288274
outputRow paddedHeaders
289275
outputRow $ (map . map) (const '-') paddedHeaders
290276
forM_ rowsHuman $ \row -> outputRow $ zipWith pad pads row
277+
where
278+
gcStats name = escapeSpaces (name <> ".benchmark-gcStats")
279+
cmd name dir =
280+
unwords $
281+
[ ghcide ?config,
282+
"--lsp",
283+
"--cwd",
284+
dir,
285+
"+RTS",
286+
"-S" <> gcStats name
287+
]
288+
++ rtsOptions ?config
289+
++ [ "-RTS"
290+
]
291+
++ concat
292+
[ ["--shake-profiling", path]
293+
| Just path <- [shakeProfiling ?config]
294+
]
295+
lspTestCaps =
296+
fullCaps {_window = Just $ WindowClientCapabilities $ Just True}
297+
conf =
298+
defaultConfig
299+
{ logStdErr = verbose ?config,
300+
logMessages = verbose ?config,
301+
logColor = False,
302+
messageTimeout = timeoutLsp ?config
303+
}
291304

292305
data BenchRun = BenchRun
293306
{ startup :: !Seconds,
@@ -304,9 +317,9 @@ waitForProgressDone :: Session ()
304317
waitForProgressDone =
305318
void(skipManyTill anyMessage message :: Session WorkDoneProgressEndNotification)
306319

307-
runBench :: HasConfig => Bench -> IO BenchRun
308-
runBench Bench {..} = handleAny (\e -> print e >> return badRun)
309-
$ runSessionWithConfig conf cmd lspTestCaps dir
320+
runBench :: (?config::Config) => (String -> Session BenchRun -> IO BenchRun) -> Bench -> IO BenchRun
321+
runBench runSess Bench {..} = handleAny (\e -> print e >> return badRun)
322+
$ runSess dir
310323
$ do
311324
doc <- openDoc exampleModulePath "haskell"
312325
(startup, _) <- duration $ do
@@ -333,53 +346,54 @@ runBench Bench {..} = handleAny (\e -> print e >> return badRun)
333346
-- sleep to give ghcide a chance to GC
334347
liftIO $ threadDelay 1100000
335348

336-
maxResidency <- liftIO $ parseMaxResidency <$> readFile gcStats
349+
maxResidency <- liftIO $
350+
ifM (doesFileExist gcStats)
351+
(parseMaxResidency <$> readFile gcStats)
352+
(pure 0)
337353

338354
return BenchRun {..}
339355
where
340-
gcStats = escapeSpaces (name <> ".benchmark-gcStats")
341-
cmd =
342-
unwords $
343-
[ ghcide ?config,
344-
"--lsp",
345-
"--cwd",
346-
dir,
347-
"+RTS",
348-
"-S" <> gcStats
349-
]
350-
++ rtsOptions ?config
351-
++ [ "-RTS"
352-
]
353-
++ concat
354-
[ ["--shake-profiling", path]
355-
| Just path <- [shakeProfiling ?config]
356-
]
357356
dir = "bench/example/" <> examplePackage
358-
lspTestCaps =
359-
fullCaps {_window = Just $ WindowClientCapabilities $ Just True}
360-
conf =
361-
defaultConfig
362-
{ logStdErr = verbose ?config,
363-
logMessages = verbose ?config,
364-
logColor = False,
365-
messageTimeout = timeoutLsp ?config
366-
}
357+
gcStats = escapeSpaces (name <> ".benchmark-gcStats")
367358

368359
setup :: HasConfig => IO (IO ())
369360
setup = do
370361
alreadyExists <- doesDirectoryExist examplesPath
371362
when alreadyExists $ removeDirectoryRecursive examplesPath
372-
callCommand $ "cabal get -v0 " <> examplePackage <> " -d " <> examplesPath
373-
writeFile
374-
(examplesPath </> examplePackage </> "hie.yaml")
375-
exampleCradle
376-
-- Need this in case there is a parent cabal.project somewhere
377-
writeFile
378-
(examplesPath </> examplePackage </> "cabal.project")
379-
"packages: ."
380-
writeFile
381-
(examplesPath </> examplePackage </> "cabal.project.local")
382-
""
363+
let path = examplesPath </> examplePackage
364+
case buildTool ?config of
365+
Cabal -> do
366+
callCommand $ "cabal get -v0 " <> examplePackage <> " -d " <> examplesPath
367+
writeFile
368+
(path </> "hie.yaml")
369+
("cradle: {cabal: {component: " <> show examplePackageName <> "}}")
370+
-- Need this in case there is a parent cabal.project somewhere
371+
writeFile
372+
(path </> "cabal.project")
373+
"packages: ."
374+
writeFile
375+
(path </> "cabal.project.local")
376+
""
377+
Stack -> do
378+
callCommand $ "stack --silent unpack " <> examplePackage <> " --to " <> examplesPath
379+
-- Generate the stack descriptor to match the one used to build ghcide
380+
stack_yaml <- fromMaybe "stack.yaml" <$> getEnv "STACK_YAML"
381+
stack_yaml_lines <- lines <$> readFile stack_yaml
382+
writeFile (path </> stack_yaml)
383+
(unlines $
384+
"packages: [.]" :
385+
[ l
386+
| l <- stack_yaml_lines
387+
, any (`isPrefixOf` l)
388+
["resolver"
389+
,"allow-newer"
390+
,"compiler"]
391+
]
392+
)
393+
394+
writeFile
395+
(path </> "hie.yaml")
396+
("cradle: {stack: {component: " <> show (examplePackageName <> ":lib") <> "}}")
383397

384398
whenJust (shakeProfiling ?config) $ createDirectoryIfMissing True
385399

@@ -401,11 +415,6 @@ escapeSpaces = map f
401415
f ' ' = '_'
402416
f x = x
403417

404-
exampleCradle :: HasConfig => String
405-
exampleCradle = case cradle ?config of
406-
Cabal -> "cradle: {cabal: {component: " <> show examplePackageName <> "}}"
407-
Stack -> "cradle: {stack: {component: " <> show (examplePackageName <> ":lib") <> "}}"
408-
409418
pad :: Int -> String -> String
410419
pad n [] = replicate n ' '
411420
pad 0 _ = error "pad"

0 commit comments

Comments
 (0)