@@ -11,6 +11,7 @@ module Development.IDE.LSP.LanguageServer
1111 , Log (.. )
1212 , ThreadQueue
1313 , runWithWorkerThreads
14+ , Setup (.. )
1415 ) where
1516
1617import Control.Concurrent.STM
@@ -81,6 +82,17 @@ instance Pretty Log where
8182 LogLspServer msg -> pretty msg
8283 LogServerShutdownMessage -> " Received shutdown message"
8384
85+ data Setup config m a
86+ = MkSetup
87+ { doInitialize :: LSP. LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either (TResponseError Method_Initialize ) (LSP. LanguageContextEnv config , a ))
88+ -- ^ the callback invoked when the language server receives the 'Method_Initialize' request
89+ , staticHandlers :: LSP. Handlers m
90+ -- ^ the statically known handlers of the lsp server
91+ , interpretHandler :: (LanguageContextEnv config , a ) -> m <~> IO
92+ -- ^ how to interpret @m@ to 'IO' and how to lift 'IO' into @m@
93+ , onExit :: [IO () ]
94+ -- ^ a list of 'IO' actions that clean up resources and must be run when the server shuts down
95+ }
8496
8597runLanguageServer
8698 :: forall config a m . (Show config )
@@ -90,18 +102,16 @@ runLanguageServer
90102 -> Handle -- output
91103 -> config
92104 -> (config -> Value -> Either T. Text config )
93- -> (config -> m config () )
94- -> (MVar ()
95- -> IO (LSP. LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either (TResponseError Method_Initialize ) (LSP. LanguageContextEnv config , a )),
96- LSP. Handlers (m config ),
97- (LanguageContextEnv config , a ) -> m config <~> IO ))
105+ -> (config -> m () )
106+ -> (MVar () -> IO (Setup config m a ))
98107 -> IO ()
99108runLanguageServer recorder options inH outH defaultConfig parseConfig onConfigChange setup = do
100109 -- This MVar becomes full when the server thread exits or we receive exit message from client.
101110 -- LSP server will be canceled when it's full.
102111 clientMsgVar <- newEmptyMVar
103112
104- (doInitialize, staticHandlers, interpretHandler) <- setup clientMsgVar
113+ MkSetup
114+ { doInitialize, staticHandlers, interpretHandler, onExit } <- setup clientMsgVar
105115
106116 let serverDefinition = LSP. ServerDefinition
107117 { LSP. parseConfig = parseConfig
@@ -115,28 +125,29 @@ runLanguageServer recorder options inH outH defaultConfig parseConfig onConfigCh
115125 , LSP. options = modifyOptions options
116126 }
117127
118- let lspCologAction :: MonadIO m2 => Colog. LogAction m2 (Colog. WithSeverity LspServerLog )
128+ let lspCologAction :: forall io . MonadIO io => Colog. LogAction io (Colog. WithSeverity LspServerLog )
119129 lspCologAction = toCologActionWithPrio (cmapWithPrio LogLspServer recorder)
120130
121- void $ untilMVar clientMsgVar $
122- void $ LSP. runServerWithHandles
131+ let runServer =
132+ LSP. runServerWithHandles
123133 lspCologAction
124134 lspCologAction
125135 inH
126136 outH
127137 serverDefinition
128138
139+ untilMVar clientMsgVar $
140+ runServer `finally` sequence_ onExit
141+
129142setupLSP ::
130- forall config err .
143+ forall config .
131144 Recorder (WithPriority Log )
132145 -> FilePath -- ^ root directory, see Note [Root Directory]
133146 -> (FilePath -> IO FilePath ) -- ^ Map root paths to the location of the hiedb for the project
134147 -> LSP. Handlers (ServerM config )
135148 -> (LSP. LanguageContextEnv config -> FilePath -> WithHieDb -> ThreadQueue -> IO IdeState )
136149 -> MVar ()
137- -> IO (LSP. LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either err (LSP. LanguageContextEnv config , IdeState )),
138- LSP. Handlers (ServerM config ),
139- (LanguageContextEnv config , IdeState ) -> ServerM config <~> IO )
150+ -> IO (Setup config (ServerM config ) IdeState )
140151setupLSP recorder defaultRoot getHieDbLoc userHandlers getIdeState clientMsgVar = do
141152 -- Send everything over a channel, since you need to wait until after initialise before
142153 -- LspFuncs is available
@@ -171,7 +182,7 @@ setupLSP recorder defaultRoot getHieDbLoc userHandlers getIdeState clientMsgVar
171182 cancelled <- readTVar cancelledRequests
172183 unless (reqId `Set.member` cancelled) retry
173184
174- let asyncHandlers = mconcat
185+ let staticHandlers = mconcat
175186 [ userHandlers
176187 , cancelHandler cancelRequest
177188 , exitHandler exit
@@ -184,7 +195,9 @@ setupLSP recorder defaultRoot getHieDbLoc userHandlers getIdeState clientMsgVar
184195
185196 let interpretHandler (env, st) = LSP. Iso (LSP. runLspT env . flip (runReaderT . unServerM) (clientMsgChan,st)) liftIO
186197
187- pure (doInitialize, asyncHandlers, interpretHandler)
198+ let onExit = [stopReactorLoop, exit]
199+
200+ pure MkSetup {doInitialize, staticHandlers, interpretHandler, onExit}
188201
189202
190203handleInit
@@ -266,10 +279,12 @@ runWithWorkerThreads recorder dbLoc f = evalContT $ do
266279 liftIO $ f hiedb (ThreadQueue threadQueue sessionRestartTQueue sessionLoaderTQueue)
267280
268281-- | Runs the action until it ends or until the given MVar is put.
282+ -- It is important, that the thread that puts the 'MVar' is not dropped before it puts the 'MVar' i.e. it should
283+ -- occur as the final action in a 'finally' or 'bracket', because otherwise this thread will finish early (as soon
284+ -- as the thread receives the BlockedIndefinitelyOnMVar exception)
269285-- Rethrows any exceptions.
270- untilMVar :: MonadUnliftIO m => MVar () -> m () -> m ()
271- untilMVar mvar io = void $
272- waitAnyCancel =<< traverse async [ io , readMVar mvar ]
286+ untilMVar :: MonadUnliftIO m => MVar () -> m a -> m ()
287+ untilMVar mvar io = race_ (readMVar mvar) io
273288
274289cancelHandler :: (SomeLspId -> IO () ) -> LSP. Handlers (ServerM c )
275290cancelHandler cancelRequest = LSP. notificationHandler SMethod_CancelRequest $ \ TNotificationMessage {_params= CancelParams {_id}} ->
0 commit comments