@@ -9,27 +9,30 @@ module Development.IDE.Core.ProgressReporting
9
9
, mRunLspTCallback
10
10
-- for tests
11
11
, recordProgress
12
- , InProgress (.. )
12
+ , InProgressState (.. )
13
13
)
14
14
where
15
15
16
16
import Control.Concurrent.Async
17
+ import Control.Concurrent.STM (TVar , atomically , newTVarIO ,
18
+ readTVar , writeTVar )
17
19
import Control.Concurrent.Strict
18
20
import Control.Monad.Extra
19
21
import Control.Monad.IO.Class
20
22
import Control.Monad.Trans.Class (lift )
21
23
import Data.Foldable (for_ )
22
24
import Data.Functor (($>) )
23
- import qualified Data.HashMap.Strict as HMap
24
25
import qualified Data.Text as T
25
26
import Data.Unique
26
27
import Development.IDE.GHC.Orphans ()
27
28
import Development.IDE.Graph hiding (ShakeValue )
28
29
import Development.IDE.Types.Location
29
30
import Development.IDE.Types.Options
31
+ import qualified Focus
30
32
import qualified Language.LSP.Server as LSP
31
33
import Language.LSP.Types
32
34
import qualified Language.LSP.Types as LSP
35
+ import qualified StmContainers.Map as STM
33
36
import System.Time.Extra
34
37
import UnliftIO.Exception (bracket_ )
35
38
@@ -69,26 +72,37 @@ updateState _ StopProgress (Running a) = cancel a $> Stopped
69
72
updateState _ StopProgress st = pure st
70
73
71
74
-- | Data structure to track progress across the project
72
- data InProgress = InProgress
73
- { todo :: ! Int -- ^ Number of files to do
74
- , done :: ! Int -- ^ Number of files done
75
- , current :: ! ( HMap. HashMap NormalizedFilePath Int )
75
+ data InProgressState = InProgressState
76
+ { todoVar :: TVar Int -- ^ Number of files to do
77
+ , doneVar :: TVar Int -- ^ Number of files done
78
+ , currentVar :: STM. Map NormalizedFilePath Int
76
79
}
77
80
78
- recordProgress :: NormalizedFilePath -> (Int -> Int ) -> InProgress -> InProgress
79
- recordProgress file shift InProgress {.. } = case HMap. alterF alter file current of
80
- ((prev, new), m') ->
81
- let (done',todo') =
82
- case (prev,new) of
83
- (Nothing ,0 ) -> (done+ 1 , todo+ 1 )
84
- (Nothing ,_) -> (done, todo+ 1 )
85
- (Just 0 , 0 ) -> (done , todo)
86
- (Just 0 , _) -> (done- 1 , todo)
87
- (Just _, 0 ) -> (done+ 1 , todo)
88
- (Just _, _) -> (done , todo)
89
- in InProgress todo' done' m'
81
+ newInProgress :: IO InProgressState
82
+ newInProgress = InProgressState <$> newTVarIO 0 <*> newTVarIO 0 <*> STM. newIO
83
+
84
+ recordProgress :: InProgressState -> NormalizedFilePath -> (Int -> Int ) -> IO ()
85
+ recordProgress InProgressState {.. } file shift = atomically $ do
86
+ done <- readTVar doneVar
87
+ todo <- readTVar todoVar
88
+ (prev, new) <- STM. focus alterPrevAndNew file currentVar
89
+ let (done',todo') =
90
+ case (prev,new) of
91
+ (Nothing ,0 ) -> (done+ 1 , todo+ 1 )
92
+ (Nothing ,_) -> (done, todo+ 1 )
93
+ (Just 0 , 0 ) -> (done , todo)
94
+ (Just 0 , _) -> (done- 1 , todo)
95
+ (Just _, 0 ) -> (done+ 1 , todo)
96
+ (Just _, _) -> (done , todo)
97
+ writeTVar todoVar todo'
98
+ writeTVar doneVar done'
90
99
where
91
- alter x = let x' = maybe (shift 0 ) shift x in ((x,x'), Just x')
100
+ alterPrevAndNew = do
101
+ prev <- Focus. lookup
102
+ Focus. alter alter
103
+ new <- Focus. lookupWithDefault 0
104
+ return (prev, new)
105
+ alter x = let x' = maybe (shift 0 ) shift x in Just x'
92
106
93
107
-- | A 'ProgressReporting' that enqueues Begin and End notifications in a new
94
108
-- thread, with a grace period (nothing will be sent if 'KickCompleted' arrives
@@ -100,17 +114,16 @@ delayedProgressReporting
100
114
-> ProgressReportingStyle
101
115
-> IO ProgressReporting
102
116
delayedProgressReporting before after lspEnv optProgressStyle = do
103
- inProgressVar <- newVar $ InProgress 0 0 mempty
117
+ inProgressState <- newInProgress
104
118
progressState <- newVar NotStarted
105
119
let progressUpdate event = updateStateVar $ Event event
106
120
progressStop = updateStateVar StopProgress
107
- updateStateVar = modifyVar_ progressState . updateState (mRunLspT lspEnv $ lspShakeProgress inProgressVar )
121
+ updateStateVar = modifyVar_ progressState . updateState (mRunLspT lspEnv $ lspShakeProgress inProgressState )
108
122
109
- inProgress :: NormalizedFilePath -> Action a -> Action a
110
- inProgress = withProgressVar inProgressVar
123
+ inProgress = updateStateForFile inProgressState
111
124
return ProgressReporting {.. }
112
125
where
113
- lspShakeProgress inProgress = do
126
+ lspShakeProgress InProgressState { .. } = do
114
127
-- first sleep a bit, so we only show progress messages if it's going to take
115
128
-- a "noticable amount of time" (we often expect a thread kill to arrive before the sleep finishes)
116
129
liftIO $ sleep before
@@ -143,7 +156,8 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
143
156
loop _ _ | optProgressStyle == NoProgress =
144
157
forever $ liftIO $ threadDelay maxBound
145
158
loop id prev = do
146
- InProgress {.. } <- liftIO $ readVar inProgress
159
+ done <- liftIO $ atomically $ readTVar doneVar
160
+ todo <- liftIO $ atomically $ readTVar todoVar
147
161
liftIO $ sleep after
148
162
if todo == 0 then loop id 0 else do
149
163
let next = 100 * fromIntegral done / fromIntegral todo
@@ -166,12 +180,12 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
166
180
}
167
181
loop id next
168
182
169
- withProgressVar var file = actionBracket (f succ ) (const $ f pred ) . const
183
+ updateStateForFile inProgress file = actionBracket (f succ ) (const $ f pred ) . const
170
184
-- This functions are deliberately eta-expanded to avoid space leaks.
171
185
-- Do not remove the eta-expansion without profiling a session with at
172
186
-- least 1000 modifications.
173
187
where
174
- f shift = modifyVar' var $ recordProgress file shift
188
+ f shift = recordProgress inProgress file shift
175
189
176
190
mRunLspT :: Applicative m => Maybe (LSP. LanguageContextEnv c ) -> LSP. LspT c m () -> m ()
177
191
mRunLspT (Just lspEnv) f = LSP. runLspT lspEnv f
0 commit comments