11{-# LANGUAGE DerivingStrategies #-}
22{-# LANGUAGE OverloadedStrings #-}
33{-# LANGUAGE RecordWildCards #-}
4+ {-# LANGUAGE TypeFamilies #-}
45
56module Language.LSP.Server.Control (
67 -- * Running
@@ -29,7 +30,7 @@ import Control.Applicative ((<|>))
2930import Control.Concurrent
3031import Control.Concurrent.Async
3132import Control.Concurrent.STM.TChan
32- import Control.Exception (finally )
33+ import Control.Exception (catchJust , finally , throwIO )
3334import Control.Monad
3435import Control.Monad.IO.Class
3536import Control.Monad.STM
@@ -51,19 +52,23 @@ import Language.LSP.VFS
5152import Network.WebSockets qualified as WS
5253import Prettyprinter
5354import System.IO
55+ import System.IO.Error (isResourceVanishedError )
5456
5557data 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
6670instance 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
180196runServerWithConfig 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
231250parseOne ::
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
0 commit comments