Skip to content

Commit c6319d3

Browse files
committed
Abstract monitoring and put EKG behind a Cabal flag
1 parent ab13cfe commit c6319d3

File tree

10 files changed

+200
-98
lines changed

10 files changed

+200
-98
lines changed

docs/contributing/contributing.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -229,7 +229,7 @@ See the [tutorial](./plugin-tutorial.md) on writing a plugin in HLS.
229229

230230
### Metrics
231231

232-
HLS opens a metrics server on port 8000 exposing GC and ghcide metrics. The ghcide metrics currently exposed are:
232+
When ghcide is built with the `ekg` flag, HLS opens a metrics server on port 8999 exposing GC and ghcide metrics. The ghcide metrics currently exposed are:
233233

234234
- `ghcide.values_count`- count of build results in the store
235235
- `ghcide.database_count` - count of build keys in the store (these two would be the same in the absence of GC)

ghcide/exe/Arguments.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
33

4+
{-# LANGUAGE CPP #-}
45
module Arguments(Arguments(..), getArguments) where
56

67
import Development.IDE (IdeState)
@@ -19,6 +20,9 @@ data Arguments = Arguments
1920
,argsVerbose :: Bool
2021
,argsCommand :: Command
2122
,argsConservativeChangeTracking :: Bool
23+
#ifdef MONITORING_EKG
24+
,argsMonitoringPort :: Int
25+
#endif
2226
}
2327

2428
getArguments :: IdePlugins IdeState -> IO Arguments
@@ -40,6 +44,9 @@ arguments plugins = Arguments
4044
<*> switch (short 'd' <> long "verbose" <> help "Include internal events in logging output")
4145
<*> (commandP plugins <|> lspCommand <|> checkCommand)
4246
<*> switch (long "conservative-change-tracking" <> help "disable reactive change tracking (for testing/debugging)")
47+
#ifdef MONITORING_EKG
48+
<*> option auto (long "monitoring-port" <> metavar "PORT" <> value 8999 <> showDefault <> help "Port to use for monitoring")
49+
#endif
4350
where
4451
checkCommand = Check <$> many (argument str (metavar "FILES/DIRS..."))
4552
lspCommand = LSP <$ flag' True (long "lsp" <> help "Start talking to an LSP client")

