Skip to content

Commit 9146668

Browse files
committed
Fully support use of workspace/configuration
`lsp` will now rely primarily on `workspace/configuration` to get configuration from the client. See `Note [LSP configuration]` for details. `lsp-test` also now handles `workspace/configuration` properly.
1 parent cde1658 commit 9146668

File tree

18 files changed

+429
-177
lines changed

18 files changed

+429
-177
lines changed

lsp-test/ChangeLog.md

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,16 @@
11
# Revision history for lsp-test
22

3+
## Unreleased
4+
5+
- Many changes relating to LSP client configuration
6+
- `lsp-test` now responds to `workspace/configuration` requests.
7+
- New function `setConfig` for setting the client configuration and notifying the server.
8+
- `lsp-test` does not send a `workspace/didChangeConfiguration` request on startup.
9+
- New `SessionConfig` option to ignore `workspace/configuration` requests, as they
10+
are often not useful in sessions. This is on by default.
11+
- `ignoreLogNotifications` is now on by default. Experience shows the norm is to ignore these
12+
and it is simpler to turn this on only when they are required.
13+
314
## 0.15.0.1
415

516
* Adds helper functions to resolve code lens, code actions, and completion items.

lsp-test/bench/SimpleBench.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,8 +32,10 @@ handlers = mconcat
3232

