@@ -9,27 +9,30 @@ 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 (TVar , atomically , newTVarIO ,
18+ readTVar , writeTVar )
1719import Control.Concurrent.Strict
1820import Control.Monad.Extra
1921import Control.Monad.IO.Class
2022import Control.Monad.Trans.Class (lift )
2123import Data.Foldable (for_ )
2224import Data.Functor (($>) )
23- import qualified Data.HashMap.Strict as HMap
2425import qualified Data.Text as T
2526import Data.Unique
2627import Development.IDE.GHC.Orphans ()
2728import Development.IDE.Graph hiding (ShakeValue )
2829import Development.IDE.Types.Location
2930import Development.IDE.Types.Options
31+ import qualified Focus
3032import qualified Language.LSP.Server as LSP
3133import Language.LSP.Types
3234import qualified Language.LSP.Types as LSP
35+ import qualified StmContainers.Map as STM
3336import System.Time.Extra
3437import UnliftIO.Exception (bracket_ )
3538
@@ -69,26 +72,37 @@ updateState _ StopProgress (Running a) = cancel a $> Stopped
6972updateState _ StopProgress st = pure st
7073
7174-- | 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
7679 }
7780
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'
9099 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'
92106
93107-- | A 'ProgressReporting' that enqueues Begin and End notifications in a new
94108-- thread, with a grace period (nothing will be sent if 'KickCompleted' arrives
@@ -100,17 +114,16 @@ delayedProgressReporting
100114 -> ProgressReportingStyle
101115 -> IO ProgressReporting
102116delayedProgressReporting before after lspEnv optProgressStyle = do
103- inProgressVar <- newVar $ InProgress 0 0 mempty
117+ inProgressState <- newInProgress
104118 progressState <- newVar NotStarted
105119 let progressUpdate event = updateStateVar $ Event event
106120 progressStop = updateStateVar StopProgress
107- updateStateVar = modifyVar_ progressState . updateState (mRunLspT lspEnv $ lspShakeProgress inProgressVar )
121+ updateStateVar = modifyVar_ progressState . updateState (mRunLspT lspEnv $ lspShakeProgress inProgressState )
108122
109- inProgress :: NormalizedFilePath -> Action a -> Action a
110- inProgress = withProgressVar inProgressVar
123+ inProgress = updateStateForFile inProgressState
111124 return ProgressReporting {.. }
112125 where
113- lspShakeProgress inProgress = do
126+ lspShakeProgress InProgressState { .. } = do
114127 -- first sleep a bit, so we only show progress messages if it's going to take
115128 -- a "noticable amount of time" (we often expect a thread kill to arrive before the sleep finishes)
116129 liftIO $ sleep before
@@ -143,7 +156,8 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
143156 loop _ _ | optProgressStyle == NoProgress =
144157 forever $ liftIO $ threadDelay maxBound
145158 loop id prev = do
146- InProgress {.. } <- liftIO $ readVar inProgress
159+ done <- liftIO $ atomically $ readTVar doneVar
160+ todo <- liftIO $ atomically $ readTVar todoVar
147161 liftIO $ sleep after
148162 if todo == 0 then loop id 0 else do
149163 let next = 100 * fromIntegral done / fromIntegral todo
@@ -166,12 +180,12 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
166180 }
167181 loop id next
168182
169- withProgressVar var file = actionBracket (f succ ) (const $ f pred ) . const
183+ updateStateForFile inProgress file = actionBracket (f succ ) (const $ f pred ) . const
170184 -- This functions are deliberately eta-expanded to avoid space leaks.
171185 -- Do not remove the eta-expansion without profiling a session with at
172186 -- least 1000 modifications.
173187 where
174- f shift = modifyVar' var $ recordProgress file shift
188+ f shift = recordProgress inProgress file shift
175189
176190mRunLspT :: Applicative m => Maybe (LSP. LanguageContextEnv c ) -> LSP. LspT c m () -> m ()
177191mRunLspT (Just lspEnv) f = LSP. runLspT lspEnv f
0 commit comments