Skip to content

Commit c4ca81b

Browse files
soulomoonfendor
andauthored
Gracefully exit the server (#622)
* Ensure graceful LSP server shutdown and robust IO handling - Track shutdown/exit separately and wait for sender to flush before exit - Make runServerWithHandles resilient to broken pipes and log truncated messages - Have runServerWith/ioLoop return proper exit codes based on shutdown state - Adjust processing to use sender wait action during shutdown and log exit - Fix functional test harness to assert zero exit code instead of ExitSuccess - Tidy minor CI workflow whitespace in format.yaml and nix.yaml --------- Co-authored-by: fendor <fendor@users.noreply.github.com>
1 parent 2d2c468 commit c4ca81b

File tree

6 files changed

+124
-54
lines changed

6 files changed

+124
-54
lines changed

.github/workflows/format.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
name: Format
22

3-
on:
3+
on:
44
push:
55
branches:
66
- master

.github/workflows/nix.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
name: Nix
22

3-
on:
3+
on:
44
push:
55
branches:
66
- master

lsp-test/func-test/FuncTest.hs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -39,13 +39,15 @@ runSessionWithServer logger defn testConfig caps root session = do
3939
(hinRead, hinWrite) <- createPipe
4040
(houtRead, houtWrite) <- createPipe
4141

42-
server <- async $ void $ runServerWithHandles logger (L.hoistLogAction liftIO logger) hinRead houtWrite defn
42+
server <- async $ runServerWithHandles logger (L.hoistLogAction liftIO logger) hinRead houtWrite defn
4343

4444
res <- Test.runSessionWithHandles hinWrite houtRead testConfig caps root session
4545

4646
timeout 3000000 $ do
47-
Left (fromException -> Just ExitSuccess) <- waitCatch server
48-
pure ()
47+
return_code <- wait server
48+
case return_code of
49+
0 -> pure ()
50+
_ -> error $ "Server exited with non-zero code: " ++ show return_code
4951

5052
pure res
5153

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

Lines changed: 54 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE DerivingStrategies #-}
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE RecordWildCards #-}
4+
{-# LANGUAGE TypeFamilies #-}
45

56
module Language.LSP.Server.Control (
67
-- * Running
@@ -29,7 +30,7 @@ import Control.Applicative ((<|>))
2930
import Control.Concurrent
3031
import Control.Concurrent.Async
3132
import Control.Concurrent.STM.TChan
32-
import Control.Exception (finally)
33+
import Control.Exception (catchJust, finally, throwIO)
3334
import Control.Monad
3435
import Control.Monad.IO.Class
3536
import Control.Monad.STM
@@ -51,19 +52,23 @@ import Language.LSP.VFS
5152
import Network.WebSockets qualified as WS
5253
import Prettyprinter
5354
import System.IO
55+
import System.IO.Error (isResourceVanishedError)
5456

5557
data LspServerLog
5658
= LspProcessingLog Processing.LspProcessingLog
5759
| DecodeInitializeError String
5860
| HeaderParseFail [String] String
5961
| EOF
62+
| BrokenPipeWhileSending TL.Text -- truncated outgoing message (including header)
6063
| Starting
64+
| ServerStopped
6165
| ParsedMsg T.Text
6266
| SendMsg TL.Text
6367
| WebsocketLog WebsocketLog
6468
deriving (Show)
6569

6670
instance Pretty LspServerLog where
71+
pretty ServerStopped = "Server stopped"
6772
pretty (LspProcessingLog l) = pretty l
6873
pretty (DecodeInitializeError err) =
6974
vsep
@@ -76,7 +81,12 @@ instance Pretty LspServerLog where
7681
, pretty (intercalate " > " ctxs) <> ": " <+> pretty err
7782
]
7883
pretty EOF = "Got EOF"
79-
pretty Starting = "Starting server"
84+
pretty (BrokenPipeWhileSending msg) =
85+
vsep
86+
[ "Broken pipe while sending (client likely closed output handle):"
87+
, indent 2 (pretty msg)
88+
]
89+
pretty Starting = "Server starting"
8090
pretty (ParsedMsg msg) = "---> " <> pretty msg
8191
pretty (SendMsg msg) = "<--2-- " <> pretty msg
8292
pretty (WebsocketLog msg) = "Websocket:" <+> pretty msg
@@ -130,9 +140,15 @@ runServerWithHandles ioLogger logger hin hout serverDefinition = do
130140
let
131141
clientIn = BS.hGetSome hin defaultChunkSize
132142

133-
clientOut out = do
134-
BSL.hPut hout out
135-
hFlush hout
143+
clientOut out =
144+
catchJust
145+
(\e -> if isResourceVanishedError e then Just e else Nothing)
146+
(BSL.hPut hout out >> hFlush hout)
147+
( \e -> do
148+
let txt = TL.toStrict $ TL.take 400 $ TL.decodeUtf8 out -- limit size
149+
ioLogger <& BrokenPipeWhileSending (TL.fromStrict txt) `WithSeverity` Error
150+
throwIO e
151+
)
136152

137153
runServerWith ioLogger logger clientIn clientOut serverDefinition
138154

@@ -179,15 +195,12 @@ runServerWithConfig ::
179195
IO Int
180196
runServerWithConfig ServerConfig{..} serverDefinition = do
181197
ioLogger <& Starting `WithSeverity` Info
182-
183-
cout <- atomically newTChan :: IO (TChan J.Value)
184-
_rhpid <- forkIO $ sendServer ioLogger cout outwards prepareOutwards
185-
186-
let sendMsg msg = atomically $ writeTChan cout $ J.toJSON msg
187-
188-
ioLoop ioLogger lspLogger inwards parseInwards serverDefinition emptyVFS sendMsg
189-
190-
return 1
198+
cout <- atomically newTChan :: IO (TChan FromServerMessage)
199+
withAsync (sendServer ioLogger cout outwards prepareOutwards) $ \sendServerAsync -> do
200+
let sendMsg = atomically . writeTChan cout
201+
res <- ioLoop ioLogger lspLogger inwards parseInwards serverDefinition emptyVFS sendMsg (wait sendServerAsync)
202+
ioLogger <& ServerStopped `WithSeverity` Info
203+
return res
191204

192205
-- ---------------------------------------------------------------------
193206

@@ -200,33 +213,39 @@ ioLoop ::
200213
ServerDefinition config ->
201214
VFS ->
202215
(FromServerMessage -> IO ()) ->
203-
IO ()
204-
ioLoop ioLogger logger clientIn parser serverDefinition vfs sendMsg = do
216+
IO () ->
217+
IO Int
218+
ioLoop ioLogger logger clientIn parser serverDefinition vfs sendMsg waitSenderFinish = do
205219
minitialize <- parseOne ioLogger clientIn (parse parser "")
206220
case minitialize of
207-
Nothing -> pure ()
221+
Nothing -> pure 1
208222
Just (msg, remainder) -> do
209223
case J.eitherDecode $ BSL.fromStrict msg of
210-
Left err -> ioLogger <& DecodeInitializeError err `WithSeverity` Error
224+
Left err -> do
225+
ioLogger <& DecodeInitializeError err `WithSeverity` Error
226+
return 1
211227
Right initialize -> do
212-
mInitResp <- Processing.initializeRequestHandler pioLogger serverDefinition vfs sendMsg initialize
228+
mInitResp <- Processing.initializeRequestHandler pioLogger serverDefinition vfs sendMsg waitSenderFinish initialize
213229
case mInitResp of
214-
Nothing -> pure ()
230+
Nothing -> pure 1
215231
Just env -> runLspT env $ loop (parse parser remainder)
216232
where
217233
pioLogger = L.cmap (fmap LspProcessingLog) ioLogger
218234
pLogger = L.cmap (fmap LspProcessingLog) logger
219235

220-
loop :: Result BS.StrictByteString -> LspM config ()
221236
loop = go
222237
where
223238
go r = do
224-
res <- parseOne logger clientIn r
225-
case res of
226-
Nothing -> pure ()
227-
Just (msg, remainder) -> do
228-
Processing.processMessage pLogger $ BSL.fromStrict msg
229-
go (parse parser remainder)
239+
b <- isExiting
240+
if b
241+
then pure 0
242+
else do
243+
res <- parseOne logger clientIn r
244+
case res of
245+
Nothing -> pure 1
246+
Just (msg, remainder) -> do
247+
Processing.processMessage pLogger $ BSL.fromStrict msg
248+
go (parse parser remainder)
230249

231250
parseOne ::
232251
MonadIO m =>
@@ -366,9 +385,10 @@ withWebsocketRunServer wsConf withLspDefinition ioLogger lspLogger =
366385
-- ---------------------------------------------------------------------
367386

368387
-- | Simple server to make sure all output is serialised
369-
sendServer :: LogAction IO (WithSeverity LspServerLog) -> TChan J.Value -> (BSL.LazyByteString -> IO ()) -> (BSL.LazyByteString -> BSL.LazyByteString) -> IO ()
370-
sendServer _logger msgChan clientOut prepareMessage = do
371-
forever $ do
388+
sendServer :: LogAction IO (WithSeverity LspServerLog) -> TChan FromServerMessage -> (BSL.LazyByteString -> IO ()) -> (BSL.LazyByteString -> BSL.LazyByteString) -> IO ()
389+
sendServer _logger msgChan clientOut prepareMessage = go
390+
where
391+
go = do
372392
msg <- atomically $ readTChan msgChan
373393

374394
-- We need to make sure we only send over the content of the message,
@@ -377,6 +397,10 @@ sendServer _logger msgChan clientOut prepareMessage = do
377397
let out = prepareMessage str
378398

379399
clientOut out
400+
-- close the client sender when we send out the shutdown request's response
401+
case msg of
402+
FromServerRsp SMethod_Shutdown _ -> pure ()
403+
_ -> go
380404

381405
-- TODO: figure out how to re-enable
382406
-- This can lead to infinite recursion in logging, see https://github.com/haskell/lsp/issues/447

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

Lines changed: 44 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -137,6 +137,9 @@ data LanguageContextEnv config = LanguageContextEnv
137137
-- ^ The delay before starting a progress reporting session, in microseconds
138138
, resProgressUpdateDelay :: Int
139139
-- ^ The delay between sending progress updates, in microseconds
140+
, resWaitSender :: !(IO ())
141+
-- ^ An IO action that waits for the sender thread to finish sending all pending messages.
142+
-- This is used to ensure all responses are sent before the server exits. See Note [Shutdown]
140143
}
141144

142145
-- ---------------------------------------------------------------------
@@ -211,9 +214,9 @@ data LanguageContextState config = LanguageContextState
211214
, resRegistrationsReq :: !(TVar (RegistrationMap Request))
212215
, resLspId :: !(TVar Int32)
213216
, resShutdown :: !(C.Barrier ())
214-
-- ^ Has the server received 'shutdown'? Can be used to conveniently trigger e.g. thread termination,
215-
-- but if you need a cleanup action to terminate before exiting, then you should install a full
216-
-- 'shutdown' handler
217+
-- ^ Barrier signaled when the server receives the 'shutdown' request. See Note [Shutdown]
218+
, resExit :: !(C.Barrier ())
219+
-- ^ Barrier signaled when the server receives the 'exit' notification. See Note [Shutdown]
217220
}
218221