3333
server :: ServerDefinition ()
3434
server = ServerDefinition
35-
{ onConfigurationChange = const $ const $ Right ()
35+
{ parseConfig = const $ const $ Right ()
36+
, onConfigChange = const $ pure ()
3637
, defaultConfig = ()
38+
, configSection = "demo"
3739
, doInitialize = \env _req -> pure $ Right env
3840
, staticHandlers = \_caps -> handlers
3941
, interpretHandler = \env -> Iso (runLspT env) liftIO

lsp-test/func-test/FuncTest.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,8 +32,10 @@ main = hspec $ do
3232
killVar <- newEmptyMVar
3333

3434
let definition = ServerDefinition
35-
{ onConfigurationChange = const $ const $ Right ()
35+
{ parseConfig = const $ const $ Right ()
36+
, onConfigChange = const $ pure ()
3637
, defaultConfig = ()
38+
, configSection = "demo"
3739
, doInitialize = \env _req -> pure $ Right env
3840
, staticHandlers = \_caps -> handlers killVar
3941
, interpretHandler = \env -> Iso (runLspT env) liftIO
@@ -79,8 +81,10 @@ main = hspec $ do
7981
wf2 = WorkspaceFolder (filePathToUri "/foo/baz") "My other workspace"
8082

8183
definition = ServerDefinition
82-
{ onConfigurationChange = const $ const $ Right ()
84+
{ parseConfig = const $ const $ Right ()
85+
, onConfigChange = const $ pure ()
8386
, defaultConfig = ()
87+
, configSection = "demo"
8488
, doInitialize = \env _req -> pure $ Right env
8589
, staticHandlers = \_caps -> handlers
8690
, interpretHandler = \env -> Iso (runLspT env) liftIO

lsp-test/func-test/func-test.cabal

Lines changed: 0 additions & 18 deletions
This file was deleted.

lsp-test/lsp-test.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@ library
5959
, filepath
6060
, Glob >=0.9 && <0.11
6161
, lens
62+
, lens-aeson
6263
, lsp ^>=2.1
6364
, lsp-types ^>=2.0
6465
, mtl <2.4

lsp-test/src/Language/LSP/Test.hs

Lines changed: 19 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,8 @@ module Language.LSP.Test
4949

5050
-- ** Initialization
5151
, initializeResponse
52+
-- ** Config
53+
, setConfig
5254
-- ** Documents
5355
, createDoc
5456
, openDoc
@@ -121,6 +123,7 @@ import qualified Data.Set as Set
121123
import qualified Data.Text as T
122124
import qualified Data.Text.IO as T
123125
import Data.Aeson hiding (Null)
126+
import qualified Data.Aeson as J
124127
import Data.Default
125128
import Data.List
126129
import Data.Maybe
@@ -224,7 +227,8 @@ runSessionWithHandles' serverProc serverIn serverOut config' caps rootDir sessio
224227
Nothing
225228
(InL $ filePathToUri absRootDir)
226229
caps
227-
(lspConfig config')
230+
-- TODO: make this configurable?
231+
(Just $ lspConfig config')
228232
(Just TraceValues_Off)
229233
(fmap InL $ initialWorkspaceFolders config)
230234
runSession' serverIn serverOut serverProc listenServer config caps rootDir exitServer $ do
@@ -243,10 +247,6 @@ runSessionWithHandles' serverProc serverIn serverOut config' caps rootDir sessio
243247
liftIO $ putMVar initRspVar initRspMsg
244248
sendNotification SMethod_Initialized InitializedParams
245249

246-
case lspConfig config of
247-
Just cfg -> sendNotification SMethod_WorkspaceDidChangeConfiguration (DidChangeConfigurationParams cfg)
248-
Nothing -> return ()
249-
250250
-- ... relay them back to the user Session so they can match on them!
251251
-- As long as they are allowed.
252252
forM_ inBetween checkLegalBetweenMessage
@@ -401,6 +401,20 @@ sendResponse = sendMessage
401401
initializeResponse :: Session (TResponseMessage Method_Initialize)
402402
initializeResponse = ask >>= (liftIO . readMVar) . initRsp
403403

404+
-- | Set the client config. This will send a notification to the server that the
405+
-- config has changed.
406+
setConfig :: Value
407+
-> Session ()
408+
setConfig newConfig = do
409+
modify (\ss -> ss { curLspConfig = newConfig})
410+
caps <- asks sessionCapabilities
411+
let supportsConfiguration = fromMaybe False $ caps ^? L.workspace . _Just . L.configuration . _Just
412+
-- TODO: make this configurable?
413+
-- if they support workspace/configuration then be annoying and don't send the full config so
414+
-- they have to request it
415+
configToSend = if supportsConfiguration then J.Null else newConfig
416+
sendNotification SMethod_WorkspaceDidChangeConfiguration $ DidChangeConfigurationParams configToSend
417+
404418
-- | /Creates/ a new text document. This is different from 'openDoc'
405419
-- as it sends a workspace/didChangeWatchedFiles notification letting the server
406420
-- know that a file was created within the workspace, __provided that the server

lsp-test/src/Language/LSP/Test/Parsing.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,8 @@ module Language.LSP.Test.Parsing
2020
, anyNotification
2121
, anyMessage
2222
, loggingNotification
23+
, configurationRequest
24+
, loggingOrConfiguration
2325
, publishDiagnosticsNotification
2426
) where
2527

@@ -207,6 +209,16 @@ loggingNotification = named "Logging notification" $ satisfy shouldSkip
207209
shouldSkip (FromServerMess SMethod_WindowShowDocument _) = True
208210
shouldSkip _ = False
209211

212+
-- | Matches if the message is a configuration request from the server.
213+
configurationRequest :: Session FromServerMessage
214+
configurationRequest = named "Configuration request" $ satisfy shouldSkip
215+
where
216+
shouldSkip (FromServerMess SMethod_WorkspaceConfiguration _) = True
217+
shouldSkip _ = False
218+
219+
loggingOrConfiguration :: Session FromServerMessage
220+
loggingOrConfiguration = loggingNotification <|> configurationRequest
221+
210222
-- | Matches a 'Language.LSP.Types.TextDocumentPublishDiagnostics'
211223
-- (textDocument/publishDiagnostics) notification.
212224
publishDiagnosticsNotification :: Session (TMessage Method_TextDocumentPublishDiagnostics)

lsp-test/src/Language/LSP/Test/Session.hs

Lines changed: 54 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
{-# LANGUAGE RankNTypes #-}
1010
{-# LANGUAGE TypeInType #-}
1111
{-# LANGUAGE TypeOperators #-}
12+
{-# LANGUAGE TypeApplications #-}
1213

1314
module Language.LSP.Test.Session
1415
( Session(..)
@@ -43,8 +44,6 @@ import Control.Lens hiding (List, Empty)
4344
import Control.Monad
4445
import Control.Monad.Catch (MonadThrow)
4546
import Control.Monad.Except
46-
import Control.Monad.IO.Class
47-
import Control.Monad.Trans.Class
4847
#if __GLASGOW_HASKELL__ == 806
4948
import Control.Monad.Fail
5049
#endif
@@ -54,7 +53,9 @@ import Control.Monad.Trans.State (StateT, runStateT, execState)
5453
import qualified Control.Monad.Trans.State as State
5554
import qualified Data.ByteString.Lazy.Char8 as B
5655
import Data.Aeson hiding (Error, Null)
56+
import qualified Data.Aeson as J
5757
import Data.Aeson.Encode.Pretty
58+
import Data.Aeson.Lens ()
5859
import Data.Conduit as Conduit
5960
import Data.Conduit.Parser as Parser
6061
import Data.Default
@@ -84,6 +85,8 @@ import System.Timeout ( timeout )
8485
import Data.IORef
8586
import Colog.Core (LogAction (..), WithSeverity (..), Severity (..))
8687
import Data.Row
88+
import Data.String (fromString)
89+
import Data.Either (partitionEithers)
8790

8891
-- | A session representing one instance of launching and connecting to a server.
8992
--
@@ -112,20 +115,26 @@ data SessionConfig = SessionConfig
112115
-- ^ Trace the messages sent and received to stdout, defaults to False.
113116
-- Can be overriden with the environment variable @LSP_TEST_LOG_MESSAGES@.
114117
, logColor :: Bool -- ^ Add ANSI color to the logged messages, defaults to True.
115-
, lspConfig :: Maybe Value -- ^ The initial LSP config as JSON value, defaults to Nothing.
118+
, lspConfig :: Value
119+
-- ^ The initial LSP config as JSON value, defaults to Null.
120+
-- This should include the config section for the server if it has one, i.e. if
121+
-- the server has a 'mylang' config section, then the config should be an object
122+
-- with a 'mylang' key whose value is the actual config for the server. You
123+
-- can also include other config sections if your server may request those.
116124
, ignoreLogNotifications :: Bool
117-
-- ^ Whether or not to ignore 'Language.LSP.Types.ShowMessageNotification' and
118-
-- 'Language.LSP.Types.LogMessageNotification', defaults to False.
119-
--
120-
-- @since 0.9.0.0
125+
-- ^ Whether or not to ignore @window/showMessage@ and @window/logMessage@ notifications
126+
-- from the server, defaults to True.
127+
, ignoreConfigurationRequests :: Bool
128+
-- ^ Whether or not to ignore @workspace/configuration@ requests from the server,
129+
-- defaults to True.
121130
, initialWorkspaceFolders :: Maybe [WorkspaceFolder]
122131
-- ^ The initial workspace folders to send in the @initialize@ request.
123132
-- Defaults to Nothing.
124133
}
125134

126135
-- | The configuration used in 'Language.LSP.Test.runSession'.
127136
defaultConfig :: SessionConfig
128-
defaultConfig = SessionConfig 60 False False True Nothing False Nothing
137+
defaultConfig = SessionConfig 60 False False True J.Null True True Nothing
129138

130139
instance Default SessionConfig where
131140
def = defaultConfig
@@ -179,6 +188,7 @@ data SessionState = SessionState
179188
-- Used for providing exception information
180189
, lastReceivedMessage :: !(Maybe FromServerMessage)
181190
, curDynCaps :: !(Map.Map T.Text SomeRegistration)
191+
, curLspConfig :: Value
182192
-- ^ The capabilities that the server has dynamically registered with us so
183193
-- far
184194
, curProgressSessions :: !(Set.Set ProgressToken)
@@ -227,15 +237,9 @@ runSessionMonad context state (Session session) = runReaderT (runStateT conduit
227237

228238
chanSource = do
229239
msg <- liftIO $ readChan (messageChan context)
230-
unless (ignoreLogNotifications (config context) && isLogNotification msg) $
231-
yield msg
240+
yield msg
232241
chanSource
233242

234-
isLogNotification (ServerMessage (FromServerMess SMethod_WindowShowMessage _)) = True
235-
isLogNotification (ServerMessage (FromServerMess SMethod_WindowLogMessage _)) = True
236-
isLogNotification (ServerMessage (FromServerMess SMethod_WindowShowDocument _)) = True
237-
isLogNotification _ = False
238-
239243
watchdog :: ConduitM SessionMessage FromServerMessage (StateT SessionState (ReaderT SessionContext IO)) ()
240244
watchdog = Conduit.awaitForever $ \msg -> do
241245
curId <- getCurTimeoutId
@@ -273,7 +277,7 @@ runSession' serverIn serverOut mServerProc serverHandler config caps rootDir exi
273277
mainThreadId <- myThreadId
274278

275279
let context = SessionContext serverIn absRootDir messageChan timeoutIdVar reqMap initRsp config caps
276-
initState vfs = SessionState 0 vfs mempty False Nothing mempty mempty
280+
initState vfs = SessionState 0 vfs mempty False Nothing mempty (lspConfig config) mempty
277281
runSession' ses = initVFS $ \vfs -> runSessionMonad context (initState vfs) ses
278282

279283
errorHandler = throwTo mainThreadId :: SessionException -> IO ()
@@ -302,17 +306,44 @@ runSession' serverIn serverOut mServerProc serverHandler config caps rootDir exi
302306

303307
updateStateC :: ConduitM FromServerMessage FromServerMessage (StateT SessionState (ReaderT SessionContext IO)) ()
304308
updateStateC = awaitForever $ \msg -> do
309+
context <- ask @SessionContext
305310
updateState msg
306-
respond msg
307-
yield msg
308-
where
309-
respond :: (MonadIO m, HasReader SessionContext m) => FromServerMessage -> m ()
310-
respond (FromServerMess SMethod_WindowWorkDoneProgressCreate req) =
311+
case msg of
312+
FromServerMess SMethod_WindowWorkDoneProgressCreate req ->
311313
sendMessage $ TResponseMessage "2.0" (Just $ req ^. L.id) (Right Null)
312-
respond (FromServerMess SMethod_WorkspaceApplyEdit r) = do
314+
FromServerMess SMethod_WorkspaceApplyEdit r -> do
313315
sendMessage $ TResponseMessage "2.0" (Just $ r ^. L.id) (Right $ ApplyWorkspaceEditResult True Nothing Nothing)
314-
respond _ = pure ()
316+
FromServerMess SMethod_WorkspaceConfiguration r -> do
317+
let requestedSections = mapMaybe (\i -> i ^? L.section . _Just) $ r ^. L.params . L.items
318+
c <- curLspConfig <$> get @SessionState
319+
case c of
320+
Object o -> do
321+
let configsOrErrs = (flip fmap) requestedSections $ \section ->
322+
case o ^. at (fromString $ T.unpack section) of
323+
Just config -> Right config
324+
Nothing -> Left section
325+
326+
let (errs, configs) = partitionEithers configsOrErrs
327+
328+
if null errs
329+
then sendMessage $ TResponseMessage "2.0" (Just $ r ^. L.id) (Right configs)
330+
else sendMessage @_ @(TResponseError Method_WorkspaceConfiguration) $
331+
TResponseError (InL LSPErrorCodes_RequestFailed) ("No configuration for requested sections: " <> (T.pack $ show errs)) Nothing
332+
333+
_ -> sendMessage @_ @(TResponseError Method_WorkspaceConfiguration) $ TResponseError (InL LSPErrorCodes_RequestFailed) "No configuration" Nothing
334+
_ -> pure ()
335+
unless ((ignoreLogNotifications (config context) && isLogNotification msg) || (ignoreConfigurationRequests (config context) && isConfigRequest msg)) $
336+
yield msg
337+
338+
where
339+
340+
isLogNotification (FromServerMess SMethod_WindowShowMessage _) = True
341+
isLogNotification (FromServerMess SMethod_WindowLogMessage _) = True
342+
isLogNotification (FromServerMess SMethod_WindowShowDocument _) = True
343+
isLogNotification _ = False
315344

345+
isConfigRequest (FromServerMess SMethod_WorkspaceConfiguration _) = True
346+
isConfigRequest _ = False
316347

317348
-- extract Uri out from DocumentChange
318349
-- didn't put this in `lsp-types` because TH was getting in the way

lsp-test/test/DummyServer.hs

Lines changed: 16 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,10 @@ module DummyServer where
77
import Control.Monad
88
import Control.Monad.Reader
99
import Data.Aeson hiding (defaultOptions, Null)
10+
import qualified Data.Aeson as J
1011
import qualified Data.Map.Strict as M
1112
import Data.List (isSuffixOf)
13+
import qualified Data.Text as T
1214
import Data.String
1315
import UnliftIO.Concurrent
1416
import Language.LSP.Server
@@ -27,10 +29,15 @@ withDummyServer f = do
2729
(houtRead, houtWrite) <- createPipe
2830

2931
handlerEnv <- HandlerEnv <$> newEmptyMVar <*> newEmptyMVar
30-
let definition = ServerDefinition
32+
let
33+
definition = ServerDefinition
3134
{ doInitialize = \env _req -> pure $ Right env
32-
, defaultConfig = ()
33-
, onConfigurationChange = const $ pure $ Right ()
35+
, defaultConfig = 1 :: Int
36+
, configSection = "dummy"
37+
, parseConfig = \_old new -> case fromJSON new of
38+
J.Success v -> Right v
39+
J.Error err -> Left $ T.pack err
40+
, onConfigChange = const $ pure ()
3441
, staticHandlers = \_caps -> handlers
3542
, interpretHandler = \env ->
3643
Iso (\m -> runLspT env (runReaderT m handlerEnv)) liftIO
@@ -48,13 +55,18 @@ data HandlerEnv = HandlerEnv
4855
, absRegToken :: MVar (RegistrationToken Method_WorkspaceDidChangeWatchedFiles)
4956
}
5057

51-
handlers :: Handlers (ReaderT HandlerEnv (LspM ()))
58+
handlers :: Handlers (ReaderT HandlerEnv (LspM Int))
5259
handlers =
5360
mconcat
5461
[ notificationHandler SMethod_Initialized $
5562
\_noti ->
5663
sendNotification SMethod_WindowLogMessage $
5764
LogMessageParams MessageType_Log "initialized"
65+
66+
, requestHandler (SMethod_CustomMethod (Proxy @"getConfig")) $ \_req resp -> do
67+
config <- getConfig
68+
resp $ Right $ toJSON config
69+
5870
, requestHandler SMethod_TextDocumentHover $
5971
\_req responder ->
6072
responder $

0 commit comments

Comments
 (0)