ghcide/exe/Main.hs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
33
{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above
4+
{-# LANGUAGE CPP #-}
45
{-# LANGUAGE TemplateHaskell #-}
56

67
module Main(main) where
@@ -24,7 +25,6 @@ import Development.IDE.Types.Logger (Logger (Logger),
2425
LoggingColumn (DataColumn, PriorityColumn),
2526
Pretty (pretty),
2627
Priority (Debug, Info, Error),
27-
Recorder (Recorder),
2828
WithPriority (WithPriority, priority),
2929
cfilter, cmapWithPrio,
3030
makeDefaultStderrRecorder, layoutPretty, renderStrict, defaultLayoutOptions)
@@ -43,6 +43,11 @@ import System.Exit (exitSuccess)
4343
import System.IO (hPutStrLn, stderr)
4444
import System.Info (compilerVersion)
4545

46+
#ifdef MONITORING_EKG
47+
import qualified Development.IDE.Monitoring.OpenTelemetry as OpenTelemetry
48+
import qualified Development.IDE.Monitoring.EKG as EKG
49+
#endif
50+
4651
data Log
4752
= LogIDEMain IDEMain.Log
4853
| LogRules Rules.Log
@@ -142,4 +147,10 @@ main = withTelemetryLogger $ \telemetryLogger -> do
142147
, optCheckProject = pure $ checkProject config
143148
, optRunSubset = not argsConservativeChangeTracking
144149
}
150+
#ifdef MONITORING_EKG
151+
, IDEMain.argsMonitoring = OpenTelemetry.monitoring <> EKG.monitoring logger argsMonitoringPort
152+
#ifdef MONITORING_EKG
153+
#endif
154+
#endif
155+
145156
}

ghcide/ghcide.cabal

Lines changed: 20 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,11 @@ flag ghc-patched-unboxed-bytecode
3030
default: False
3131
manual: True
3232

33+
flag ekg
34+
description: Enable EKG monitoring of the build graph and other metrics on port 8999
35+
default: False
36+
manual: True
37+
3338
library
3439
default-language: Haskell2010
3540
build-depends:
@@ -48,8 +53,6 @@ library
4853
dependent-map,
4954
dependent-sum,
5055
dlist,
51-
ekg-wai,
52-
ekg-core,
5356
exceptions,
5457
extra >= 1.7.4,
5558
enummapset,
@@ -200,6 +203,8 @@ library
200203
Development.IDE.Types.KnownTargets
201204
Development.IDE.Types.Location
202205
Development.IDE.Types.Logger
206+
Development.IDE.Types.Monitoring
207+
Development.IDE.Monitoring.OpenTelemetry
203208
Development.IDE.Types.Options
204209
Development.IDE.Types.Shake
205210
Development.IDE.Plugin
@@ -238,6 +243,14 @@ library
238243
exposed-modules:
239244
Development.IDE.GHC.Compat.CPP
240245

246+
if flag(ekg)
247+
build-depends:
248+
ekg-wai,
249+
ekg-core,
250+
cpp-options: -DMONITORING_EKG
251+
exposed-modules:
252+
Development.IDE.Monitoring.EKG
253+
241254
flag test-exe
242255
description: Build the ghcide-test-preprocessor executable
243256
default: True
@@ -358,6 +371,11 @@ executable ghcide
358371

359372
if !flag(executable)
360373
buildable: False
374+
if flag(ekg)
375+
build-depends:
376+
ekg-wai,
377+
ekg-core,
378+
cpp-options: -DMONITORING_EKG
361379

362380
test-suite ghcide-tests
363381
type: exitcode-stdio-1.0

ghcide/src/Development/IDE/Core/Service.hs

Lines changed: 20 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -18,30 +18,30 @@ module Development.IDE.Core.Service(
1818
Log(..),
1919
) where
2020

21-
import Control.Applicative ((<|>))
21+
import Control.Applicative ((<|>))
2222
import Development.IDE.Core.Debouncer
23-
import Development.IDE.Core.FileExists (fileExistsRules)
24-
import Development.IDE.Core.OfInterest hiding (Log, LogShake)
23+
import Development.IDE.Core.FileExists (fileExistsRules)
24+
import Development.IDE.Core.OfInterest hiding (Log, LogShake)
2525
import Development.IDE.Graph
26-
import Development.IDE.Types.Logger as Logger (Logger,
27-
Pretty (pretty),
28-
Priority (Debug),
29-
Recorder,
30-
WithPriority,
31-
cmapWithPrio)
32-
import Development.IDE.Types.Options (IdeOptions (..))
26+
import Development.IDE.Types.Logger as Logger (Logger,
27+
Pretty (pretty),
28+
Priority (Debug),
29+
Recorder,
30+
WithPriority,
31+
cmapWithPrio)
32+
import Development.IDE.Types.Options (IdeOptions (..))
3333
import Ide.Plugin.Config
34-
import qualified Language.LSP.Server as LSP
35-
import qualified Language.LSP.Types as LSP
34+
import qualified Language.LSP.Server as LSP
35+
import qualified Language.LSP.Types as LSP
3636

3737
import Control.Monad
38-
import qualified Development.IDE.Core.FileExists as FileExists
39-
import qualified Development.IDE.Core.OfInterest as OfInterest
40-
import Development.IDE.Core.Shake hiding (Log)
41-
import qualified Development.IDE.Core.Shake as Shake
42-
import Development.IDE.Types.Shake (WithHieDb)
43-
import System.Environment (lookupEnv)
44-
import System.Metrics
38+
import qualified Development.IDE.Core.FileExists as FileExists
39+
import qualified Development.IDE.Core.OfInterest as OfInterest
40+
import Development.IDE.Core.Shake hiding (Log)
41+
import qualified Development.IDE.Core.Shake as Shake
42+
import Development.IDE.Types.Monitoring (Monitoring)
43+
import Development.IDE.Types.Shake (WithHieDb)
44+
import System.Environment (lookupEnv)
4545

4646
data Log
4747
= LogShake Shake.Log
@@ -68,7 +68,7 @@ initialise :: Recorder (WithPriority Log)
6868
-> IdeOptions
6969
-> WithHieDb
7070
-> IndexQueue
71-
-> Maybe Store
71+
-> Monitoring
7272
-> IO IdeState
7373
initialise recorder defaultConfig mainRule lspEnv logger debouncer options withHieDb hiedbChan metrics = do
7474
shakeProfiling <- do

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 25 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,6 @@ import Data.Typeable
118118
import Data.Unique
119119
import Data.Vector (Vector)
120120
import qualified Data.Vector as Vector
121-
import Debug.Trace.Flags (userTracingEnabled)
122121
import Development.IDE.Core.Debouncer
123122
import Development.IDE.Core.FileUtils (getModTime)
124123
import Development.IDE.Core.PositionMapping
@@ -168,8 +167,8 @@ import qualified "list-t" ListT
168167
import qualified StmContainers.Map as STM
169168
import System.FilePath hiding (makeRelative)
170169
import System.IO.Unsafe (unsafePerformIO)
171-
import System.Metrics (Store, registerCounter, registerGauge)
172170
import System.Time.Extra
171+
import Development.IDE.Types.Monitoring (Monitoring(..))
173172

174173
data Log
175174
= LogCreateHieDbExportsMapStart
@@ -464,6 +463,7 @@ data IdeState = IdeState
464463
,shakeSession :: MVar ShakeSession
465464
,shakeExtras :: ShakeExtras
466465
,shakeDatabaseProfile :: ShakeDatabase -> IO (Maybe FilePath)
466+
,stopMonitoring :: IO ()
467467
}
468468

