Skip to content

Commit 3d65a23

Browse files
committed
bench: Add more metrics
Add columns to keep track of total GHC rebuilds, time for first response and average time per response
1 parent a538641 commit 3d65a23

File tree

6 files changed

+88
-28
lines changed

6 files changed

+88
-28
lines changed

Diff for: ghcide/bench/lib/Experiments.hs

+26-8
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,9 @@ import Development.IDE.Test (getBuildEdgesCount,
3737
getBuildKeysBuilt,
3838
getBuildKeysChanged,
3939
getBuildKeysVisited,
40-
getStoredKeys)
40+
getStoredKeys,
41+
getRebuildsCount,
42+
)
4143
import Development.IDE.Test.Diagnostic
4244
import Development.Shake (CmdOption (Cwd, FileStdout),
4345
cmd_)
@@ -329,12 +331,15 @@ runBenchmarksFun dir allBenchmarks = do
329331
, "setup"
330332
, "userTime"
331333
, "delayedTime"
334+
, "firstBuildTime"
335+
, "averageTimePerResponse"
332336
, "totalTime"
333337
, "buildRulesBuilt"
334338
, "buildRulesChanged"
335339
, "buildRulesVisited"
336340
, "buildRulesTotal"
337341
, "buildEdges"
342+
, "ghcRebuilds"
338343
]
339344
rows =
340345
[ [ name,
@@ -344,15 +349,21 @@ runBenchmarksFun dir allBenchmarks = do
344349
show runSetup',
345350
show userWaits,
346351
show delayedWork,
352+
show $ firstResponse+firstResponseDelayed,
353+
-- Exclude first response as it has a lot of setup time included
354+
-- Assume that number of requests = number of modules * number of samples
355+
show ((userWaits - firstResponse)/((fromIntegral samples - 1)*modules)),
347356
show runExperiment,
348357
show rulesBuilt,
349358
show rulesChanged,
350359
show rulesVisited,
351360
show rulesTotal,
352-
show edgesTotal
361+
show edgesTotal,
362+
show rebuildsTotal
353363
]
354364
| (Bench {name, samples}, BenchRun {..}) <- results,
355365
let runSetup' = if runSetup < 0.01 then 0 else runSetup
366+
modules = fromIntegral $ length $ exampleModules $ example ?config
356367
]
357368
csv = unlines $ map (intercalate ", ") (headers : rows)
358369
writeFile (outputCSV ?config) csv
@@ -369,12 +380,14 @@ runBenchmarksFun dir allBenchmarks = do
369380
showDuration runSetup',
370381
showDuration userWaits,
371382
showDuration delayedWork,
383+
showDuration firstResponse,
372384
showDuration runExperiment,
373385
show rulesBuilt,
374386
show rulesChanged,
375387
show rulesVisited,
376388
show rulesTotal,
377-
show edgesTotal
389+
show edgesTotal,
390+
show rebuildsTotal
378391
]
379392
| (Bench {name, samples}, BenchRun {..}) <- results,
380393
let runSetup' = if runSetup < 0.01 then 0 else runSetup
@@ -420,16 +433,19 @@ data BenchRun = BenchRun
420433
runExperiment :: !Seconds,
421434
userWaits :: !Seconds,
422435
delayedWork :: !Seconds,
436+
firstResponse :: !Seconds,
437+
firstResponseDelayed :: !Seconds,
423438
rulesBuilt :: !Int,
424439
rulesChanged :: !Int,
425440
rulesVisited :: !Int,
426441
rulesTotal :: !Int,
427442
edgesTotal :: !Int,
443+
rebuildsTotal :: !Int,
428444
success :: !Bool
429445
}
430446

431447
badRun :: BenchRun
432-
badRun = BenchRun 0 0 0 0 0 0 0 0 0 0 False
448+
badRun = BenchRun 0 0 0 0 0 0 0 0 0 0 0 0 0 False
433449

434450
waitForProgressStart :: Session ()
435451
waitForProgressStart = void $ do
@@ -482,26 +498,28 @@ runBench runSess b = handleAny (\e -> print e >> return badRun)
482498

