Skip to content
Merged
Show file tree
Hide file tree
Changes from 3 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
14 changes: 12 additions & 2 deletions ghcide/src/Development/IDE/Core/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -102,6 +102,7 @@ import Data.Functor
import qualified Data.HashMap.Strict as HashMap
import Data.Tuple.Extra (dupe)
import Data.Unique as Unique
import Development.IDE.Core.Tracing (withTrace)
import qualified Language.LSP.Server as LSP
import qualified Language.LSP.Types as LSP

Expand Down Expand Up @@ -899,7 +900,8 @@ loadHieFile ncu f = do
-- Assumes file exists.
-- Requires the 'HscEnv' to be set up with dependencies
loadInterface
:: MonadIO m => HscEnv
:: (MonadIO m, MonadMask m)
=> HscEnv
-> ModSummary
-> SourceModified
-> Maybe LinkableType
Expand Down Expand Up @@ -939,7 +941,15 @@ loadInterface session ms sourceMod linkableNeeded regen = do
hmi <- liftIO $ mkDetailsFromIface sessionWithMsDynFlags iface linkable
return ([], Just $ mkHiFileResult ms hmi)
else regen linkableNeeded
(_reason, _) -> regen linkableNeeded
(_reason, _) -> withTrace "regenerate interface" $ \setTag -> do
setTag "Module" $ moduleNameString $ moduleName $ ms_mod ms
setTag "Reason" $ showReason _reason
regen linkableNeeded

showReason :: RecompileRequired -> String
showReason UpToDate = "UpToDate"
showReason MustCompile = "MustCompile"
showReason (RecompBecause s) = s

mkDetailsFromIface :: HscEnv -> ModIface -> Maybe Linkable -> IO HomeModInfo
mkDetailsFromIface session iface linkable = do
Expand Down
4 changes: 3 additions & 1 deletion ghcide/src/Development/IDE/Core/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -439,8 +439,10 @@ recordDirtyKeys
-> k
-> [NormalizedFilePath]
-> IO ()
recordDirtyKeys ShakeExtras{dirtyKeys} key file =
recordDirtyKeys ShakeExtras{dirtyKeys} key file = withEventTrace "recordDirtyKeys" $ \addEvent -> do
atomicModifyIORef_ dirtyKeys $ \x -> foldl' (flip HSet.insert) x (toKey key <$> file)
addEvent (fromString $ "dirty " <> show key) (fromString $ unlines $ map fromNormalizedFilePath file)


-- | We return Nothing if the rule has not run and Just Failed if it has failed to produce a value.
getValues ::
Expand Down
27 changes: 23 additions & 4 deletions ghcide/src/Development/IDE/Core/Tracing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,8 @@ module Development.IDE.Core.Tracing
, getInstrumentCached
, otTracedProvider
, otSetUri
)
, withTrace
,withEventTrace)
where

import Control.Concurrent.Async (Async, async)
Expand All @@ -19,13 +20,11 @@ import Control.Exception.Safe (SomeException, catch,
generalBracket)
import Control.Monad (forM_, forever, void, when,
(>=>))
import Control.Monad.Catch (ExitCase (..))
import Control.Monad.Catch (ExitCase (..), MonadMask)
import Control.Monad.Extra (whenJust)
import Control.Monad.IO.Unlift
import Control.Seq (r0, seqList, seqTuple2, using)
#if MIN_VERSION_ghc(8,8,0)
import Data.ByteString (ByteString)
#endif
import Data.ByteString.Char8 (pack)
import Data.Dynamic (Dynamic)
import qualified Data.HashMap.Strict as HMap
Expand Down Expand Up @@ -57,6 +56,26 @@ import OpenTelemetry.Eventlog (Instrument, SpanInFlight (..),
mkValueObserver, observe,
setTag, withSpan, withSpan_)

withTrace :: (MonadMask m, MonadIO m) =>
String -> ((String -> String -> m ()) -> m a) -> m a
withTrace name act
| userTracingEnabled
= withSpan (fromString name) $ \sp -> do
let setSpan' k v = setTag sp (fromString k) (fromString v)
act setSpan'
| otherwise = act (\_ _ -> pure ())

#if MIN_VERSION_ghc(8,8,0)
withEventTrace :: (MonadMask m, MonadIO m) => String -> ((ByteString -> ByteString -> m ()) -> m a) -> m a
#else
withEventTrace :: (MonadMask m, MonadIO m) => String -> ((String -> ByteString -> m ()) -> m a) -> m a
#endif
withEventTrace name act
| userTracingEnabled
= withSpan (fromString name) $ \sp -> do
act (addEvent sp)
| otherwise = act (\_ _ -> pure ())

-- | Trace a handler using OpenTelemetry. Adds various useful info into tags in the OpenTelemetry span.
otTracedHandler
:: MonadUnliftIO m
Expand Down
8 changes: 4 additions & 4 deletions ghcide/src/Development/IDE/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,8 @@ import Development.IDE.Core.Service (initialise, runAction)
import Development.IDE.Core.Shake (IdeState (shakeExtras),
ShakeExtras (state),
shakeSessionInit, uses)
import Development.IDE.Core.Tracing (measureMemory)
import Development.IDE.Core.Tracing (measureMemory,
withEventTrace)
import Development.IDE.Graph (action)
import Development.IDE.LSP.LanguageServer (runLanguageServer)
import Development.IDE.Plugin (Plugin (pluginHandlers, pluginModifyDynflags, pluginRules))
Expand Down Expand Up @@ -101,7 +102,6 @@ import Ide.Types (IdeCommand (IdeCommand),
ipMap)
import qualified Language.LSP.Server as LSP
import Numeric.Natural (Natural)
import OpenTelemetry.Eventlog (addEvent, withSpan)
import Options.Applicative hiding (action)
import qualified System.Directory.Extra as IO
import System.Exit (ExitCode (ExitFailure),
Expand Down Expand Up @@ -239,8 +239,8 @@ stderrLogger logLevel = do
telemetryLogger :: IO Logger
telemetryLogger
| userTracingEnabled = return $ Logger $ \p m ->
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

withEventTrace also contains this guard. You could remove it; but that would change this from a single check of userTracingEnabled to create a no-op Logger to a check of userTracingEnabled on every step. Not sure if that's bad, but probably worth a comment to make it clear it's a deliberate decision if so.

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

good shout, I'll add a comment

withSpan "log" $ \sp ->
addEvent sp (fromString $ "Log " <> show p) (encodeUtf8 $ trim m)
withEventTrace "Log" $ \addEvent ->
addEvent (fromString $ "Log " <> show p) (encodeUtf8 $ trim m)
| otherwise = mempty
where
-- eventlog message size is limited by EVENT_PAYLOAD_SIZE_MAX = STG_WORD16_MAX
Expand Down