Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- handleMessage :: Show config => InitializeCallbacks config -> TVar (LanguageContextData config) -> ByteString -> IO ()
- data LanguageContextData config = LanguageContextData {
- resSeqDebugContextData :: !Int
- resHandlers :: !Handlers
- resOptions :: !Options
- resSendResponse :: !SendFunc
- resVFS :: !VFS
- reverseMap :: !(Map FilePath FilePath)
- resDiagnostics :: !DiagnosticStore
- resConfig :: !(Maybe config)
- resLspId :: !(TVar Int)
- resLspFuncs :: LspFuncs config
- resCaptureFile :: !(Maybe FilePath)
- resWorkspaceFolders :: ![WorkspaceFolder]
- resProgressData :: !ProgressData
- type Handler b = b -> IO ()
- data InitializeCallbacks config = InitializeCallbacks {
- onInitialConfiguration :: InitializeRequest -> Either Text config
- onConfigurationChange :: DidChangeConfigurationNotification -> Either Text config
- onStartup :: LspFuncs config -> IO (Maybe ResponseError)
- data LspFuncs c = LspFuncs {
- clientCapabilities :: !ClientCapabilities
- config :: !(IO (Maybe c))
- sendFunc :: !SendFunc
- getVirtualFileFunc :: !(NormalizedUri -> IO (Maybe VirtualFile))
- persistVirtualFileFunc :: !(NormalizedUri -> IO FilePath)
- reverseFileMapFunc :: !(IO (FilePath -> FilePath))
- publishDiagnosticsFunc :: !PublishDiagnosticsFunc
- flushDiagnosticsBySourceFunc :: !FlushDiagnosticsBySourceFunc
- getNextReqId :: !(IO LspId)
- rootPath :: !(Maybe FilePath)
- getWorkspaceFolders :: !(IO (Maybe [WorkspaceFolder]))
- withProgress :: !(forall a. Text -> ProgressCancellable -> ((Progress -> IO ()) -> IO a) -> IO a)
- withIndefiniteProgress :: !(forall a. Text -> ProgressCancellable -> IO a -> IO a)
- data Progress = Progress (Maybe Double) (Maybe Text)
- data ProgressCancellable
- data ProgressCancelledException
- 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 DefinitionRequest))
- typeDefinitionHandler :: !(Maybe (Handler TypeDefinitionRequest))
- 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))
- documentColorHandler :: !(Maybe (Handler DocumentColorRequest))
- colorPresentationHandler :: !(Maybe (Handler ColorPresentationRequest))
- documentFormattingHandler :: !(Maybe (Handler DocumentFormattingRequest))
- documentRangeFormattingHandler :: !(Maybe (Handler DocumentRangeFormattingRequest))
- documentTypeFormattingHandler :: !(Maybe (Handler DocumentOnTypeFormattingRequest))
- renameHandler :: !(Maybe (Handler RenameRequest))
- prepareRenameHandler :: !(Maybe (Handler PrepareRenameRequest))
- foldingRangeHandler :: !(Maybe (Handler FoldingRangeRequest))
- 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))
- didChangeWorkspaceFoldersNotificationHandler :: !(Maybe (Handler DidChangeWorkspaceFoldersNotification))
- initializedHandler :: !(Maybe (Handler InitializedNotification))
- willSaveTextDocumentNotificationHandler :: !(Maybe (Handler WillSaveTextDocumentNotification))
- cancelNotificationHandler :: !(Maybe (Handler CancelNotification))
- responseHandler :: !(Maybe (Handler BareResponseMessage))
- initializeRequestHandler :: !(Maybe (Handler InitializeRequest))
- exitNotificationHandler :: !(Maybe (Handler ExitNotification))
- customRequestHandler :: !(Maybe (Handler CustomClientRequest))
- customNotificationHandler :: !(Maybe (Handler CustomClientNotification))
- data Options = Options {
- textDocumentSync :: Maybe TextDocumentSyncOptions
- completionProvider :: Maybe CompletionOptions
- signatureHelpProvider :: Maybe SignatureHelpOptions
- typeDefinitionProvider :: Maybe GotoOptions
- implementationProvider :: Maybe GotoOptions
- codeActionProvider :: Maybe CodeActionOptions
- codeLensProvider :: Maybe CodeLensOptions
- documentOnTypeFormattingProvider :: Maybe DocumentOnTypeFormattingOptions
- renameProvider :: Maybe RenameOptions
- documentLinkProvider :: Maybe DocumentLinkOptions
- colorProvider :: Maybe ColorOptions
- foldingRangeProvider :: Maybe FoldingRangeOptions
- executeCommandProvider :: Maybe ExecuteCommandOptions
- defaultLanguageContextData :: Handlers -> Options -> LspFuncs config -> TVar Int -> SendFunc -> Maybe FilePath -> LanguageContextData config
- 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 config => InitializeCallbacks config -> TVar (LanguageContextData config) -> ByteString -> IO () Source #
data LanguageContextData config 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
data InitializeCallbacks config Source #
Contains all the callbacks to use for initialized the language server. it is parameterized over a config type variable representing the type for the specific configuration data the language server needs to use.
InitializeCallbacks | |
|
Returned to the server on startup, providing ways to interact with the client.
LspFuncs | |
|
A package indicating the perecentage of progress complete and a
an optional message to go with it during a withProgress
Since: 0.10.0.0
data ProgressCancellable Source #
Whether or not the user should be able to cancel a 'withProgress'/'withIndefiniteProgress' session
Since: 0.11.0.0
data ProgressCancelledException Source #
Thrown if the user cancels a Cancellable
'withProgress'/'withIndefiniteProgress'/ session
Since: 0.11.0.0
Instances
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 config -> TVar Int -> SendFunc -> Maybe FilePath -> LanguageContextData config 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.