Skip to content

Commit 47bf559

Browse files
committed
Sacrifice delayedProgressReporting
1 parent 5c2cf2f commit 47bf559

File tree

2 files changed

+11
-84
lines changed

2 files changed

+11
-84
lines changed

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

Lines changed: 7 additions & 79 deletions
Original file line numberDiff line numberDiff line change
@@ -3,19 +3,16 @@ module Development.IDE.Core.ProgressReporting
33
( ProgressEvent(..)
44
, ProgressReporting(..)
55
, noProgressReporting
6-
, delayedProgressReporting
7-
, directProgressReporting
6+
, makeProgressReporting
87
-- utilities, reexported for use in Core.Shake
98
, mRunLspT
109
, mRunLspTCallback
1110
) where
1211

1312
import Control.Concurrent.Async
14-
import Control.Concurrent.STM
1513
import Control.Concurrent.Strict
1614
import Control.Monad.Extra
1715
import Control.Monad.IO.Class
18-
import qualified Control.Monad.STM as STM
1916
import Control.Monad.Trans.Class (lift)
2017
import Data.Foldable (for_, traverse_)
2118
import Data.HashMap.Strict (HashMap)
@@ -32,7 +29,6 @@ import qualified Language.LSP.Server as LSP
3229
import Language.LSP.Types
3330
import qualified Language.LSP.Types as LSP
3431
import System.Time.Extra
35-
import UnliftIO.Exception (bracket_)
3632

3733
data ProgressEvent
3834
= KickStarted
@@ -55,14 +51,16 @@ noProgressReporting = return $ ProgressReporting
5551
-- synchronously. Progress notifications are sent from a sampling thread.
5652
--
5753
-- This 'ProgressReporting' is currently used only in tests.
58-
directProgressReporting
54+
makeProgressReporting
5955
:: Seconds -- ^ sampling rate
56+
-> Seconds -- ^ initial delay
6057
-> Maybe (LSP.LanguageContextEnv config)
6158
-> ProgressReportingStyle
6259
-> IO ProgressReporting
63-
directProgressReporting sample env style = do
60+
makeProgressReporting sample delay env style = do
6461
st <- newIORef Nothing
6562
inProgressVar <- newIORef (HMap.empty @NormalizedFilePath @Int)
63+
delayVar <- newIORef delay
6664

6765
let progressUpdate KickStarted = do
6866
readIORef st >>= traverse_ (mRunLspT env . stop)
@@ -86,6 +84,8 @@ directProgressReporting sample env style = do
8684

8785
progressLoop :: Seconds -> LSP.LspM a ()
8886
progressLoop prev = do
87+
delayActual <- liftIO $ atomicModifyIORef delayVar (0,)
88+
liftIO $ sleep delayActual
8989
mbToken <- liftIO $ readIORef st
9090
next <- case mbToken of
9191
Nothing ->
@@ -101,78 +101,6 @@ directProgressReporting sample env style = do
101101

102102
pure ProgressReporting {..}
103103

104-
-- | A 'ProgressReporting' that enqueues Begin and End notifications in a new
105-
-- thread, with a grace period (nothing will be sent if 'KickCompleted' arrives
106-
-- before the end of the grace period).
107-
-- Avoid using in tests where progress notifications are used to assert invariants.
108-
delayedProgressReporting
109-
:: Seconds -- ^ sampling rate, also used as grace period before Begin
110-
-> Maybe (LSP.LanguageContextEnv c)
111-
-> ProgressReportingStyle
112-
-> IO ProgressReporting
113-
delayedProgressReporting sample lspEnv style = do
114-
inProgressVar <- newVar (HMap.empty @NormalizedFilePath @Int)
115-
mostRecentProgressEvent <- newTVarIO KickCompleted
116-
progressAsync <- async $
117-
progressThread mostRecentProgressEvent inProgressVar
118-
let progressUpdate = atomically . writeTVar mostRecentProgressEvent
119-
progressStop = cancel progressAsync
120-
inProgress :: NormalizedFilePath -> Action a -> Action a
121-
inProgress = withProgressVar inProgressVar
122-
return ProgressReporting{..}
123-
where
124-
-- The progress thread is a state machine with two states:
125-
-- 1. Idle
126-
-- 2. Reporting a kick event
127-
-- And two transitions, modelled by 'ProgressEvent':
128-
-- 1. KickCompleted - transitions from Reporting into Idle
129-
-- 2. KickStarted - transitions from Idle into Reporting
130-
-- When transitioning from Idle to Reporting a new async is spawned that
131-
-- sends progress updates in a loop. The async is cancelled when transitioning
132-
-- from Reporting to Idle.
133-
progressThread mostRecentProgressEvent inProgress = progressLoopIdle
134-
where
135-
progressLoopIdle = do
136-
atomically $ do
137-
v <- readTVar mostRecentProgressEvent
138-
case v of
139-
KickCompleted -> STM.retry
140-
KickStarted -> return ()
141-
asyncReporter <- async $ mRunLspT lspEnv $ do
142-
-- first sleep a bit, so we only show progress messages if it's going to take
143-
-- a "noticable amount of time" (we often expect a thread kill to arrive before the sleep finishes)
144-
liftIO $ sleep sample
145-
lspShakeProgress style inProgress
146-
progressLoopReporting asyncReporter
147-
progressLoopReporting asyncReporter = do
148-
atomically $ do
149-
v <- readTVar mostRecentProgressEvent
150-
case v of
151-
KickStarted -> STM.retry
152-
KickCompleted -> return ()
153-
cancel asyncReporter
154-
progressLoopIdle
155-
156-
lspShakeProgress style inProgress = do
157-
u <- liftIO newProgressToken
158-
159-
ready <- create u
160-
161-
for_ ready $ \_ ->
162-
bracket_ (start u) (stop u) (loop u 0)
163-
where
164-
loop id prev = do
165-
liftIO $ sleep sample
166-
current <- liftIO $ readVar inProgress
167-
next <- progress style prev current id
168-
loop id next
169-
170-
withProgressVar var file = actionBracket (f succ) (const $ f pred) . const
171-
-- This functions are deliberately eta-expanded to avoid space leaks.
172-
-- Do not remove the eta-expansion without profiling a session with at
173-
-- least 1000 modifications.
174-
where f shift = void $ modifyVar' var $ HMap.insertWith (\_ x -> shift x) file (shift 0)
175-
176104
newProgressToken :: IO ProgressToken
177105
newProgressToken = ProgressTextToken . T.pack . show . hashUnique <$> liftIO newUnique
178106

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

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -486,12 +486,11 @@ shakeOpen lspEnv defaultConfig logger debouncer
486486
let hiedbWriter = HieDbWriter{..}
487487
exportsMap <- newVar mempty
488488

489-
progress <-
489+
progress <- do
490+
let delay = if testing then 0 else 0.1
491+
sampling = 0.1
490492
if reportProgress
491-
then (if testing
492-
then directProgressReporting
493-
else delayedProgressReporting
494-
) 0.1 lspEnv optProgressStyle
493+
then makeProgressReporting delay sampling lspEnv optProgressStyle
495494
else noProgressReporting
496495
actionQueue <- newQueue
497496

0 commit comments

Comments
 (0)