-
-
Notifications
You must be signed in to change notification settings - Fork 389
/
Copy pathLanguageServer.hs
302 lines (268 loc) · 13.5 KB
/
LanguageServer.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
-- WARNING: A copy of DA.Daml.LanguageServer, try to keep them in sync
-- This version removes the daml: handling
module Development.IDE.LSP.LanguageServer
( runLanguageServer
, setupLSP
, Log(..)
, ThreadQueue
, runWithWorkerThreads
) where
import Control.Concurrent.STM
import Control.Monad.Extra
import Control.Monad.IO.Class
import Control.Monad.Reader
import Data.Aeson (Value)
import Data.Maybe
import qualified Data.Set as Set
import qualified Data.Text as T
import Development.IDE.LSP.Server
import Development.IDE.Session (runWithDb)
import Ide.Types (traceWithSpan)
import Language.LSP.Protocol.Message
import Language.LSP.Protocol.Types
import qualified Language.LSP.Server as LSP
import System.IO
import UnliftIO.Async
import UnliftIO.Concurrent
import UnliftIO.Directory
import UnliftIO.Exception
import qualified Colog.Core as Colog
import Control.Monad.IO.Unlift (MonadUnliftIO)
import Control.Monad.Trans.Cont (evalContT)
import Development.IDE.Core.IdeConfiguration
import Development.IDE.Core.Shake hiding (Log)
import Development.IDE.Core.Tracing
import Development.IDE.Core.WorkerThread (withWorkerQueue,
withWorkerQueueOfOne)
import qualified Development.IDE.Session as Session
import Development.IDE.Types.Shake (WithHieDb,
WithHieDbShield (..))
import Ide.Logger
import Language.LSP.Server (LanguageContextEnv,
LspServerLog,
type (<~>))
data Log
= LogRegisteringIdeConfig !IdeConfiguration
| LogReactorThreadException !SomeException
| LogReactorMessageActionException !SomeException
| LogReactorThreadStopped
| LogCancelledRequest !SomeLspId
| LogSession Session.Log
| LogLspServer LspServerLog
| LogServerShutdownMessage
deriving Show
instance Pretty Log where
pretty = \case
LogRegisteringIdeConfig ideConfig ->
-- This log is also used to identify if HLS starts successfully in vscode-haskell,
-- don't forget to update the corresponding test in vscode-haskell if the text in
-- the next line has been modified.
"Registering IDE configuration:" <+> viaShow ideConfig
LogReactorThreadException e ->
vcat
[ "ReactorThreadException"
, pretty $ displayException e ]
LogReactorMessageActionException e ->
vcat
[ "ReactorMessageActionException"
, pretty $ displayException e ]
LogReactorThreadStopped ->
"Reactor thread stopped"
LogCancelledRequest requestId ->
"Cancelled request" <+> viaShow requestId
LogSession msg -> pretty msg
LogLspServer msg -> pretty msg
LogServerShutdownMessage -> "Received shutdown message"
runLanguageServer
:: forall config a m. (Show config)
=> Recorder (WithPriority Log)
-> LSP.Options
-> Handle -- input
-> Handle -- output
-> config
-> (config -> Value -> Either T.Text config)
-> (config -> m config ())
-> (MVar ()
-> IO (LSP.LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either (TResponseError Method_Initialize) (LSP.LanguageContextEnv config, a)),
LSP.Handlers (m config),
(LanguageContextEnv config, a) -> m config <~> IO))
-> IO ()
runLanguageServer recorder options inH outH defaultConfig parseConfig onConfigChange setup = do
-- This MVar becomes full when the server thread exits or we receive exit message from client.
-- LSP server will be canceled when it's full.
clientMsgVar <- newEmptyMVar
(doInitialize, staticHandlers, interpretHandler) <- setup clientMsgVar
let serverDefinition = LSP.ServerDefinition
{ LSP.parseConfig = parseConfig
, LSP.onConfigChange = onConfigChange
, LSP.defaultConfig = defaultConfig
-- TODO: magic string
, LSP.configSection = "haskell"
, LSP.doInitialize = doInitialize
, LSP.staticHandlers = const staticHandlers
, LSP.interpretHandler = interpretHandler
, LSP.options = modifyOptions options
}
let lspCologAction :: MonadIO m2 => Colog.LogAction m2 (Colog.WithSeverity LspServerLog)
lspCologAction = toCologActionWithPrio (cmapWithPrio LogLspServer recorder)
void $ untilMVar clientMsgVar $
void $ LSP.runServerWithHandles
lspCologAction
lspCologAction
inH
outH
serverDefinition
setupLSP ::
forall config err.
Recorder (WithPriority Log)
-> FilePath -- ^ root directory, see Note [Root Directory]
-> (FilePath -> IO FilePath) -- ^ Map root paths to the location of the hiedb for the project
-> LSP.Handlers (ServerM config)
-> (LSP.LanguageContextEnv config -> FilePath -> WithHieDb -> ThreadQueue -> IO IdeState)
-> MVar ()
-> IO (LSP.LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either err (LSP.LanguageContextEnv config, IdeState)),
LSP.Handlers (ServerM config),
(LanguageContextEnv config, IdeState) -> ServerM config <~> IO)
setupLSP recorder defaultRoot getHieDbLoc userHandlers getIdeState clientMsgVar = do
-- Send everything over a channel, since you need to wait until after initialise before
-- LspFuncs is available
clientMsgChan :: Chan ReactorMessage <- newChan
-- An MVar to control the lifetime of the reactor loop.
-- The loop will be stopped and resources freed when it's full
reactorLifetime <- newEmptyMVar
let stopReactorLoop = void $ tryPutMVar reactorLifetime ()
-- Forcefully exit
let exit = void $ tryPutMVar clientMsgVar ()
-- The set of requests ids that we have received but not finished processing
pendingRequests <- newTVarIO Set.empty
-- The set of requests that have been cancelled and are also in pendingRequests
cancelledRequests <- newTVarIO Set.empty
let cancelRequest reqId = atomically $ do
queued <- readTVar pendingRequests
-- We want to avoid that the list of cancelled requests
-- keeps growing if we receive cancellations for requests
-- that do not exist or have already been processed.
when (reqId `Set.member` queued) $
modifyTVar cancelledRequests (Set.insert reqId)
let clearReqId reqId = atomically $ do
modifyTVar pendingRequests (Set.delete reqId)
modifyTVar cancelledRequests (Set.delete reqId)
-- We implement request cancellation by racing waitForCancel against
-- the actual request handler.
let waitForCancel reqId = atomically $ do
cancelled <- readTVar cancelledRequests
unless (reqId `Set.member` cancelled) retry
let asyncHandlers = mconcat
[ userHandlers
, cancelHandler cancelRequest
, exitHandler exit
, shutdownHandler recorder stopReactorLoop
]
-- Cancel requests are special since they need to be handled
-- out of order to be useful. Existing handlers are run afterwards.
let doInitialize = handleInit recorder defaultRoot getHieDbLoc getIdeState reactorLifetime exit clearReqId waitForCancel clientMsgChan
let interpretHandler (env, st) = LSP.Iso (LSP.runLspT env . flip (runReaderT . unServerM) (clientMsgChan,st)) liftIO
pure (doInitialize, asyncHandlers, interpretHandler)
handleInit
:: Recorder (WithPriority Log)
-> FilePath -- ^ root directory, see Note [Root Directory]
-> (FilePath -> IO FilePath)
-> (LSP.LanguageContextEnv config -> FilePath -> WithHieDb -> ThreadQueue -> IO IdeState)
-> MVar ()
-> IO ()
-> (SomeLspId -> IO ())
-> (SomeLspId -> IO ())
-> Chan ReactorMessage
-> LSP.LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either err (LSP.LanguageContextEnv config, IdeState))
handleInit recorder defaultRoot getHieDbLoc getIdeState lifetime exitClientMsg clearReqId waitForCancel clientMsgChan env (TRequestMessage _ _ m params) = otTracedHandler "Initialize" (show m) $ \sp -> do
traceWithSpan sp params
-- only shift if lsp root is different from the rootDir
-- see Note [Root Directory]
root <- case LSP.resRootPath env of
Just lspRoot | lspRoot /= defaultRoot -> setCurrentDirectory lspRoot >> return lspRoot
_ -> pure defaultRoot
dbLoc <- getHieDbLoc root
let initConfig = parseConfiguration params
logWith recorder Info $ LogRegisteringIdeConfig initConfig
dbMVar <- newEmptyMVar
let handleServerException (Left e) = do
logWith recorder Error $ LogReactorThreadException e
exitClientMsg
handleServerException (Right _) = pure ()
exceptionInHandler e = do
logWith recorder Error $ LogReactorMessageActionException e
checkCancelled :: forall m . LspId m -> IO () -> (TResponseError m -> IO ()) -> IO ()
checkCancelled _id act k =
let sid = SomeLspId _id
in flip finally (clearReqId sid) $
catch (do
-- We could optimize this by first checking if the id
-- is in the cancelled set. However, this is unlikely to be a
-- bottleneck and the additional check might hide
-- issues with async exceptions that need to be fixed.
cancelOrRes <- race (waitForCancel sid) act
case cancelOrRes of
Left () -> do
logWith recorder Debug $ LogCancelledRequest sid
k $ TResponseError (InL LSPErrorCodes_RequestCancelled) "" Nothing
Right res -> pure res
) $ \(e :: SomeException) -> do
exceptionInHandler e
k $ TResponseError (InR ErrorCodes_InternalError) (T.pack $ show e) Nothing
_ <- flip forkFinally handleServerException $ do
untilMVar lifetime $ runWithWorkerThreads (cmapWithPrio LogSession recorder) dbLoc $ \withHieDb' threadQueue' -> do
putMVar dbMVar (WithHieDbShield withHieDb',threadQueue')
forever $ do
msg <- readChan clientMsgChan
-- We dispatch notifications synchronously and requests asynchronously
-- This is to ensure that all file edits and config changes are applied before a request is handled
case msg of
ReactorNotification act -> handle exceptionInHandler act
ReactorRequest _id act k -> void $ async $ checkCancelled _id act k
logWith recorder Info LogReactorThreadStopped
(WithHieDbShield withHieDb, threadQueue) <- takeMVar dbMVar
ide <- getIdeState env root withHieDb threadQueue
registerIdeConfiguration (shakeExtras ide) initConfig
pure $ Right (env,ide)
-- | runWithWorkerThreads
-- create several threads to run the session, db and session loader
-- see Note [Serializing runs in separate thread]
runWithWorkerThreads :: Recorder (WithPriority Session.Log) -> FilePath -> (WithHieDb -> ThreadQueue -> IO ()) -> IO ()
runWithWorkerThreads recorder dbLoc f = evalContT $ do
sessionRestartTQueue <- withWorkerQueue id
sessionLoaderTQueue <- withWorkerQueueOfOne id
(WithHieDbShield hiedb, threadQueue) <- runWithDb recorder dbLoc
liftIO $ f hiedb (ThreadQueue threadQueue sessionRestartTQueue sessionLoaderTQueue)
-- | Runs the action until it ends or until the given MVar is put.
-- Rethrows any exceptions.
untilMVar :: MonadUnliftIO m => MVar () -> m () -> m ()
untilMVar mvar io = void $
waitAnyCancel =<< traverse async [ io , readMVar mvar ]
cancelHandler :: (SomeLspId -> IO ()) -> LSP.Handlers (ServerM c)
cancelHandler cancelRequest = LSP.notificationHandler SMethod_CancelRequest $ \TNotificationMessage{_params=CancelParams{_id}} ->
liftIO $ cancelRequest (SomeLspId (toLspId _id))
where toLspId :: (Int32 |? T.Text) -> LspId a
toLspId (InL x) = IdInt x
toLspId (InR y) = IdString y
shutdownHandler :: Recorder (WithPriority Log) -> IO () -> LSP.Handlers (ServerM c)
shutdownHandler recorder stopReactor = LSP.requestHandler SMethod_Shutdown $ \_ resp -> do
(_, ide) <- ask
liftIO $ logWith recorder Debug LogServerShutdownMessage
-- stop the reactor to free up the hiedb connection
liftIO stopReactor
-- flush out the Shake session to record a Shake profile if applicable
liftIO $ shakeShut ide
resp $ Right Null
exitHandler :: IO () -> LSP.Handlers (ServerM c)
exitHandler exit = LSP.notificationHandler SMethod_Exit $ const $ liftIO exit
modifyOptions :: LSP.Options -> LSP.Options
modifyOptions x = x{ LSP.optTextDocumentSync = Just $ tweakTDS origTDS
}
where
tweakTDS tds = tds{_openClose=Just True, _change=Just TextDocumentSyncKind_Incremental, _save=Just $ InR $ SaveOptions Nothing}
origTDS = fromMaybe tdsDefault $ LSP.optTextDocumentSync x
tdsDefault = TextDocumentSyncOptions Nothing Nothing Nothing Nothing Nothing