@@ -9,27 +9,31 @@ module Development.IDE.Core.ProgressReporting
99 , mRunLspTCallback
1010 -- for tests
1111 , recordProgress
12- , InProgress (.. )
12+ , InProgressState (.. )
1313 )
1414 where
1515
1616import Control.Concurrent.Async
17+ import Control.Concurrent.STM.Stats (STM , TVar , atomically ,
18+ newTVarIO , readTVar ,
19+ readTVarIO , writeTVar )
1720import Control.Concurrent.Strict
1821import Control.Monad.Extra
1922import Control.Monad.IO.Class
2023import Control.Monad.Trans.Class (lift )
2124import Data.Foldable (for_ )
2225import Data.Functor (($>) )
23- import qualified Data.HashMap.Strict as HMap
2426import qualified Data.Text as T
2527import Data.Unique
2628import Development.IDE.GHC.Orphans ()
2729import Development.IDE.Graph hiding (ShakeValue )
2830import Development.IDE.Types.Location
2931import Development.IDE.Types.Options
32+ import qualified Focus
3033import qualified Language.LSP.Server as LSP
3134import Language.LSP.Types
3235import qualified Language.LSP.Types as LSP
36+ import qualified StmContainers.Map as STM
3337import System.Time.Extra
3438import UnliftIO.Exception (bracket_ )
3539
@@ -69,26 +73,37 @@ updateState _ StopProgress (Running a) = cancel a $> Stopped
6973updateState _ StopProgress st = pure st
7074
7175-- | 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 )
76+ data InProgressState = InProgressState
77+ { todoVar :: TVar Int -- ^ Number of files to do
78+ , doneVar :: TVar Int -- ^ Number of files done
79+ , currentVar :: STM. Map NormalizedFilePath Int
7680 }
7781
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'
82+ newInProgress :: IO InProgressState
83+ newInProgress = InProgressState <$> newTVarIO 0 <*> newTVarIO 0 <*> STM. newIO
84+
85+ recordProgress :: InProgressState -> NormalizedFilePath -> (Int -> Int ) -> STM ()
86+ recordProgress InProgressState {.. } file shift = do
87+ done <- readTVar doneVar
88+ todo <- readTVar todoVar
89+ (prev, new) <- STM. focus alterPrevAndNew file currentVar
90+ let (done',todo') =
91+ case (prev,new) of
92+ (Nothing ,0 ) -> (done+ 1 , todo+ 1 )
93+ (Nothing ,_) -> (done, todo+ 1 )
94+ (Just 0 , 0 ) -> (done , todo)
95+ (Just 0 , _) -> (done- 1 , todo)
96+ (Just _, 0 ) -> (done+ 1 , todo)
97+ (Just _, _) -> (done , todo)
98+ writeTVar todoVar todo'
99+ writeTVar doneVar done'
90100 where
91- alter x = let x' = maybe (shift 0 ) shift x in ((x,x'), Just x')
101+ alterPrevAndNew = do
102+ prev <- Focus. lookup
103+ Focus. alter alter
104+ new <- Focus. lookupWithDefault 0
105+ return (prev, new)
106+ alter x = let x' = maybe (shift 0 ) shift x in Just x'
92107
93108-- | A 'ProgressReporting' that enqueues Begin and End notifications in a new
94109-- thread, with a grace period (nothing will be sent if 'KickCompleted' arrives
@@ -100,17 +115,16 @@ delayedProgressReporting
100115 -> ProgressReportingStyle
101116 -> IO ProgressReporting
102117delayedProgressReporting before after lspEnv optProgressStyle = do
103- inProgressVar <- newVar $ InProgress 0 0 mempty
118+ inProgressState <- newInProgress
104119 progressState <- newVar NotStarted
105120 let progressUpdate event = updateStateVar $ Event event
106121 progressStop = updateStateVar StopProgress
107- updateStateVar = modifyVar_ progressState . updateState (mRunLspT lspEnv $ lspShakeProgress inProgressVar )
122+ updateStateVar = modifyVar_ progressState . updateState (mRunLspT lspEnv $ lspShakeProgress inProgressState )
108123
109- inProgress :: NormalizedFilePath -> Action a -> Action a
110- inProgress = withProgressVar inProgressVar
124+ inProgress = updateStateForFile inProgressState
111125 return ProgressReporting {.. }
112126 where
113- lspShakeProgress inProgress = do
127+ lspShakeProgress InProgressState { .. } = do
114128 -- first sleep a bit, so we only show progress messages if it's going to take
115129 -- a "noticable amount of time" (we often expect a thread kill to arrive before the sleep finishes)
116130 liftIO $ sleep before
@@ -143,7 +157,8 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
143157 loop _ _ | optProgressStyle == NoProgress =
144158 forever $ liftIO $ threadDelay maxBound
145159 loop id prev = do
146- InProgress {.. } <- liftIO $ readVar inProgress
160+ done <- liftIO $ readTVarIO doneVar
161+ todo <- liftIO $ readTVarIO todoVar
147162 liftIO $ sleep after
148163 if todo == 0 then loop id 0 else do
149164 let next = 100 * fromIntegral done / fromIntegral todo
@@ -166,12 +181,12 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
166181 }
167182 loop id next
168183
169- withProgressVar var file = actionBracket (f succ ) (const $ f pred ) . const
184+ updateStateForFile inProgress file = actionBracket (f succ ) (const $ f pred ) . const
170185 -- This functions are deliberately eta-expanded to avoid space leaks.
171186 -- Do not remove the eta-expansion without profiling a session with at
172187 -- least 1000 modifications.
173188 where
174- f shift = modifyVar' var $ recordProgress file shift
189+ f shift = atomically $ recordProgress inProgress file shift
175190
176191mRunLspT :: Applicative m => Maybe (LSP. LanguageContextEnv c ) -> LSP. LspT c m () -> m ()
177192mRunLspT (Just lspEnv) f = LSP. runLspT lspEnv f
0 commit comments