483499
liftIO $ output $ "Running " <> name <> " benchmark"
484500
(runSetup, ()) <- duration $ benchSetup docs
485-
let loop !userWaits !delayedWork 0 = return $ Just (userWaits, delayedWork)
486-
loop !userWaits !delayedWork n = do
501+
let loop' (Just timeForFirstResponse) !userWaits !delayedWork 0 = return $ Just (userWaits, delayedWork, timeForFirstResponse)
502+
loop' timeForFirstResponse !userWaits !delayedWork n = do
487503
(t, res) <- duration $ experiment docs
488504
if not res
489505
then return Nothing
490506
else do
491507
output (showDuration t)
492508
-- Wait for the delayed actions to finish
493509
td <- waitForBuildQueue
494-
loop (userWaits+t) (delayedWork+td) (n -1)
510+
loop' (timeForFirstResponse <|> (Just (t,td))) (userWaits+t) (delayedWork+td) (n -1)
511+
loop = loop' Nothing
495512

496513
(runExperiment, result) <- duration $ loop 0 0 samples
497514
let success = isJust result
498-
(userWaits, delayedWork) = fromMaybe (0,0) result
515+
(userWaits, delayedWork, (firstResponse, firstResponseDelayed)) = fromMaybe (0,0,(0,0)) result
499516

500517
rulesTotal <- length <$> getStoredKeys
501518
rulesBuilt <- either (const 0) length <$> getBuildKeysBuilt
502519
rulesChanged <- either (const 0) length <$> getBuildKeysChanged
503520
rulesVisited <- either (const 0) length <$> getBuildKeysVisited
504521
edgesTotal <- fromRight 0 <$> getBuildEdgesCount
522+
rebuildsTotal <- fromRight 0 <$> getRebuildsCount
505523

506524
return BenchRun {..}
507525

Diff for: ghcide/src/Development/IDE/Core/Rules.hs