469469

@@ -559,11 +559,13 @@ shakeOpen :: Recorder (WithPriority Log)
559559
-> WithHieDb
560560
-> IndexQueue
561561
-> ShakeOptions
562-
-> Maybe Store
562+
-> Monitoring
563563
-> Rules ()
564564
-> IO IdeState
565565
shakeOpen recorder lspEnv defaultConfig logger debouncer
566-
shakeProfileDir (IdeReportProgress reportProgress) ideTesting@(IdeTesting testing) withHieDb indexQueue opts metrics rules = mdo
566+
shakeProfileDir (IdeReportProgress reportProgress)
567+
ideTesting@(IdeTesting testing)
568+
withHieDb indexQueue opts monitoring rules = mdo
567569
let log :: Logger.Priority -> Log -> IO ()
568570
log = logWith recorder
569571

@@ -611,52 +613,37 @@ shakeOpen recorder lspEnv defaultConfig logger debouncer
611613
rules
612614
shakeSession <- newEmptyMVar
613615
shakeDatabaseProfile <- shakeDatabaseProfileIO shakeProfileDir
614-
let ideState = IdeState{..}
615616

616617
IdeOptions
617618
{ optOTMemoryProfiling = IdeOTMemoryProfiling otProfilingEnabled
618619
, optProgressStyle
619620
, optCheckParents
620621
} <- getIdeOptionsIO shakeExtras
621622

622-
void $ startTelemetry shakeDb shakeExtras
623623
startProfilingTelemetry otProfilingEnabled logger $ state shakeExtras
624624

