@@ -38,12 +38,8 @@ import Development.IDE.Core.Tracing
38
38
import Development.IDE.LSP.HoverDefinition
39
39
import Development.IDE.Types.Logger
40
40
41
- import Control.Monad.IO.Unlift (MonadUnliftIO )
42
41
import System.IO.Unsafe (unsafeInterleaveIO )
43
42
44
- issueTrackerUrl :: T. Text
45
- issueTrackerUrl = " https://github.com/haskell/haskell-language-server/issues"
46
-
47
43
runLanguageServer
48
44
:: forall config . (Show config )
49
45
=> LSP. Options
@@ -58,16 +54,11 @@ runLanguageServer
58
54
runLanguageServer options inH outH getHieDbLoc defaultConfig onConfigurationChange userHandlers getIdeState = do
59
55
60
56
-- This MVar becomes full when the server thread exits or we receive exit message from client.
61
- -- LSP server will be canceled when it's full.
57
+ -- LSP loop will be canceled when it's full.
62
58
clientMsgVar <- newEmptyMVar
63
59
-- Forcefully exit
64
60
let exit = void $ tryPutMVar clientMsgVar ()
65
61
66
- -- An MVar to control the lifetime of the reactor loop.
67
- -- The loop will be stopped and resources freed when it's full
68
- reactorLifetime <- newEmptyMVar
69
- let stopReactorLoop = void $ tryPutMVar reactorLifetime ()
70
-
71
62
-- The set of requests ids that we have received but not finished processing
72
63
pendingRequests <- newTVarIO Set. empty
73
64
-- The set of requests that have been cancelled and are also in pendingRequests
@@ -102,7 +93,7 @@ runLanguageServer options inH outH getHieDbLoc defaultConfig onConfigurationChan
102
93
[ ideHandlers
103
94
, cancelHandler cancelRequest
104
95
, exitHandler exit
105
- , shutdownHandler stopReactorLoop
96
+ , shutdownHandler
106
97
]
107
98
-- Cancel requests are special since they need to be handled
108
99
-- out of order to be useful. Existing handlers are run afterwards.
@@ -111,23 +102,25 @@ runLanguageServer options inH outH getHieDbLoc defaultConfig onConfigurationChan
111
102
let serverDefinition = LSP. ServerDefinition
112
103
{ LSP. onConfigurationChange = onConfigurationChange
113
104
, LSP. defaultConfig = defaultConfig
114
- , LSP. doInitialize = handleInit reactorLifetime exit clearReqId waitForCancel clientMsgChan
105
+ , LSP. doInitialize = handleInit exit clearReqId waitForCancel clientMsgChan
115
106
, LSP. staticHandlers = asyncHandlers
116
107
, LSP. interpretHandler = \ (env, st) -> LSP. Iso (LSP. runLspT env . flip runReaderT (clientMsgChan,st)) liftIO
117
108
, LSP. options = modifyOptions options
118
109
}
119
110
120
- void $ untilMVar clientMsgVar $
121
- void $ LSP. runServerWithHandles
111
+ void $ waitAnyCancel =<< traverse async
112
+ [ void $ LSP. runServerWithHandles
122
113
inH
123
114
outH
124
115
serverDefinition
116
+ , void $ readMVar clientMsgVar
117
+ ]
125
118
126
119
where
127
120
handleInit
128
- :: MVar () -> IO () -> (SomeLspId -> IO () ) -> (SomeLspId -> IO () ) -> Chan ReactorMessage
121
+ :: IO () -> (SomeLspId -> IO () ) -> (SomeLspId -> IO () ) -> Chan ReactorMessage
129
122
-> LSP. LanguageContextEnv config -> RequestMessage Initialize -> IO (Either err (LSP. LanguageContextEnv config , IdeState ))
130
- handleInit lifetime exitClientMsg clearReqId waitForCancel clientMsgChan env (RequestMessage _ _ m params) = otTracedHandler " Initialize" (show m) $ \ sp -> do
123
+ handleInit exitClientMsg clearReqId waitForCancel clientMsgChan env (RequestMessage _ _ m params) = otTracedHandler " Initialize" (show m) $ \ sp -> do
131
124
traceWithSpan sp params
132
125
let root = LSP. resRootPath env
133
126
dir <- maybe getCurrentDirectory return root
@@ -145,71 +138,58 @@ runLanguageServer options inH outH getHieDbLoc defaultConfig onConfigurationChan
145
138
registerIdeConfiguration (shakeExtras ide) initConfig
146
139
147
140
let handleServerException (Left e) = do
148
- logError logger $
141
+ logError (ideLogger ide) $
149
142
T. pack $ " Fatal error in server thread: " <> show e
150
- sendErrorMessage e
151
143
exitClientMsg
152
- handleServerException (Right _) = pure ()
153
-
154
- sendErrorMessage (e :: SomeException ) = do
155
- LSP. runLspT env $ LSP. sendNotification SWindowShowMessage $
156
- ShowMessageParams MtError $ T. unlines
157
- [ " Unhandled exception, please [report](" <> issueTrackerUrl <> " ): "
158
- , T. pack(show e)
159
- ]
160
-
161
- exceptionInHandler e = do
162
- logError logger $ T. pack $
163
- " Unexpected exception, please report!\n " ++
164
- " Exception: " ++ show e
165
- sendErrorMessage e
166
-
144
+ handleServerException _ = pure ()
167
145
logger = ideLogger ide
168
-
169
- checkCancelled _id act k =
170
- flip finally (clearReqId _id) $
171
- catch (do
172
- -- We could optimize this by first checking if the id
173
- -- is in the cancelled set. However, this is unlikely to be a
174
- -- bottleneck and the additional check might hide
175
- -- issues with async exceptions that need to be fixed.
176
- cancelOrRes <- race (waitForCancel _id) act
177
- case cancelOrRes of
178
- Left () -> do
179
- logDebug (ideLogger ide) $ T. pack $ " Cancelled request " <> show _id
180
- k $ ResponseError RequestCancelled " " Nothing
181
- Right res -> pure res
182
- ) $ \ (e :: SomeException ) -> do
183
- exceptionInHandler e
184
- k $ ResponseError InternalError (T. pack $ show e) Nothing
185
- _ <- flip forkFinally handleServerException $ untilMVar lifetime $ runWithDb logger dbLoc $ \ hiedb hieChan -> do
146
+ _ <- flip forkFinally handleServerException $ runWithDb logger dbLoc $ \ hiedb hieChan -> do
186
147
putMVar dbMVar (hiedb,hieChan)
187
148
forever $ do
188
149
msg <- readChan clientMsgChan
189
150
-- We dispatch notifications synchronously and requests asynchronously
190
151
-- This is to ensure that all file edits and config changes are applied before a request is handled
191
152
case msg of
192
- ReactorNotification act -> handle exceptionInHandler act
193
- ReactorRequest _id act k -> void $ async $ checkCancelled _id act k
153
+ ReactorNotification act -> do
154
+ catch act $ \ (e :: SomeException ) ->
155
+ logError (ideLogger ide) $ T. pack $
156
+ " Unexpected exception on notification, please report!\n " ++
157
+ " Exception: " ++ show e
158
+ ReactorRequest _id act k -> void $ async $
159
+ checkCancelled ide clearReqId waitForCancel _id act k
194
160
pure $ Right (env,ide)
195
161
162
+ checkCancelled
163
+ :: IdeState -> (SomeLspId -> IO () ) -> (SomeLspId -> IO () ) -> SomeLspId
164
+ -> IO () -> (ResponseError -> IO () ) -> IO ()
165
+ checkCancelled ide clearReqId waitForCancel _id act k =
166
+ flip finally (clearReqId _id) $
167
+ catch (do
168
+ -- We could optimize this by first checking if the id
169
+ -- is in the cancelled set. However, this is unlikely to be a
170
+ -- bottleneck and the additional check might hide
171
+ -- issues with async exceptions that need to be fixed.
172
+ cancelOrRes <- race (waitForCancel _id) act
173
+ case cancelOrRes of
174
+ Left () -> do
175
+ logDebug (ideLogger ide) $ T. pack $ " Cancelled request " <> show _id
176
+ k $ ResponseError RequestCancelled " " Nothing
177
+ Right res -> pure res
178
+ ) $ \ (e :: SomeException ) -> do
179
+ logError (ideLogger ide) $ T. pack $
180
+ " Unexpected exception on request, please report!\n " ++
181
+ " Exception: " ++ show e
182
+ k $ ResponseError InternalError (T. pack $ show e) Nothing
196
183
197
- -- | Runs the action until it ends or until the given MVar is put.
198
- -- Rethrows any exceptions.
199
- untilMVar :: MonadUnliftIO m => MVar () -> m () -> m ()
200
- untilMVar mvar io = void $
201
- waitAnyCancel =<< traverse async [ io , readMVar mvar ]
202
184
203
185
cancelHandler :: (SomeLspId -> IO () ) -> LSP. Handlers (ServerM c )
204
186
cancelHandler cancelRequest = LSP. notificationHandler SCancelRequest $ \ NotificationMessage {_params= CancelParams {_id}} ->
205
187
liftIO $ cancelRequest (SomeLspId _id)
206
188
207
- shutdownHandler :: IO () -> LSP. Handlers (ServerM c )
208
- shutdownHandler stopReactor = LSP. requestHandler SShutdown $ \ _ resp -> do
189
+ shutdownHandler :: LSP. Handlers (ServerM c )
190
+ shutdownHandler = LSP. requestHandler SShutdown $ \ _ resp -> do
209
191
(_, ide) <- ask
210
- liftIO $ logDebug (ideLogger ide) " Received shutdown message"
211
- -- stop the reactor to free up the hiedb connection
212
- liftIO stopReactor
192
+ liftIO $ logDebug (ideLogger ide) " Received exit message"
213
193
-- flush out the Shake session to record a Shake profile if applicable
214
194
liftIO $ shakeShut ide
215
195
resp $ Right Empty
0 commit comments