+25-8
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,7 @@ module Development.IDE.Core.Rules(
5454
ghcSessionDepsDefinition,
5555
getParsedModuleDefinition,
5656
typeCheckRuleDefinition,
57+
getRebuildCount,
5758
GhcSessionDepsConfig(..),
5859
Log(..),
5960
DisplayTHWarning(..),
@@ -911,6 +912,20 @@ getModIfaceRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $
911912
liftIO $ void $ modifyVar' compiledLinkables $ \old -> extendModuleEnv old mod time
912913
pure res
913914

915+
-- | Count of total times we asked GHC to recompile
916+
newtype RebuildCounter = RebuildCounter { getRebuildCountVar :: TVar Int }
917+
instance IsIdeGlobal RebuildCounter
918+
919+
getRebuildCount :: Action Int
920+
getRebuildCount = do
921+
count <- getRebuildCountVar <$> getIdeGlobalAction
922+
liftIO $ readTVarIO count
923+
924+
incrementRebuildCount :: Action ()
925+
incrementRebuildCount = do
926+
count <- getRebuildCountVar <$> getIdeGlobalAction
927+
liftIO $ atomically $ modifyTVar' count (+1)
928+
914929
-- | Also generates and indexes the `.hie` file, along with the `.o` file if needed
915930
-- Invariant maintained is that if the `.hi` file was successfully written, then the
916931
-- `.hie` and `.o` file (if needed) were also successfully written
@@ -940,10 +955,10 @@ regenerateHiFile sess f ms compNeeded = do
940955
Just tmr -> do
941956

942957
-- compile writes .o file
943-
let compile = compileModule (RunSimplifier True) hsc (pm_mod_summary pm) $ tmrTypechecked tmr
958+
let compile = liftIO $ compileModule (RunSimplifier True) hsc (pm_mod_summary pm) $ tmrTypechecked tmr
944959

945960
-- Bang pattern is important to avoid leaking 'tmr'
946-
(diags'', !res) <- liftIO $ compileToObjCodeIfNeeded hsc compNeeded compile tmr
961+
(diags'', !res) <- compileToObjCodeIfNeeded hsc compNeeded compile tmr
947962

948963
-- Write hi file
949964
hiDiags <- case res of
@@ -967,18 +982,17 @@ regenerateHiFile sess f ms compNeeded = do
967982
pure (hiDiags <> gDiags <> concat wDiags)
968983
Nothing -> pure []
969984

970-
971985
return (diags <> diags' <> diags'' <> hiDiags, res)
972986

973987

974-
type CompileMod m = m (IdeResult ModGuts)
975-
976988
-- | HscEnv should have deps included already
977-
compileToObjCodeIfNeeded :: MonadIO m => HscEnv -> Maybe LinkableType -> CompileMod m -> TcModuleResult -> m (IdeResult HiFileResult)
978-
compileToObjCodeIfNeeded hsc Nothing _ tmr = liftIO $ do
979-
res <- mkHiFileResultNoCompile hsc tmr
989+
compileToObjCodeIfNeeded :: HscEnv -> Maybe LinkableType -> Action (IdeResult ModGuts) -> TcModuleResult -> Action (IdeResult HiFileResult)
990+
compileToObjCodeIfNeeded hsc Nothing _ tmr = do
991+
incrementRebuildCount
992+
res <- liftIO $ mkHiFileResultNoCompile hsc tmr
980993
pure ([], Just $! res)
981994
compileToObjCodeIfNeeded hsc (Just linkableType) getGuts tmr = do
995+
incrementRebuildCount
982996
(diags, mguts) <- getGuts
983997
case mguts of
984998
Nothing -> pure (diags, Nothing)
@@ -1079,6 +1093,7 @@ computeLinkableTypeForDynFlags d
10791093
newtype CompiledLinkables = CompiledLinkables { getCompiledLinkables :: Var (ModuleEnv UTCTime) }
10801094
instance IsIdeGlobal CompiledLinkables
10811095

1096+
10821097
writeHiFileAction :: HscEnv -> HiFileResult -> Action [FileDiagnostic]
10831098
writeHiFileAction hsc hiFile = do
10841099
extras <- getShakeExtras
@@ -1115,6 +1130,8 @@ mainRule :: Recorder (WithPriority Log) -> RulesConfig -> Rules ()
11151130
mainRule recorder RulesConfig{..} = do
11161131
linkables <- liftIO $ newVar emptyModuleEnv
11171132
addIdeGlobal $ CompiledLinkables linkables
1133+
rebuildCountVar <- liftIO $ newTVarIO 0
1134+
addIdeGlobal $ RebuildCounter rebuildCountVar
11181135
getParsedModuleRule recorder
11191136
getParsedModuleWithCommentsRule recorder
11201137
getLocatedImportsRule recorder

Diff for: ghcide/src/Development/IDE/Plugin/Test.hs

+5
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ import Development.IDE.Core.OfInterest (getFilesOfInterest)
2828
import Development.IDE.Core.RuleTypes
2929
import Development.IDE.Core.Service
3030
import Development.IDE.Core.Shake
31+
import Development.IDE.Core.Rules
3132
import Development.IDE.GHC.Compat
3233
import Development.IDE.Graph (Action)
3334
import qualified Development.IDE.Graph as Graph
@@ -64,6 +65,7 @@ data TestRequest
6465
| GarbageCollectDirtyKeys CheckParents Age -- ^ :: [String] (list of keys collected)
6566
| GetStoredKeys -- ^ :: [String] (list of keys in store)
6667
| GetFilesOfInterest -- ^ :: [FilePath]
68+
| GetRebuildsCount -- ^ :: Int (number of times we recompiled with GHC)
6769
deriving Generic
6870
deriving anyclass (FromJSON, ToJSON)
6971

@@ -131,6 +133,9 @@ testRequestHandler s GetStoredKeys = do
131133
testRequestHandler s GetFilesOfInterest = do
132134
ff <- liftIO $ getFilesOfInterest s
133135
return $ Right $ toJSON $ map fromNormalizedFilePath $ HM.keys ff
136+
testRequestHandler s GetRebuildsCount = do
137+
count <- liftIO $ runAction "get build count" s getRebuildCount
138+
return $ Right $ toJSON count
134139

135140
getDatabaseKeys :: (Graph.Result -> Step)
136141
-> ShakeDatabase

Diff for: ghcide/test/src/Development/IDE/Test.hs

+4
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ module Development.IDE.Test
3333
, getBuildKeysVisited
3434
, getBuildKeysChanged
3535
, getBuildEdgesCount
36+
, getRebuildsCount
3637
, configureCheckProject
3738
, isReferenceReady
3839
, referenceReady) where
@@ -225,6 +226,9 @@ getBuildKeysChanged = tryCallTestPlugin GetBuildKeysChanged
225226
getBuildEdgesCount :: Session (Either ResponseError Int)
226227
getBuildEdgesCount = tryCallTestPlugin GetBuildEdgesCount
227228

229+
getRebuildsCount :: Session (Either ResponseError Int)
230+
getRebuildsCount = tryCallTestPlugin GetRebuildsCount
231+
228232
getInterfaceFilesDir :: TextDocumentIdentifier -> Session FilePath
229233
getInterfaceFilesDir TextDocumentIdentifier{_uri} = callTestPlugin (GetInterfaceFilesDir _uri)
230234

Diff for: shake-bench/shake-bench.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ library
2929
filepath,
3030
lens,
3131
lens-aeson,
32+
mtl,
3233
shake,
3334
text
3435
default-language: Haskell2010

Diff for: shake-bench/src/Development/Benchmark/Rules.hs

+27-12
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,7 @@ module Development.Benchmark.Rules
6969
import Control.Applicative
7070
import Control.Lens ((^.))
7171
import Control.Monad
72+
import qualified Control.Monad.State as S
7273
import Data.Aeson (FromJSON (..),
7374
ToJSON (..),
7475
Value (..), object,
@@ -561,7 +562,8 @@ instance Read Frame where
561562
data RunLog = RunLog
562563
{ runVersion :: !String,
563564
runFrames :: ![Frame],
564-
runSuccess :: !Bool
565+
runSuccess :: !Bool,
566+
runFirstReponse :: !(Maybe Seconds)
565567
}
566568

567569
loadRunLog :: HasCallStack => Escaped FilePath -> String -> Action RunLog
@@ -577,10 +579,16 @@ loadRunLog (Escaped csv_fp) ver = do
577579
generation f == 1
578580
]
579581
-- TODO this assumes a certain structure in the CSV file
580-
success = case map (T.split (== ',') . T.pack) csv of
581-
[_header, _name:s:_] | Just s <- readMaybe (T.unpack s) -> s
582+
(success, firstResponse) = case map (map T.strip . T.split (== ',') . T.pack) csv of
583+
[header, row]
584+
| let table = zip header row
585+
timeForFirstResponse :: Maybe Seconds
586+
timeForFirstResponse = readMaybe . T.unpack =<< lookup "firstBuildTime" table
587+
, Just s <- lookup "success" table
588+
, Just s <- readMaybe (T.unpack s)
589+
-> (s,timeForFirstResponse)
582590
_ -> error $ "Cannot parse: " <> csv_fp
583-
return $ RunLog ver frames success
591+
return $ RunLog ver frames success firstResponse
584592

585593
--------------------------------------------------------------------------------
586594

@@ -615,14 +623,21 @@ plotDiagram includeFailed t@Diagram {traceMetric, runLogs} out = do
615623
E.layout_title E..= title t
616624
E.setColors myColors
617625
forM_ runLogs $ \rl ->
618-
when (includeFailed || runSuccess rl) $ E.plot $ do
619-
lplot <- E.line
620-
(runVersion rl ++ if runSuccess rl then "" else " (FAILED)")
621-
[ [ (totElapsed f, extract f)
622-
| f <- runFrames rl
623-
]
624-
]
625-
return (lplot E.& E.plot_lines_style . E.line_width E.*~ 2)
626+
when (includeFailed || runSuccess rl) $ do
627+
-- Get the color we are going to use
628+
~(c:_) <- E.liftCState $ S.gets (E.view E.colors)
629+
E.plot $ do
630+
lplot <- E.line
631+
(runVersion rl ++ if runSuccess rl then "" else " (FAILED)")
632+
[ [ (totElapsed f, extract f)
633+
| f <- runFrames rl
634+
]
635+
]
636+
return (lplot E.& E.plot_lines_style . E.line_width E.*~ 2)
637+
case (runFirstReponse rl) of
638+
Just t -> E.plot $ pure $
639+
E.vlinePlot ("First build" ++ runVersion rl) (E.defaultPlotLineStyle E.& E.line_color E..~ c) t
640+
_ -> pure ()
626641

627642
--------------------------------------------------------------------------------
628643

0 commit comments

Comments
 (0)