219222
type ResponseMap = IxMap LspId (Product SMethod ServerResponseCallback)
@@ -754,6 +757,17 @@ isShuttingDown = do
754757
Just _ -> True
755758
Nothing -> False
756759

760+
{- | Check if the server has received the 'exit' notification.
761+
See Note [Shutdown]
762+
-}
763+
isExiting :: (m ~ LspM config) => m Bool
764+
isExiting = do
765+
b <- resExit . resState <$> getLspEnv
766+
r <- liftIO $ C.waitBarrierMaybe b
767+
pure $ case r of
768+
Just () -> True
769+
Nothing -> False
770+
757771
-- | Blocks until the server receives a 'shutdown' request.
758772
waitShuttingDown :: (m ~ LspM config) => m ()
759773
waitShuttingDown = do
@@ -843,18 +857,34 @@ The client can still always choose to cancel for another reason.
843857
-}
844858

845859
{- Note [Shutdown]
846-
The 'shutdown' request basically tells the server to clean up and stop doing things.
847-
In particular, it allows us to ignore or reject all further messages apart from 'exit'.
860+
~~~~~~~~~~~~~~~~~~
861+
The LSP protocol has a two-phase shutdown sequence:
862+
863+
1. `shutdown` request: ask the server to stop doing work and finish
864+
any in-flight operations.
865+
2. `exit` notification: tell the server to terminate the process.
866+
867+
We expose two `Barrier`s to track this state:
868+
869+
- `resShutdown`: signalled when we receive the `shutdown` request.
870+
Use `isShuttingDown` to check this.
871+
- `resExit`: signalled when we receive the `exit` notification.
872+
Use `isExiting` to check this.
873+
874+
Shutdown is itself a request, and we assume the client will not send
875+
`exit` before `shutdown`. If you want to be sure that some cleanup has
876+
run before the server exits, make that cleanup part of your customize
877+
`shutdown` handler.
848878
849-
We also provide a `Barrier` that indicates whether or not we are shutdown, this can
850-
be convenient, e.g. you can race a thread against `waitBarrier` to have it automatically
851-
be cancelled when we receive `shutdown`.
879+
We use a dedicated sender thread to serialise all messages that go to
880+
the client. That thread is set up to stop sending messages after the
881+
`shutdown` response has been sent.
852882
853-
Shutdown is a request, and the client won't send `exit` until a server responds, so if you
854-
want to be sure that some cleanup happens, you need to ensure we don't respond to `shutdown`
855-
until it's done. The best way to do this is just to install a specific `shutdown` handler.
883+
While handling the `shutdown` request we call `resWaitSender` to wait
884+
for the sender thread to flush and finish. Otherwise, we might get a
885+
"broken pipe" error from trying to send messages after the client has
886+
closed our output handle.
856887
857-
After the `shutdown` request, we don't handle any more requests and notifications other than
858-
`exit`. We also don't handle any more responses to requests we have sent but just throw the
859-
responses away.
888+
After the `shutdown` request has been processed, we do not handle any
889+
more requests or notifications except for `exit`.
860890
-}

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

