1
+ {-# LANGUAGE ScopedTypeVariables #-}
2
+ {-# LANGUAGE TypeFamilies #-}
3
+
1
4
module Development.IDE.Core.ProgressReporting
2
5
( ProgressEvent (.. ),
3
6
ProgressReporting (.. ),
7
+ ProgressReportingNoTrace ,
4
8
noProgressReporting ,
5
9
progressReporting ,
6
- progressReportingOutsideState ,
10
+ progressReportingNoTrace ,
7
11
-- utilities, reexported for use in Core.Shake
8
12
mRunLspT ,
9
13
mRunLspTCallback ,
10
14
-- for tests
11
15
recordProgress ,
12
16
InProgressState (.. ),
17
+ progressStop ,
18
+ progressUpdate
13
19
)
14
20
where
15
21
@@ -42,15 +48,37 @@ data ProgressEvent
42
48
| ProgressCompleted
43
49
| ProgressStarted
44
50
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 ()
51
+ data ProgressReportingNoTrace m = ProgressReportingNoTrace
52
+ { progressUpdateI :: ProgressEvent -> m () ,
53
+ progressStopI :: IO ()
50
54
-- ^ we are using IO here because creating and stopping the `ProgressReporting`
51
55
-- is different from how we use it.
52
56
}
53
57
58
+ data ProgressReporting m = ProgressReporting
59
+ {
60
+ inProgress :: forall a . NormalizedFilePath -> m a -> m a ,
61
+ -- ^ see Note [ProgressReporting API and InProgressState]
62
+ progressReportingInner :: ProgressReportingNoTrace m
63
+ }
64
+
65
+
66
+ class ProgressReportingClass a where
67
+ type M a :: * -> *
68
+ progressUpdate :: a -> ProgressEvent -> M a ()
69
+ progressStop :: a -> IO ()
70
+
71
+ instance ProgressReportingClass (ProgressReportingNoTrace m ) where
72
+ type M (ProgressReportingNoTrace m ) = m
73
+ progressUpdate = progressUpdateI
74
+ progressStop = progressStopI
75
+
76
+ instance ProgressReportingClass (ProgressReporting m ) where
77
+ type M (ProgressReporting m ) = m
78
+ progressUpdate :: ProgressReporting m -> ProgressEvent -> M (ProgressReporting m ) ()
79
+ progressUpdate = progressUpdateI . progressReportingInner
80
+ progressStop = progressStopI . progressReportingInner
81
+
54
82
{- Note [ProgressReporting API and InProgressState]
55
83
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
56
84
The progress of tasks can be tracked in two ways:
@@ -67,13 +95,17 @@ An alternative design could involve using GADTs to eliminate this discrepancy be
67
95
`InProgressState` and `InProgressStateOutSide`.
68
96
-}
69
97
98
+ noProgressReportingNoTrace :: (MonadUnliftIO m ) => (ProgressReportingNoTrace m )
99
+ noProgressReportingNoTrace = ProgressReportingNoTrace
100
+ { progressUpdateI = const $ pure () ,
101
+ progressStopI = pure ()
102
+ }
70
103
noProgressReporting :: (MonadUnliftIO m ) => IO (ProgressReporting m )
71
104
noProgressReporting =
72
105
return $
73
106
ProgressReporting
74
- { progressUpdate = const $ pure () ,
75
- inProgress = const id ,
76
- progressStop = pure ()
107
+ { inProgress = const id ,
108
+ progressReportingInner = noProgressReportingNoTrace
77
109
}
78
110
79
111
-- | State used in 'delayedProgressReporting'
@@ -106,19 +138,12 @@ data InProgressState
106
138
doneVar :: TVar Int ,
107
139
currentVar :: STM. Map NormalizedFilePath Int
108
140
}
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
- }
141
+
116
142
117
143
newInProgress :: IO InProgressState
118
144
newInProgress = InProgressState <$> newTVarIO 0 <*> newTVarIO 0 <*> STM. newIO
119
145
120
146
recordProgress :: InProgressState -> NormalizedFilePath -> (Int -> Int ) -> IO ()
121
- recordProgress InProgressStateOutSide {} _ _ = return ()
122
147
recordProgress InProgressState {.. } file shift = do
123
148
(prev, new) <- atomicallyNamed " recordProgress" $ STM. focus alterPrevAndNew file currentVar
124
149
atomicallyNamed " recordProgress2" $ do
@@ -138,50 +163,45 @@ recordProgress InProgressState {..} file shift = do
138
163
alter x = let x' = maybe (shift 0 ) shift x in Just x'
139
164
140
165
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.
166
+ -- | `progressReportingNoTrace` initiates a new progress reporting session.
153
167
-- It functions similarly to `progressReporting`, but it utilizes an external state for progress tracking.
154
168
-- Refer to Note [ProgressReporting API and InProgressState] for more details.
155
- progressReportingOutsideState ::
169
+ progressReportingNoTrace ::
156
170
(MonadUnliftIO m , MonadIO m ) =>
157
171
STM Int ->
158
172
STM Int ->
159
173
Maybe (LSP. LanguageContextEnv c ) ->
160
174
T. Text ->
161
175
ProgressReportingStyle ->
162
- IO (ProgressReporting m )
163
- progressReportingOutsideState todo done = progressReporting' (pure $ InProgressStateOutSide todo done)
176
+ IO (ProgressReportingNoTrace m )
177
+ progressReportingNoTrace _ _ Nothing _title _optProgressStyle = return noProgressReportingNoTrace
178
+ progressReportingNoTrace todo done (Just lspEnv) title optProgressStyle = do
179
+ progressState <- newVar NotStarted
180
+ let progressUpdateI event = liftIO $ updateStateVar $ Event event
181
+ progressStopI = updateStateVar StopProgress
182
+ updateStateVar = modifyVar_ progressState . updateState (progressCounter lspEnv title optProgressStyle todo done)
183
+ return ProgressReportingNoTrace {.. }
164
184
165
- progressReporting' ::
185
+ -- | `progressReporting` initiates a new progress reporting session.
186
+ -- It necessitates the active tracking of progress using the `inProgress` function.
187
+ -- Refer to Note [ProgressReporting API and InProgressState] for more details.
188
+ progressReporting ::
189
+ forall c m .
166
190
(MonadUnliftIO m , MonadIO m ) =>
167
- IO InProgressState ->
168
191
Maybe (LSP. LanguageContextEnv c ) ->
169
192
T. Text ->
170
193
ProgressReportingStyle ->
171
194
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)
195
+ progressReporting Nothing _title _optProgressStyle = noProgressReporting
196
+ progressReporting (Just lspEnv) title optProgressStyle = do
197
+ inProgressState <- newInProgress
198
+ progressReportingInner <- progressReportingNoTrace (readTVar $ todoVar inProgressState)
199
+ (readTVar $ doneVar inProgressState) ( Just lspEnv) title optProgressStyle
200
+ let
201
+ inProgress :: forall a . NormalizedFilePath -> m a -> m a
179
202
inProgress = updateStateForFile inProgressState
180
203
return ProgressReporting {.. }
181
204
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)
185
205
updateStateForFile inProgress file = UnliftIO. bracket (liftIO $ f succ ) (const $ liftIO $ f pred ) . const
186
206
where
187
207
-- This functions are deliberately eta-expanded to avoid space leaks.
0 commit comments