Skip to content

Commit

Permalink
confine CPP to the EKG module
Browse files Browse the repository at this point in the history
  • Loading branch information
pepeiborra committed May 6, 2022
1 parent 700d73f commit e7f3df4
Show file tree
Hide file tree
Showing 6 changed files with 22 additions and 33 deletions.
3 changes: 0 additions & 3 deletions ghcide/.hlint.yaml
Expand Up @@ -111,7 +111,6 @@
- Development.IDE.GHC.Util
- Development.IDE.Import.FindImports
- Development.IDE.LSP.Outline
- Development.IDE.Main
- Development.IDE.Spans.Calculate
- Development.IDE.Spans.Documentation
- Development.IDE.Spans.Common
Expand All @@ -123,8 +122,6 @@
- Development.IDE.Plugin.Completions
- Development.IDE.Plugin.Completions.Logic
- Development.IDE.Types.Location
- Main
- Arguments

- flags:
- default: false
Expand Down
7 changes: 1 addition & 6 deletions ghcide/exe/Arguments.hs
@@ -1,7 +1,6 @@
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0

{-# LANGUAGE CPP #-}
module Arguments(Arguments(..), getArguments) where

import Development.IDE (IdeState)
Expand All @@ -20,9 +19,7 @@ data Arguments = Arguments
,argsVerbose :: Bool
,argsCommand :: Command
,argsConservativeChangeTracking :: Bool
#ifdef MONITORING_EKG
,argsMonitoringPort :: Int
#endif
}

getArguments :: IdePlugins IdeState -> IO Arguments
Expand All @@ -44,9 +41,7 @@ arguments plugins = Arguments
<*> switch (short 'd' <> long "verbose" <> help "Include internal events in logging output")
<*> (commandP plugins <|> lspCommand <|> checkCommand)
<*> switch (long "conservative-change-tracking" <> help "disable reactive change tracking (for testing/debugging)")
#ifdef MONITORING_EKG
<*> option auto (long "monitoring-port" <> metavar "PORT" <> value 8999 <> showDefault <> help "Port to use for monitoring")
#endif
<*> option auto (long "monitoring-port" <> metavar "PORT" <> value 8999 <> showDefault <> help "Port to use for EKG monitoring (if the binary is built with EKG)")
where
checkCommand = Check <$> many (argument str (metavar "FILES/DIRS..."))
lspCommand = LSP <$ flag' True (long "lsp" <> help "Start talking to an LSP client")
10 changes: 2 additions & 8 deletions ghcide/exe/Main.hs
@@ -1,7 +1,6 @@
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}

module Main(main) where
Expand All @@ -20,6 +19,8 @@ import Development.IDE.Core.Rules (mainRule)
import qualified Development.IDE.Core.Rules as Rules
import Development.IDE.Core.Tracing (withTelemetryLogger)
import qualified Development.IDE.Main as IDEMain
import qualified Development.IDE.Monitoring.OpenTelemetry as OpenTelemetry
import qualified Development.IDE.Monitoring.EKG as EKG
import qualified Development.IDE.Plugin.HLS.GhcIde as GhcIde
import Development.IDE.Types.Logger (Logger (Logger),
LoggingColumn (DataColumn, PriorityColumn),
Expand All @@ -43,11 +44,6 @@ import System.Exit (exitSuccess)
import System.IO (hPutStrLn, stderr)
import System.Info (compilerVersion)

#ifdef MONITORING_EKG
import qualified Development.IDE.Monitoring.OpenTelemetry as OpenTelemetry
import qualified Development.IDE.Monitoring.EKG as EKG
#endif

data Log
= LogIDEMain IDEMain.Log
| LogRules Rules.Log
Expand Down Expand Up @@ -147,7 +143,5 @@ main = withTelemetryLogger $ \telemetryLogger -> do
, optCheckProject = pure $ checkProject config
, optRunSubset = not argsConservativeChangeTracking
}
#ifdef MONITORING_EKG
, IDEMain.argsMonitoring = OpenTelemetry.monitoring <> EKG.monitoring logger argsMonitoringPort
#endif
}
3 changes: 1 addition & 2 deletions ghcide/ghcide.cabal
Expand Up @@ -187,6 +187,7 @@ library
Development.IDE.GHC.Util
Development.IDE.Import.DependencyInformation
Development.IDE.Import.FindImports
Development.IDE.Monitoring.EKG
Development.IDE.LSP.HoverDefinition
Development.IDE.LSP.LanguageServer
Development.IDE.LSP.Outline
Expand Down Expand Up @@ -248,8 +249,6 @@ library
ekg-wai,
ekg-core,
cpp-options: -DMONITORING_EKG
exposed-modules:
Development.IDE.Monitoring.EKG

