Maintainer | luke_lau@icloud.com |
---|---|
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Provides the framework to start functionally testing Language Server Protocol servers. You should import Language.LSP.Types alongside this.
Synopsis
- data Session a
- runSession :: String -> ClientCapabilities -> FilePath -> Session a -> IO a
- runSessionWithConfig :: SessionConfig -> String -> ClientCapabilities -> FilePath -> Session a -> IO a
- runSessionWithConfigCustomProcess :: (CreateProcess -> CreateProcess) -> SessionConfig -> String -> ClientCapabilities -> FilePath -> Session a -> IO a
- runSessionWithHandles :: Handle -> Handle -> SessionConfig -> ClientCapabilities -> FilePath -> Session a -> IO a
- runSessionWithHandles' :: Maybe ProcessHandle -> Handle -> Handle -> SessionConfig -> ClientCapabilities -> FilePath -> Session a -> IO a
- setIgnoringLogNotifications :: Bool -> Session ()
- setIgnoringConfigurationRequests :: Bool -> Session ()
- setIgnoringRegistrationRequests :: Bool -> Session ()
- data SessionConfig = SessionConfig {
- messageTimeout :: Int
- logStdErr :: Bool
- logMessages :: Bool
- logColor :: Bool
- lspConfig :: Object
- ignoreLogNotifications :: Bool
- ignoreConfigurationRequests :: Bool
- ignoreRegistrationRequests :: Bool
- initialWorkspaceFolders :: Maybe [WorkspaceFolder]
- defaultConfig :: SessionConfig
- fullLatestClientCaps :: ClientCapabilities
- data SessionException
- = Timeout (Maybe FromServerMessage)
- | NoContentLengthHeader
- | UnexpectedMessage String FromServerMessage
- | ReplayOutOfOrder FromServerMessage [FromServerMessage]
- | UnexpectedDiagnostics
- | IncorrectApplyEditRequest String
- | forall m.Show (ErrorData m) => UnexpectedResponseError (LspId m) (TResponseError m)
- | UnexpectedServerTermination
- | IllegalInitSequenceMessage FromServerMessage
- | MessageSendError Value IOError
- anySessionException :: SessionException -> Bool
- withTimeout :: Int -> Session a -> Session a
- request :: SClientMethod m -> MessageParams m -> Session (TResponseMessage m)
- request_ :: SClientMethod (m :: Method ClientToServer Request) -> MessageParams m -> Session ()
- sendRequest :: SClientMethod m -> MessageParams m -> Session (LspId m)
- sendNotification :: SClientMethod (m :: Method ClientToServer Notification) -> MessageParams m -> Session ()
- sendResponse :: (ToJSON (MessageResult m), ToJSON (ErrorData m)) => TResponseMessage m -> Session ()
- satisfy :: (FromServerMessage -> Bool) -> Session FromServerMessage
- satisfyMaybe :: (FromServerMessage -> Maybe a) -> Session a
- message :: SServerMethod m -> Session (TMessage m)
- response :: SMethod (m :: Method ClientToServer Request) -> Session (TResponseMessage m)
- responseForId :: SMethod (m :: Method ClientToServer Request) -> LspId m -> Session (TResponseMessage m)
- customRequest :: KnownSymbol s => Proxy s -> Session (TMessage (Method_CustomMethod s :: Method ServerToClient Request))
- customNotification :: KnownSymbol s => Proxy s -> Session (TMessage (Method_CustomMethod s :: Method ServerToClient Notification))
- anyRequest :: Session FromServerMessage
- anyResponse :: Session FromServerMessage
- anyNotification :: Session FromServerMessage
- anyMessage :: Session FromServerMessage
- loggingNotification :: Session FromServerMessage
- configurationRequest :: Session FromServerMessage
- loggingOrConfiguration :: Session FromServerMessage
- publishDiagnosticsNotification :: Session (TMessage Method_TextDocumentPublishDiagnostics)
- initializeResponse :: Session (TResponseMessage Method_Initialize)
- modifyConfig :: (Object -> Object) -> Session ()
- setConfig :: Object -> Session ()
- modifyConfigSection :: String -> (Value -> Value) -> Session ()
- setConfigSection :: String -> Value -> Session ()
- createDoc :: FilePath -> LanguageKind -> Text -> Session TextDocumentIdentifier
- openDoc :: FilePath -> LanguageKind -> Session TextDocumentIdentifier
- closeDoc :: TextDocumentIdentifier -> Session ()
- changeDoc :: TextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> Session ()
- documentContents :: TextDocumentIdentifier -> Session Text
- getDocumentEdit :: TextDocumentIdentifier -> Session Text
- getDocUri :: FilePath -> Session Uri
- getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier
- getDocumentSymbols :: TextDocumentIdentifier -> Session (Either [SymbolInformation] [DocumentSymbol])
- waitForDiagnostics :: Session [Diagnostic]
- waitForDiagnosticsSource :: String -> Session [Diagnostic]
- noDiagnostics :: Session ()
- getCurrentDiagnostics :: TextDocumentIdentifier -> Session [Diagnostic]
- getIncompleteProgressSessions :: Session (Set ProgressToken)
- executeCommand :: Command -> Session ()
- getCodeActions :: TextDocumentIdentifier -> Range -> Session [Command |? CodeAction]
- getAndResolveCodeActions :: TextDocumentIdentifier -> Range -> Session [Command |? CodeAction]
- getAllCodeActions :: TextDocumentIdentifier -> Session [Command |? CodeAction]
- executeCodeAction :: CodeAction -> Session ()
- resolveCodeAction :: CodeAction -> Session CodeAction
- resolveAndExecuteCodeAction :: CodeAction -> Session ()
- getCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem]
- getAndResolveCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem]
- getReferences :: TextDocumentIdentifier -> Position -> Bool -> Session [Location]
- getDeclarations :: TextDocumentIdentifier -> Position -> Session (Declaration |? ([DeclarationLink] |? Null))
- getDefinitions :: TextDocumentIdentifier -> Position -> Session (Definition |? ([DefinitionLink] |? Null))
- getTypeDefinitions :: TextDocumentIdentifier -> Position -> Session (Definition |? ([DefinitionLink] |? Null))
- getImplementations :: TextDocumentIdentifier -> Position -> Session (Definition |? ([DefinitionLink] |? Null))
- rename :: TextDocumentIdentifier -> Position -> String -> Session ()
- getHover :: TextDocumentIdentifier -> Position -> Session (Maybe Hover)
- getHighlights :: TextDocumentIdentifier -> Position -> Session [DocumentHighlight]
- formatDoc :: TextDocumentIdentifier -> FormattingOptions -> Session ()
- formatRange :: TextDocumentIdentifier -> FormattingOptions -> Range -> Session ()
- applyEdit :: TextDocumentIdentifier -> TextEdit -> Session VersionedTextDocumentIdentifier
- getCodeLenses :: TextDocumentIdentifier -> Session [CodeLens]
- getAndResolveCodeLenses :: TextDocumentIdentifier -> Session [CodeLens]
- resolveCodeLens :: CodeLens -> Session CodeLens
- getInlayHints :: TextDocumentIdentifier -> Range -> Session [InlayHint]
- getAndResolveInlayHints :: TextDocumentIdentifier -> Range -> Session [InlayHint]
- resolveInlayHint :: InlayHint -> Session InlayHint
- prepareCallHierarchy :: CallHierarchyPrepareParams -> Session [CallHierarchyItem]
- incomingCalls :: CallHierarchyIncomingCallsParams -> Session [CallHierarchyIncomingCall]
- outgoingCalls :: CallHierarchyOutgoingCallsParams -> Session [CallHierarchyOutgoingCall]
- getSemanticTokens :: TextDocumentIdentifier -> Session (SemanticTokens |? Null)
- getRegisteredCapabilities :: Session [SomeRegistration]
Sessions
A session representing one instance of launching and connecting to a server.
You can send and receive messages to the server within Session
via
message
,
sendRequest
and
sendNotification
.
Instances
MonadFail Session Source # | |
Defined in Language.LSP.Test.Session | |
MonadIO Session Source # | |
Defined in Language.LSP.Test.Session | |
Alternative Session Source # | |
Applicative Session Source # | |
Functor Session Source # | |
Monad Session Source # | |
MonadThrow Session Source # | |
Defined in Language.LSP.Test.Session throwM :: (HasCallStack, Exception e) => e -> Session a # |
:: String | The command to run the server. |
-> ClientCapabilities | The capabilities that the client should declare. |
-> FilePath | The filepath to the root directory for the session. |
-> Session a | The session to run. |
-> IO a |
Starts a new session.
runSession "hie" fullLatestClientCaps "path/to/root/dir" $ do doc <- openDoc "Desktop/simple.hs" "haskell" diags <- waitForDiagnostics let pos = Position 12 5 params = TextDocumentPositionParams doc hover <- request STextdocumentHover params
:: SessionConfig | Configuration options for the session. |
-> String | The command to run the server. |
-> ClientCapabilities | The capabilities that the client should declare. |
-> FilePath | The filepath to the root directory for the session. |
-> Session a | The session to run. |
-> IO a |
Starts a new session with a custom configuration.
runSessionWithConfigCustomProcess Source #
:: (CreateProcess -> CreateProcess) | Tweak the |
-> SessionConfig | Configuration options for the session. |
-> String | The command to run the server. |
-> ClientCapabilities | The capabilities that the client should declare. |
-> FilePath | The filepath to the root directory for the session. |
-> Session a | The session to run. |
-> IO a |
Starts a new session with a custom configuration and server CreateProcess
.
runSessionWithHandles Source #
:: Handle | The input handle |
-> Handle | The output handle |
-> SessionConfig | |
-> ClientCapabilities | The capabilities that the client should declare. |
-> FilePath | The filepath to the root directory for the session. |
-> Session a | The session to run. |
-> IO a |
Starts a new session, using the specified handles to communicate with the server. You can use this to host the server within the same process. An example with lsp might look like:
(hinRead, hinWrite) <- createPipe (houtRead, houtWrite) <- createPipe forkIO $ void $ runServerWithHandles hinRead houtWrite serverDefinition runSessionWithHandles hinWrite houtRead defaultConfig fullLatestClientCaps "." $ do -- ...
runSessionWithHandles' Source #
:: Maybe ProcessHandle | |
-> Handle | The input handle |
-> Handle | The output handle |
-> SessionConfig | |
-> ClientCapabilities | The capabilities that the client should declare. |
-> FilePath | The filepath to the root directory for the session. |
-> Session a | The session to run. |
-> IO a |
setIgnoringLogNotifications :: Bool -> Session () Source #
setIgnoringConfigurationRequests :: Bool -> Session () Source #
setIgnoringRegistrationRequests :: Bool -> Session () Source #
Config
data SessionConfig Source #
Stuff you can configure for a Session
.
SessionConfig | |
|
Instances
Default SessionConfig Source # | |
Defined in Language.LSP.Test.Session def :: SessionConfig # |
defaultConfig :: SessionConfig Source #
The configuration used in runSession
.
fullLatestClientCaps :: ClientCapabilities #
Exceptions
data SessionException Source #
An exception that can be thrown during a Session
Timeout (Maybe FromServerMessage) | |
NoContentLengthHeader | |
UnexpectedMessage String FromServerMessage | |
ReplayOutOfOrder FromServerMessage [FromServerMessage] | |
UnexpectedDiagnostics | |
IncorrectApplyEditRequest String | |
forall m.Show (ErrorData m) => UnexpectedResponseError (LspId m) (TResponseError m) | |
UnexpectedServerTermination | |
IllegalInitSequenceMessage FromServerMessage | |
MessageSendError Value IOError |
Instances
Exception SessionException Source # | |
Defined in Language.LSP.Test.Exceptions | |
Show SessionException Source # | |
Defined in Language.LSP.Test.Exceptions showsPrec :: Int -> SessionException -> ShowS # show :: SessionException -> String # showList :: [SessionException] -> ShowS # |
anySessionException :: SessionException -> Bool Source #
A predicate that matches on any SessionException
withTimeout :: Int -> Session a -> Session a Source #
Execute a block f that will throw a Timeout
exception
after duration seconds. This will override the global timeout
for waiting for messages to arrive defined in SessionConfig
.
Sending
request :: SClientMethod m -> MessageParams m -> Session (TResponseMessage m) Source #
Sends a request to the server and waits for its response.
Will skip any messages in between the request and the response
rsp <- request STextDocumentDocumentSymbol params
Note: will skip any messages in between the request and the response.
request_ :: SClientMethod (m :: Method ClientToServer Request) -> MessageParams m -> Session () Source #
The same as sendRequest
, but discard the response.
:: SClientMethod m | The request method. |
-> MessageParams m | The request parameters. |
-> Session (LspId m) | The id of the request that was sent. |
Sends a request to the server. Unlike request
, this doesn't wait for the response.
:: SClientMethod (m :: Method ClientToServer Notification) | The notification method. |
-> MessageParams m | The notification parameters. |
-> Session () |
Sends a notification to the server.
sendResponse :: (ToJSON (MessageResult m), ToJSON (ErrorData m)) => TResponseMessage m -> Session () Source #
Sends a response to the server.
Receiving
To receive a message, specify the method of the message to expect:
msg1 <- message SWorkspaceApplyEdit msg2 <- message STextDocumentHover
Session
is actually just a parser
that operates on messages under the hood. This means that you
can create and combine parsers to match specific sequences of
messages that you expect.
For example, if you wanted to match either a definition or references request:
defOrImpl = message STextDocumentDefinition <|> message STextDocumentReferences
If you wanted to match any number of telemetry notifications immediately followed by a response:
logThenDiags = skipManyTill (message STelemetryEvent) anyResponse
satisfy :: (FromServerMessage -> Bool) -> Session FromServerMessage Source #
Consumes and returns the next message, if it satisfies the specified predicate.
Since: 0.5.2.0
satisfyMaybe :: (FromServerMessage -> Maybe a) -> Session a Source #
Consumes and returns the result of the specified predicate if it returns Just
.
Since: 0.6.1.0
message :: SServerMethod m -> Session (TMessage m) Source #
Matches a request or a notification coming from the server. Doesn't match Custom Messages
response :: SMethod (m :: Method ClientToServer Request) -> Session (TResponseMessage m) Source #
Matches a response coming from the server.
responseForId :: SMethod (m :: Method ClientToServer Request) -> LspId m -> Session (TResponseMessage m) Source #
Like response
, but matches a response for a specific id.
customRequest :: KnownSymbol s => Proxy s -> Session (TMessage (Method_CustomMethod s :: Method ServerToClient Request)) Source #
customNotification :: KnownSymbol s => Proxy s -> Session (TMessage (Method_CustomMethod s :: Method ServerToClient Notification)) Source #
anyRequest :: Session FromServerMessage Source #
Matches if the message is a request.
anyResponse :: Session FromServerMessage Source #
Matches if the message is a response.
anyNotification :: Session FromServerMessage Source #
Matches if the message is a notification.
anyMessage :: Session FromServerMessage Source #
Matches any type of message.
loggingNotification :: Session FromServerMessage Source #
Matches if the message is a log message notification or a show message notification/request.
configurationRequest :: Session FromServerMessage Source #
Matches if the message is a configuration request from the server.
loggingOrConfiguration :: Session FromServerMessage Source #
publishDiagnosticsNotification :: Session (TMessage Method_TextDocumentPublishDiagnostics) Source #
Matches a TextDocumentPublishDiagnostics
(textDocument/publishDiagnostics) notification.
Utilities
Quick helper functions for common tasks.
Initialization
initializeResponse :: Session (TResponseMessage Method_Initialize) Source #
Returns the initialize response that was received from the server. The initialize requests and responses are not included the session, so if you need to test it use this.
Config
modifyConfig :: (Object -> Object) -> Session () Source #
Modify the client config. This will send a notification to the server that the config has changed.
setConfig :: Object -> Session () Source #
Set the client config. This will send a notification to the server that the config has changed.
modifyConfigSection :: String -> (Value -> Value) -> Session () Source #
Modify a client config section (if already present, otherwise does nothing). This will send a notification to the server that the config has changed.
setConfigSection :: String -> Value -> Session () Source #
Set a client config section. This will send a notification to the server that the config has changed.
Documents
:: FilePath | The path to the document to open, relative to the root directory. |
-> LanguageKind | The text document's language identifier, e.g. |
-> Text | The content of the text document to create. |
-> Session TextDocumentIdentifier | The identifier of the document just created. |
Creates a new text document. This is different from openDoc
as it sends a workspace/didChangeWatchedFiles notification letting the server
know that a file was created within the workspace, __provided that the server
has registered for it__, and the file matches any patterns the server
registered for.
It does not actually create a file on disk, but is useful for convincing
the server that one does exist.
Since: 11.0.0.0
openDoc :: FilePath -> LanguageKind -> Session TextDocumentIdentifier Source #
Opens a text document that exists on disk, and sends a textDocument/didOpen notification to the server.
closeDoc :: TextDocumentIdentifier -> Session () Source #
Closes a text document and sends a textDocument/didOpen notification to the server.
changeDoc :: TextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> Session () Source #
Changes a text document and sends a textDocument/didOpen notification to the server.
documentContents :: TextDocumentIdentifier -> Session Text Source #
The current text contents of a document.
getDocumentEdit :: TextDocumentIdentifier -> Session Text Source #
Parses an ApplyEditRequest, checks that it is for the passed document and returns the new content
getDocUri :: FilePath -> Session Uri Source #
Gets the Uri for the file corrected to the session directory.
getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier Source #
Adds the current version to the document, as tracked by the session.
Symbols
getDocumentSymbols :: TextDocumentIdentifier -> Session (Either [SymbolInformation] [DocumentSymbol]) Source #
Returns the symbols in a document.
Diagnostics
waitForDiagnostics :: Session [Diagnostic] Source #
Waits for diagnostics to be published and returns them.
waitForDiagnosticsSource :: String -> Session [Diagnostic] Source #
The same as waitForDiagnostics
, but will only match a specific
_source
.
noDiagnostics :: Session () Source #
Expects a PublishDiagnosticsNotification
and throws an
UnexpectedDiagnostics
exception if there are any diagnostics
returned.
getCurrentDiagnostics :: TextDocumentIdentifier -> Session [Diagnostic] Source #
Returns the current diagnostics that have been sent to the client. Note that this does not wait for more to come in.
getIncompleteProgressSessions :: Session (Set ProgressToken) Source #
Returns the tokens of all progress sessions that have started but not yet ended.
Commands
executeCommand :: Command -> Session () Source #
Executes a command.
Code Actions
getCodeActions :: TextDocumentIdentifier -> Range -> Session [Command |? CodeAction] Source #
Returns the code actions in the specified range.
getAndResolveCodeActions :: TextDocumentIdentifier -> Range -> Session [Command |? CodeAction] Source #
Returns the code actions in the specified range, resolving any with a non empty _data_ field.
getAllCodeActions :: TextDocumentIdentifier -> Session [Command |? CodeAction] Source #
Returns all the code actions in a document by querying the code actions at each of the current diagnostics' positions.
executeCodeAction :: CodeAction -> Session () Source #
Executes a code action. Matching with the specification, if a code action contains both an edit and a command, the edit will be applied first.
resolveCodeAction :: CodeAction -> Session CodeAction Source #
Resolves the provided code action.
resolveAndExecuteCodeAction :: CodeAction -> Session () Source #
If a code action contains a _data_ field: resolves the code action, then executes it. Otherwise, just executes it.
Completions
getCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem] Source #
Returns the completions for the position in the document.
getAndResolveCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem] Source #
Returns the completions for the position in the document, resolving any with a non empty _data_ field.
References
:: TextDocumentIdentifier | The document to lookup in. |
-> Position | The position to lookup. |
-> Bool | Whether to include declarations as references. |
-> Session [Location] | The locations of the references. |
Returns the references for the position in the document.
Definitions
:: TextDocumentIdentifier | The document the term is in. |
-> Position | The position the term is at. |
-> Session (Declaration |? ([DeclarationLink] |? Null)) |
Returns the declarations(s) for the term at the specified position.
:: TextDocumentIdentifier | The document the term is in. |
-> Position | The position the term is at. |
-> Session (Definition |? ([DefinitionLink] |? Null)) |
Returns the definition(s) for the term at the specified position.
:: TextDocumentIdentifier | The document the term is in. |
-> Position | The position the term is at. |
-> Session (Definition |? ([DefinitionLink] |? Null)) |
Returns the type definition(s) for the term at the specified position.
:: TextDocumentIdentifier | The document the term is in. |
-> Position | The position the term is at. |
-> Session (Definition |? ([DefinitionLink] |? Null)) |
Returns the type definition(s) for the term at the specified position.
Renaming
rename :: TextDocumentIdentifier -> Position -> String -> Session () Source #
Renames the term at the specified position.
Hover
getHover :: TextDocumentIdentifier -> Position -> Session (Maybe Hover) Source #
Returns the hover information at the specified position.
Highlights
getHighlights :: TextDocumentIdentifier -> Position -> Session [DocumentHighlight] Source #
Returns the highlighted occurrences of the term at the specified position
Formatting
formatDoc :: TextDocumentIdentifier -> FormattingOptions -> Session () Source #
Applies formatting to the specified document.
formatRange :: TextDocumentIdentifier -> FormattingOptions -> Range -> Session () Source #
Applies formatting to the specified range in a document.
Edits
applyEdit :: TextDocumentIdentifier -> TextEdit -> Session VersionedTextDocumentIdentifier Source #
Applys an edit to the document and returns the updated document version.
Code lenses
getCodeLenses :: TextDocumentIdentifier -> Session [CodeLens] Source #
Returns the code lenses for the specified document.
getAndResolveCodeLenses :: TextDocumentIdentifier -> Session [CodeLens] Source #
Returns the code lenses for the specified document, resolving any with a non empty _data_ field.
resolveCodeLens :: CodeLens -> Session CodeLens Source #
Resolves the provided code lens.
Inlay Hints
getInlayHints :: TextDocumentIdentifier -> Range -> Session [InlayHint] Source #
Returns the inlay hints in the specified range.
getAndResolveInlayHints :: TextDocumentIdentifier -> Range -> Session [InlayHint] Source #
Returns the inlay hints in the specified range, resolving any with a non empty _data_ field.
resolveInlayHint :: InlayHint -> Session InlayHint Source #
Resolves the provided inlay hint.
Call hierarchy
prepareCallHierarchy :: CallHierarchyPrepareParams -> Session [CallHierarchyItem] Source #
Pass a param and return the response from prepareCallHierarchy
incomingCalls :: CallHierarchyIncomingCallsParams -> Session [CallHierarchyIncomingCall] Source #
outgoingCalls :: CallHierarchyOutgoingCallsParams -> Session [CallHierarchyOutgoingCall] Source #
SemanticTokens
getSemanticTokens :: TextDocumentIdentifier -> Session (SemanticTokens |? Null) Source #
Pass a param and return the response from semanticTokensFull
Capabilities
getRegisteredCapabilities :: Session [SomeRegistration] Source #
Returns a list of capabilities that the server has requested to dynamically
register during the Session
.
Since: 0.11.0.0