Maintainer | luke_lau@icloud.com |
---|---|
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Provides the framework to start functionally testing Language Server Protocol servers. You should import Language.Haskell.LSP.Types alongside this.
Synopsis
- type Session = ParserStateReader FromServerMessage SessionState SessionContext IO
- runSession :: String -> ClientCapabilities -> FilePath -> Session a -> IO a
- runSessionWithConfig :: SessionConfig -> String -> ClientCapabilities -> FilePath -> Session a -> IO a
- data SessionConfig = SessionConfig {}
- defaultConfig :: SessionConfig
- fullCaps :: ClientCapabilities
- data SessionException
- anySessionException :: SessionException -> Bool
- withTimeout :: Int -> Session a -> Session a
- request :: (ToJSON params, FromJSON a) => ClientMethod -> params -> Session (ResponseMessage a)
- request_ :: ToJSON params => ClientMethod -> params -> Session ()
- sendRequest :: ToJSON params => ClientMethod -> params -> Session LspId
- sendNotification :: ToJSON a => ClientMethod -> a -> Session ()
- sendResponse :: ToJSON a => ResponseMessage a -> Session ()
- message :: forall a. (Typeable a, FromJSON a) => Session a
- anyRequest :: Session FromServerMessage
- anyResponse :: Session FromServerMessage
- anyNotification :: Session FromServerMessage
- anyMessage :: Session FromServerMessage
- loggingNotification :: Session FromServerMessage
- publishDiagnosticsNotification :: Session PublishDiagnosticsNotification
- responseForId :: forall a. FromJSON a => LspId -> Session (ResponseMessage a)
- initializeResponse :: Session InitializeResponse
- openDoc :: FilePath -> String -> Session TextDocumentIdentifier
- closeDoc :: TextDocumentIdentifier -> Session ()
- documentContents :: TextDocumentIdentifier -> Session Text
- getDocumentEdit :: TextDocumentIdentifier -> Session Text
- getDocUri :: FilePath -> Session Uri
- getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier
- getDocumentSymbols :: TextDocumentIdentifier -> Session (Either [DocumentSymbol] [SymbolInformation])
- waitForDiagnostics :: Session [Diagnostic]
- waitForDiagnosticsSource :: String -> Session [Diagnostic]
- noDiagnostics :: Session ()
- getCurrentDiagnostics :: TextDocumentIdentifier -> Session [Diagnostic]
- executeCommand :: Command -> Session ()
- getCodeActions :: TextDocumentIdentifier -> Range -> Session [CAResult]
- getAllCodeActions :: TextDocumentIdentifier -> Session [CAResult]
- executeCodeAction :: CodeAction -> Session ()
- getCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem]
- getReferences :: TextDocumentIdentifier -> Position -> Bool -> Session [Location]
- getDefinitions :: TextDocumentIdentifier -> Position -> Session [Location]
- 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
Sessions
type Session = ParserStateReader FromServerMessage SessionState SessionContext IO 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 getMessage
,
sendRequest
and sendNotification
.
:: 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 TextDocumentHover params
Config
:: 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 sesion with a custom configuration.
data SessionConfig Source #
Stuff you can configure for a Session
.
SessionConfig | |
|
Instances
Default SessionConfig Source # | |
Defined in Language.Haskell.LSP.Test.Session def :: SessionConfig # |
defaultConfig :: SessionConfig Source #
The configuration used in runSession
.
fullCaps :: ClientCapabilities #
The whole shebang. The real deal. Capabilities for full conformance to the current (v3.10) LSP specification.
Exceptions
data SessionException Source #
An exception that can be thrown during a Session
Instances
Eq SessionException Source # | |
Defined in Language.Haskell.LSP.Test.Exceptions (==) :: SessionException -> SessionException -> Bool # (/=) :: SessionException -> SessionException -> Bool # | |
Show SessionException Source # | |
Defined in Language.Haskell.LSP.Test.Exceptions showsPrec :: Int -> SessionException -> ShowS # show :: SessionException -> String # showList :: [SessionException] -> ShowS # | |
Exception SessionException Source # | |
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 TimeoutException
after duration seconds. This will override the global timeout
for waiting for messages to arrive defined in SessionConfig
.
Sending
request :: (ToJSON params, FromJSON a) => ClientMethod -> params -> Session (ResponseMessage a) 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 TextDocumentDocumentSymbol params :: Session DocumentSymbolsResponse
Note: will skip any messages in between the request and the response.
request_ :: ToJSON params => ClientMethod -> params -> Session () Source #
The same as sendRequest
, but discard the response.
:: ToJSON params | |
=> ClientMethod | The request method. |
-> params | The request parameters. |
-> Session LspId | The id of the request that was sent. |
Sends a request to the server. Unlike request
, this doesn't wait for the response.
:: ToJSON a | |
=> ClientMethod | The notification method. |
-> a | The notification parameters. |
-> Session () |
Sends a notification to the server.
sendResponse :: ToJSON a => ResponseMessage a -> Session () Source #
Sends a response to the server.
Receving
To receive a message, just specify the type that expect:
msg1 <- message :: Session ApplyWorkspaceEditRequest msg2 <- message :: Session HoverResponse
Session
is actually just a parser
that operates on messages under the hood. This means that you
can create and combine parsers to match speicifc sequences of
messages that you expect.
For example, if you wanted to match either a definition or references request:
defOrImpl = (message :: Session DefinitionRequest) <|> (message :: Session ReferencesRequest)
If you wanted to match any number of telemetry notifications immediately followed by a response:
logThenDiags = skipManyTill (message :: Session TelemetryNotification) anyResponse
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.
publishDiagnosticsNotification :: Session PublishDiagnosticsNotification Source #
Matches a PublishDiagnosticsNotification
(textDocument/publishDiagnostics) notification.
responseForId :: forall a. FromJSON a => LspId -> Session (ResponseMessage a) Source #
Matches a response for a specific id.
Utilities
Quick helper functions for common tasks. ** Initialization
initializeResponse :: Session InitializeResponse 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.
Documents
openDoc :: FilePath -> String -> Session TextDocumentIdentifier Source #
Opens a text document and sends a notification to the client.
closeDoc :: TextDocumentIdentifier -> Session () Source #
Closes a text document and sends a notification to the client.
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 [DocumentSymbol] [SymbolInformation]) 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
$sel:_source:Diagnostic
.
noDiagnostics :: Session () Source #
Expects a PublishDiagnosticsNotification
and throws an
UnexpectedDiagnosticsException
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.
Commands
executeCommand :: Command -> Session () Source #
Executes a command.
Code Actions
getCodeActions :: TextDocumentIdentifier -> Range -> Session [CAResult] Source #
Returns the code actions in the specified range.
getAllCodeActions :: TextDocumentIdentifier -> Session [CAResult] 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.
Completions
getCompletions :: TextDocumentIdentifier -> Position -> Session [CompletionItem] Source #
Returns the completions for the position in the document.
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 [Location] | The location(s) of the definitions |
Returns the 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 occurences 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.