Lines changed: 19 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,6 @@ import Language.LSP.Protocol.Utils.SMethodMap qualified as SMethodMap
5959
import Language.LSP.Server.Core
6060
import Language.LSP.VFS as VFS
6161
import Prettyprinter
62-
import System.Exit
6362

6463
data LspProcessingLog
6564
= VfsLog VfsLog
@@ -119,9 +118,11 @@ initializeRequestHandler ::
119118
ServerDefinition config ->
120119
VFS ->
121120
(FromServerMessage -> IO ()) ->
121+
-- | Action that waits for the sender thread to finish. We use it to set 'LanguageContextEnv.resWaitSender', See Note [Shutdown].
122+
IO () ->
122123
TMessage Method_Initialize ->
123124
IO (Maybe (LanguageContextEnv config))
124-
initializeRequestHandler logger ServerDefinition{..} vfs sendFunc req = do
125+
initializeRequestHandler logger ServerDefinition{..} vfs sendFunc waitSender req = do
125126
let sendResp = sendFunc . FromServerRsp SMethod_Initialize
126127
handleErr (Left err) = do
127128
sendResp $ makeResponseError (req ^. L.id) err
@@ -172,6 +173,7 @@ initializeRequestHandler logger ServerDefinition{..} vfs sendFunc req = do
172173
resRegistrationsReq <- newTVarIO mempty
173174
resLspId <- newTVarIO 0
174175
resShutdown <- C.newBarrier
176+
resExit <- C.newBarrier
175177
pure LanguageContextState{..}
176178

