Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Language.LSP.Client.Session
Synopsis
- data SessionState = SessionState {
- pendingRequests :: TVar RequestMap
- notificationHandlers :: TVar NotificationMap
- lastRequestId :: TVar Int32
- serverCapabilities :: TVar (HashMap Text SomeRegistration)
- clientCapabilities :: ClientCapabilities
- progressTokens :: TVar (HashSet ProgressToken)
- outgoing :: TQueue FromClientMessage
- vfs :: TVar VFS
- rootDir :: FilePath
- defaultSessionState :: MonadIO io => VFS -> io SessionState
- type SessionT = ReaderT SessionState
- type Session = SessionT IO
- class Monad m => MonadSession m where
- liftSession :: forall a. Session a -> m a
- documentChangeUri :: DocumentChange -> Uri
- handleServerMessage :: MonadSession m => FromServerMessage -> m ()
- sendRequest :: forall (method :: Method 'ClientToServer 'Request) m. (TMessage method ~ TRequestMessage method, MonadSession m) => SMethod method -> MessageParams method -> (TResponseMessage method -> IO ()) -> m (LspId method)
- sendResponse :: forall (method :: Method 'ServerToClient 'Request) m. MonadSession m => TRequestMessage method -> Either (TResponseError method) (MessageResult method) -> m ()
- request :: forall (method :: Method 'ClientToServer 'Request) m. (TMessage method ~ TRequestMessage method, MonadSession m) => SMethod method -> MessageParams method -> m (TResponseMessage method)
- getResponseResult :: Show (ErrorData m) => TResponseMessage m -> MessageResult m
- sendNotification :: forall (method :: Method 'ClientToServer 'Notification) m. (TMessage method ~ TNotificationMessage method, MonadSession m) => SMethod method -> MessageParams method -> m ()
- receiveNotification :: forall (method :: Method 'ServerToClient 'Notification) m. (TMessage method ~ TNotificationMessage method, MonadSession m) => SMethod method -> (TMessage method -> IO ()) -> m ()
- clearNotificationCallback :: forall (method :: Method 'ServerToClient 'Notification) m. MonadSession m => SMethod method -> m ()
- sendMessage :: MonadSession m => FromClientMessage -> m ()
- lspClientInfo :: ClientInfo
- initialize :: MonadSession m => Maybe Value -> m InitializeResult
- createDoc :: MonadSession m => FilePath -> LanguageKind -> Text -> m TextDocumentIdentifier
- openDoc :: MonadSession m => FilePath -> LanguageKind -> m TextDocumentIdentifier
- openDoc' :: MonadSession m => FilePath -> LanguageKind -> Text -> m TextDocumentIdentifier
- closeDoc :: MonadSession m => TextDocumentIdentifier -> m ()
- changeDoc :: MonadSession m => TextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> m ()
- getDocUri :: MonadSession m => FilePath -> m Uri
- documentContents :: MonadSession m => TextDocumentIdentifier -> m (Maybe Rope)
- getVersionedDoc :: MonadSession m => TextDocumentIdentifier -> m VersionedTextDocumentIdentifier
- getAllVersionedDocs :: MonadSession m => m [VersionedTextDocumentIdentifier]
Documentation
data SessionState Source #
Constructors
SessionState | |
Fields
|
Instances
MonadIO m => MonadSession (SessionT m) Source # | |
Defined in Language.LSP.Client.Session Methods liftSession :: Session a -> SessionT m a Source # |
defaultSessionState :: MonadIO io => VFS -> io SessionState Source #
type SessionT = ReaderT SessionState Source #
class Monad m => MonadSession m where Source #
Methods
liftSession :: forall a. Session a -> m a Source #
Instances
MonadIO m => MonadSession (SessionT m) Source # | |
Defined in Language.LSP.Client.Session Methods liftSession :: Session a -> SessionT m a Source # | |
(MonadTrans t, MonadSession m, Monad (t m)) => MonadSession (t m) Source # | |
Defined in Language.LSP.Client.Session Methods liftSession :: Session a -> t m a Source # |
documentChangeUri :: DocumentChange -> Uri Source #
handleServerMessage :: MonadSession m => FromServerMessage -> m () Source #
Fires whenever the client receives a message from the server. Updates the session state as needed.
Note that this does not provide any business logic beyond updating the session state; you most likely
want to use sendRequest
and receiveNotification
to register callbacks for specific messages.
sendRequest :: forall (method :: Method 'ClientToServer 'Request) m. (TMessage method ~ TRequestMessage method, MonadSession m) => SMethod method -> MessageParams method -> (TResponseMessage method -> IO ()) -> m (LspId method) Source #
Sends a request to the server, with a callback that fires when the response arrives. Multiple requests can be waiting at the same time.
sendResponse :: forall (method :: Method 'ServerToClient 'Request) m. MonadSession m => TRequestMessage method -> Either (TResponseError method) (MessageResult method) -> m () Source #
Send a response to the server. This is used internally to acknowledge server requests. Users of this library cannot register callbacks to server requests, so this function is probably of no use to them.
request :: forall (method :: Method 'ClientToServer 'Request) m. (TMessage method ~ TRequestMessage method, MonadSession m) => SMethod method -> MessageParams method -> m (TResponseMessage method) Source #
Sends a request to the server and synchronously waits for its response.
getResponseResult :: Show (ErrorData m) => TResponseMessage m -> MessageResult m Source #
Checks the response for errors and throws an exception if needed. Returns the result if successful.InitializeParams
sendNotification :: forall (method :: Method 'ClientToServer 'Notification) m. (TMessage method ~ TNotificationMessage method, MonadSession m) => SMethod method -> MessageParams method -> m () Source #
Sends a notification to the server. Updates the VFS if the notification is a document update.
receiveNotification :: forall (method :: Method 'ServerToClient 'Notification) m. (TMessage method ~ TNotificationMessage method, MonadSession m) => SMethod method -> (TMessage method -> IO ()) -> m () Source #
Registers a callback for notifications received from the server. If multiple callbacks are registered for the same notification method, they will all be called.
clearNotificationCallback :: forall (method :: Method 'ServerToClient 'Notification) m. MonadSession m => SMethod method -> m () Source #
Clears the registered callback for the given notification method, if any. If multiple callbacks have been registered, this clears all of them.
sendMessage :: MonadSession m => FromClientMessage -> m () Source #
Queues a message to be sent to the server at the client's earliest convenience.
lspClientInfo :: ClientInfo Source #
initialize :: MonadSession m => Maybe Value -> m InitializeResult Source #
Performs the initialisation handshake and synchronously waits for its completion. When the function completes, the session is initialised.
Arguments
:: MonadSession m | |
=> FilePath | The path to the document to open, relative to the root directory. |
-> LanguageKind | The text document's language |
-> Text | The content of the text document to create. |
-> m 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.
openDoc :: MonadSession m => FilePath -> LanguageKind -> m TextDocumentIdentifier Source #
Opens a text document that exists on disk, and sends a
textDocument/didOpen
notification to the server.
openDoc' :: MonadSession m => FilePath -> LanguageKind -> Text -> m TextDocumentIdentifier Source #
This is a variant of openDoc
that takes the file content as an argument.
Use this is the file exists outside of the current workspace.
closeDoc :: MonadSession m => TextDocumentIdentifier -> m () Source #
Closes a text document and sends a textDocument/didClose
notification to the server.
changeDoc :: MonadSession m => TextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> m () Source #
Changes a text document and sends a textDocument/didChange
notification to the server.
getDocUri :: MonadSession m => FilePath -> m Uri Source #
Gets the Uri for the file relative to the session's root directory.
documentContents :: MonadSession m => TextDocumentIdentifier -> m (Maybe Rope) Source #
The current text contents of a document.
getVersionedDoc :: MonadSession m => TextDocumentIdentifier -> m VersionedTextDocumentIdentifier Source #
Adds the current version to the document, as tracked by the session.
getAllVersionedDocs :: MonadSession m => m [VersionedTextDocumentIdentifier] Source #
Get all the versioned documents tracked by the session.