@@ -77,6 +77,7 @@ module Development.IDE.Core.Shake(
77
77
addPersistentRule ,
78
78
garbageCollectDirtyKeys ,
79
79
garbageCollectDirtyKeysOlderThan ,
80
+ Log
80
81
) where
81
82
82
83
import Control.Concurrent.Async
@@ -149,6 +150,7 @@ import Language.LSP.Types.Capabilities
149
150
import OpenTelemetry.Eventlog
150
151
151
152
import Control.Concurrent.STM.Stats (atomicallyNamed )
153
+ import Control.Exception.Base (SomeException (SomeException ))
152
154
import Control.Exception.Extra hiding (bracket_ )
153
155
import Data.Aeson (toJSON )
154
156
import qualified Data.ByteString.Char8 as BS8
@@ -160,6 +162,7 @@ import qualified Data.HashSet as HSet
160
162
import Data.String (fromString )
161
163
import Data.Text (pack )
162
164
import Debug.Trace.Flags (userTracingEnabled )
165
+ import Development.IDE.Types.Action (DelayedActionInternal )
163
166
import qualified Development.IDE.Types.Exports as ExportsMap
164
167
import qualified Focus
165
168
import HieDb.Types
@@ -169,6 +172,16 @@ import Ide.Types (PluginId)
169
172
import qualified "list-t" ListT
170
173
import qualified StmContainers.Map as STM
171
174
175
+ data Log
176
+ = LogCreateHieDbExportsMapStart
177
+ -- logDebug logger "Initializing exports map from hiedb"
178
+ | LogCreateHieDbExportsMapFinish ! Int
179
+ -- logDebug logger $ "Done initializing exports map from hiedb (" <> pack(show (ExportsMap.size em)) <> ")"
180
+ | LogBuildSessionRestart ! String ! [DelayedActionInternal ] ! (HashSet Key ) ! Seconds ! (Maybe FilePath )
181
+ | LogDelayedAction ! (DelayedAction () ) ! Seconds
182
+ | LogBuildSessionFinish ! (Maybe SomeException )
183
+ deriving Show
184
+
172
185
-- | We need to serialize writes to the database, so we send any function that
173
186
-- needs to write to the database over the channel, where it will be picked up by
174
187
-- a worker thread.
@@ -494,7 +507,8 @@ seqValue val = case val of
494
507
Failed _ -> val
495
508
496
509
-- | Open a 'IdeState', should be shut using 'shakeShut'.
497
- shakeOpen :: Maybe (LSP. LanguageContextEnv Config )
510
+ shakeOpen :: Recorder Log
511
+ -> Maybe (LSP. LanguageContextEnv Config )
498
512
-> Config
499
513
-> Logger
500
514
-> Debouncer NormalizedUri
@@ -507,8 +521,10 @@ shakeOpen :: Maybe (LSP.LanguageContextEnv Config)
507
521
-> ShakeOptions
508
522
-> Rules ()
509
523
-> IO IdeState
510
- shakeOpen lspEnv defaultConfig logger debouncer
524
+ shakeOpen recorder lspEnv defaultConfig logger debouncer
511
525
shakeProfileDir (IdeReportProgress reportProgress) ideTesting@ (IdeTesting testing) withHieDb indexQueue vfs opts rules = mdo
526
+ let log :: Log -> IO ()
527
+ log = logWith recorder
512
528
513
529
us <- mkSplitUniqSupply ' r'
514
530
ideNc <- newIORef (initNameCache us knownKeyNames)
@@ -520,19 +536,20 @@ shakeOpen lspEnv defaultConfig logger debouncer
520
536
publishedDiagnostics <- STM. newIO
521
537
positionMapping <- STM. newIO
522
538
knownTargetsVar <- newTVarIO $ hashed HMap. empty
523
- let restartShakeSession = shakeRestart ideState
539
+ let restartShakeSession = shakeRestart recorder ideState
524
540
persistentKeys <- newTVarIO HMap. empty
525
541
indexPending <- newTVarIO HMap. empty
526
542
indexCompleted <- newTVarIO 0
527
543
indexProgressToken <- newVar Nothing
528
544
let hiedbWriter = HieDbWriter {.. }
529
545
exportsMap <- newTVarIO mempty
530
546
-- lazily initialize the exports map with the contents of the hiedb
547
+ -- TODO: exceptions can be swallowed here?
531
548
_ <- async $ do
532
- logDebug logger " Initializing exports map from hiedb "
549
+ log LogCreateHieDbExportsMapStart
533
550
em <- createExportsMapHieDb withHieDb
534
551
atomically $ modifyTVar' exportsMap (<> em)
535
- logDebug logger $ " Done initializing exports map from hiedb ( " <> pack( show ( ExportsMap. size em)) <> " ) "
552
+ log $ LogCreateHieDbExportsMapFinish ( ExportsMap. size em)
536
553
537
554
progress <- do
538
555
let (before, after) = if testing then (0 ,0.1 ) else (0.1 ,0.1 )
@@ -584,9 +601,9 @@ startTelemetry db extras@ShakeExtras{..}
584
601
585
602
586
603
-- | Must be called in the 'Initialized' handler and only once
587
- shakeSessionInit :: IdeState -> IO ()
588
- shakeSessionInit ide@ IdeState {.. } = do
589
- initSession <- newSession shakeExtras shakeDb [] " shakeSessionInit"
604
+ shakeSessionInit :: Recorder Log -> IdeState -> IO ()
605
+ shakeSessionInit recorder ide@ IdeState {.. } = do
606
+ initSession <- newSession recorder shakeExtras shakeDb [] " shakeSessionInit"
590
607
putMVar shakeSession initSession
591
608
logDebug (ideLogger ide) " Shake session initialized"
592
609
@@ -626,15 +643,19 @@ delayedAction a = do
626
643
-- | Restart the current 'ShakeSession' with the given system actions.
627
644
-- Any actions running in the current session will be aborted,
628
645
-- but actions added via 'shakeEnqueue' will be requeued.
629
- shakeRestart :: IdeState -> String -> [DelayedAction () ] -> IO ()
630
- shakeRestart IdeState {.. } reason acts =
646
+ shakeRestart :: Recorder Log -> IdeState -> String -> [DelayedAction () ] -> IO ()
647
+ shakeRestart recorder IdeState {.. } reason acts =
631
648
withMVar'
632
649
shakeSession
633
650
(\ runner -> do
651
+ let log = logWith recorder
634
652
(stopTime,() ) <- duration (cancelShakeSession runner)
635
653
res <- shakeDatabaseProfile shakeDb
636
654
backlog <- readTVarIO $ dirtyKeys shakeExtras
637
655
queue <- atomicallyNamed " actionQueue - peek" $ peekInProgress $ actionQueue shakeExtras
656
+
657
+ log $ LogBuildSessionRestart reason queue backlog stopTime res
658
+
638
659
let profile = case res of
639
660
Just fp -> " , profile saved at " <> fp
640
661
_ -> " "
@@ -643,14 +664,13 @@ shakeRestart IdeState{..} reason acts =
643
664
queueMsg = " with queue " ++ show (map actionName queue)
644
665
keysMsg = " for keys " ++ show (HSet. toList backlog) ++ " "
645
666
abortMsg = " (aborting the previous one took " ++ showDuration stopTime ++ profile ++ " )"
646
- logDebug (logger shakeExtras) msg
647
667
notifyTestingLogMessage shakeExtras msg
648
668
)
649
669
-- It is crucial to be masked here, otherwise we can get killed
650
670
-- between spawning the new thread and updating shakeSession.
651
671
-- See https://github.com/haskell/ghcide/issues/79
652
672
(\ () -> do
653
- (,() ) <$> newSession shakeExtras shakeDb acts reason)
673
+ (,() ) <$> newSession recorder shakeExtras shakeDb acts reason)
654
674
655
675
notifyTestingLogMessage :: ShakeExtras -> T. Text -> IO ()
656
676
notifyTestingLogMessage extras msg = do
@@ -684,12 +704,13 @@ shakeEnqueue ShakeExtras{actionQueue, logger} act = do
684
704
-- | Set up a new 'ShakeSession' with a set of initial actions
685
705
-- Will crash if there is an existing 'ShakeSession' running.
686
706
newSession
687
- :: ShakeExtras
707
+ :: Recorder Log
708
+ -> ShakeExtras
688
709
-> ShakeDatabase
689
710
-> [DelayedActionInternal ]
690
711
-> String
691
712
-> IO ShakeSession
692
- newSession extras@ ShakeExtras {.. } shakeDb acts reason = do
713
+ newSession recorder extras@ ShakeExtras {.. } shakeDb acts reason = do
693
714
IdeOptions {optRunSubset} <- getIdeOptionsIO extras
694
715
reenqueued <- atomicallyNamed " actionQueue - peek" $ peekInProgress actionQueue
695
716
allPendingKeys <-
@@ -712,7 +733,7 @@ newSession extras@ShakeExtras{..} shakeDb acts reason = do
712
733
let msg = T. pack $ " finish: " ++ actionName d
713
734
++ " (took " ++ showDuration runTime ++ " )"
714
735
liftIO $ do
715
- logPriority logger (actionPriority d) msg
736
+ logWith recorder $ LogDelayedAction d runTime
716
737
notifyTestingLogMessage extras msg
717
738
718
739
-- The inferred type signature doesn't work in ghc >= 9.0.1
@@ -729,14 +750,19 @@ newSession extras@ShakeExtras{..} shakeDb acts reason = do
729
750
Right _ -> " completed"
730
751
let msg = T. pack $ " Finishing build session(" ++ res' ++ " )"
731
752
return $ do
732
- logDebug logger msg
753
+ let exception =
754
+ case res of
755
+ Left e -> Just e
756
+ _ -> Nothing
757
+ logWith recorder $ LogBuildSessionFinish exception
733
758
notifyTestingLogMessage extras msg
734
759
735
760
-- Do the work in a background thread
736
761
workThread <- asyncWithUnmask workRun
737
762
738
763
-- run the wrap up in a separate thread since it contains interruptible
739
764
-- commands (and we are not using uninterruptible mask)
765
+ -- TODO: can possibly swallow exceptions?
740
766
_ <- async $ join $ wait workThread
741
767
742
768
-- Cancelling is required to flush the Shake database when either
0 commit comments