177179
-- Call the 'duringInitialization' callback to let the server kick stuff up
@@ -187,6 +189,7 @@ initializeRequestHandler logger ServerDefinition{..} vfs sendFunc req = do
187189
rootDir
188190
(optProgressStartDelay options)
189191
(optProgressUpdateDelay options)
192+
waitSender
190193
configChanger config = forward interpreter (onConfigChange config)
191194
handlers = transmuteHandlers interpreter (staticHandlers clientCaps)
192195
interpreter = interpretHandler initializationResult
@@ -440,6 +443,13 @@ handle logger m msg =
440443
SMethod_WorkspaceDidChangeConfiguration -> handle' logger (Just $ handleDidChangeConfiguration logger) m msg
441444
-- See Note [LSP configuration]
442445
SMethod_Initialized -> handle' logger (Just $ \_ -> initialDynamicRegistrations logger >> requestConfigUpdate (cmap (fmap LspCore) logger)) m msg
446+
SMethod_Exit -> handle' logger (Just $ \_ -> signalExit) m msg
447+
where
448+
signalExit :: LspM config ()
449+
signalExit = do
450+
logger <& Exiting `WithSeverity` Info
451+
b <- resExit . resState <$> getLspEnv
452+
liftIO $ signalBarrier b ()
443453
SMethod_Shutdown -> handle' logger (Just $ \_ -> signalShutdown) m msg
444454
where
445455
-- See Note [Shutdown]
@@ -497,6 +507,10 @@ handle' logger mAction m msg = do
497507
-- See Note [Shutdown]
498508
IsClientReq | shutdown, not (allowedMethod m) -> requestDuringShutdown msg
499509
IsClientReq -> case pickHandler dynReqHandlers reqHandlers of
510+
Just h | SMethod_Shutdown <- m -> do
511+
waitSender <- resWaitSender <$> getLspEnv
512+
liftIO $ h msg (runLspT env . sendResponse msg)
513+
liftIO waitSender
500514
Just h -> liftIO $ h msg (runLspT env . sendResponse msg)
501515
Nothing
502516
| SMethod_Shutdown <- m -> liftIO $ shutdownRequestHandler msg (runLspT env . sendResponse msg)
@@ -557,9 +571,9 @@ progressCancelHandler logger (TNotificationMessage _ _ (WorkDoneProgressCancelPa
557571
liftIO cancelAction
558572

559573
exitNotificationHandler :: (MonadIO m) => LogAction m (WithSeverity LspProcessingLog) -> Handler m Method_Exit
560-
exitNotificationHandler logger _ = do
561-
logger <& Exiting `WithSeverity` Info
562-
liftIO exitSuccess
574+
exitNotificationHandler _logger _ = do
575+
-- default exit handler do nothing
576+
return ()
563577

564578
-- | Default Shutdown handler
565579
shutdownRequestHandler :: Handler IO Method_Shutdown

0 commit comments

Comments
 (0)