2
2
{-# LANGUAGE ExistentialQuantification #-}
3
3
{-# LANGUAGE ImplicitParams #-}
4
4
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
39
19
import Control.Applicative.Combinators (skipManyTill )
40
20
import Control.Concurrent
41
21
import Control.Exception.Safe
42
22
import Control.Monad.Extra
43
23
import Control.Monad.IO.Class
24
+ import Data.Char (isDigit )
44
25
import Data.List
45
26
import Data.Maybe
46
27
import Data.Version
@@ -54,7 +35,7 @@ import System.FilePath ((</>))
54
35
import System.Process
55
36
import System.Time.Extra
56
37
import Text.ParserCombinators.ReadP (readP_to_S )
57
- import Data.Char ( isDigit )
38
+ import System.Environment.Blank ( getEnv )
58
39
59
40
-- Points to a string in the target file,
60
41
-- convenient for hygienic edits
@@ -82,16 +63,8 @@ breakingEdit =
82
63
identifierP :: Position
83
64
identifierP = Position 853 12
84
65
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 =
95
68
[ ---------------------------------------------------------------------------------------
96
69
bench " hover" 10 $ \ doc ->
97
70
isJust <$> getHover doc identifierP,
@@ -131,12 +104,19 @@ main = do
131
104
not . null <$> getCodeActions doc (Range p p)
132
105
),
133
106
---------------------------------------------------------------------------------------
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
+ )
138
119
]
139
- `finally` cleanUp
140
120
141
121
---------------------------------------------------------------------------------------------
142
122
@@ -165,7 +145,7 @@ data Config = Config
165
145
-- For some reason, the Shake profile files are truncated and won't load
166
146
shakeProfiling :: ! (Maybe FilePath ),
167
147
outputCSV :: ! FilePath ,
168
- cradle :: ! Cradle ,
148
+ buildTool :: ! CabalStack ,
169
149
rtsOptions :: ! [String ],
170
150
matches :: ! [String ],
171
151
repetitions :: Maybe Natural ,
@@ -175,11 +155,14 @@ data Config = Config
175
155
}
176
156
deriving (Eq , Show )
177
157
158
+ defConfig :: Config
159
+ Success defConfig = execParserPure defaultPrefs (info configP fullDesc) []
160
+
178
161
quiet , verbose :: Config -> Bool
179
162
verbose = (== All ) . verbosity
180
163
quiet = (== Quiet ) . verbosity
181
164
182
- data Cradle = Cabal | Stack
165
+ data CabalStack = Cabal | Stack
183
166
deriving (Eq , Show )
184
167
185
168
type HasConfig = (? config :: Config )
@@ -193,7 +176,7 @@ configP =
193
176
)
194
177
<*> optional (strOption (long " shake-profiling" <> metavar " PATH" ))
195
178
<*> 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) " )
197
180
<*> many (strOption (long " rts" <> help " additional RTS options for ghcide" ))
198
181
<*> many (strOption (short ' s' <> long " select" <> help " select which benchmarks to run" ))
199
182
<*> optional (option auto (long " samples" <> metavar " NAT" <> help " override sampling count" ))
@@ -231,26 +214,29 @@ select Bench {name, enabled} =
231
214
mm = matches ? config
232
215
233
216
benchWithSetup ::
234
- HasConfig =>
235
217
String ->
236
218
Natural ->
237
219
(TextDocumentIdentifier -> Session p ) ->
238
220
(p -> Experiment ) ->
239
221
Bench
240
- benchWithSetup name defSamples benchSetup experiment = Bench {.. }
222
+ benchWithSetup name samples benchSetup experiment = Bench {.. }
241
223
where
242
224
enabled = True
243
- samples = fromMaybe defSamples (repetitions ? config)
244
225
245
- bench :: HasConfig => String -> Natural -> Experiment -> Bench
226
+ bench :: String -> Natural -> Experiment -> Bench
246
227
bench name defSamples userExperiment =
247
228
benchWithSetup name defSamples (const $ pure () ) experiment
248
229
where
249
230
experiment () = userExperiment
250
231
251
232
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
254
240
255
241
-- output raw data as CSV
256
242
let headers = [" name" , " success" , " samples" , " startup" , " setup" , " experiment" , " maxResidency" ]
@@ -288,6 +274,33 @@ runBenchmarks (filter select -> benchmarks) = do
288
274
outputRow paddedHeaders
289
275
outputRow $ (map . map ) (const ' -' ) paddedHeaders
290
276
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
+ }
291
304
292
305
data BenchRun = BenchRun
293
306
{ startup :: ! Seconds ,
@@ -304,9 +317,9 @@ waitForProgressDone :: Session ()
304
317
waitForProgressDone =
305
318
void(skipManyTill anyMessage message :: Session WorkDoneProgressEndNotification )
306
319
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
310
323
$ do
311
324
doc <- openDoc exampleModulePath " haskell"
312
325
(startup, _) <- duration $ do
@@ -333,53 +346,54 @@ runBench Bench {..} = handleAny (\e -> print e >> return badRun)
333
346
-- sleep to give ghcide a chance to GC
334
347
liftIO $ threadDelay 1100000
335
348
336
- maxResidency <- liftIO $ parseMaxResidency <$> readFile gcStats
349
+ maxResidency <- liftIO $
350
+ ifM (doesFileExist gcStats)
351
+ (parseMaxResidency <$> readFile gcStats)
352
+ (pure 0 )
337
353
338
354
return BenchRun {.. }
339
355
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
- ]
357
356
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" )
367
358
368
359
setup :: HasConfig => IO (IO () )
369
360
setup = do
370
361
alreadyExists <- doesDirectoryExist examplesPath
371
362
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" ) <> " }}" )
383
397
384
398
whenJust (shakeProfiling ? config) $ createDirectoryIfMissing True
385
399
@@ -401,11 +415,6 @@ escapeSpaces = map f
401
415
f ' ' = ' _'
402
416
f x = x
403
417
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
-
409
418
pad :: Int -> String -> String
410
419
pad n [] = replicate n ' '
411
420
pad 0 _ = error " pad"
0 commit comments