Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype List a = List [a]
- newtype Uri = Uri {}
- uriToFilePath :: Uri -> Maybe FilePath
- filePathToUri :: FilePath -> Uri
- data LspId
- data LspIdRsp
- responseId :: LspId -> LspIdRsp
- data ClientMethod
- = Initialize
- | Initialized
- | Shutdown
- | Exit
- | CancelRequest
- | WorkspaceDidChangeConfiguration
- | WorkspaceDidChangeWatchedFiles
- | WorkspaceSymbol
- | WorkspaceExecuteCommand
- | TextDocumentDidOpen
- | TextDocumentDidChange
- | TextDocumentWillSave
- | TextDocumentWillSaveWaitUntil
- | TextDocumentDidSave
- | TextDocumentDidClose
- | TextDocumentCompletion
- | CompletionItemResolve
- | TextDocumentHover
- | TextDocumentSignatureHelp
- | TextDocumentReferences
- | TextDocumentDocumentHighlight
- | TextDocumentDocumentSymbol
- | TextDocumentFormatting
- | TextDocumentRangeFormatting
- | TextDocumentOnTypeFormatting
- | TextDocumentDefinition
- | TextDocumentCodeAction
- | TextDocumentCodeLens
- | CodeLensResolve
- | TextDocumentDocumentLink
- | DocumentLinkResolve
- | TextDocumentRename
- | Misc Text
- data ServerMethod
- data RequestMessage m req resp = RequestMessage {}
- class HasId s a | s -> a where
- class HasJsonrpc s a | s -> a where
- class HasMethod s a | s -> a where
- class HasParams s a | s -> a where
- data ErrorCode
- data ResponseError = ResponseError {}
- class HasCode s a | s -> a where
- class HasMessage s a | s -> a where
- class HasXdata s a | s -> a where
- data ResponseMessage a = ResponseMessage {}
- class HasError s a | s -> a where
- class HasResult s a | s -> a where
- type ErrorResponse = ResponseMessage ()
- type BareResponseMessage = ResponseMessage Value
- data NotificationMessage m a = NotificationMessage {}
- data CancelParams = CancelParams {}
- type CancelNotification = NotificationMessage ClientMethod CancelParams
- data Position = Position {
- _line :: Int
- _character :: Int
- class HasCharacter s a | s -> a where
- class HasLine s a | s -> a where
- data Range = Range {}
- class HasEnd s a | s -> a where
- class HasStart s a | s -> a where
- data Location = Location {}
- class HasRange s a | s -> a where
- class HasUri s a | s -> a where
- data DiagnosticSeverity
- type DiagnosticSource = Text
- data Diagnostic = Diagnostic {}
- class HasSeverity s a | s -> a where
- class HasSource s a | s -> a where
- data Command = Command {}
- class HasArguments s a | s -> a where
- class HasCommand s a | s -> a where
- class HasTitle s a | s -> a where
- data TextEdit = TextEdit {}
- class HasNewText s a | s -> a where
- type TextDocumentVersion = Int
- data VersionedTextDocumentIdentifier = VersionedTextDocumentIdentifier {}
- class HasVersion s a | s -> a where
- data TextDocumentEdit = TextDocumentEdit {}
- class HasEdits s a | s -> a where
- class HasTextDocument s a | s -> a where
- type WorkspaceEditMap = HashMap Uri (List TextEdit)
- data WorkspaceEdit = WorkspaceEdit {}
- class HasChanges s a | s -> a where
- class HasDocumentChanges s a | s -> a where
- data TextDocumentIdentifier = TextDocumentIdentifier {}
- data TextDocumentItem = TextDocumentItem {}
- class HasLanguageId s a | s -> a where
- class HasText s a | s -> a where
- data TextDocumentPositionParams = TextDocumentPositionParams {}
- class HasPosition s a | s -> a where
- data DocumentFilter = DocumentFilter {}
- class HasLanguage s a | s -> a where
- class HasPattern s a | s -> a where
- class HasScheme s a | s -> a where
- type DocumentSelector = List DocumentFilter
- data Trace
- data InitializeParams = InitializeParams {}
- class HasCapabilities s a | s -> a where
- class HasInitializationOptions s a | s -> a where
- class HasProcessId s a | s -> a where
- class HasRootPath s a | s -> a where
- class HasRootUri s a | s -> a where
- class HasTrace s a | s -> a where
- data InitializeError = InitializeError {}
- class HasRetry s a | s -> a where
- data TextDocumentSyncKind
- data CompletionOptions = CompletionOptions {}
- class HasResolveProvider s a | s -> a where
- class HasTriggerCharacters s a | s -> a where
- data SignatureHelpOptions = SignatureHelpOptions {}
- data CodeLensOptions = CodeLensOptions {}
- data DocumentOnTypeFormattingOptions = DocumentOnTypeFormattingOptions {}
- class HasFirstTriggerCharacter s a | s -> a where
- class HasMoreTriggerCharacter s a | s -> a where
- data DocumentLinkOptions = DocumentLinkOptions {}
- data ExecuteCommandOptions = ExecuteCommandOptions {}
- class HasCommands s a | s -> a where
- data SaveOptions = SaveOptions {}
- class HasIncludeText s a | s -> a where
- data TextDocumentSyncOptions = TextDocumentSyncOptions {}
- class HasChange s a | s -> a where
- class HasOpenClose s a | s -> a where
- class HasSave s a | s -> a where
- class HasWillSave s a | s -> a where
- class HasWillSaveWaitUntil s a | s -> a where
- data InitializeResponseCapabilitiesInner = InitializeResponseCapabilitiesInner {
- _textDocumentSync :: Maybe TextDocumentSyncOptions
- _hoverProvider :: Maybe Bool
- _completionProvider :: Maybe CompletionOptions
- _signatureHelpProvider :: Maybe SignatureHelpOptions
- _definitionProvider :: Maybe Bool
- _referencesProvider :: Maybe Bool
- _documentHighlightProvider :: Maybe Bool
- _documentSymbolProvider :: Maybe Bool
- _workspaceSymbolProvider :: Maybe Bool
- _codeActionProvider :: Maybe Bool
- _codeLensProvider :: Maybe CodeLensOptions
- _documentFormattingProvider :: Maybe Bool
- _documentRangeFormattingProvider :: Maybe Bool
- _documentOnTypeFormattingProvider :: Maybe DocumentOnTypeFormattingOptions
- _renameProvider :: Maybe Bool
- _documentLinkProvider :: Maybe DocumentLinkOptions
- _executeCommandProvider :: Maybe ExecuteCommandOptions
- _experimental :: Maybe Value
- class HasCodeActionProvider s a | s -> a where
- class HasCodeLensProvider s a | s -> a where
- class HasCompletionProvider s a | s -> a where
- class HasDefinitionProvider s a | s -> a where
- class HasDocumentFormattingProvider s a | s -> a where
- class HasDocumentHighlightProvider s a | s -> a where
- class HasDocumentLinkProvider s a | s -> a where
- class HasDocumentOnTypeFormattingProvider s a | s -> a where
- class HasDocumentRangeFormattingProvider s a | s -> a where
- class HasDocumentSymbolProvider s a | s -> a where
- class HasExecuteCommandProvider s a | s -> a where
- class HasExperimental s a | s -> a where
- class HasHoverProvider s a | s -> a where
- class HasReferencesProvider s a | s -> a where
- class HasRenameProvider s a | s -> a where
- class HasSignatureHelpProvider s a | s -> a where
- class HasTextDocumentSync s a | s -> a where
- class HasWorkspaceSymbolProvider s a | s -> a where
- data InitializeResponseCapabilities = InitializeResponseCapabilities {}
- type InitializeResponse = ResponseMessage InitializeResponseCapabilities
- type InitializeRequest = RequestMessage ClientMethod InitializeParams InitializeResponseCapabilities
- data InitializedParams = InitializedParams {
- type InitializedNotification = NotificationMessage ClientMethod (Maybe InitializedParams)
- type ShutdownRequest = RequestMessage ClientMethod (Maybe Value) Text
- type ShutdownResponse = ResponseMessage Text
- data ExitParams = ExitParams {
- type ExitNotification = NotificationMessage ClientMethod (Maybe ExitParams)
- data MessageType
- data ShowMessageParams = ShowMessageParams {
- _xtype :: MessageType
- _message :: Text
- class HasXtype s a | s -> a where
- type ShowMessageNotification = NotificationMessage ServerMethod ShowMessageParams
- data MessageActionItem = MessageActionItem {}
- data ShowMessageRequestParams = ShowMessageRequestParams {
- _xtype :: MessageType
- _message :: Text
- _actions :: Maybe [MessageActionItem]
- class HasActions s a | s -> a where
- type ShowMessageRequest = RequestMessage ServerMethod ShowMessageRequestParams Text
- type ShowMessageResponse = ResponseMessage Text
- data LogMessageParams = LogMessageParams {
- _xtype :: MessageType
- _message :: Text
- type LogMessageNotification = NotificationMessage ServerMethod LogMessageParams
- type TelemetryNotification = NotificationMessage ServerMethod Value
- data Registration = Registration {
- _id :: Text
- _method :: ClientMethod
- _registerOptions :: Maybe Value
- class HasRegisterOptions s a | s -> a where
- data RegistrationParams = RegistrationParams {}
- class HasRegistrations s a | s -> a where
- type RegisterCapabilityRequest = RequestMessage ServerMethod RegistrationParams ()
- data TextDocumentRegistrationOptions = TextDocumentRegistrationOptions {}
- class HasDocumentSelector s a | s -> a where
- data Unregistration = Unregistration {}
- data UnregistrationParams = UnregistrationParams {}
- class HasUnregistrations s a | s -> a where
- type UnregisterCapabilityRequest = RequestMessage ServerMethod UnregistrationParams ()
- data DidChangeConfigurationParams = DidChangeConfigurationParams {}
- class HasSettings s a | s -> a where
- type DidChangeConfigurationNotification = NotificationMessage ClientMethod DidChangeConfigurationParams
- data DidOpenTextDocumentParams = DidOpenTextDocumentParams {}
- type DidOpenTextDocumentNotification = NotificationMessage ClientMethod DidOpenTextDocumentParams
- data TextDocumentContentChangeEvent = TextDocumentContentChangeEvent {}
- class HasRangeLength s a | s -> a where
- data DidChangeTextDocumentParams = DidChangeTextDocumentParams {}
- class HasContentChanges s a | s -> a where
- type DidChangeTextDocumentNotification = NotificationMessage ClientMethod DidChangeTextDocumentParams
- data TextDocumentChangeRegistrationOptions = TextDocumentChangeRegistrationOptions {}
- class HasSyncKind s a | s -> a where
- data TextDocumentSaveReason
- data WillSaveTextDocumentParams = WillSaveTextDocumentParams {}
- class HasReason s a | s -> a where
- type WillSaveTextDocumentNotification = NotificationMessage ClientMethod WillSaveTextDocumentParams
- type WillSaveWaitUntilTextDocumentRequest = RequestMessage ClientMethod WillSaveTextDocumentParams (List TextEdit)
- type WillSaveWaitUntilTextDocumentResponse = ResponseMessage (List TextEdit)
- data DidSaveTextDocumentParams = DidSaveTextDocumentParams {}
- type DidSaveTextDocumentNotification = NotificationMessage ClientMethod DidSaveTextDocumentParams
- data DidCloseTextDocumentParams = DidCloseTextDocumentParams {}
- type DidCloseTextDocumentNotification = NotificationMessage ClientMethod DidCloseTextDocumentParams
- data FileChangeType
- data FileEvent = FileEvent {
- _uri :: Uri
- _xtype :: FileChangeType
- data DidChangeWatchedFilesParams = DidChangeWatchedFilesParams {}
- type DidChangeWatchedFilesNotification = NotificationMessage ClientMethod DidChangeWatchedFilesParams
- data PublishDiagnosticsParams = PublishDiagnosticsParams {
- _uri :: Uri
- _diagnostics :: List Diagnostic
- class HasDiagnostics s a | s -> a where
- type PublishDiagnosticsNotification = NotificationMessage ServerMethod PublishDiagnosticsParams
- data InsertTextFormat
- data CompletionItemKind
- data CompletionItem = CompletionItem {
- _label :: Text
- _kind :: Maybe CompletionItemKind
- _detail :: Maybe Text
- _documentation :: Maybe Text
- _sortText :: Maybe Text
- _filterText :: Maybe Text
- _insertText :: Maybe Text
- _insertTextFormat :: Maybe InsertTextFormat
- _textEdit :: Maybe TextEdit
- _additionalTextEdits :: Maybe (List TextEdit)
- _command :: Maybe Command
- _xdata :: Maybe Value
- class HasAdditionalTextEdits s a | s -> a where
- class HasDetail s a | s -> a where
- class HasDocumentation s a | s -> a where
- class HasFilterText s a | s -> a where
- class HasInsertText s a | s -> a where
- class HasInsertTextFormat s a | s -> a where
- class HasKind s a | s -> a where
- class HasLabel s a | s -> a where
- class HasSortText s a | s -> a where
- class HasTextEdit s a | s -> a where
- data CompletionListType = CompletionListType {}
- class HasIsIncomplete s a | s -> a where
- class HasItems s a | s -> a where
- data CompletionResponseResult
- type CompletionResponse = ResponseMessage CompletionResponseResult
- type CompletionRequest = RequestMessage ClientMethod TextDocumentPositionParams CompletionResponseResult
- data CompletionRegistrationOptions = CompletionRegistrationOptions {}
- type CompletionItemResolveRequest = RequestMessage ClientMethod CompletionItem CompletionItem
- type CompletionItemResolveResponse = ResponseMessage CompletionItem
- data LanguageString = LanguageString {}
- class HasValue s a | s -> a where
- data MarkedString
- data Hover = Hover {}
- class HasContents s a | s -> a where
- type HoverRequest = RequestMessage ClientMethod TextDocumentPositionParams Hover
- type HoverResponse = ResponseMessage Hover
- data ParameterInformation = ParameterInformation {
- _label :: Text
- _documentation :: Maybe Text
- data SignatureInformation = SignatureInformation {}
- class HasParameters s a | s -> a where
- data SignatureHelp = SignatureHelp {}
- class HasActiveParameter s a | s -> a where
- class HasActiveSignature s a | s -> a where
- class HasSignatures s a | s -> a where
- type SignatureHelpRequest = RequestMessage ClientMethod TextDocumentPositionParams SignatureHelp
- type SignatureHelpResponse = ResponseMessage SignatureHelp
- data SignatureHelpRegistrationOptions = SignatureHelpRegistrationOptions {}
- data DefinitionResponseParams
- type DefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams DefinitionResponseParams
- type DefinitionResponse = ResponseMessage DefinitionResponseParams
- data ReferenceContext = ReferenceContext {}
- class HasIncludeDeclaration s a | s -> a where
- data ReferenceParams = ReferenceParams {}
- class HasContext s a | s -> a where
- type ReferencesRequest = RequestMessage ClientMethod ReferenceParams (List Location)
- type ReferencesResponse = ResponseMessage (List Location)
- data DocumentHighlightKind
- data DocumentHighlight = DocumentHighlight {}
- type DocumentHighlightRequest = RequestMessage ClientMethod TextDocumentPositionParams (List DocumentHighlight)
- type DocumentHighlightsResponse = ResponseMessage (List DocumentHighlight)
- data DocumentSymbolParams = DocumentSymbolParams {}
- data SymbolKind
- data SymbolInformation = SymbolInformation {
- _name :: Text
- _kind :: SymbolKind
- _location :: Location
- _containerName :: Maybe Text
- class HasContainerName s a | s -> a where
- class HasLocation s a | s -> a where
- class HasName s a | s -> a where
- type DocumentSymbolRequest = RequestMessage ClientMethod DocumentSymbolParams (List SymbolInformation)
- type DocumentSymbolsResponse = ResponseMessage (List SymbolInformation)
- data WorkspaceSymbolParams = WorkspaceSymbolParams {}
- class HasQuery s a | s -> a where
- type WorkspaceSymbolRequest = RequestMessage ClientMethod WorkspaceSymbolParams (List SymbolInformation)
- type WorkspaceSymbolsResponse = ResponseMessage (List SymbolInformation)
- data CodeActionContext = CodeActionContext {}
- data CodeActionParams = CodeActionParams {}
- type CodeActionRequest = RequestMessage ClientMethod CodeActionParams (List Command)
- type CodeActionResponse = ResponseMessage (List Command)
- data CodeLensParams = CodeLensParams {}
- data CodeLens = CodeLens {}
- type CodeLensRequest = RequestMessage ClientMethod CodeLensParams (List CodeLens)
- type CodeLensResponse = ResponseMessage (List CodeLens)
- data CodeLensRegistrationOptions = CodeLensRegistrationOptions {}
- type CodeLensResolveRequest = RequestMessage ClientMethod CodeLens (List CodeLens)
- type CodeLensResolveResponse = ResponseMessage (List CodeLens)
- data DocumentLinkParams = DocumentLinkParams {}
- data DocumentLink = DocumentLink {}
- class HasTarget s a | s -> a where
- type DocumentLinkRequest = RequestMessage ClientMethod DocumentLinkParams (List DocumentLink)
- type DocumentLinkResponse = ResponseMessage (List DocumentLink)
- type DocumentLinkResolveRequest = RequestMessage ClientMethod DocumentLink DocumentLink
- type DocumentLinkResolveResponse = ResponseMessage DocumentLink
- data FormattingOptions = FormattingOptions {
- _tabSize :: Int
- _insertSpaces :: Bool
- class HasInsertSpaces s a | s -> a where
- class HasTabSize s a | s -> a where
- data DocumentFormattingParams = DocumentFormattingParams {}
- class HasOptions s a | s -> a where
- type DocumentFormattingRequest = RequestMessage ClientMethod DocumentFormattingParams (List TextEdit)
- type DocumentFormattingResponse = ResponseMessage (List TextEdit)
- data DocumentRangeFormattingParams = DocumentRangeFormattingParams {}
- type DocumentRangeFormattingRequest = RequestMessage ClientMethod DocumentRangeFormattingParams (List TextEdit)
- type DocumentRangeFormattingResponse = ResponseMessage (List TextEdit)
- data DocumentOnTypeFormattingParams = DocumentOnTypeFormattingParams {}
- class HasCh s a | s -> a where
- type DocumentOnTypeFormattingRequest = RequestMessage ClientMethod DocumentOnTypeFormattingParams (List TextEdit)
- type DocumentOnTypeFormattingResponse = ResponseMessage (List TextEdit)
- data DocumentOnTypeFormattingRegistrationOptions = DocumentOnTypeFormattingRegistrationOptions {}
- data RenameParams = RenameParams {}
- class HasNewName s a | s -> a where
- type RenameRequest = RequestMessage ClientMethod RenameParams WorkspaceEdit
- type RenameResponse = ResponseMessage WorkspaceEdit
- data ExecuteCommandParams = ExecuteCommandParams {}
- type ExecuteCommandRequest = RequestMessage ClientMethod ExecuteCommandParams Value
- type ExecuteCommandResponse = ResponseMessage Value
- data ExecuteCommandRegistrationOptions = ExecuteCommandRegistrationOptions {}
- data ApplyWorkspaceEditParams = ApplyWorkspaceEditParams {}
- class HasEdit s a | s -> a where
- data ApplyWorkspaceEditResponseBody = ApplyWorkspaceEditResponseBody {}
- class HasApplied s a | s -> a where
- type ApplyWorkspaceEditRequest = RequestMessage ServerMethod ApplyWorkspaceEditParams ApplyWorkspaceEditResponseBody
- type ApplyWorkspaceEditResponse = ResponseMessage ApplyWorkspaceEditResponseBody
- data TraceParams = TraceParams {}
- data TraceNotification = TraceNotification {}
Documentation
This data type is used to host a FromJSON instance for the encoding used by elisp, where an empty list shows up as "null"
List [a] |
filePathToUri :: FilePath -> Uri Source #
Id used for a request, Can be either a String or an Int
Id used for a response, Can be either a String or an Int, or Null. If a request doesn't provide a result value the receiver of a request still needs to return a response message to conform to the JSON RPC specification. The result property of the ResponseMessage should be set to null in this case to signal a successful request.
responseId :: LspId -> LspIdRsp Source #
data ClientMethod Source #
data ServerMethod Source #
data RequestMessage m req resp Source #
(Eq req, Eq m) => Eq (RequestMessage m req resp) Source # | |
(Read req, Read m) => Read (RequestMessage m req resp) Source # | |
(Show req, Show m) => Show (RequestMessage m req resp) Source # | |
(ToJSON m, ToJSON req, ToJSON resp) => ToJSON (RequestMessage m req resp) Source # | |
(FromJSON m, FromJSON req, FromJSON resp) => FromJSON (RequestMessage m req resp) Source # | |
HasParams (RequestMessage m req resp) req Source # | |
HasMethod (RequestMessage m req resp) m Source # | |
HasJsonrpc (RequestMessage m req resp) Text Source # | |
HasId (RequestMessage m req resp) LspId Source # | |
class HasId s a | s -> a where Source #
HasId CancelParams LspId Source # | |
HasId Registration Text Source # | |
HasId Unregistration Text Source # | |
HasId (ResponseMessage a) LspIdRsp Source # | |
HasId (RequestMessage m req resp) LspId Source # | |
class HasJsonrpc s a | s -> a where Source #
HasJsonrpc (ResponseMessage a) Text Source # | |
HasJsonrpc (NotificationMessage m a) Text Source # | |
HasJsonrpc (RequestMessage m req resp) Text Source # | |
class HasMethod s a | s -> a where Source #
HasMethod Registration ClientMethod Source # | |
HasMethod Unregistration Text Source # | |
HasMethod (NotificationMessage m a) m Source # | |
HasMethod (RequestMessage m req resp) m Source # | |
class HasParams s a | s -> a where Source #
HasParams TraceNotification TraceParams Source # | |
HasParams DidChangeWatchedFilesParams (List FileEvent) Source # | |
HasParams (NotificationMessage m a) a Source # | |
HasParams (RequestMessage m req resp) req Source # | |
ParseError | |
InvalidRequest | |
MethodNotFound | |
InvalidParams | |
InternalError | Note: server error codes are reserved from -32099 to -32000 |
data ResponseError Source #
class HasMessage s a | s -> a where Source #
data ResponseMessage a Source #
Eq a => Eq (ResponseMessage a) Source # | |
Read a => Read (ResponseMessage a) Source # | |
Show a => Show (ResponseMessage a) Source # | |
ToJSON a => ToJSON (ResponseMessage a) Source # | |
FromJSON a => FromJSON (ResponseMessage a) Source # | |
HasJsonrpc (ResponseMessage a) Text Source # | |
HasId (ResponseMessage a) LspIdRsp Source # | |
HasResult (ResponseMessage a) (Maybe a) Source # | |
HasError (ResponseMessage a) (Maybe ResponseError) Source # | |
type ErrorResponse = ResponseMessage () Source #
data NotificationMessage m a Source #
(Eq a, Eq m) => Eq (NotificationMessage m a) Source # | |
(Read a, Read m) => Read (NotificationMessage m a) Source # | |
(Show a, Show m) => Show (NotificationMessage m a) Source # | |
(ToJSON m, ToJSON a) => ToJSON (NotificationMessage m a) Source # | |
(FromJSON m, FromJSON a) => FromJSON (NotificationMessage m a) Source # | |
HasParams (NotificationMessage m a) a Source # | |
HasMethod (NotificationMessage m a) m Source # | |
HasJsonrpc (NotificationMessage m a) Text Source # | |
Position | |
|
class HasCharacter s a | s -> a where Source #
class HasRange s a | s -> a where Source #
data DiagnosticSeverity Source #
type DiagnosticSource = Text Source #
data Diagnostic Source #
class HasSeverity s a | s -> a where Source #
class HasArguments s a | s -> a where Source #
class HasCommand s a | s -> a where Source #
class HasNewText s a | s -> a where Source #
type TextDocumentVersion = Int Source #
data VersionedTextDocumentIdentifier Source #
class HasVersion s a | s -> a where Source #
data TextDocumentEdit Source #
class HasTextDocument s a | s -> a where Source #
textDocument :: Lens' s a Source #
data WorkspaceEdit Source #
class HasChanges s a | s -> a where Source #
class HasDocumentChanges s a | s -> a where Source #
documentChanges :: Lens' s a Source #
data TextDocumentIdentifier Source #
data TextDocumentItem Source #
class HasLanguageId s a | s -> a where Source #
languageId :: Lens' s a Source #
data TextDocumentPositionParams Source #
class HasPosition s a | s -> a where Source #
data DocumentFilter Source #
class HasLanguage s a | s -> a where Source #
class HasPattern s a | s -> a where Source #
type DocumentSelector = List DocumentFilter Source #
data InitializeParams Source #
InitializeParams | |
|
class HasCapabilities s a | s -> a where Source #
capabilities :: Lens' s a Source #
class HasInitializationOptions s a | s -> a where Source #
initializationOptions :: Lens' s a Source #
class HasProcessId s a | s -> a where Source #
class HasRootPath s a | s -> a where Source #
class HasRootUri s a | s -> a where Source #
data InitializeError Source #
Eq InitializeError Source # | |
Read InitializeError Source # | |
Show InitializeError Source # | |
ToJSON InitializeError Source # | |
FromJSON InitializeError Source # | |
HasRetry InitializeError Bool Source # | Note: Omitting this parameter from the capabilities is effectively a fourth state, where DidSave events are generated without sending document contents. |
class HasRetry s a | s -> a where Source #
HasRetry InitializeError Bool Source # | Note: Omitting this parameter from the capabilities is effectively a fourth state, where DidSave events are generated without sending document contents. |
data TextDocumentSyncKind Source #
data CompletionOptions Source #
class HasResolveProvider s a | s -> a where Source #
resolveProvider :: Lens' s a Source #
class HasTriggerCharacters s a | s -> a where Source #
triggerCharacters :: Lens' s a Source #
data SignatureHelpOptions Source #
data CodeLensOptions Source #
data DocumentOnTypeFormattingOptions Source #
class HasFirstTriggerCharacter s a | s -> a where Source #
firstTriggerCharacter :: Lens' s a Source #
class HasMoreTriggerCharacter s a | s -> a where Source #
moreTriggerCharacter :: Lens' s a Source #
data DocumentLinkOptions Source #
DocumentLinkOptions | |
|
data ExecuteCommandOptions Source #
class HasCommands s a | s -> a where Source #
data SaveOptions Source #
SaveOptions | |
|
class HasIncludeText s a | s -> a where Source #
includeText :: Lens' s a Source #
data TextDocumentSyncOptions Source #
TextDocumentSyncOptions | |
|
class HasOpenClose s a | s -> a where Source #
class HasWillSave s a | s -> a where Source #
class HasWillSaveWaitUntil s a | s -> a where Source #
willSaveWaitUntil :: Lens' s a Source #
data InitializeResponseCapabilitiesInner Source #
class HasCodeActionProvider s a | s -> a where Source #
codeActionProvider :: Lens' s a Source #
class HasCodeLensProvider s a | s -> a where Source #
codeLensProvider :: Lens' s a Source #
class HasCompletionProvider s a | s -> a where Source #
completionProvider :: Lens' s a Source #
class HasDefinitionProvider s a | s -> a where Source #
definitionProvider :: Lens' s a Source #
class HasDocumentFormattingProvider s a | s -> a where Source #
documentFormattingProvider :: Lens' s a Source #
class HasDocumentHighlightProvider s a | s -> a where Source #
documentHighlightProvider :: Lens' s a Source #
class HasDocumentLinkProvider s a | s -> a where Source #
documentLinkProvider :: Lens' s a Source #
class HasDocumentOnTypeFormattingProvider s a | s -> a where Source #
class HasDocumentRangeFormattingProvider s a | s -> a where Source #
class HasDocumentSymbolProvider s a | s -> a where Source #
documentSymbolProvider :: Lens' s a Source #
class HasExecuteCommandProvider s a | s -> a where Source #
executeCommandProvider :: Lens' s a Source #
class HasExperimental s a | s -> a where Source #
experimental :: Lens' s a Source #
class HasHoverProvider s a | s -> a where Source #
hoverProvider :: Lens' s a Source #
class HasReferencesProvider s a | s -> a where Source #
referencesProvider :: Lens' s a Source #
class HasRenameProvider s a | s -> a where Source #
renameProvider :: Lens' s a Source #
class HasSignatureHelpProvider s a | s -> a where Source #
signatureHelpProvider :: Lens' s a Source #
class HasTextDocumentSync s a | s -> a where Source #
textDocumentSync :: Lens' s a Source #
class HasWorkspaceSymbolProvider s a | s -> a where Source #
workspaceSymbolProvider :: Lens' s a Source #
data InitializeResponseCapabilities Source #
Information about the capabilities of a language server
type InitializeRequest = RequestMessage ClientMethod InitializeParams InitializeResponseCapabilities Source #
data InitializedParams Source #
type ShutdownRequest = RequestMessage ClientMethod (Maybe Value) Text Source #
type ShutdownResponse = ResponseMessage Text Source #
data ExitParams Source #
Notification from the server to actually exit now, after shutdown acked
data MessageType Source #
data ShowMessageParams Source #
data MessageActionItem Source #
data ShowMessageRequestParams Source #
ShowMessageRequestParams | |
|
class HasActions s a | s -> a where Source #
data LogMessageParams Source #
data Registration Source #
Registration | |
|
class HasRegisterOptions s a | s -> a where Source #
registerOptions :: Lens' s a Source #
data RegistrationParams Source #
class HasRegistrations s a | s -> a where Source #
registrations :: Lens' s a Source #
type RegisterCapabilityRequest = RequestMessage ServerMethod RegistrationParams () Source #
Note: originates at the server
data TextDocumentRegistrationOptions Source #
class HasDocumentSelector s a | s -> a where Source #
documentSelector :: Lens' s a Source #
data UnregistrationParams Source #
class HasUnregistrations s a | s -> a where Source #
unregistrations :: Lens' s a Source #
class HasSettings s a | s -> a where Source #
type DidChangeConfigurationNotification = NotificationMessage ClientMethod DidChangeConfigurationParams Source #
type DidOpenTextDocumentNotification = NotificationMessage ClientMethod DidOpenTextDocumentParams Source #
data TextDocumentContentChangeEvent Source #
class HasRangeLength s a | s -> a where Source #
rangeLength :: Lens' s a Source #
data DidChangeTextDocumentParams Source #
class HasContentChanges s a | s -> a where Source #
contentChanges :: Lens' s a Source #
type DidChangeTextDocumentNotification = NotificationMessage ClientMethod DidChangeTextDocumentParams Source #
data TextDocumentChangeRegistrationOptions Source #
class HasSyncKind s a | s -> a where Source #
data TextDocumentSaveReason Source #
SaveManual | Manually triggered, e.g. by the user pressing save, by starting debugging, or by an API call. |
SaveAfterDelay | Automatic after a delay |
SaveFocusOut | When the editor lost focus |
data WillSaveTextDocumentParams Source #
type WillSaveTextDocumentNotification = NotificationMessage ClientMethod WillSaveTextDocumentParams Source #
type WillSaveWaitUntilTextDocumentRequest = RequestMessage ClientMethod WillSaveTextDocumentParams (List TextEdit) Source #
type DidSaveTextDocumentNotification = NotificationMessage ClientMethod DidSaveTextDocumentParams Source #
type DidCloseTextDocumentNotification = NotificationMessage ClientMethod DidCloseTextDocumentParams Source #
data FileChangeType Source #
FileEvent | |
|
type DidChangeWatchedFilesNotification = NotificationMessage ClientMethod DidChangeWatchedFilesParams Source #
data PublishDiagnosticsParams Source #
class HasDiagnostics s a | s -> a where Source #
diagnostics :: Lens' s a Source #
type PublishDiagnosticsNotification = NotificationMessage ServerMethod PublishDiagnosticsParams Source #
data InsertTextFormat Source #
PlainText | The primary text to be inserted is treated as a plain string. |
Snippet | The primary text to be inserted is treated as a snippet. A snippet can define tab stops and placeholders with `$1`, `$2` and `${3:foo}`. `$0` defines the final tab stop, it defaults to the end of the snippet. Placeholders with equal identifiers are linked, that is typing in one will update others too. See also: https://github.com/Microsoft/vscode/blob/master/src/vs/editor/contrib/snippet/common/snippet.md |
data CompletionItemKind Source #
data CompletionItem Source #
CompletionItem | |
|
class HasAdditionalTextEdits s a | s -> a where Source #
additionalTextEdits :: Lens' s a Source #
class HasDocumentation s a | s -> a where Source #
documentation :: Lens' s a Source #
class HasFilterText s a | s -> a where Source #
filterText :: Lens' s a Source #
class HasInsertText s a | s -> a where Source #
insertText :: Lens' s a Source #
class HasInsertTextFormat s a | s -> a where Source #
insertTextFormat :: Lens' s a Source #
class HasSortText s a | s -> a where Source #
class HasTextEdit s a | s -> a where Source #
data CompletionListType Source #
class HasIsIncomplete s a | s -> a where Source #
isIncomplete :: Lens' s a Source #
type CompletionRequest = RequestMessage ClientMethod TextDocumentPositionParams CompletionResponseResult Source #
data CompletionRegistrationOptions Source #
type CompletionItemResolveRequest = RequestMessage ClientMethod CompletionItem CompletionItem Source #
data MarkedString Source #
class HasContents s a | s -> a where Source #
type HoverResponse = ResponseMessage Hover Source #
data ParameterInformation Source #
data SignatureInformation Source #
SignatureInformation | |
|
class HasParameters s a | s -> a where Source #
parameters :: Lens' s a Source #
data SignatureHelp Source #
SignatureHelp | |
|
class HasActiveParameter s a | s -> a where Source #
activeParameter :: Lens' s a Source #
class HasActiveSignature s a | s -> a where Source #
activeSignature :: Lens' s a Source #
class HasSignatures s a | s -> a where Source #
signatures :: Lens' s a Source #
type SignatureHelpRequest = RequestMessage ClientMethod TextDocumentPositionParams SignatureHelp Source #
data SignatureHelpRegistrationOptions Source #
type DefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams DefinitionResponseParams Source #
data ReferenceContext Source #
class HasIncludeDeclaration s a | s -> a where Source #
includeDeclaration :: Lens' s a Source #
data ReferenceParams Source #
class HasContext s a | s -> a where Source #
type ReferencesResponse = ResponseMessage (List Location) Source #
data DocumentHighlightKind Source #
data DocumentHighlight Source #
type DocumentHighlightRequest = RequestMessage ClientMethod TextDocumentPositionParams (List DocumentHighlight) Source #
data DocumentSymbolParams Source #
data SymbolKind Source #
data SymbolInformation Source #
SymbolInformation | |
|
class HasContainerName s a | s -> a where Source #
containerName :: Lens' s a Source #
class HasLocation s a | s -> a where Source #
type DocumentSymbolRequest = RequestMessage ClientMethod DocumentSymbolParams (List SymbolInformation) Source #
data WorkspaceSymbolParams Source #
type WorkspaceSymbolRequest = RequestMessage ClientMethod WorkspaceSymbolParams (List SymbolInformation) Source #
data CodeActionContext Source #
data CodeActionParams Source #
type CodeActionResponse = ResponseMessage (List Command) Source #
data CodeLensParams Source #
type CodeLensResponse = ResponseMessage (List CodeLens) Source #
data CodeLensRegistrationOptions Source #
data DocumentLinkParams Source #
data DocumentLink Source #
type DocumentLinkRequest = RequestMessage ClientMethod DocumentLinkParams (List DocumentLink) Source #
data FormattingOptions Source #
FormattingOptions | |
|
class HasInsertSpaces s a | s -> a where Source #
insertSpaces :: Lens' s a Source #
class HasTabSize s a | s -> a where Source #
data DocumentFormattingParams Source #
class HasOptions s a | s -> a where Source #
type DocumentFormattingRequest = RequestMessage ClientMethod DocumentFormattingParams (List TextEdit) Source #
data DocumentRangeFormattingParams Source #
type DocumentRangeFormattingRequest = RequestMessage ClientMethod DocumentRangeFormattingParams (List TextEdit) Source #
data DocumentOnTypeFormattingParams Source #
type DocumentOnTypeFormattingRequest = RequestMessage ClientMethod DocumentOnTypeFormattingParams (List TextEdit) Source #
data RenameParams Source #
class HasNewName s a | s -> a where Source #
data ExecuteCommandRegistrationOptions Source #
class HasApplied s a | s -> a where Source #
type ApplyWorkspaceEditRequest = RequestMessage ServerMethod ApplyWorkspaceEditParams ApplyWorkspaceEditResponseBody Source #
Sent from the server to the client
data TraceParams Source #