Skip to content

Commit 495af1f

Browse files
authored
Formalize the ProgressReporting Type (#4335)
* add ProgressReportingNoTrace * fix doc * cleanup * stylish * turn ProgressReporting into IO * rename * Revert "rename" This reverts commit 03961fa. * rename * rename to PerFileProgressReporting * prefix hidden field with `_`
1 parent 376f7f1 commit 495af1f

File tree

4 files changed

+87
-79
lines changed

4 files changed

+87
-79
lines changed

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,7 @@ import Data.Tuple.Extra (dupe)
7171
import Debug.Trace
7272
import Development.IDE.Core.FileStore (resetInterfaceStore)
7373
import Development.IDE.Core.Preprocessor
74-
import Development.IDE.Core.ProgressReporting (ProgressReporting (..))
74+
import Development.IDE.Core.ProgressReporting (progressUpdate)
7575
import Development.IDE.Core.RuleTypes
7676
import Development.IDE.Core.Shake
7777
import Development.IDE.Core.Tracing (withTrace)

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

+2-2
Original file line numberDiff line numberDiff line change
@@ -141,7 +141,7 @@ kick = do
141141
toJSON $ map fromNormalizedFilePath files
142142

143143
signal (Proxy @"kick/start")
144-
progressUpdate progress ProgressNewStarted
144+
liftIO $ progressUpdate progress ProgressNewStarted
145145

146146
-- Update the exports map
147147
results <- uses GenerateCore files
@@ -152,7 +152,7 @@ kick = do
152152
let mguts = catMaybes results
153153
void $ liftIO $ atomically $ modifyTVar' exportsMap (updateExportsMapMg mguts)
154154

155-
progressUpdate progress ProgressCompleted
155+
liftIO $ progressUpdate progress ProgressCompleted
156156

157157
GarbageCollectVar var <- getIdeGlobalAction
158158
garbageCollectionScheduled <- liftIO $ readVar var

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

+77-71
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,21 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
2+
{-# LANGUAGE TypeFamilies #-}
3+
14
module Development.IDE.Core.ProgressReporting
25
( ProgressEvent (..),
3-
ProgressReporting (..),
4-
noProgressReporting,
6+
PerFileProgressReporting (..),
7+
ProgressReporting,
8+
noPerFileProgressReporting,
59
progressReporting,
6-
progressReportingOutsideState,
10+
progressReportingNoTrace,
711
-- utilities, reexported for use in Core.Shake
812
mRunLspT,
913
mRunLspTCallback,
1014
-- for tests
1115
recordProgress,
1216
InProgressState (..),
17+
progressStop,
18+
progressUpdate
1319
)
1420
where
1521

@@ -34,46 +40,63 @@ import Language.LSP.Server (ProgressAmount (..),
3440
withProgress)
3541
import qualified Language.LSP.Server as LSP
3642
import qualified StmContainers.Map as STM
37-
import UnliftIO (Async, MonadUnliftIO, async,
38-
bracket, cancel)
43+
import UnliftIO (Async, async, bracket, cancel)
3944

4045
data ProgressEvent
4146
= ProgressNewStarted
4247
| ProgressCompleted
4348
| ProgressStarted
4449

45-
data ProgressReporting m = ProgressReporting
46-
{ progressUpdate :: ProgressEvent -> m (),
47-
inProgress :: forall a. NormalizedFilePath -> m a -> m a,
48-
-- ^ see Note [ProgressReporting API and InProgressState]
49-
progressStop :: IO ()
50+
data ProgressReporting = ProgressReporting
51+
{ _progressUpdate :: ProgressEvent -> IO (),
52+
_progressStop :: IO ()
5053
-- ^ we are using IO here because creating and stopping the `ProgressReporting`
5154
-- is different from how we use it.
5255
}
5356

57+
data PerFileProgressReporting = PerFileProgressReporting
58+
{
59+
inProgress :: forall a. NormalizedFilePath -> IO a -> IO a,
60+
-- ^ see Note [ProgressReporting API and InProgressState]
61+
progressReportingInner :: ProgressReporting
62+
}
63+
64+
class ProgressReporter a where
65+
progressUpdate :: a -> ProgressEvent -> IO ()
66+
progressStop :: a -> IO ()
67+
68+
instance ProgressReporter ProgressReporting where
69+
progressUpdate = _progressUpdate
70+
progressStop = _progressStop
71+
72+
instance ProgressReporter PerFileProgressReporting where
73+
progressUpdate = _progressUpdate . progressReportingInner
74+
progressStop = _progressStop . progressReportingInner
75+
5476
{- Note [ProgressReporting API and InProgressState]
5577
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
5678
The progress of tasks can be tracked in two ways:
5779
58-
1. `InProgressState`: This is an internal state that actively tracks the progress.
80+
1. `ProgressReporting`: we have an internal state that actively tracks the progress.
5981
Changes to the progress are made directly to this state.
6082
61-
2. `InProgressStateOutSide`: This is an external state that tracks the progress.
83+
2. `ProgressReporting`: there is an external state that tracks the progress.
6284
The external state is converted into an STM Int for the purpose of reporting progress.
6385
64-
The `inProgress` function is only useful when we are using `InProgressState`.
65-
66-
An alternative design could involve using GADTs to eliminate this discrepancy between
67-
`InProgressState` and `InProgressStateOutSide`.
86+
The `inProgress` function is only useful when we are using `ProgressReporting`.
6887
-}
6988

70-
noProgressReporting :: (MonadUnliftIO m) => IO (ProgressReporting m)
71-
noProgressReporting =
89+
noProgressReporting :: ProgressReporting
90+
noProgressReporting = ProgressReporting
91+
{ _progressUpdate = const $ pure (),
92+
_progressStop = pure ()
93+
}
94+
noPerFileProgressReporting :: IO PerFileProgressReporting
95+
noPerFileProgressReporting =
7296
return $
73-
ProgressReporting
74-
{ progressUpdate = const $ pure (),
75-
inProgress = const id,
76-
progressStop = pure ()
97+
PerFileProgressReporting
98+
{ inProgress = const id,
99+
progressReportingInner = noProgressReporting
77100
}
78101

79102
-- | State used in 'delayedProgressReporting'
@@ -106,29 +129,20 @@ data InProgressState
106129
doneVar :: TVar Int,
107130
currentVar :: STM.Map NormalizedFilePath Int
108131
}
109-
| InProgressStateOutSide
110-
-- we transform the outside state into STM Int for progress reporting purposes
111-
{ -- | Number of files to do
112-
todo :: STM Int,
113-
-- | Number of files done
114-
done :: STM Int
115-
}
116132

117133
newInProgress :: IO InProgressState
118134
newInProgress = InProgressState <$> newTVarIO 0 <*> newTVarIO 0 <*> STM.newIO
119135

120136
recordProgress :: InProgressState -> NormalizedFilePath -> (Int -> Int) -> IO ()
121-
recordProgress InProgressStateOutSide {} _ _ = return ()
122137
recordProgress InProgressState {..} file shift = do
123138
(prev, new) <- atomicallyNamed "recordProgress" $ STM.focus alterPrevAndNew file currentVar
124-
atomicallyNamed "recordProgress2" $ do
125-
case (prev, new) of
126-
(Nothing, 0) -> modifyTVar' doneVar (+ 1) >> modifyTVar' todoVar (+ 1)
127-
(Nothing, _) -> modifyTVar' todoVar (+ 1)
128-
(Just 0, 0) -> pure ()
129-
(Just 0, _) -> modifyTVar' doneVar pred
130-
(Just _, 0) -> modifyTVar' doneVar (+ 1)
131-
(Just _, _) -> pure ()
139+
atomicallyNamed "recordProgress2" $ case (prev, new) of
140+
(Nothing, 0) -> modifyTVar' doneVar (+ 1) >> modifyTVar' todoVar (+ 1)
141+
(Nothing, _) -> modifyTVar' todoVar (+ 1)
142+
(Just 0, 0) -> pure ()
143+
(Just 0, _) -> modifyTVar' doneVar pred
144+
(Just _, 0) -> modifyTVar' doneVar (+ 1)
145+
(Just _, _) -> pure ()
132146
where
133147
alterPrevAndNew = do
134148
prev <- Focus.lookup
@@ -138,57 +152,49 @@ recordProgress InProgressState {..} file shift = do
138152
alter x = let x' = maybe (shift 0) shift x in Just x'
139153

140154

141-
-- | `progressReporting` initiates a new progress reporting session.
142-
-- It necessitates the active tracking of progress using the `inProgress` function.
143-
-- Refer to Note [ProgressReporting API and InProgressState] for more details.
144-
progressReporting ::
145-
(MonadUnliftIO m, MonadIO m) =>
146-
Maybe (LSP.LanguageContextEnv c) ->
147-
T.Text ->
148-
ProgressReportingStyle ->
149-
IO (ProgressReporting m)
150-
progressReporting = progressReporting' newInProgress
151-
152-
-- | `progressReportingOutsideState` initiates a new progress reporting session.
155+
-- | `progressReportingNoTrace` initiates a new progress reporting session.
153156
-- It functions similarly to `progressReporting`, but it utilizes an external state for progress tracking.
154157
-- Refer to Note [ProgressReporting API and InProgressState] for more details.
155-
progressReportingOutsideState ::
156-
(MonadUnliftIO m, MonadIO m) =>
158+
progressReportingNoTrace ::
157159
STM Int ->
158160
STM Int ->
159161
Maybe (LSP.LanguageContextEnv c) ->
160162
T.Text ->
161163
ProgressReportingStyle ->
162-
IO (ProgressReporting m)
163-
progressReportingOutsideState todo done = progressReporting' (pure $ InProgressStateOutSide todo done)
164+
IO ProgressReporting
165+
progressReportingNoTrace _ _ Nothing _title _optProgressStyle = return noProgressReporting
166+
progressReportingNoTrace todo done (Just lspEnv) title optProgressStyle = do
167+
progressState <- newVar NotStarted
168+
let _progressUpdate event = liftIO $ updateStateVar $ Event event
169+
_progressStop = updateStateVar StopProgress
170+
updateStateVar = modifyVar_ progressState . updateState (progressCounter lspEnv title optProgressStyle todo done)
171+
return ProgressReporting {..}
164172

165-
progressReporting' ::
166-
(MonadUnliftIO m, MonadIO m) =>
167-
IO InProgressState ->
173+
-- | `progressReporting` initiates a new progress reporting session.
174+
-- It necessitates the active tracking of progress using the `inProgress` function.
175+
-- Refer to Note [ProgressReporting API and InProgressState] for more details.
176+
progressReporting ::
168177
Maybe (LSP.LanguageContextEnv c) ->
169178
T.Text ->
170179
ProgressReportingStyle ->
171-
IO (ProgressReporting m)
172-
progressReporting' _newState Nothing _title _optProgressStyle = noProgressReporting
173-
progressReporting' newState (Just lspEnv) title optProgressStyle = do
174-
inProgressState <- newState
175-
progressState <- newVar NotStarted
176-
let progressUpdate event = liftIO $ updateStateVar $ Event event
177-
progressStop = updateStateVar StopProgress
178-
updateStateVar = modifyVar_ progressState . updateState (lspShakeProgressNew inProgressState)
179-
inProgress = updateStateForFile inProgressState
180-
return ProgressReporting {..}
180+
IO PerFileProgressReporting
181+
progressReporting Nothing _title _optProgressStyle = noPerFileProgressReporting
182+
progressReporting (Just lspEnv) title optProgressStyle = do
183+
inProgressState <- newInProgress
184+
progressReportingInner <- progressReportingNoTrace (readTVar $ todoVar inProgressState)
185+
(readTVar $ doneVar inProgressState) (Just lspEnv) title optProgressStyle
186+
let
187+
inProgress :: NormalizedFilePath -> IO a -> IO a
188+
inProgress = updateStateForFile inProgressState
189+
return PerFileProgressReporting {..}
181190
where
182-
lspShakeProgressNew :: InProgressState -> IO ()
183-
lspShakeProgressNew InProgressStateOutSide {..} = progressCounter lspEnv title optProgressStyle todo done
184-
lspShakeProgressNew InProgressState {..} = progressCounter lspEnv title optProgressStyle (readTVar todoVar) (readTVar doneVar)
185191
updateStateForFile inProgress file = UnliftIO.bracket (liftIO $ f succ) (const $ liftIO $ f pred) . const
186192
where
187193
-- This functions are deliberately eta-expanded to avoid space leaks.
188194
-- Do not remove the eta-expansion without profiling a session with at
189195
-- least 1000 modifications.
190196

191-
f shift = recordProgress inProgress file shift
197+
f = recordProgress inProgress file
192198

193199
-- Kill this to complete the progress session
194200
progressCounter ::

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

+7-5
Original file line numberDiff line numberDiff line change
@@ -174,6 +174,7 @@ import qualified StmContainers.Map as STM
174174
import System.FilePath hiding (makeRelative)
175175
import System.IO.Unsafe (unsafePerformIO)
176176
import System.Time.Extra
177+
import UnliftIO (MonadUnliftIO (withRunInIO))
177178

178179

179180
data Log
@@ -244,7 +245,7 @@ data HieDbWriter
244245
{ indexQueue :: IndexQueue
245246
, indexPending :: TVar (HMap.HashMap NormalizedFilePath Fingerprint) -- ^ Avoid unnecessary/out of date indexing
246247
, indexCompleted :: TVar Int -- ^ to report progress
247-
, indexProgressReporting :: ProgressReporting IO
248+
, indexProgressReporting :: ProgressReporting
248249
}
249250

250251
-- | Actions to queue up on the index worker thread
@@ -294,7 +295,7 @@ data ShakeExtras = ShakeExtras
294295
-- positions in a version of that document to positions in the latest version
295296
-- First mapping is delta from previous version and second one is an
296297
-- accumulation to the current version.
297-
,progress :: ProgressReporting Action
298+
,progress :: PerFileProgressReporting
298299
,ideTesting :: IdeTesting
299300
-- ^ Whether to enable additional lsp messages used by the test suite for checking invariants
300301
,restartShakeSession
@@ -676,7 +677,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
676677
indexPending <- newTVarIO HMap.empty
677678
indexCompleted <- newTVarIO 0
678679
semanticTokensId <- newTVarIO 0
679-
indexProgressReporting <- progressReportingOutsideState
680+
indexProgressReporting <- progressReportingNoTrace
680681
(liftM2 (+) (length <$> readTVar indexPending) (readTVar indexCompleted))
681682
(readTVar indexCompleted)
682683
lspEnv "Indexing" optProgressStyle
@@ -693,7 +694,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
693694
progress <-
694695
if reportProgress
695696
then progressReporting lspEnv "Processing" optProgressStyle
696-
else noProgressReporting
697+
else noPerFileProgressReporting
697698
actionQueue <- newQueue
698699

699700
let clientCapabilities = maybe def LSP.resClientCapabilities lspEnv
@@ -1216,7 +1217,8 @@ defineEarlyCutoff'
12161217
defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do
12171218
ShakeExtras{state, progress, dirtyKeys} <- getShakeExtras
12181219
options <- getIdeOptions
1219-
(if optSkipProgress options key then id else inProgress progress file) $ do
1220+
let trans g x = withRunInIO $ \run -> g (run x)
1221+
(if optSkipProgress options key then id else trans (inProgress progress file)) $ do
12201222
val <- case mbOld of
12211223
Just old | mode == RunDependenciesSame -> do
12221224
mbValue <- liftIO $ atomicallyNamed "define - read 1" $ getValues state key file

0 commit comments

Comments
 (0)