@@ -168,11 +168,11 @@ import qualified Language.LSP.Server as LSP
168
168
import Language.LSP.VFS hiding (start )
169
169
import qualified "list-t" ListT
170
170
import OpenTelemetry.Eventlog hiding (addEvent )
171
+ import qualified Prettyprinter as Pretty
171
172
import qualified StmContainers.Map as STM
172
173
import System.FilePath hiding (makeRelative )
173
174
import System.IO.Unsafe (unsafePerformIO )
174
175
import System.Time.Extra
175
-
176
176
-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
177
177
178
178
#if !MIN_VERSION_ghc(9,3,0)
@@ -191,6 +191,12 @@ data Log
191
191
| LogDiagsDiffButNoLspEnv ! [FileDiagnostic ]
192
192
| LogDefineEarlyCutoffRuleNoDiagHasDiag ! FileDiagnostic
193
193
| 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 )]
194
200
deriving Show
195
201
196
202
instance Pretty Log where
@@ -224,6 +230,16 @@ instance Pretty Log where
224
230
LogDefineEarlyCutoffRuleCustomNewnessHasDiag fileDiagnostic ->
225
231
" defineEarlyCutoff RuleWithCustomNewnessCheck - file diagnostic:"
226
232
<+> 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)
227
243
228
244
-- | We need to serialize writes to the database, so we send any function that
229
245
-- needs to write to the database over the channel, where it will be picked up by
@@ -254,7 +270,7 @@ data ShakeExtras = ShakeExtras
254
270
{ -- eventer :: LSP.FromServerMessage -> IO ()
255
271
lspEnv :: Maybe (LSP. LanguageContextEnv Config )
256
272
,debouncer :: Debouncer NormalizedUri
257
- ,logger :: Logger
273
+ ,shakeRecorder :: Recorder ( WithPriority Log )
258
274
,idePlugins :: IdePlugins IdeState
259
275
,globals :: TVar (HMap. HashMap TypeRep Dynamic )
260
276
-- ^ Registry of global state used by rules.
@@ -439,7 +455,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
439
455
| otherwise = do
440
456
pmap <- readTVarIO persistentKeys
441
457
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)
443
459
f <- MaybeT $ pure $ lookupKeyMap (newKey k) pmap
444
460
(dv,del,ver) <- MaybeT $ runIdeAction " lastValueIO" s $ f file
445
461
MaybeT $ pure $ (,del,ver) <$> fromDynamic dv
@@ -602,7 +618,6 @@ shakeOpen :: Recorder (WithPriority Log)
602
618
-> Maybe (LSP. LanguageContextEnv Config )
603
619
-> Config
604
620
-> IdePlugins IdeState
605
- -> Logger
606
621
-> Debouncer NormalizedUri
607
622
-> Maybe FilePath
608
623
-> IdeReportProgress
@@ -613,7 +628,7 @@ shakeOpen :: Recorder (WithPriority Log)
613
628
-> Monitoring
614
629
-> Rules ()
615
630
-> IO IdeState
616
- shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer
631
+ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
617
632
shakeProfileDir (IdeReportProgress reportProgress)
618
633
ideTesting@ (IdeTesting testing)
619
634
withHieDb indexQueue opts monitoring rules = mdo
@@ -660,7 +675,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer
660
675
dirtyKeys <- newTVarIO mempty
661
676
-- Take one VFS snapshot at the start
662
677
vfsVar <- newTVarIO =<< vfsSnapshot lspEnv
663
- pure ShakeExtras {.. }
678
+ pure ShakeExtras {shakeRecorder = recorder, .. }
664
679
shakeDb <-
665
680
shakeNewDatabase
666
681
opts { shakeExtra = newShakeExtra shakeExtras }
@@ -707,7 +722,7 @@ shakeSessionInit recorder ide@IdeState{..} = do
707
722
vfs <- vfsSnapshot (lspEnv shakeExtras)
708
723
initSession <- newSession recorder shakeExtras (VFSModified vfs) shakeDb [] " shakeSessionInit"
709
724
putMVar shakeSession initSession
710
- logDebug (ideLogger ide) " Shake session initialized "
725
+ logWith recorder Debug LogSessionInitialised
711
726
712
727
shakeShut :: IdeState -> IO ()
713
728
shakeShut IdeState {.. } = do
@@ -775,7 +790,7 @@ shakeRestart recorder IdeState{..} vfs reason acts =
775
790
--
776
791
-- Appropriate for user actions other than edits.
777
792
shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a )
778
- shakeEnqueue ShakeExtras {actionQueue, logger } act = do
793
+ shakeEnqueue ShakeExtras {actionQueue, shakeRecorder } act = do
779
794
(b, dai) <- instantiateDelayedAction act
780
795
atomicallyNamed " actionQueue - push" $ pushQueue dai actionQueue
781
796
let wait' barrier =
@@ -784,7 +799,7 @@ shakeEnqueue ShakeExtras{actionQueue, logger} act = do
784
799
fail $ " internal bug: forever blocked on MVar for " <>
785
800
actionName act)
786
801
, Handler (\ e@ AsyncCancelled -> do
787
- logPriority logger Debug $ T. pack $ actionName act <> " was cancelled "
802
+ logWith shakeRecorder Debug $ LogCancelledAction ( T. pack $ actionName act)
788
803
789
804
atomicallyNamed " actionQueue - abort" $ abortQueue dai actionQueue
790
805
throw e)
@@ -908,13 +923,12 @@ garbageCollectDirtyKeysOlderThan maxAge checkParents = otTracedGarbageCollection
908
923
garbageCollectKeys :: String -> Int -> CheckParents -> [(Key , Int )] -> Action [Key ]
909
924
garbageCollectKeys label maxAge checkParents agedKeys = do
910
925
start <- liftIO offsetTime
911
- ShakeExtras {state, dirtyKeys, lspEnv, logger , ideTesting} <- getShakeExtras
926
+ ShakeExtras {state, dirtyKeys, lspEnv, shakeRecorder , ideTesting} <- getShakeExtras
912
927
(n:: Int , garbage ) <- liftIO $
913
928
foldM (removeDirtyKey dirtyKeys state) (0 ,[] ) agedKeys
914
929
t <- liftIO start
915
930
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
918
932
when (coerce ideTesting) $ liftIO $ mRunLspT lspEnv $
919
933
LSP. sendNotification (SMethod_CustomMethod (Proxy @ " ghcide/GC" ))
920
934
(toJSON $ mapMaybe (fmap showKey . fromKeyType) garbage)
@@ -1305,13 +1319,11 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
1305
1319
| otherwise = c
1306
1320
1307
1321
1308
- ideLogger :: IdeState -> Logger
1309
- ideLogger IdeState {shakeExtras= ShakeExtras {logger }} = logger
1322
+ ideLogger :: IdeState -> Recorder ( WithPriority Log )
1323
+ ideLogger IdeState {shakeExtras= ShakeExtras {shakeRecorder }} = shakeRecorder
1310
1324
1311
- actionLogger :: Action Logger
1312
- actionLogger = do
1313
- ShakeExtras {logger} <- getShakeExtras
1314
- return logger
1325
+ actionLogger :: Action (Recorder (WithPriority Log ))
1326
+ actionLogger = shakeRecorder <$> getShakeExtras
1315
1327
1316
1328
--------------------------------------------------------------------------------
1317
1329
type STMDiagnosticStore = STM. Map NormalizedUri StoreItem
0 commit comments