11{-# LANGUAGE OverloadedStrings #-}
22{-# LANGUAGE ScopedTypeVariables #-}
33{-# LANGUAGE RankNTypes #-}
4- {-# LANGUAGE LambdaCase #-}
54
65-- So we can keep using the old prettyprinter modules (which have a better
76-- compatibility range) for now.
@@ -17,57 +16,35 @@ module Language.LSP.Server.Control
1716 ) where
1817
1918import qualified Colog.Core as L
20- import Colog.Core (LogAction (.. ), WithSeverity (.. ), Severity (.. ), (<&) )
21- import Control.Concurrent
19+ import Colog.Core (LogAction (.. ), WithSeverity (.. ), Severity (.. ), (<&) , cmap )
20+ import qualified Control.Concurrent.Async as Async
2221import Control.Concurrent.STM.TChan
23- import Control.Monad
2422import Control.Monad.STM
2523import Control.Monad.IO.Class
2624import qualified Data.Aeson as J
27- import qualified Data.Attoparsec.ByteString as Attoparsec
28- import Data.Attoparsec.ByteString.Char8
2925import qualified Data.ByteString as BS
3026import Data.ByteString.Builder.Extra (defaultChunkSize )
31- import qualified Data.ByteString.Lazy as BSL
32- import qualified Data.Text.Lazy as TL
33- import qualified Data.Text.Lazy.Encoding as TL
3427import qualified Data.Text as T
35- import qualified Data.Text.Encoding as T
3628import Data.Text.Prettyprint.Doc
37- import Data.List
3829import Language.LSP.Server.Core
3930import qualified Language.LSP.Server.Processing as Processing
40- import Language.LSP.Types
4131import Language.LSP.VFS
32+ import qualified Language.LSP.Server.IO as IO
4233import Language.LSP.Logging (defaultClientLogger )
4334import System.IO
4435
4536data LspServerLog =
4637 LspProcessingLog Processing. LspProcessingLog
47- | DecodeInitializeError String
48- | HeaderParseFail [String ] String
49- | EOF
38+ | LspIoLog IO. LspIoLog
5039 | Starting
51- | ParsedMsg T. Text
52- | SendMsg TL. Text
40+ | Stopping
5341 deriving (Show )
5442
5543instance Pretty LspServerLog where
5644 pretty (LspProcessingLog l) = pretty l
57- pretty (DecodeInitializeError err) =
58- vsep [
59- " Got error while decoding initialize:"
60- , pretty err
61- ]
62- pretty (HeaderParseFail ctxs err) =
63- vsep [
64- " Failed to parse message header:"
65- , pretty (intercalate " > " ctxs) <> " : " <+> pretty err
66- ]
67- pretty EOF = " Got EOF"
45+ pretty (LspIoLog l) = pretty l
6846 pretty Starting = " Starting server"
69- pretty (ParsedMsg msg) = " ---> " <> pretty msg
70- pretty (SendMsg msg) = " <--2-- " <> pretty msg
47+ pretty Stopping = " Stopping server"
7148
7249-- ---------------------------------------------------------------------
7350
@@ -116,7 +93,7 @@ runServerWithHandles ioLogger logger hin hout serverDefinition = do
11693 clientIn = BS. hGetSome hin defaultChunkSize
11794
11895 clientOut out = do
119- BSL . hPut hout out
96+ BS . hPut hout out
12097 hFlush hout
12198
12299 runServerWith ioLogger logger clientIn clientOut serverDefinition
@@ -130,113 +107,34 @@ runServerWith ::
130107 -- ^ The logger to use once the server has started and can successfully send messages.
131108 -> IO BS. ByteString
132109 -- ^ Client input.
133- -> (BSL . ByteString -> IO () )
110+ -> (BS . ByteString -> IO () )
134111 -- ^ Function to provide output to.
135112 -> ServerDefinition config
136113 -> IO Int -- exit code
137114runServerWith ioLogger logger clientIn clientOut serverDefinition = do
138115
139116 ioLogger <& Starting `WithSeverity ` Info
140117
141- cout <- atomically newTChan :: IO ( TChan J. Value )
142- _rhpid <- forkIO $ sendServer ioLogger cout clientOut
118+ cout <- atomically newTChan
119+ cin <- atomically newTChan
143120
144- let sendMsg msg = atomically $ writeTChan cout $ J. toJSON msg
121+ let serverOut = IO. serverOut (cmap (fmap LspIoLog ) ioLogger) (atomically $ readTChan cout) clientOut
122+ serverIn = IO. serverIn (cmap (fmap LspIoLog ) ioLogger) (atomically . writeTChan cin) clientIn
145123
146- initVFS $ \ vfs -> do
147- ioLoop ioLogger logger clientIn serverDefinition vfs sendMsg
124+ sendMsg msg = atomically $ writeTChan cout $ J. toJSON msg
125+ recvMsg = atomically $ readTChan cin
148126
149- return 1
150-
151- -- ---------------------------------------------------------------------
152-
153- ioLoop ::
154- forall config
155- . LogAction IO (WithSeverity LspServerLog )
156- -> LogAction (LspM config ) (WithSeverity LspServerLog )
157- -> IO BS. ByteString
158- -> ServerDefinition config
159- -> VFS
160- -> (FromServerMessage -> IO () )
161- -> IO ()
162- ioLoop ioLogger logger clientIn serverDefinition vfs sendMsg = do
163- minitialize <- parseOne ioLogger clientIn (parse parser " " )
164- case minitialize of
165- Nothing -> pure ()
166- Just (msg,remainder) -> do
167- case J. eitherDecode $ BSL. fromStrict msg of
168- Left err -> ioLogger <& DecodeInitializeError err `WithSeverity ` Error
169- Right initialize -> do
170- mInitResp <- Processing. initializeRequestHandler serverDefinition vfs sendMsg initialize
171- case mInitResp of
172- Nothing -> pure ()
173- Just env -> runLspT env $ loop (parse parser remainder)
174- where
175-
176- loop :: Result BS. ByteString -> LspM config ()
177- loop = go
178- where
179- pLogger = L. cmap (fmap LspProcessingLog ) logger
180- go r = do
181- res <- parseOne logger clientIn r
182- case res of
183- Nothing -> pure ()
184- Just (msg,remainder) -> do
185- Processing. processMessage pLogger $ BSL. fromStrict msg
186- go (parse parser remainder)
187-
188- parser = do
189- _ <- string " Content-Length: "
190- len <- decimal
191- _ <- string _TWO_CRLF
192- Attoparsec. take len
193-
194- parseOne ::
195- MonadIO m
196- => LogAction m (WithSeverity LspServerLog )
197- -> IO BS. ByteString
198- -> Result BS. ByteString
199- -> m (Maybe (BS. ByteString ,BS. ByteString ))
200- parseOne logger clientIn = go
201- where
202- go (Fail _ ctxs err) = do
203- logger <& HeaderParseFail ctxs err `WithSeverity ` Error
204- pure Nothing
205- go (Partial c) = do
206- bs <- liftIO clientIn
207- if BS. null bs
208- then do
209- logger <& EOF `WithSeverity ` Error
210- pure Nothing
211- else go (c bs)
212- go (Done remainder msg) = do
213- logger <& ParsedMsg (T. decodeUtf8 msg) `WithSeverity ` Debug
214- pure $ Just (msg,remainder)
215-
216- -- ---------------------------------------------------------------------
217-
218- -- | Simple server to make sure all output is serialised
219- sendServer :: LogAction IO (WithSeverity LspServerLog ) -> TChan J. Value -> (BSL. ByteString -> IO () ) -> IO ()
220- sendServer logger msgChan clientOut = do
221- forever $ do
222- msg <- atomically $ readTChan msgChan
223-
224- -- We need to make sure we only send over the content of the message,
225- -- and no other tags/wrapper stuff
226- let str = J. encode msg
227-
228- let out = BSL. concat
229- [ TL. encodeUtf8 $ TL. pack $ " Content-Length: " ++ show (BSL. length str)
230- , BSL. fromStrict _TWO_CRLF
231- , str ]
232-
233- clientOut out
234- logger <& SendMsg (TL. decodeUtf8 str) `WithSeverity ` Debug
235-
236- -- |
237- --
238- --
239- _TWO_CRLF :: BS. ByteString
240- _TWO_CRLF = " \r\n\r\n "
127+ processingLoop = initVFS $ \ vfs ->
128+ Processing. processingLoop
129+ (cmap (fmap LspProcessingLog ) ioLogger)
130+ (cmap (fmap LspProcessingLog ) logger)
131+ vfs
132+ serverDefinition
133+ sendMsg
134+ recvMsg
241135
136+ -- Bind all the threads together so that any of them terminating will terminate everything
137+ serverOut `Async.race_` serverIn `Async.race_` processingLoop
242138
139+ ioLogger <& Stopping `WithSeverity ` Info
140+ return 0
0 commit comments