Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- handleMessage :: Show c => InitializeCallback c -> TVar (LanguageContextData c) -> ByteString -> ByteString -> IO ()
- data LanguageContextData a = LanguageContextData {
- resSeqDebugContextData :: !Int
- resHandlers :: !Handlers
- resOptions :: !Options
- resSendResponse :: !SendFunc
- resVFS :: !VFS
- resDiagnostics :: !DiagnosticStore
- resConfig :: !(Maybe a)
- resLspId :: !(TVar Int)
- resLspFuncs :: LspFuncs a
- resCaptureFile :: !(Maybe FilePath)
- type Handler b = b -> IO ()
- type InitializeCallback c = (DidChangeConfigurationNotification -> Either Text c, LspFuncs c -> IO (Maybe ResponseError))
- data LspFuncs c = LspFuncs {
- clientCapabilities :: !ClientCapabilities
- config :: !(IO (Maybe c))
- sendFunc :: !SendFunc
- getVirtualFileFunc :: !(Uri -> IO (Maybe VirtualFile))
- publishDiagnosticsFunc :: !PublishDiagnosticsFunc
- flushDiagnosticsBySourceFunc :: !FlushDiagnosticsBySourceFunc
- getNextReqId :: !(IO LspId)
- rootPath :: !(Maybe FilePath)
- type SendFunc = FromServerMessage -> IO ()
- data Handlers = Handlers {
- hoverHandler :: !(Maybe (Handler HoverRequest))
- completionHandler :: !(Maybe (Handler CompletionRequest))
- completionResolveHandler :: !(Maybe (Handler CompletionItemResolveRequest))
- signatureHelpHandler :: !(Maybe (Handler SignatureHelpRequest))
- definitionHandler :: !(Maybe (Handler ImplementationRequest))
- implementationHandler :: !(Maybe (Handler ImplementationRequest))
- referencesHandler :: !(Maybe (Handler ReferencesRequest))
- documentHighlightHandler :: !(Maybe (Handler DocumentHighlightRequest))
- documentSymbolHandler :: !(Maybe (Handler DocumentSymbolRequest))
- workspaceSymbolHandler :: !(Maybe (Handler WorkspaceSymbolRequest))
- codeActionHandler :: !(Maybe (Handler CodeActionRequest))
- codeLensHandler :: !(Maybe (Handler CodeLensRequest))
- codeLensResolveHandler :: !(Maybe (Handler CodeLensResolveRequest))
- documentFormattingHandler :: !(Maybe (Handler DocumentFormattingRequest))
- documentRangeFormattingHandler :: !(Maybe (Handler DocumentRangeFormattingRequest))
- documentTypeFormattingHandler :: !(Maybe (Handler DocumentOnTypeFormattingRequest))
- renameHandler :: !(Maybe (Handler RenameRequest))
- documentLinkHandler :: !(Maybe (Handler DocumentLinkRequest))
- documentLinkResolveHandler :: !(Maybe (Handler DocumentLinkResolveRequest))
- executeCommandHandler :: !(Maybe (Handler ExecuteCommandRequest))
- willSaveWaitUntilTextDocHandler :: !(Maybe (Handler WillSaveWaitUntilTextDocumentRequest))
- didChangeConfigurationParamsHandler :: !(Maybe (Handler DidChangeConfigurationNotification))
- didOpenTextDocumentNotificationHandler :: !(Maybe (Handler DidOpenTextDocumentNotification))
- didChangeTextDocumentNotificationHandler :: !(Maybe (Handler DidChangeTextDocumentNotification))
- didCloseTextDocumentNotificationHandler :: !(Maybe (Handler DidCloseTextDocumentNotification))
- didSaveTextDocumentNotificationHandler :: !(Maybe (Handler DidSaveTextDocumentNotification))
- didChangeWatchedFilesNotificationHandler :: !(Maybe (Handler DidChangeWatchedFilesNotification))
- initializedHandler :: !(Maybe (Handler InitializedNotification))
- willSaveTextDocumentNotificationHandler :: !(Maybe (Handler WillSaveTextDocumentNotification))
- cancelNotificationHandler :: !(Maybe (Handler CancelNotification))
- responseHandler :: !(Maybe (Handler BareResponseMessage))
- initializeRequestHandler :: !(Maybe (Handler InitializeRequest))
- exitNotificationHandler :: !(Maybe (Handler ExitNotification))
- data Options = Options {
- textDocumentSync :: Maybe TextDocumentSyncOptions
- completionProvider :: Maybe CompletionOptions
- signatureHelpProvider :: Maybe SignatureHelpOptions
- codeLensProvider :: Maybe CodeLensOptions
- documentOnTypeFormattingProvider :: Maybe DocumentOnTypeFormattingOptions
- documentLinkProvider :: Maybe DocumentLinkOptions
- executeCommandProvider :: Maybe ExecuteCommandOptions
- defaultLanguageContextData :: Handlers -> Options -> LspFuncs c -> TVar Int -> SendFunc -> Maybe FilePath -> LanguageContextData c
- makeResponseMessage :: RequestMessage ClientMethod req resp -> resp -> ResponseMessage resp
- makeResponseError :: LspIdRsp -> ResponseError -> ResponseMessage ()
- setupLogger :: Maybe FilePath -> [String] -> Priority -> IO ()
- sendErrorResponseS :: SendFunc -> LspIdRsp -> ErrorCode -> Text -> IO ()
- sendErrorLogS :: SendFunc -> Text -> IO ()
- sendErrorShowS :: SendFunc -> Text -> IO ()
- reverseSortEdit :: WorkspaceEdit -> WorkspaceEdit
Documentation
handleMessage :: Show c => InitializeCallback c -> TVar (LanguageContextData c) -> ByteString -> ByteString -> IO () Source #
data LanguageContextData a Source #
state used by the LSP dispatcher to manage the message loop
LanguageContextData | |
|
type Handler b = b -> IO () Source #
The Handler type captures a function that receives local read-only state
a
, a function to send a reply message once encoded as a ByteString, and a
received message of type b
type InitializeCallback c = (DidChangeConfigurationNotification -> Either Text c, LspFuncs c -> IO (Maybe ResponseError)) Source #
The function in the LSP process that is called once the initialize
message is received. Message processing will only continue once this returns,
so it should create whatever processes are needed.
Returned to the server on startup, providing ways to interact with the client.
LspFuncs | |
|
type SendFunc = FromServerMessage -> IO () Source #
A function to send a message to the client
Callbacks from the language server to the language handler
Language Server Protocol options supported by the given language server. These are automatically turned into capabilities reported to the client during initialization.
defaultLanguageContextData :: Handlers -> Options -> LspFuncs c -> TVar Int -> SendFunc -> Maybe FilePath -> LanguageContextData c Source #
makeResponseMessage :: RequestMessage ClientMethod req resp -> resp -> ResponseMessage resp Source #
makeResponseError :: LspIdRsp -> ResponseError -> ResponseMessage () Source #
setupLogger :: Maybe FilePath -> [String] -> Priority -> IO () Source #
===============================================================
utility
Logger
reverseSortEdit :: WorkspaceEdit -> WorkspaceEdit Source #
The changes in a workspace edit should be applied from the end of the file toward the start. Sort them into this order.