625625
checkParents <- optCheckParents
626-
for_ metrics $ \store -> do
627-
let readValuesCounter = fromIntegral . countRelevantKeys checkParents <$> getStateKeys shakeExtras
628-
readDirtyKeys = fromIntegral . countRelevantKeys checkParents . HSet.toList <$> readTVarIO(dirtyKeys shakeExtras)
629-
readIndexPending = fromIntegral . HMap.size <$> readTVarIO (indexPending $ hiedbWriter shakeExtras)
630-
readExportsMap = fromIntegral . HMap.size . getExportsMap <$> readTVarIO (exportsMap shakeExtras)
631-
readDatabaseCount = fromIntegral . countRelevantKeys checkParents . map fst <$> shakeGetDatabaseKeys shakeDb
632-
readDatabaseStep = fromIntegral <$> shakeGetBuildStep shakeDb
633-
634-
registerGauge "ghcide.values_count" readValuesCounter store
635-
registerGauge "ghcide.dirty_keys_count" readDirtyKeys store
636-
registerGauge "ghcide.indexing_pending_count" readIndexPending store
637-
registerGauge "ghcide.exports_map_count" readExportsMap store
638-
registerGauge "ghcide.database_count" readDatabaseCount store
639-
registerCounter "ghcide.num_builds" readDatabaseStep store
640626

641-
return ideState
627+
-- monitoring
628+
let readValuesCounter = fromIntegral . countRelevantKeys checkParents <$> getStateKeys shakeExtras
629+
readDirtyKeys = fromIntegral . countRelevantKeys checkParents . HSet.toList <$> readTVarIO(dirtyKeys shakeExtras)
630+
readIndexPending = fromIntegral . HMap.size <$> readTVarIO (indexPending $ hiedbWriter shakeExtras)
631+
readExportsMap = fromIntegral . HMap.size . getExportsMap <$> readTVarIO (exportsMap shakeExtras)
632+
readDatabaseCount = fromIntegral . countRelevantKeys checkParents . map fst <$> shakeGetDatabaseKeys shakeDb
633+
readDatabaseStep = fromIntegral <$> shakeGetBuildStep shakeDb
642634

643-
startTelemetry :: ShakeDatabase -> ShakeExtras -> IO (Async ())
644-
startTelemetry db extras@ShakeExtras{..}
645-
| userTracingEnabled = do
646-
countKeys <- mkValueObserver "cached keys count"
647-
countDirty <- mkValueObserver "dirty keys count"
648-
countBuilds <- mkValueObserver "builds count"
649-
IdeOptions{optCheckParents} <- getIdeOptionsIO extras
650-
checkParents <- optCheckParents
651-
regularly 1 $ do
652-
observe countKeys . countRelevantKeys checkParents =<< getStateKeys extras
653-
readTVarIO dirtyKeys >>= observe countDirty . countRelevantKeys checkParents . HSet.toList
654-
shakeGetBuildStep db >>= observe countBuilds
635+
registerGauge monitoring "ghcide.values_count" readValuesCounter
636+
registerGauge monitoring "ghcide.dirty_keys_count" readDirtyKeys
637+
registerGauge monitoring "ghcide.indexing_pending_count" readIndexPending
638+
registerGauge monitoring "ghcide.exports_map_count" readExportsMap
639+
registerGauge monitoring "ghcide.database_count" readDatabaseCount
640+
registerCounter monitoring "ghcide.num_builds" readDatabaseStep
641+
642+
stopMonitoring <- start monitoring
643+
644+
let ideState = IdeState{..}
645+
return ideState
655646

656-
| otherwise = async (pure ())
657-
where
658-
regularly :: Seconds -> IO () -> IO (Async ())
659-
regularly delay act = async $ forever (act >> sleep delay)
660647

661648
getStateKeys :: ShakeExtras -> IO [Key]
662649
getStateKeys = (fmap.fmap) fst . atomically . ListT.toList . STM.listT . state
@@ -679,6 +666,7 @@ shakeShut IdeState{..} = do
679666
for_ runner cancelShakeSession
680667
void $ shakeDatabaseProfile shakeDb
681668
progressStop $ progress shakeExtras
669+
stopMonitoring
682670

683671

684672
-- | This is a variant of withMVar where the first argument is run unmasked and if it throws

0 commit comments

Comments
 (0)