lsp-test-0.17.0.0: Functional test framework for LSP servers.
Maintainerluke_lau@icloud.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageGHC2021

Language.LSP.Test

Description

Provides the framework to start functionally testing Language Server Protocol servers. You should import Language.LSP.Types alongside this.

Synopsis

Sessions

data Session a Source #

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

Instances details
MonadFail Session Source # 
Instance details

Defined in Language.LSP.Test.Session

Methods

fail :: String -> Session a #

MonadIO Session Source # 
Instance details

Defined in Language.LSP.Test.Session

Methods

liftIO :: IO a -> Session a #

Alternative Session Source # 
Instance details

Defined in Language.LSP.Test.Session

Methods

empty :: Session a #

(<|>) :: Session a -> Session a -> Session a #

some :: Session a -> Session [a] #

many :: Session a -> Session [a] #

Applicative Session Source # 
Instance details

Defined in Language.LSP.Test.Session

Methods

pure :: a -> Session a #

(<*>) :: Session (a -> b) -> Session a -> Session b #

liftA2 :: (a -> b -> c) -> Session a -> Session b -> Session c #

(*>) :: Session a -> Session b -> Session b #

(<*) :: Session a -> Session b -> Session a #

Functor Session Source # 
Instance details

Defined in Language.LSP.Test.Session

Methods

fmap :: (a -> b) -> Session a -> Session b #

(<$) :: a -> Session b -> Session a #

Monad Session Source # 
Instance details

Defined in Language.LSP.Test.Session

Methods

(>>=) :: Session a -> (a -> Session b) -> Session b #

(>>) :: Session a -> Session b -> Session b #

return :: a -> Session a #

MonadThrow Session Source # 
Instance details

Defined in Language.LSP.Test.Session

Methods

throwM :: (HasCallStack, Exception e) => e -> Session a #

runSession Source #

Arguments

:: 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" fullCaps "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

runSessionWithConfig Source #

Arguments

:: 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 #

Arguments

:: (CreateProcess -> CreateProcess)

Tweak the CreateProcess used to start the server.

-> 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 #

Arguments

:: 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 fullCaps "." $ do
  -- ...

runSessionWithHandles' Source #

Arguments

:: 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 

Config

data SessionConfig Source #

Stuff you can configure for a Session.

Constructors

SessionConfig 

Fields

  • messageTimeout :: Int

    Maximum time to wait for a message in seconds, defaults to 60.

  • logStdErr :: Bool

    Redirect the server's stderr to this stdout, defaults to False. Can be overriden with LSP_TEST_LOG_STDERR.

  • logMessages :: Bool

    Trace the messages sent and received to stdout, defaults to False. Can be overriden with the environment variable LSP_TEST_LOG_MESSAGES.

  • logColor :: Bool

    Add ANSI color to the logged messages, defaults to True.

  • lspConfig :: Object

    The initial LSP config as JSON object, defaults to the empty object. This should include the config section for the server if it has one, i.e. if the server has a mylang config section, then the config should be an object with a mylang key whose value is the actual config for the server. You can also include other config sections if your server may request those.

  • ignoreLogNotifications :: Bool

    Whether or not to ignore window/showMessage and window/logMessage notifications from the server, defaults to True.

  • ignoreConfigurationRequests :: Bool

    Whether or not to ignore workspace/configuration requests from the server, defaults to True.

  • ignoreRegistrationRequests :: Bool

    Whether or not to ignore client/registerCapability and client/unregisterCapability requests from the server, defaults to True.

  • initialWorkspaceFolders :: Maybe [WorkspaceFolder]

    The initial workspace folders to send in the initialize request. Defaults to Nothing.

Instances

Instances details
Default SessionConfig Source # 
Instance details

Defined in Language.LSP.Test.Session

Methods

def :: SessionConfig #

defaultConfig :: SessionConfig Source #

The configuration used in runSession.

fullCaps :: ClientCapabilities #

Exceptions

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.

sendRequest Source #

Arguments

:: 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.

sendNotification Source #

Arguments

:: 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

createDoc Source #

Arguments

:: FilePath

The path to the document to open, relative to the root directory.

-> Text

The text document's language identifier, e.g. "haskell".

-> 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 -> Text -> 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

getReferences Source #

Arguments

:: 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

getDeclarations Source #

Arguments

:: 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.

getDefinitions Source #

Arguments

:: 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.

getTypeDefinitions Source #

Arguments

:: 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.

getImplementations Source #

Arguments

:: 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.

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