Skip to content

Commit 1b9cc1d

Browse files
committed
Remove stateful interface
1 parent b81f25c commit 1b9cc1d

File tree

1 file changed

+63
-99
lines changed

1 file changed

+63
-99
lines changed

lsp/src/Language/LSP/Server/Core.hs

Lines changed: 63 additions & 99 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@
66
{-# LANGUAGE OverloadedStrings #-}
77
{-# LANGUAGE RoleAnnotations #-}
88
{-# LANGUAGE TypeFamilyDependencies #-}
9-
{-# LANGUAGE NumericUnderscores #-}
109
{-# LANGUAGE UndecidableInstances #-}
1110
{-# LANGUAGE CUSKs #-}
1211
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
@@ -66,6 +65,7 @@ import Language.LSP.Protocol.Utils.SMethodMap qualified as SMethodMap
6665
import Language.LSP.VFS hiding (end)
6766
import Prettyprinter
6867
import System.Random hiding (next)
68+
import UnliftIO qualified as U
6969
import UnliftIO.Exception qualified as UE
7070

7171
-- ---------------------------------------------------------------------
@@ -244,21 +244,25 @@ data VFSData = VFSData
244244
{-# INLINE modifyState #-}
245245
modifyState :: MonadLsp config m => (LanguageContextState config -> TVar a) -> (a -> a) -> m ()
246246
modifyState sel f = do
247-
tvarDat <- sel . resState <$> getLspEnv
247+
tvarDat <- getStateVar sel
248248
liftIO $ atomically $ modifyTVar' tvarDat f
249249

250250
{-# INLINE stateState #-}
251251
stateState :: MonadLsp config m => (LanguageContextState config -> TVar s) -> (s -> (a, s)) -> m a
252252
stateState sel f = do
253-
tvarDat <- sel . resState <$> getLspEnv
253+
tvarDat <- getStateVar sel
254254
liftIO $ atomically $ stateTVar tvarDat f
255255

256256
{-# INLINE getsState #-}
257257
getsState :: MonadLsp config m => (LanguageContextState config -> TVar a) -> m a
258258
getsState f = do
259-
tvarDat <- f . resState <$> getLspEnv
259+
tvarDat <- getStateVar f
260260
liftIO $ readTVarIO tvarDat
261261

262+
{-# INLINE getStateVar #-}
263+
getStateVar :: MonadLsp config m => (LanguageContextState config -> TVar a) -> m (TVar a)
264+
getStateVar f = f . resState <$> getLspEnv
265+
262266
-- ---------------------------------------------------------------------
263267

264268
{- | Options that the server may configure.
@@ -313,8 +317,8 @@ instance Default Options where
313317
Nothing
314318
False
315319
-- See Note [Delayed progress reporting]
316-
1_000_000
317-
5_00_000
320+
0
321+
0
318322

319323
defaultOptions :: Options
320324
defaultOptions = def
@@ -645,14 +649,6 @@ unregisterCapability (RegistrationToken m (RegistrationId uuid)) = do
645649
-- PROGRESS
646650
--------------------------------------------------------------------------------
647651

648-
addProgressCancellationHandler :: MonadLsp config m => ProgressToken -> IO () -> m ()
649-
addProgressCancellationHandler n act = modifyState (progressCancel . resProgressData) $ Map.insert n act
650-
{-# INLINE addProgressCancellationHandler #-}
651-
652-
deleteProgressCancellationHandler :: MonadLsp config m => ProgressToken -> m ()
653-
deleteProgressCancellationHandler n = modifyState (progressCancel . resProgressData) $ Map.delete n
654-
{-# INLINE deleteProgressCancellationHandler #-}
655-
656652
-- Get a new id for the progress session and make a new one
657653
getNewProgressId :: MonadLsp config m => m ProgressToken
658654
getNewProgressId = do
@@ -661,56 +657,56 @@ getNewProgressId = do
661657
in (L.ProgressToken $ L.InL cur, next)
662658
{-# INLINE getNewProgressId #-}
663659

664-
{- | A stateful representation of a progress tracker.
665-
Do not use this unless you need to, prefer to use the 'withProgress' functions.
666-
-}
667-
data ProgressTracker = ProgressTracker
668-
{ updateProgress :: ProgressAmount -> IO ()
669-
-- ^ Send a progress update to the tracker.
670-
, progressEnded :: MVar ()
671-
-- ^ Has the progress tracking ended? This can happen two ways: the client can cancel it
672-
-- (in which case the server should cancel the corresponding work); or the server can
673-
-- set it when it finishes the work.
674-
}
675-
676-
-- | Create a 'ProgressTracker'.
677-
makeProgressTracker ::
678-
forall c m.
660+
withProgressBase ::
661+
forall c m a.
679662
MonadLsp c m =>
663+
Bool ->
680664
Text ->
681-
ProgressAmount ->
682665
Maybe ProgressToken ->
683666
ProgressCancellable ->
684-
m ProgressTracker
685-
makeProgressTracker title initialProgress clientToken cancellable = do
667+
((ProgressAmount -> m ()) -> m a) ->
668+
m a
669+
withProgressBase indefinite title clientToken cancellable f = do
670+
let initialProgress = ProgressAmount (if indefinite then Nothing else Just 0) Nothing
686671
LanguageContextEnv{resProgressStartDelay = startDelay, resProgressUpdateDelay = updateDelay} <- getLspEnv
687672

688673
tokenVar <- liftIO newEmptyTMVarIO
689674
reportVar <- liftIO $ newTMVarIO initialProgress
690675
endBarrier <- liftIO newEmptyMVar
691676

692677
let
693-
sendProgressReport :: (J.ToJSON r) => ProgressToken -> r -> m ()
694-
sendProgressReport token report = sendNotification SMethod_Progress $ ProgressParams token $ J.toJSON report
678+
updater :: ProgressAmount -> m ()
679+
updater pa = liftIO $ atomically $ do
680+
-- I don't know of a way to do this with a normal MVar!
681+
-- That is: put something into it regardless of whether it is full or empty
682+
_ <- tryTakeTMVar reportVar
683+
putTMVar reportVar pa
684+
685+
progressEnded :: IO ()
686+
progressEnded = readMVar endBarrier
687+
688+
endProgress :: IO ()
689+
endProgress = void $ tryPutMVar endBarrier ()
695690

696-
-- \| Once we have a 'ProgressToken', store it in the variable and also register the cancellation
691+
-- Once we have a 'ProgressToken', store it in the variable and also register the cancellation
697692
-- handler.
698693
registerToken :: ProgressToken -> m ()
699694
registerToken t = do
700-
-- TODO: this is currently racy, we need these two to occur in one STM
701-
-- transaction
702-
liftIO $ atomically $ putTMVar tokenVar t
703-
addProgressCancellationHandler t (void $ tryPutMVar endBarrier ())
695+
handlers <- getProgressCancellationHandlers
696+
liftIO $ atomically $ do
697+
putTMVar tokenVar t
698+
modifyTVar handlers (Map.insert t endProgress)
704699

705-
-- \| Deregister our 'ProgressToken', specifically its cancellation handler. It is important
700+
-- Deregister our 'ProgressToken', specifically its cancellation handler. It is important
706701
-- to do this reliably or else we will leak handlers.
707702
unregisterToken :: m ()
708703
unregisterToken = do
709-
-- TODO: this is also racy, see above
710-
t <- liftIO $ atomically $ tryReadTMVar tokenVar
711-
for_ t deleteProgressCancellationHandler
704+
handlers <- getProgressCancellationHandlers
705+
liftIO $ atomically $ do
706+
mt <- tryReadTMVar tokenVar
707+
for_ mt $ \t -> modifyTVar handlers (Map.delete t)
712708

713-
-- \| Find and register our 'ProgressToken', asking the client for it if necessary.
709+
-- Find and register our 'ProgressToken', asking the client for it if necessary.
714710
-- Note that this computation may terminate before we get the token, we need to wait
715711
-- for the token var to be filled if we want to use it.
716712
createToken :: m ()
@@ -743,7 +739,7 @@ makeProgressTracker title initialProgress clientToken cancellable = do
743739
-- The client sent us an error, we can't use the token.
744740
Left _err -> pure ()
745741

746-
-- \| Actually send the progress reports.
742+
-- Actually send the progress reports.
747743
sendReports :: m ()
748744
sendReports = do
749745
t <- liftIO $ atomically $ readTMVar tokenVar
@@ -771,54 +767,28 @@ makeProgressTracker title initialProgress clientToken cancellable = do
771767
sendProgressReport t $ WorkDoneProgressReport L.AString Nothing msg pct
772768
end t = sendProgressReport t (WorkDoneProgressEnd L.AString Nothing)
773769

774-
-- \| Blocks until the progress reporting should end.
775-
endProgress :: IO ()
776-
endProgress = readMVar endBarrier
777-
778-
progressThreads :: m (Async ())
779-
progressThreads = withRunInIO $ \runInBase ->
780-
async $
781-
-- Create the token and then start sending reports; all of which races with the check for the
782-
-- progress having ended. In all cases, make sure to unregister the token at the end.
783-
(runInBase (createToken >> sendReports) `race_` endProgress) `E.finally` runInBase unregisterToken
784-
785-
-- Launch the threads with no handle, rely on the end barrier to kill them
786-
_threads <- progressThreads
787-
788-
-- The update function for clients: just write to the var
789-
let update pa = atomically $ do
790-
-- I don't know of a way to do this with a normal MVar!
791-
-- That is: put something into it regardless of whether it is full or empty
792-
_ <- tryTakeTMVar reportVar
793-
putTMVar reportVar pa
794-
pure $ ProgressTracker update endBarrier
770+
-- Create the token and then start sending reports; all of which races with the check for the
771+
-- progress having ended. In all cases, make sure to unregister the token at the end.
772+
progressThreads :: m ()
773+
progressThreads =
774+
((createToken >> sendReports) `UE.finally` unregisterToken) `U.race_` liftIO progressEnded
775+
776+
withRunInIO $ \runInBase -> do
777+
withAsync (runInBase $ f updater) $ \mainAct ->
778+
-- If the progress gets cancelled then we need to get cancelled too
779+
withAsync (runInBase progressThreads) $ \pthreads -> do
780+
r <- waitEither mainAct pthreads
781+
-- TODO: is this weird? I can't see how else to gracefully use the ending barrier
782+
-- as a guard to cancel the other async
783+
case r of
784+
Left a -> pure a
785+
Right _ -> cancelWith mainAct ProgressCancelledException >> wait mainAct
786+
where
787+
sendProgressReport :: (J.ToJSON r) => ProgressToken -> r -> m ()
788+
sendProgressReport token report = sendNotification SMethod_Progress $ ProgressParams token $ J.toJSON report
795789

796-
withProgressBase ::
797-
forall c m a.
798-
MonadLsp c m =>
799-
Bool ->
800-
Text ->
801-
Maybe ProgressToken ->
802-
ProgressCancellable ->
803-
((ProgressAmount -> m ()) -> m a) ->
804-
m a
805-
withProgressBase indefinite title clientToken cancellable f = withRunInIO $ \runInBase -> do
806-
let initialPercentage = if indefinite then Nothing else Just 0
807-
E.bracket
808-
-- Create the progress tracker, which will start the progress threads
809-
(runInBase $ makeProgressTracker title (ProgressAmount initialPercentage Nothing) clientToken cancellable)
810-
-- When we finish, trigger the progress ending barrier
811-
(\tracker -> tryPutMVar (progressEnded tracker) ())
812-
$ \tracker -> do
813-
-- Tie the given computation to the progress ending barrier so it will cancel us if triggered
814-
withAsync (runInBase $ f (liftIO . updateProgress tracker)) $ \mainAct ->
815-
withAsync (readMVar (progressEnded tracker)) $ \ender -> do
816-
-- TODO: is this weird? I can't see how else to gracefully use the ending barrier
817-
-- as a guard to cancel the other async
818-
r <- waitEither mainAct ender
819-
case r of
820-
Left a -> pure a
821-
Right _ -> cancelWith mainAct ProgressCancelledException >> wait mainAct
790+
getProgressCancellationHandlers :: m (TVar (Map.Map ProgressToken (IO ())))
791+
getProgressCancellationHandlers = getStateVar (progressCancel . resProgressData)
822792

823793
clientSupportsServerInitiatedProgress :: L.ClientCapabilities -> Bool
824794
clientSupportsServerInitiatedProgress caps = fromMaybe False $ caps ^? L.window . _Just . L.workDoneProgress . _Just
@@ -1050,13 +1020,7 @@ like the client's job. Nonetheless, this does not always happen, and so it is he
10501020
to moderate the spam.
10511021
10521022
For this reason we have configurable delays on starting progress tracking and on sending
1053-
updates.
1054-
1055-
The default values we use are based on the usual interface responsiveness research:
1056-
- 1s is about the point at which people definitely notice something is happening, so
1057-
this is where we start progress reporting.
1058-
- Updates are at 0.5s, so they happen fast enough that things are clearly happening,
1059-
without being too distracting.
1023+
updates. However, the defaults are set to 0, so it's opt-in.
10601024
-}
10611025

10621026
{- Note [Request cancellation]

0 commit comments

Comments
 (0)