1
1
{-# LANGUAGE OverloadedStrings #-}
2
+ {-# LANGUAGE DerivingStrategies #-}
3
+ {-# LANGUAGE RecordWildCards #-}
2
4
3
5
module Language.LSP.Server.Control (
4
6
-- * Running
5
- runServer ,
6
7
runServerWith ,
7
- runServerWithHandles ,
8
+ runServerWithConfig ,
9
+ ServerConfig (.. ),
8
10
LspServerLog (.. ),
11
+
12
+ -- ** Using standard 'IO' 'Handle's
13
+ runServer ,
14
+
15
+ -- ** Using 'Handle's
16
+ runServerWithHandles ,
17
+ prependHeader ,
18
+ parseHeaders ,
19
+
20
+ -- ** Using websockets
21
+ WebsocketConfig (.. ),
22
+ withWebsocket ,
23
+ withWebsocketRunServer ,
9
24
) where
10
25
11
26
import Colog.Core (LogAction (.. ), Severity (.. ), WithSeverity (.. ), (<&) )
@@ -33,6 +48,9 @@ import Language.LSP.Server.Processing qualified as Processing
33
48
import Language.LSP.VFS
34
49
import Prettyprinter
35
50
import System.IO
51
+ import qualified Network.WebSockets as WS
52
+ import Control.Concurrent.Async
53
+ import Control.Exception (finally )
36
54
37
55
data LspServerLog
38
56
= LspProcessingLog Processing. LspProcessingLog
@@ -42,6 +60,7 @@ data LspServerLog
42
60
| Starting
43
61
| ParsedMsg T. Text
44
62
| SendMsg TL. Text
63
+ | WebsocketLog WebsocketLog
45
64
deriving (Show )
46
65
47
66
instance Pretty LspServerLog where
@@ -60,6 +79,7 @@ instance Pretty LspServerLog where
60
79
pretty Starting = " Starting server"
61
80
pretty (ParsedMsg msg) = " ---> " <> pretty msg
62
81
pretty (SendMsg msg) = " <--2-- " <> pretty msg
82
+ pretty (WebsocketLog msg) = " Websocket:" <+> pretty msg
63
83
64
84
-- ---------------------------------------------------------------------
65
85
@@ -71,18 +91,20 @@ instance Pretty LspServerLog where
71
91
runServer :: forall config . ServerDefinition config -> IO Int
72
92
runServer =
73
93
runServerWithHandles
74
- ioLogger
75
- lspLogger
94
+ defaultIOLogger
95
+ defaultLspLogger
76
96
stdin
77
97
stdout
78
- where
98
+
99
+ defaultIOLogger :: LogAction IO (WithSeverity LspServerLog )
100
+ defaultIOLogger = L. cmap (show . prettyMsg) L. logStringStderr
101
+ where
79
102
prettyMsg l = " [" <> viaShow (L. getSeverity l) <> " ] " <> pretty (L. getMsg l)
80
- ioLogger :: LogAction IO (WithSeverity LspServerLog )
81
- ioLogger = L. cmap (show . prettyMsg) L. logStringStderr
82
- lspLogger :: LogAction (LspM config ) (WithSeverity LspServerLog )
83
- lspLogger =
84
- let clientLogger = L. cmap (fmap (T. pack . show . pretty)) defaultClientLogger
85
- in clientLogger <> L. hoistLogAction liftIO ioLogger
103
+
104
+ defaultLspLogger :: LogAction (LspM config ) (WithSeverity LspServerLog )
105
+ defaultLspLogger =
106
+ let clientLogger = L. cmap (fmap (T. pack . show . pretty)) defaultClientLogger
107
+ in clientLogger <> L. hoistLogAction liftIO defaultIOLogger
86
108
87
109
{- | Starts a language server over the specified handles.
88
110
This function will return once the @exit@ notification is received.
@@ -116,27 +138,55 @@ runServerWithHandles ioLogger logger hin hout serverDefinition = do
116
138
117
139
{- | Starts listening and sending requests and responses
118
140
using the specified I/O.
141
+
142
+ Assumes that the client sends (and wants to receive) the Content-Length
143
+ header. If you do not want this to be the case, use 'runServerWithConfig'
119
144
-}
120
145
runServerWith ::
121
146
-- | The logger to use outside the main body of the server where we can't assume the ability to send messages.
122
147
LogAction IO (WithSeverity LspServerLog ) ->
123
148
-- | The logger to use once the server has started and can successfully send messages.
124
149
LogAction (LspM config ) (WithSeverity LspServerLog ) ->
125
150
-- | Client input.
126
- IO BS. ByteString ->
151
+ IO BS. StrictByteString ->
127
152
-- | Function to provide output to.
128
- (BSL. ByteString -> IO () ) ->
153
+ (BSL. LazyByteString -> IO () ) ->
129
154
ServerDefinition config ->
130
155
IO Int -- exit code
131
- runServerWith ioLogger logger clientIn clientOut serverDefinition = do
156
+ runServerWith ioLogger lspLogger inwards outwards
157
+ = runServerWithConfig ServerConfig {prepareOutwards = prependHeader, parseInwards = parseHeaders, .. }
158
+
159
+ -- ---------------------------------------------------------------------
160
+
161
+ data ServerConfig config
162
+ = ServerConfig
163
+ { ioLogger :: LogAction IO (WithSeverity LspServerLog )
164
+ -- ^ The logger to use outside the main body of the server where we can't assume the ability to send messages.
165
+ , lspLogger :: LogAction (LspM config ) (WithSeverity LspServerLog )
166
+ -- ^ The logger to use once the server has started and can successfully send messages.
167
+ , inwards :: IO BS. StrictByteString
168
+ -- ^ Client input.
169
+ , outwards :: BSL. LazyByteString -> IO ()
170
+ -- ^ Function to provide output to.
171
+ , prepareOutwards :: BSL. LazyByteString -> BSL. LazyByteString
172
+ -- ^ how to prepare an outgoing response for sending. This can be used, to e.g. prepend the Content-Length header, c.f. 'prependHeader'
173
+ , parseInwards :: Attoparsec. Parser BS. StrictByteString
174
+ -- ^ how to parse the input. This can be used to consume the Content-Length and Content-Type headers, c.f. 'parseHeaders'
175
+ }
176
+
177
+ runServerWithConfig ::
178
+ ServerConfig config ->
179
+ ServerDefinition config ->
180
+ IO Int
181
+ runServerWithConfig ServerConfig {.. } serverDefinition = do
132
182
ioLogger <& Starting `WithSeverity ` Info
133
183
134
184
cout <- atomically newTChan :: IO (TChan J. Value )
135
- _rhpid <- forkIO $ sendServer ioLogger cout clientOut
185
+ _rhpid <- forkIO $ sendServer ioLogger cout outwards prepareOutwards
136
186
137
187
let sendMsg msg = atomically $ writeTChan cout $ J. toJSON msg
138
188
139
- ioLoop ioLogger logger clientIn serverDefinition emptyVFS sendMsg
189
+ ioLoop ioLogger lspLogger inwards parseInwards serverDefinition emptyVFS sendMsg
140
190
141
191
return 1
142
192
@@ -146,12 +196,13 @@ ioLoop ::
146
196
forall config .
147
197
LogAction IO (WithSeverity LspServerLog ) ->
148
198
LogAction (LspM config ) (WithSeverity LspServerLog ) ->
149
- IO BS. ByteString ->
199
+ IO BS. StrictByteString ->
200
+ Attoparsec. Parser BS. StrictByteString ->
150
201
ServerDefinition config ->
151
202
VFS ->
152
203
(FromServerMessage -> IO () ) ->
153
204
IO ()
154
- ioLoop ioLogger logger clientIn serverDefinition vfs sendMsg = do
205
+ ioLoop ioLogger logger clientIn parser serverDefinition vfs sendMsg = do
155
206
minitialize <- parseOne ioLogger clientIn (parse parser " " )
156
207
case minitialize of
157
208
Nothing -> pure ()
@@ -167,7 +218,7 @@ ioLoop ioLogger logger clientIn serverDefinition vfs sendMsg = do
167
218
pioLogger = L. cmap (fmap LspProcessingLog ) ioLogger
168
219
pLogger = L. cmap (fmap LspProcessingLog ) logger
169
220
170
- loop :: Result BS. ByteString -> LspM config ()
221
+ loop :: Result BS. StrictByteString -> LspM config ()
171
222
loop = go
172
223
where
173
224
go r = do
@@ -178,30 +229,12 @@ ioLoop ioLogger logger clientIn serverDefinition vfs sendMsg = do
178
229
Processing. processMessage pLogger $ BSL. fromStrict msg
179
230
go (parse parser remainder)
180
231
181
- parser = do
182
- try contentType <|> return ()
183
- len <- contentLength
184
- try contentType <|> return ()
185
- _ <- string _ONE_CRLF
186
- Attoparsec. take len
187
-
188
- contentLength = do
189
- _ <- string " Content-Length: "
190
- len <- decimal
191
- _ <- string _ONE_CRLF
192
- return len
193
-
194
- contentType = do
195
- _ <- string " Content-Type: "
196
- skipWhile (/= ' \r ' )
197
- _ <- string _ONE_CRLF
198
- return ()
199
232
200
233
parseOne ::
201
234
MonadIO m =>
202
235
LogAction m (WithSeverity LspServerLog ) ->
203
- IO BS. ByteString ->
204
- Result BS. ByteString ->
236
+ IO BS. StrictByteString ->
237
+ Result BS. StrictByteString ->
205
238
m (Maybe (BS. ByteString , BS. ByteString ))
206
239
parseOne logger clientIn = go
207
240
where
@@ -223,30 +256,155 @@ parseOne logger clientIn = go
223
256
224
257
-- ---------------------------------------------------------------------
225
258
259
+ data WebsocketLog
260
+ = WebsocketShutDown
261
+ | WebsocketNewConnection
262
+ | WebsocketConnectionClosed
263
+ | WebsocketPing
264
+ | WebsocketStarted
265
+ | WebsocketIncomingRequest
266
+ | WebsocketOutgoingResponse
267
+ deriving stock Show
268
+
269
+
270
+ instance Pretty WebsocketLog where
271
+ pretty l = case l of
272
+ WebsocketPing -> " Ping"
273
+ WebsocketStarted -> " Started Server, waiting for connections"
274
+ WebsocketShutDown -> " Shut down server"
275
+ WebsocketNewConnection -> " New connection established"
276
+ WebsocketIncomingRequest -> " Received request"
277
+ WebsocketConnectionClosed -> " Closed connection to client"
278
+ WebsocketOutgoingResponse -> " Sent response"
279
+
280
+ -- | 'host' and 'port' of the websocket server to set up
281
+ data WebsocketConfig
282
+ = WebsocketConfig
283
+ { host :: ! String
284
+ -- ^ the host of the websocket server, e.g. @"localhost"@
285
+ , port :: ! Int
286
+ -- ^ the port of the websocket server, e.g. @8080@
287
+ }
288
+
289
+ -- | Set up a websocket server, then call call the continuation (in our case this corresponds to the language server) after accepting a connection
290
+ withWebsocket
291
+ :: LogAction IO (WithSeverity LspServerLog )
292
+ -- ^ The logger
293
+ -> WebsocketConfig
294
+ -- ^ The configuration of the websocket server
295
+ -> (IO BS. StrictByteString -> (BSL. LazyByteString -> IO () ) -> IO r )
296
+ -- ^ invoke the lsp server, passing communication functions
297
+ -> IO ()
298
+ withWebsocket logger conf startLspServer = do
299
+ let wsLogger = L. cmap (fmap WebsocketLog ) logger
300
+
301
+ WS. runServer (host conf) (port conf) $ \ pending -> do
302
+
303
+ conn <- WS. acceptRequest pending
304
+ wsLogger <& WebsocketNewConnection `WithSeverity ` Debug
305
+
306
+ outChan <- newChan
307
+ inChan <- newChan
308
+
309
+ let inwards = readChan inChan
310
+ outwards = writeChan outChan
311
+
312
+ WS. withPingThread conn 30 (wsLogger <& WebsocketPing `WithSeverity ` Debug ) $ do
313
+ withAsync (startLspServer inwards outwards) $ \ _lspAsync ->
314
+ race_
315
+ (forever $ do
316
+ msg <- readChan outChan
317
+ wsLogger <& WebsocketOutgoingResponse `WithSeverity ` Debug
318
+ WS. sendTextData conn msg
319
+ )
320
+ (forever $ do
321
+ msg <- WS. receiveData conn
322
+ wsLogger <& WebsocketIncomingRequest `WithSeverity ` Debug
323
+ writeChan inChan msg
324
+ )
325
+ `finally` do
326
+ wsLogger <& WebsocketConnectionClosed `WithSeverity ` Debug
327
+
328
+ withWebsocketRunServer
329
+ :: WebsocketConfig
330
+ -- ^ Configuration for the websocket
331
+ -> ((ServerDefinition config -> IO Int ) -> IO Int )
332
+ -- ^ How to set up a new 'ServerDefinition' for a specific configuration. z
333
+ -- This is passed as CPS'd 'IO' to allow for setting (- and cleaning) up
334
+ -- a server per websocket connection
335
+ -> LogAction IO (WithSeverity LspServerLog )
336
+ -- ^ The 'IO' logger
337
+ -> LogAction (LspM config ) (WithSeverity LspServerLog )
338
+ -- ^ The logger that logs in 'LspM' to the client
339
+ -> IO ()
340
+ withWebsocketRunServer wsConf withLspDefinition ioLogger lspLogger
341
+ = withWebsocket ioLogger wsConf $ \ inwards outwards -> do
342
+ withLspDefinition $ \ lspDefinition ->
343
+ runServerWithConfig
344
+ ServerConfig
345
+ { ioLogger
346
+ , lspLogger
347
+ , inwards
348
+ , outwards
349
+ -- NOTE: if you run the language server on websockets, you do not
350
+ -- need to prepend headers to requests and responses, because
351
+ -- the chunking is already handled by the websocket, i.e. there's
352
+ -- no situation where the client or the server has to rely on input/
353
+ -- output chunking
354
+ , prepareOutwards = id
355
+ , parseInwards = Attoparsec. takeByteString}
356
+ lspDefinition
357
+
358
+ -- ---------------------------------------------------------------------
359
+
226
360
-- | Simple server to make sure all output is serialised
227
- sendServer :: LogAction IO (WithSeverity LspServerLog ) -> TChan J. Value -> (BSL. ByteString -> IO () ) -> IO ()
228
- sendServer _logger msgChan clientOut = do
361
+ sendServer :: LogAction IO (WithSeverity LspServerLog ) -> TChan J. Value -> (BSL. LazyByteString -> IO () ) -> ( BSL. LazyByteString -> BSL. LazyByteString ) -> IO ()
362
+ sendServer _logger msgChan clientOut prepareMessage = do
229
363
forever $ do
230
364
msg <- atomically $ readTChan msgChan
231
365
232
366
-- We need to make sure we only send over the content of the message,
233
367
-- and no other tags/wrapper stuff
234
368
let str = J. encode msg
235
-
236
- let out =
237
- BSL. concat
238
- [ TL. encodeUtf8 $ TL. pack $ " Content-Length: " ++ show (BSL. length str)
239
- , BSL. fromStrict _TWO_CRLF
240
- , str
241
- ]
369
+ let out = prepareMessage str
242
370
243
371
clientOut out
244
372
245
373
-- TODO: figure out how to re-enable
246
374
-- This can lead to infinite recursion in logging, see https://github.com/haskell/lsp/issues/447
247
375
-- logger <& SendMsg (TL.decodeUtf8 str) `WithSeverity` Debug
248
376
249
- _ONE_CRLF :: BS. ByteString
377
+ -- | prepend a Content-Length header to the given message
378
+ prependHeader :: BSL. LazyByteString -> BSL. LazyByteString
379
+ prependHeader str = BSL. concat
380
+ [ TL. encodeUtf8 $ TL. pack $ " Content-Length: " ++ show (BSL. length str)
381
+ , BSL. fromStrict _TWO_CRLF
382
+ , str
383
+ ]
384
+
385
+ -- | parse Content-Length and Content-Type headers and then consume
386
+ -- input with length of the Content-Length
387
+ parseHeaders :: Attoparsec. Parser BS. StrictByteString
388
+ parseHeaders = do
389
+ try contentType <|> return ()
390
+ len <- contentLength
391
+ try contentType <|> return ()
392
+ _ <- string _ONE_CRLF
393
+ Attoparsec. take len
394
+ where
395
+ contentLength = do
396
+ _ <- string " Content-Length: "
397
+ len <- decimal
398
+ _ <- string _ONE_CRLF
399
+ return len
400
+
401
+ contentType = do
402
+ _ <- string " Content-Type: "
403
+ skipWhile (/= ' \r ' )
404
+ _ <- string _ONE_CRLF
405
+ return ()
406
+
407
+ _ONE_CRLF :: BS. StrictByteString
250
408
_ONE_CRLF = " \r\n "
251
- _TWO_CRLF :: BS. ByteString
409
+ _TWO_CRLF :: BS. StrictByteString
252
410
_TWO_CRLF = " \r\n\r\n "
0 commit comments