@@ -168,11 +168,11 @@ import qualified Language.LSP.Server as LSP
168168import Language.LSP.VFS hiding (start )
169169import qualified "list-t" ListT
170170import OpenTelemetry.Eventlog hiding (addEvent )
171+ import qualified Prettyprinter as Pretty
171172import qualified StmContainers.Map as STM
172173import System.FilePath hiding (makeRelative )
173174import System.IO.Unsafe (unsafePerformIO )
174175import System.Time.Extra
175-
176176-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
177177
178178#if !MIN_VERSION_ghc(9,3,0)
@@ -191,6 +191,12 @@ data Log
191191 | LogDiagsDiffButNoLspEnv ! [FileDiagnostic ]
192192 | LogDefineEarlyCutoffRuleNoDiagHasDiag ! FileDiagnostic
193193 | LogDefineEarlyCutoffRuleCustomNewnessHasDiag ! FileDiagnostic
194+ | LogCancelledAction ! T. Text
195+ | LogSessionInitialised
196+ | LogLookupPersistentKey ! T. Text
197+ | LogShakeGarbageCollection ! T. Text ! Int ! Seconds
198+ -- * OfInterest Log messages
199+ | LogSetFilesOfInterest ! [(NormalizedFilePath , FileOfInterestStatus )]
194200 deriving Show
195201
196202instance Pretty Log where
@@ -224,6 +230,16 @@ instance Pretty Log where
224230 LogDefineEarlyCutoffRuleCustomNewnessHasDiag fileDiagnostic ->
225231 " defineEarlyCutoff RuleWithCustomNewnessCheck - file diagnostic:"
226232 <+> pretty (showDiagnosticsColored [fileDiagnostic])
233+ LogCancelledAction action ->
234+ pretty action <+> " was cancelled"
235+ LogSessionInitialised -> " Shake session initialized"
236+ LogLookupPersistentKey key ->
237+ " LOOKUP PERSISTENT FOR:" <+> pretty key
238+ LogShakeGarbageCollection label number duration ->
239+ pretty label <+> " of" <+> pretty number <+> " keys (took " <+> pretty (showDuration duration) <> " )"
240+ LogSetFilesOfInterest ofInterest ->
241+ " Set files of interst to" <> Pretty. line
242+ <> indent 4 (pretty $ fmap (first fromNormalizedFilePath) ofInterest)
227243
228244-- | We need to serialize writes to the database, so we send any function that
229245-- needs to write to the database over the channel, where it will be picked up by
@@ -254,7 +270,7 @@ data ShakeExtras = ShakeExtras
254270 { -- eventer :: LSP.FromServerMessage -> IO ()
255271 lspEnv :: Maybe (LSP. LanguageContextEnv Config )
256272 ,debouncer :: Debouncer NormalizedUri
257- ,logger :: Logger
273+ ,shakeRecorder :: Recorder ( WithPriority Log )
258274 ,idePlugins :: IdePlugins IdeState
259275 ,globals :: TVar (HMap. HashMap TypeRep Dynamic )
260276 -- ^ Registry of global state used by rules.
@@ -439,7 +455,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
439455 | otherwise = do
440456 pmap <- readTVarIO persistentKeys
441457 mv <- runMaybeT $ do
442- liftIO $ Logger. logDebug (logger s) $ T. pack $ " LOOKUP PERSISTENT FOR: " ++ show k
458+ liftIO $ logWith (shakeRecorder s) Debug $ LogLookupPersistentKey ( T. pack $ show k)
443459 f <- MaybeT $ pure $ lookupKeyMap (newKey k) pmap
444460 (dv,del,ver) <- MaybeT $ runIdeAction " lastValueIO" s $ f file
445461 MaybeT $ pure $ (,del,ver) <$> fromDynamic dv
@@ -602,7 +618,6 @@ shakeOpen :: Recorder (WithPriority Log)
602618 -> Maybe (LSP. LanguageContextEnv Config )
603619 -> Config
604620 -> IdePlugins IdeState
605- -> Logger
606621 -> Debouncer NormalizedUri
607622 -> Maybe FilePath
608623 -> IdeReportProgress
@@ -613,7 +628,7 @@ shakeOpen :: Recorder (WithPriority Log)
613628 -> Monitoring
614629 -> Rules ()
615630 -> IO IdeState
616- shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer
631+ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
617632 shakeProfileDir (IdeReportProgress reportProgress)
618633 ideTesting@ (IdeTesting testing)
619634 withHieDb indexQueue opts monitoring rules = mdo
@@ -660,7 +675,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer
660675 dirtyKeys <- newTVarIO mempty
661676 -- Take one VFS snapshot at the start
662677 vfsVar <- newTVarIO =<< vfsSnapshot lspEnv
663- pure ShakeExtras {.. }
678+ pure ShakeExtras {shakeRecorder = recorder, .. }
664679 shakeDb <-
665680 shakeNewDatabase
666681 opts { shakeExtra = newShakeExtra shakeExtras }
@@ -707,7 +722,7 @@ shakeSessionInit recorder ide@IdeState{..} = do
707722 vfs <- vfsSnapshot (lspEnv shakeExtras)
708723 initSession <- newSession recorder shakeExtras (VFSModified vfs) shakeDb [] " shakeSessionInit"
709724 putMVar shakeSession initSession
710- logDebug (ideLogger ide) " Shake session initialized "
725+ logWith recorder Debug LogSessionInitialised
711726
712727shakeShut :: IdeState -> IO ()
713728shakeShut IdeState {.. } = do
@@ -775,7 +790,7 @@ shakeRestart recorder IdeState{..} vfs reason acts =
775790--
776791-- Appropriate for user actions other than edits.
777792shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a )
778- shakeEnqueue ShakeExtras {actionQueue, logger } act = do
793+ shakeEnqueue ShakeExtras {actionQueue, shakeRecorder } act = do
779794 (b, dai) <- instantiateDelayedAction act
780795 atomicallyNamed " actionQueue - push" $ pushQueue dai actionQueue
781796 let wait' barrier =
@@ -784,7 +799,7 @@ shakeEnqueue ShakeExtras{actionQueue, logger} act = do
784799 fail $ " internal bug: forever blocked on MVar for " <>
785800 actionName act)
786801 , Handler (\ e@ AsyncCancelled -> do
787- logPriority logger Debug $ T. pack $ actionName act <> " was cancelled "
802+ logWith shakeRecorder Debug $ LogCancelledAction ( T. pack $ actionName act)
788803
789804 atomicallyNamed " actionQueue - abort" $ abortQueue dai actionQueue
790805 throw e)
@@ -908,13 +923,12 @@ garbageCollectDirtyKeysOlderThan maxAge checkParents = otTracedGarbageCollection
908923garbageCollectKeys :: String -> Int -> CheckParents -> [(Key , Int )] -> Action [Key ]
909924garbageCollectKeys label maxAge checkParents agedKeys = do
910925 start <- liftIO offsetTime
911- ShakeExtras {state, dirtyKeys, lspEnv, logger , ideTesting} <- getShakeExtras
926+ ShakeExtras {state, dirtyKeys, lspEnv, shakeRecorder , ideTesting} <- getShakeExtras
912927 (n:: Int , garbage ) <- liftIO $
913928 foldM (removeDirtyKey dirtyKeys state) (0 ,[] ) agedKeys
914929 t <- liftIO start
915930 when (n> 0 ) $ liftIO $ do
916- logDebug logger $ T. pack $
917- label <> " of " <> show n <> " keys (took " <> showDuration t <> " )"
931+ logWith shakeRecorder Debug $ LogShakeGarbageCollection (T. pack label) n t
918932 when (coerce ideTesting) $ liftIO $ mRunLspT lspEnv $
919933 LSP. sendNotification (SMethod_CustomMethod (Proxy @ " ghcide/GC" ))
920934 (toJSON $ mapMaybe (fmap showKey . fromKeyType) garbage)
@@ -1305,13 +1319,11 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
13051319 | otherwise = c
13061320
13071321
1308- ideLogger :: IdeState -> Logger
1309- ideLogger IdeState {shakeExtras= ShakeExtras {logger }} = logger
1322+ ideLogger :: IdeState -> Recorder ( WithPriority Log )
1323+ ideLogger IdeState {shakeExtras= ShakeExtras {shakeRecorder }} = shakeRecorder
13101324
1311- actionLogger :: Action Logger
1312- actionLogger = do
1313- ShakeExtras {logger} <- getShakeExtras
1314- return logger
1325+ actionLogger :: Action (Recorder (WithPriority Log ))
1326+ actionLogger = shakeRecorder <$> getShakeExtras
13151327
13161328--------------------------------------------------------------------------------
13171329type STMDiagnosticStore = STM. Map NormalizedUri StoreItem
0 commit comments