flag test-exe
description: Build the ghcide-test-preprocessor executable
Expand Down
15 changes: 4 additions & 11 deletions ghcide/src/Development/IDE/Main.hs
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE PackageImports #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Development.IDE.Main
Expand Down Expand Up @@ -63,6 +62,9 @@ import Development.IDE.LSP.LanguageServer (runLanguageServer)
import qualified Development.IDE.LSP.LanguageServer as LanguageServer
import Development.IDE.Main.HeapStats (withHeapStats)
import qualified Development.IDE.Main.HeapStats as HeapStats
import Development.IDE.Types.Monitoring (Monitoring)
import qualified Development.IDE.Monitoring.EKG as EKG
import qualified Development.IDE.Monitoring.OpenTelemetry as OpenTelemetry
import Development.IDE.Plugin (Plugin (pluginHandlers, pluginModifyDynflags, pluginRules))
import Development.IDE.Plugin.HLS (asGhcIdePlugin)
import qualified Development.IDE.Plugin.HLS as PluginHLS
Expand Down Expand Up @@ -130,12 +132,6 @@ import System.Random (newStdGen)
import System.Time.Extra (Seconds, offsetTime,
showDuration)
import Text.Printf (printf)
import Development.IDE.Types.Monitoring (Monitoring)
import qualified Development.IDE.Monitoring.OpenTelemetry as OpenTelemetry

#ifdef MONITORING_EKG
import qualified Development.IDE.Monitoring.EKG as EKG
#endif

data Log
= LogHeapStats !HeapStats.Log
Expand Down Expand Up @@ -275,10 +271,7 @@ defaultArguments recorder logger = Arguments
-- the language server tests without the redirection.
putStr " " >> hFlush stdout
return newStdout
, argsMonitoring = OpenTelemetry.monitoring
#ifdef MONITORING_EKG
<> EKG.monitoring logger 8999
#endif
, argsMonitoring = OpenTelemetry.monitoring <> EKG.monitoring logger 8999
}


Expand Down
17 changes: 14 additions & 3 deletions ghcide/src/Development/IDE/Monitoring/EKG.hs
@@ -1,12 +1,16 @@
{-# LANGUAGE CPP #-}
module Development.IDE.Monitoring.EKG(monitoring) where

import Development.IDE.Types.Monitoring (Monitoring (..))
import Development.IDE.Types.Logger (Logger)
#ifdef MONITORING_EKG
import Control.Concurrent (killThread)
import Control.Concurrent.Async (async, waitCatch)
import Control.Monad (forM_)
import Data.Text (pack)
import Development.IDE.Types.Logger (Logger, logInfo)
import Development.IDE.Types.Monitoring (Monitoring (..))
import qualified System.Metrics as Monitoring
import Development.IDE.Types.Logger (logInfo)
import qualified System.Remote.Monitoring.Wai as Monitoring
import qualified System.Metrics as Monitoring

-- | Monitoring using EKG
monitoring :: Logger -> Int -> IO Monitoring
Expand Down Expand Up @@ -35,3 +39,10 @@ monitoring logger port = do
logInfo logger "Stopping monitoring server"
killThread $ Monitoring.serverThreadId s
return $ Monitoring {..}

#else

monitoring :: Logger -> Int -> IO Monitoring
monitoring _ _ = mempty

#endif

0 comments on commit e7f3df4

Please sign in to comment.