Skip to content

Commit 37370f4

Browse files
authored
Trace log events and fix ghcide logger (#2277)
* Monoid instance for Logger * trace log events * fix chatty ghcide logger * fix debugging printout * trace build reason * redundant import * trace WatchedFile _changes * log filtered file events
1 parent 426f22a commit 37370f4

File tree

7 files changed

+52
-18
lines changed

7 files changed

+52
-18
lines changed

ghcide/exe/Main.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -8,16 +8,15 @@ module Main(main) where
88
import Arguments (Arguments (..),
99
getArguments)
1010
import Control.Monad.Extra (unless, whenJust)
11-
import Data.Default (Default (def))
1211
import Data.Version (showVersion)
1312
import Development.GitRev (gitHash)
14-
import Development.IDE (action)
13+
import Development.IDE (Priority (Debug, Info),
14+
action)
1515
import Development.IDE.Core.OfInterest (kick)
1616
import Development.IDE.Core.Rules (mainRule)
1717
import Development.IDE.Graph (ShakeOptions (shakeThreads))
1818
import qualified Development.IDE.Main as Main
1919
import qualified Development.IDE.Plugin.HLS.GhcIde as GhcIde
20-
import qualified Development.IDE.Plugin.Test as Test
2120
import Development.IDE.Types.Options
2221
import Ide.Plugin.Config (Config (checkParents, checkProject))
2322
import Ide.PluginUtils (pluginDescToIdePlugins)
@@ -51,7 +50,8 @@ main = do
5150

5251
whenJust argsCwd IO.setCurrentDirectory
5352

54-
let arguments = if argsTesting then Main.testing else def
53+
let logPriority = if argsVerbose then Debug else Info
54+
arguments = if argsTesting then Main.testing else Main.defaultArguments logPriority
5555

5656
Main.defaultMain arguments
5757
{Main.argCommand = argsCommand

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ addFileOfInterest state f v = do
8080
OfInterestVar var <- getIdeGlobalState state
8181
(prev, files) <- modifyVar var $ \dict -> do
8282
let (prev, new) = HashMap.alterF (, Just v) f dict
83-
pure (new, (prev, dict))
83+
pure (new, (prev, new))
8484
when (prev /= Just v) $
8585
recordDirtyKeys (shakeExtras state) IsFileOfInterest [f]
8686
logDebug (ideLogger state) $

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

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -150,6 +150,7 @@ import Data.HashSet (HashSet)
150150
import qualified Data.HashSet as HSet
151151
import Data.IORef.Extra (atomicModifyIORef'_,
152152
atomicModifyIORef_)
153+
import Data.String (fromString)
153154
import Data.Text (pack)
154155
import qualified Development.IDE.Types.Exports as ExportsMap
155156
import HieDb.Types
@@ -546,7 +547,7 @@ shakeOpen lspEnv defaultConfig logger debouncer
546547
-- | Must be called in the 'Initialized' handler and only once
547548
shakeSessionInit :: IdeState -> IO ()
548549
shakeSessionInit IdeState{..} = do
549-
initSession <- newSession shakeExtras shakeDb []
550+
initSession <- newSession shakeExtras shakeDb [] "shakeSessionInit"
550551
putMVar shakeSession initSession
551552

552553
shakeShut :: IdeState -> IO ()
@@ -606,7 +607,7 @@ shakeRestart IdeState{..} reason acts =
606607
-- between spawning the new thread and updating shakeSession.
607608
-- See https://github.com/haskell/ghcide/issues/79
608609
(\() -> do
609-
(,()) <$> newSession shakeExtras shakeDb acts)
610+
(,()) <$> newSession shakeExtras shakeDb acts reason)
610611

611612
notifyTestingLogMessage :: ShakeExtras -> T.Text -> IO ()
612613
notifyTestingLogMessage extras msg = do
@@ -643,8 +644,9 @@ newSession
643644
:: ShakeExtras
644645
-> ShakeDatabase
645646
-> [DelayedActionInternal]
647+
-> String
646648
-> IO ShakeSession
647-
newSession extras@ShakeExtras{..} shakeDb acts = do
649+
newSession extras@ShakeExtras{..} shakeDb acts reason = do
648650
IdeOptions{optRunSubset} <- getIdeOptionsIO extras
649651
reenqueued <- atomically $ peekInProgress actionQueue
650652
allPendingKeys <-
@@ -673,6 +675,7 @@ newSession extras@ShakeExtras{..} shakeDb acts = do
673675
-- The inferred type signature doesn't work in ghc >= 9.0.1
674676
workRun :: (forall b. IO b -> IO b) -> IO (IO ())
675677
workRun restore = withSpan "Shake session" $ \otSpan -> do
678+
setTag otSpan "_reason" (fromString reason)
676679
whenJust allPendingKeys $ \kk -> setTag otSpan "keys" (BS8.pack $ unlines $ map show $ toList kk)
677680
let keysActs = pumpActionThread otSpan : map (run otSpan) (reenqueued ++ acts)
678681
res <- try @SomeException $

ghcide/src/Development/IDE/LSP/Notifications.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -83,15 +83,16 @@ descriptor plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers =
8383
\ide _ (DidChangeWatchedFilesParams (List fileEvents)) -> liftIO $ do
8484
-- See Note [File existence cache and LSP file watchers] which explains why we get these notifications and
8585
-- what we do with them
86-
let msg = show fileEvents
87-
logDebug (ideLogger ide) $ "Watched file events: " <> Text.pack msg
8886
-- filter out files of interest, since we already know all about those
87+
-- filter also uris that do not map to filenames, since we cannot handle them
8988
filesOfInterest <- getFilesOfInterest ide
9089
let fileEvents' =
9190
[ f | f@(FileEvent uri _) <- fileEvents
9291
, Just fp <- [uriToFilePath uri]
9392
, not $ HM.member (toNormalizedFilePath fp) filesOfInterest
9493
]
94+
let msg = show fileEvents'
95+
logDebug (ideLogger ide) $ "Watched file events: " <> Text.pack msg
9596
modifyFileExists ide fileEvents'
9697
resetFileStore ide fileEvents'
9798
setSomethingModified ide [] msg

ghcide/src/Development/IDE/Main.hs

Lines changed: 28 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# OPTIONS_GHC -Wno-orphans #-}
22
module Development.IDE.Main
33
(Arguments(..)
4+
,defaultArguments
45
,Command(..)
56
,IdeCommand(..)
67
,isLSP
@@ -22,12 +23,17 @@ import Data.Hashable (hashed)
2223
import Data.List.Extra (intercalate, isPrefixOf,
2324
nub, nubOrd, partition)
2425
import Data.Maybe (catMaybes, isJust)
26+
import Data.String
2527
import qualified Data.Text as T
28+
import Data.Text.Encoding (encodeUtf8)
2629
import qualified Data.Text.IO as T
2730
import Data.Text.Lazy.Encoding (decodeUtf8)
2831
import qualified Data.Text.Lazy.IO as LT
32+
import Data.Word (Word16)
33+
import Debug.Trace.Flags (userTracingEnabled)
2934
import Development.IDE (Action, GhcVersion (..),
30-
Rules, ghcVersion,
35+
Priority (Debug), Rules,
36+
ghcVersion,
3137
hDuplicateTo')
3238
import Development.IDE.Core.Debouncer (Debouncer,
3339
newAsyncDebouncer)
@@ -64,6 +70,7 @@ import Development.IDE.Session (SessionLoadingOptions,
6470
import Development.IDE.Types.Location (NormalizedUri,
6571
toNormalizedFilePath')
6672
import Development.IDE.Types.Logger (Logger (Logger),
73+
Priority (Info),
6774
logDebug, logInfo)
6875
import Development.IDE.Types.Options (IdeGhcSession,
6976
IdeOptions (optCheckParents, optCheckProject, optReportProgress, optRunSubset),
@@ -94,6 +101,7 @@ import Ide.Types (IdeCommand (IdeCommand),
94101
ipMap)
95102
import qualified Language.LSP.Server as LSP
96103
import Numeric.Natural (Natural)
104+
import OpenTelemetry.Eventlog (addEvent, withSpan)
97105
import Options.Applicative hiding (action)
98106
import qualified System.Directory.Extra as IO
99107
import System.Exit (ExitCode (ExitFailure),
@@ -175,10 +183,13 @@ data Arguments = Arguments
175183
}
176184

177185
instance Default Arguments where
178-
def = Arguments
186+
def = defaultArguments Info
187+
188+
defaultArguments :: Priority -> Arguments
189+
defaultArguments priority = Arguments
179190
{ argsOTMemoryProfiling = False
180191
, argCommand = LSP
181-
, argsLogger = stderrLogger
192+
, argsLogger = stderrLogger priority <> telemetryLogger
182193
, argsRules = mainRule >> action kick
183194
, argsGhcidePlugin = mempty
184195
, argsHlsPlugins = pluginDescToIdePlugins Ghcide.descriptors
@@ -207,7 +218,7 @@ instance Default Arguments where
207218
}
208219

209220
testing :: Arguments
210-
testing = def {
221+
testing = (defaultArguments Debug) {
211222
argsHlsPlugins = pluginDescToIdePlugins $
212223
idePluginsToPluginDesc (argsHlsPlugins def)
213224
++ [Test.blockCommandDescriptor "block-command", Test.plugin],
@@ -219,12 +230,22 @@ testing = def {
219230
}
220231

221232
-- | Cheap stderr logger that relies on LineBuffering
222-
stderrLogger :: IO Logger
223-
stderrLogger = do
233+
stderrLogger :: Priority -> IO Logger
234+
stderrLogger logLevel = do
224235
lock <- newLock
225-
return $ Logger $ \p m -> withLock lock $
236+
return $ Logger $ \p m -> when (p >= logLevel) $ withLock lock $
226237
T.hPutStrLn stderr $ "[" <> T.pack (show p) <> "] " <> m
227238

239+
telemetryLogger :: IO Logger
240+
telemetryLogger
241+
| userTracingEnabled = return $ Logger $ \p m ->
242+
withSpan "log" $ \sp ->
243+
addEvent sp (fromString $ "Log " <> show p) (encodeUtf8 $ trim m)
244+
| otherwise = mempty
245+
where
246+
-- eventlog message size is limited by EVENT_PAYLOAD_SIZE_MAX = STG_WORD16_MAX
247+
trim = T.take (fromIntegral(maxBound :: Word16) - 10)
248+
228249
defaultMain :: Arguments -> IO ()
229250
defaultMain Arguments{..} = do
230251
setLocaleEncoding utf8

ghcide/src/Development/IDE/Types/Logger.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,11 @@ data Priority
3333
-- if our code has gone wrong and is itself erroneous (e.g. we threw an exception).
3434
data Logger = Logger {logPriority :: Priority -> T.Text -> IO ()}
3535

36+
instance Semigroup Logger where
37+
l1 <> l2 = Logger $ \p t -> logPriority l1 p t >> logPriority l2 p t
38+
39+
instance Monoid Logger where
40+
mempty = Logger $ \_ _ -> pure ()
3641

3742
logError :: Logger -> T.Text -> IO ()
3843
logError x = logPriority x Error

hls-plugin-api/src/Ide/Types.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,8 +9,10 @@
99
{-# LANGUAGE FlexibleInstances #-}
1010
{-# LANGUAGE GADTs #-}
1111
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
12+
{-# LANGUAGE NamedFieldPuns #-}
1213
{-# LANGUAGE OverloadedStrings #-}
1314
{-# LANGUAGE PolyKinds #-}
15+
{-# LANGUAGE RecordWildCards #-}
1416
{-# LANGUAGE ScopedTypeVariables #-}
1517
{-# LANGUAGE TypeFamilies #-}
1618
{-# LANGUAGE UndecidableInstances #-}
@@ -482,7 +484,9 @@ instance {-# OVERLAPPABLE #-} (HasTextDocument a doc, HasUri doc Uri) => HasTrac
482484

483485
instance HasTracing Value
484486
instance HasTracing ExecuteCommandParams
485-
instance HasTracing DidChangeWatchedFilesParams
487+
instance HasTracing DidChangeWatchedFilesParams where
488+
traceWithSpan sp DidChangeWatchedFilesParams{_changes} =
489+
setTag sp "changes" (encodeUtf8 $ fromString $ show _changes)
486490
instance HasTracing DidChangeWorkspaceFoldersParams
487491
instance HasTracing DidChangeConfigurationParams
488492
instance HasTracing InitializeParams

0 commit comments

Comments
 (0)