Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Trace
- data InitializeParams = InitializeParams {}
- data InitializeError = InitializeError {}
- data TextDocumentSyncKind
- data CompletionOptions = CompletionOptions {}
- data SignatureHelpOptions = SignatureHelpOptions {}
- data CodeLensOptions = CodeLensOptions {}
- data DocumentOnTypeFormattingOptions = DocumentOnTypeFormattingOptions {}
- data DocumentLinkOptions = DocumentLinkOptions {}
- data ExecuteCommandOptions = ExecuteCommandOptions {}
- data SaveOptions = SaveOptions {}
- data TextDocumentSyncOptions = TextDocumentSyncOptions {}
- data TDS
- data GotoOptions
- data ColorOptions
- data FoldingRangeOptions
- data WorkspaceFolderChangeNotifications
- data WorkspaceFolderOptions = WorkspaceFolderOptions {}
- data WorkspaceOptions = WorkspaceOptions {}
- data InitializeResponseCapabilitiesInner = InitializeResponseCapabilitiesInner {
- _textDocumentSync :: Maybe TDS
- _hoverProvider :: Maybe Bool
- _completionProvider :: Maybe CompletionOptions
- _signatureHelpProvider :: Maybe SignatureHelpOptions
- _definitionProvider :: Maybe Bool
- _typeDefinitionProvider :: Maybe GotoOptions
- _implementationProvider :: Maybe GotoOptions
- _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
- _colorProvider :: Maybe ColorOptions
- _foldingRangeProvider :: Maybe FoldingRangeOptions
- _executeCommandProvider :: Maybe ExecuteCommandOptions
- _workspace :: Maybe WorkspaceOptions
- _experimental :: Maybe Value
- 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)
- type TelemetryNotification = NotificationMessage ServerMethod Value
- data Registration = Registration {
- _id :: Text
- _method :: ClientMethod
- _registerOptions :: Maybe Value
- data RegistrationParams = RegistrationParams {}
- type RegisterCapabilityRequest = RequestMessage ServerMethod RegistrationParams ()
- type RegisterCapabilityResponse = ResponseMessage ()
- data TextDocumentRegistrationOptions = TextDocumentRegistrationOptions {}
- data Unregistration = Unregistration {}
- data UnregistrationParams = UnregistrationParams {}
- type UnregisterCapabilityRequest = RequestMessage ServerMethod UnregistrationParams ()
- type UnregisterCapabilityResponse = ResponseMessage ()
- data DidChangeConfigurationParams = DidChangeConfigurationParams {}
- type DidChangeConfigurationNotification = NotificationMessage ClientMethod DidChangeConfigurationParams
- data ConfigurationItem = ConfigurationItem {}
- data ConfigurationParams = ConfigurationParams {}
- type ConfigurationRequest = RequestMessage ServerMethod ConfigurationParams (List Value)
- type ConfigurationResponse = ResponseMessage (List Value)
- data DidOpenTextDocumentParams = DidOpenTextDocumentParams {}
- type DidOpenTextDocumentNotification = NotificationMessage ClientMethod DidOpenTextDocumentParams
- data TextDocumentContentChangeEvent = TextDocumentContentChangeEvent {}
- data DidChangeTextDocumentParams = DidChangeTextDocumentParams {}
- type DidChangeTextDocumentNotification = NotificationMessage ClientMethod DidChangeTextDocumentParams
- data TextDocumentChangeRegistrationOptions = TextDocumentChangeRegistrationOptions {}
- data TextDocumentSaveReason
- data WillSaveTextDocumentParams = WillSaveTextDocumentParams {}
- 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
- type PublishDiagnosticsNotification = NotificationMessage ServerMethod PublishDiagnosticsParams
- data LanguageString = LanguageString {}
- data MarkedString
- data HoverContents
- toMarkupContent :: MarkedString -> MarkupContent
- data Hover = Hover {}
- type HoverRequest = RequestMessage ClientMethod TextDocumentPositionParams (Maybe Hover)
- type HoverResponse = ResponseMessage (Maybe Hover)
- data ParameterInformation = ParameterInformation {
- _label :: Text
- _documentation :: Maybe Text
- data SignatureInformation = SignatureInformation {}
- data SignatureHelp = SignatureHelp {}
- type SignatureHelpRequest = RequestMessage ClientMethod TextDocumentPositionParams SignatureHelp
- type SignatureHelpResponse = ResponseMessage SignatureHelp
- data SignatureHelpRegistrationOptions = SignatureHelpRegistrationOptions {}
- data LocationResponseParams
- type DefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams
- type DefinitionResponse = ResponseMessage LocationResponseParams
- type TypeDefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams
- type TypeDefinitionResponse = ResponseMessage LocationResponseParams
- type ImplementationRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams
- type ImplementationResponse = ResponseMessage LocationResponseParams
- data ReferenceContext = ReferenceContext {}
- data ReferenceParams = ReferenceParams {}
- 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 WorkspaceSymbolParams = WorkspaceSymbolParams {}
- type WorkspaceSymbolRequest = RequestMessage ClientMethod WorkspaceSymbolParams (List SymbolInformation)
- type WorkspaceSymbolsResponse = ResponseMessage (List SymbolInformation)
- 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 {}
- 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
- data DocumentFormattingParams = DocumentFormattingParams {}
- 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 {}
- type DocumentOnTypeFormattingRequest = RequestMessage ClientMethod DocumentOnTypeFormattingParams (List TextEdit)
- type DocumentOnTypeFormattingResponse = ResponseMessage (List TextEdit)
- data DocumentOnTypeFormattingRegistrationOptions = DocumentOnTypeFormattingRegistrationOptions {}
- data RenameParams = RenameParams {}
- 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 {}
- data ApplyWorkspaceEditResponseBody = ApplyWorkspaceEditResponseBody {}
- type ApplyWorkspaceEditRequest = RequestMessage ServerMethod ApplyWorkspaceEditParams ApplyWorkspaceEditResponseBody
- type ApplyWorkspaceEditResponse = ResponseMessage ApplyWorkspaceEditResponseBody
- data TraceParams = TraceParams {}
- data TraceNotification = TraceNotification {}
- data CodeActionKind
- data CodeActionContext = CodeActionContext {}
- data CodeActionParams = CodeActionParams {}
- data CodeAction = CodeAction {
- _title :: Text
- _kind :: Maybe CodeActionKind
- _diagnostics :: Maybe (List Diagnostic)
- _edit :: Maybe WorkspaceEdit
- _command :: Maybe Command
- data CAResult
- type CodeActionRequest = RequestMessage ClientMethod CodeActionParams (List CAResult)
- type CodeActionResponse = ResponseMessage (List CAResult)
- data Color = Color {}
- data ColorInformation = ColorInformation {}
- data DocumentColorParams = DocumentColorParams {}
- type DocumentColorRequest = RequestMessage ClientMethod DocumentColorParams (List ColorInformation)
- type DocumentColorResponse = ResponseMessage (List ColorInformation)
- data ColorPresentationParams = ColorPresentationParams {}
- data ColorPresentation = ColorPresentation {}
- type ColorPresentationRequest = RequestMessage ClientMethod ColorPresentationParams (List ColorPresentation)
- type ColorPresentationResponse = ResponseMessage (List ColorPresentation)
- data Command = Command {}
- data CompletionItemKind
- data InsertTextFormat
- data CompletionDoc
- data CompletionItem = CompletionItem {
- _label :: Text
- _kind :: Maybe CompletionItemKind
- _detail :: Maybe Text
- _documentation :: Maybe CompletionDoc
- _deprecated :: Maybe Bool
- _preselect :: Maybe Bool
- _sortText :: Maybe Text
- _filterText :: Maybe Text
- _insertText :: Maybe Text
- _insertTextFormat :: Maybe InsertTextFormat
- _textEdit :: Maybe TextEdit
- _additionalTextEdits :: Maybe (List TextEdit)
- _commitCharacters :: Maybe (List Text)
- _command :: Maybe Command
- _xdata :: Maybe Value
- data CompletionListType = CompletionListType {}
- data CompletionResponseResult
- data CompletionTriggerKind
- data CompletionContext = CompletionContext {}
- data CompletionParams = CompletionParams {}
- type CompletionResponse = ResponseMessage CompletionResponseResult
- type CompletionRequest = RequestMessage ClientMethod CompletionParams CompletionResponseResult
- data CompletionRegistrationOptions = CompletionRegistrationOptions {}
- type CompletionItemResolveRequest = RequestMessage ClientMethod CompletionItem CompletionItem
- type CompletionItemResolveResponse = ResponseMessage CompletionItem
- data DiagnosticSeverity
- data DiagnosticRelatedInformation = DiagnosticRelatedInformation {}
- type DiagnosticSource = Text
- data Diagnostic = Diagnostic {}
- data DocumentFilter = DocumentFilter {}
- type DocumentSelector = List DocumentFilter
- data FoldingRangeParams = FoldingRangeParams {}
- data FoldingRangeKind
- data FoldingRange = FoldingRange {}
- type FoldingRangeRequest = RequestMessage ClientMethod FoldingRangeParams (List FoldingRange)
- type FoldingRangeResponse = ResponseMessage (List FoldingRange)
- newtype List a = List [a]
- data Position = Position {
- _line :: Int
- _character :: Int
- data Range = Range {}
- data Location = Location {}
- data MarkupKind
- data MarkupContent = MarkupContent {
- _kind :: MarkupKind
- _value :: Text
- markedUpContent :: Text -> Text -> MarkupContent
- unmarkedUpContent :: Text -> MarkupContent
- sectionSeparator :: Text
- data LspId
- data LspIdRsp
- responseId :: LspId -> LspIdRsp
- requestId :: LspIdRsp -> LspId
- data ClientMethod
- = Initialize
- | Initialized
- | Shutdown
- | Exit
- | CancelRequest
- | WorkspaceDidChangeWorkspaceFolders
- | WorkspaceDidChangeConfiguration
- | WorkspaceDidChangeWatchedFiles
- | WorkspaceSymbol
- | WorkspaceExecuteCommand
- | WindowProgressCancel
- | TextDocumentDidOpen
- | TextDocumentDidChange
- | TextDocumentWillSave
- | TextDocumentWillSaveWaitUntil
- | TextDocumentDidSave
- | TextDocumentDidClose
- | TextDocumentCompletion
- | CompletionItemResolve
- | TextDocumentHover
- | TextDocumentSignatureHelp
- | TextDocumentDefinition
- | TextDocumentTypeDefinition
- | TextDocumentImplementation
- | TextDocumentReferences
- | TextDocumentDocumentHighlight
- | TextDocumentDocumentSymbol
- | TextDocumentCodeAction
- | TextDocumentCodeLens
- | CodeLensResolve
- | TextDocumentDocumentLink
- | DocumentLinkResolve
- | TextDocumentDocumentColor
- | TextDocumentColorPresentation
- | TextDocumentFormatting
- | TextDocumentRangeFormatting
- | TextDocumentOnTypeFormatting
- | TextDocumentRename
- | TextDocumentFoldingRange
- | Misc Text
- data ServerMethod
- = WindowShowMessage
- | WindowShowMessageRequest
- | WindowLogMessage
- | WindowProgressStart
- | WindowProgressReport
- | WindowProgressDone
- | TelemetryEvent
- | ClientRegisterCapability
- | ClientUnregisterCapability
- | WorkspaceWorkspaceFolders
- | WorkspaceConfiguration
- | WorkspaceApplyEdit
- | TextDocumentPublishDiagnostics
- | CancelRequestServer
- data RequestMessage m req resp = RequestMessage {}
- data ErrorCode
- data ResponseError = ResponseError {}
- data ResponseMessage a = ResponseMessage {}
- type ErrorResponse = ResponseMessage ()
- type BareResponseMessage = ResponseMessage Value
- data NotificationMessage m a = NotificationMessage {}
- data CancelParams = CancelParams {}
- type CancelNotification = NotificationMessage ClientMethod CancelParams
- type CancelNotificationServer = NotificationMessage ServerMethod CancelParams
- data DocumentSymbolParams = DocumentSymbolParams {}
- data SymbolKind
- = SkFile
- | SkModule
- | SkNamespace
- | SkPackage
- | SkClass
- | SkMethod
- | SkProperty
- | SkField
- | SkConstructor
- | SkEnum
- | SkInterface
- | SkFunction
- | SkVariable
- | SkConstant
- | SkString
- | SkNumber
- | SkBoolean
- | SkArray
- | SkObject
- | SkKey
- | SkNull
- | SkEnumMember
- | SkStruct
- | SkEvent
- | SkOperator
- | SkTypeParameter
- | SkUnknown Scientific
- data DocumentSymbol = DocumentSymbol {
- _name :: Text
- _detail :: Maybe Text
- _kind :: SymbolKind
- _deprecated :: Maybe Bool
- _range :: Range
- _selectionRange :: Range
- _children :: Maybe (List DocumentSymbol)
- data SymbolInformation = SymbolInformation {
- _name :: Text
- _kind :: SymbolKind
- _deprecated :: Maybe Bool
- _location :: Location
- _containerName :: Maybe Text
- data DSResult
- type DocumentSymbolRequest = RequestMessage ClientMethod DocumentSymbolParams DSResult
- type DocumentSymbolsResponse = ResponseMessage DSResult
- data TextDocumentIdentifier = TextDocumentIdentifier {}
- data TextDocumentItem = TextDocumentItem {}
- data TextDocumentPositionParams = TextDocumentPositionParams {}
- newtype Uri = Uri {}
- fileScheme :: String
- windowsOS :: String
- type SystemOS = String
- uriToFilePath :: Uri -> Maybe FilePath
- platformAwareUriToFilePath :: String -> Uri -> Maybe FilePath
- platformAdjustFromUriPath :: SystemOS -> String -> FilePath
- filePathToUri :: FilePath -> Uri
- platformAwareFilePathToUri :: SystemOS -> FilePath -> Uri
- platformAdjustToUriPath :: SystemOS -> FilePath -> String
- data MessageType
- data ShowMessageParams = ShowMessageParams {
- _xtype :: MessageType
- _message :: Text
- type ShowMessageNotification = NotificationMessage ServerMethod ShowMessageParams
- data MessageActionItem = MessageActionItem {}
- data ShowMessageRequestParams = ShowMessageRequestParams {
- _xtype :: MessageType
- _message :: Text
- _actions :: Maybe [MessageActionItem]
- type ShowMessageRequest = RequestMessage ServerMethod ShowMessageRequestParams Text
- type ShowMessageResponse = ResponseMessage Text
- data LogMessageParams = LogMessageParams {
- _xtype :: MessageType
- _message :: Text
- type LogMessageNotification = NotificationMessage ServerMethod LogMessageParams
- data ProgressStartParams = ProgressStartParams {}
- type ProgressStartNotification = NotificationMessage ServerMethod ProgressStartParams
- data ProgressReportParams = ProgressReportParams {}
- type ProgressReportNotification = NotificationMessage ServerMethod ProgressReportParams
- data ProgressDoneParams = ProgressDoneParams {}
- type ProgressDoneNotification = NotificationMessage ServerMethod ProgressDoneParams
- data ProgressCancelParams = ProgressCancelParams {}
- type ProgressCancelNotification = NotificationMessage ClientMethod ProgressCancelParams
- data TextEdit = TextEdit {}
- type TextDocumentVersion = Maybe Int
- data VersionedTextDocumentIdentifier = VersionedTextDocumentIdentifier {}
- data TextDocumentEdit = TextDocumentEdit {}
- type WorkspaceEditMap = HashMap Uri (List TextEdit)
- data WorkspaceEdit = WorkspaceEdit {}
- applyTextEdit :: TextEdit -> Text -> Text
- editTextEdit :: TextEdit -> TextEdit -> TextEdit
- data WorkspaceFolder = WorkspaceFolder {}
- type WorkspaceFoldersRequest = RequestMessage ServerMethod () (Maybe (List WorkspaceFolder))
- type WorkspaceFoldersResponse = ResponseMessage (Maybe (List WorkspaceFolder))
- data WorkspaceFoldersChangeEvent = WorkspaceFoldersChangeEvent {}
- data DidChangeWorkspaceFoldersParams = DidChangeWorkspaceFoldersParams {}
- type DidChangeWorkspaceFoldersNotification = NotificationMessage ClientMethod DidChangeWorkspaceFoldersParams
Documentation
data InitializeParams Source #
InitializeParams | |
|
Instances
data InitializeError Source #
Instances
data TextDocumentSyncKind Source #
Instances
data CompletionOptions Source #
Instances
data SignatureHelpOptions Source #
Instances
data CodeLensOptions Source #
Instances
data DocumentOnTypeFormattingOptions Source #
Instances
data DocumentLinkOptions Source #
DocumentLinkOptions | |
|
Instances
data ExecuteCommandOptions Source #
Instances
data SaveOptions Source #
SaveOptions | |
|
Instances
data TextDocumentSyncOptions Source #
TextDocumentSyncOptions | |
|
Instances
Wrapper for TextDocumentSyncKind fallback.
data GotoOptions Source #
GotoOptionsStatic Bool | |
GotoOptionsDynamic | |
|
Instances
data ColorOptions Source #
ColorOptionsStatic Bool | |
ColorOptionsDynamic | |
ColorOptionsDynamicDocument | |
|
Instances
data FoldingRangeOptions Source #
FoldingRangeOptionsStatic Bool | |
FoldingRangeOptionsDynamic | |
FoldingRangeOptionsDynamicDocument | |
|
Instances
data WorkspaceFolderChangeNotifications Source #
Instances
data WorkspaceFolderOptions Source #
WorkspaceFolderOptions | |
|
Instances
data WorkspaceOptions Source #
WorkspaceOptions | |
|
Instances
data InitializeResponseCapabilitiesInner Source #
InitializeResponseCapabilitiesInner | |
|
Instances
data InitializeResponseCapabilities Source #
Information about the capabilities of a language server
Instances
type InitializeRequest = RequestMessage ClientMethod InitializeParams InitializeResponseCapabilities Source #
data InitializedParams Source #
Instances
Eq InitializedParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON (==) :: InitializedParams -> InitializedParams -> Bool # (/=) :: InitializedParams -> InitializedParams -> Bool # | |
Read InitializedParams Source # | |
Show InitializedParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON showsPrec :: Int -> InitializedParams -> ShowS # show :: InitializedParams -> String # showList :: [InitializedParams] -> ShowS # | |
ToJSON InitializedParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON toJSON :: InitializedParams -> Value # toEncoding :: InitializedParams -> Encoding # toJSONList :: [InitializedParams] -> Value # toEncodingList :: [InitializedParams] -> Encoding # | |
FromJSON InitializedParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON parseJSON :: Value -> Parser InitializedParams # parseJSONList :: Value -> Parser [InitializedParams] # |
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
Instances
Eq ExitParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON (==) :: ExitParams -> ExitParams -> Bool # (/=) :: ExitParams -> ExitParams -> Bool # | |
Read ExitParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON readsPrec :: Int -> ReadS ExitParams # readList :: ReadS [ExitParams] # readPrec :: ReadPrec ExitParams # readListPrec :: ReadPrec [ExitParams] # | |
Show ExitParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON showsPrec :: Int -> ExitParams -> ShowS # show :: ExitParams -> String # showList :: [ExitParams] -> ShowS # | |
ToJSON ExitParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON toJSON :: ExitParams -> Value # toEncoding :: ExitParams -> Encoding # toJSONList :: [ExitParams] -> Value # toEncodingList :: [ExitParams] -> Encoding # | |
FromJSON ExitParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON parseJSON :: Value -> Parser ExitParams # parseJSONList :: Value -> Parser [ExitParams] # |
data Registration Source #
Registration | |
|
Instances
data RegistrationParams Source #
Instances
type RegisterCapabilityRequest = RequestMessage ServerMethod RegistrationParams () Source #
Note: originates at the server
type RegisterCapabilityResponse = ResponseMessage () Source #
data TextDocumentRegistrationOptions Source #
Instances
data Unregistration Source #
Instances
data UnregistrationParams Source #
Instances
type UnregisterCapabilityResponse = ResponseMessage () Source #
data DidChangeConfigurationParams Source #
Instances
type DidChangeConfigurationNotification = NotificationMessage ClientMethod DidChangeConfigurationParams Source #
data ConfigurationItem Source #
Instances
data ConfigurationParams Source #
Instances
type ConfigurationResponse = ResponseMessage (List Value) Source #
data DidOpenTextDocumentParams Source #
Instances
type DidOpenTextDocumentNotification = NotificationMessage ClientMethod DidOpenTextDocumentParams Source #
data TextDocumentContentChangeEvent Source #
Instances
data DidChangeTextDocumentParams Source #
Instances
type DidChangeTextDocumentNotification = NotificationMessage ClientMethod DidChangeTextDocumentParams Source #
data TextDocumentChangeRegistrationOptions Source #
Instances
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 |
Instances
data WillSaveTextDocumentParams Source #
Instances
type WillSaveTextDocumentNotification = NotificationMessage ClientMethod WillSaveTextDocumentParams Source #
type WillSaveWaitUntilTextDocumentRequest = RequestMessage ClientMethod WillSaveTextDocumentParams (List TextEdit) Source #
data DidSaveTextDocumentParams Source #
Instances
type DidSaveTextDocumentNotification = NotificationMessage ClientMethod DidSaveTextDocumentParams Source #
data DidCloseTextDocumentParams Source #
Instances
type DidCloseTextDocumentNotification = NotificationMessage ClientMethod DidCloseTextDocumentParams Source #
data FileChangeType Source #
Instances
FileEvent | |
|
Instances
data DidChangeWatchedFilesParams Source #
Instances
type DidChangeWatchedFilesNotification = NotificationMessage ClientMethod DidChangeWatchedFilesParams Source #
data PublishDiagnosticsParams Source #
Instances
type PublishDiagnosticsNotification = NotificationMessage ServerMethod PublishDiagnosticsParams Source #
data LanguageString Source #
Instances
data MarkedString Source #
Deprecated: Use MarkupContent instead, since 3.3.0 (11242017)
PlainString Text | Deprecated: Use MarkupContent instead, since 3.3.0 (11242017) |
CodeString LanguageString | Deprecated: Use MarkupContent instead, since 3.3.0 (11242017) |
Instances
Eq MarkedString Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON (==) :: MarkedString -> MarkedString -> Bool # (/=) :: MarkedString -> MarkedString -> Bool # | |
Read MarkedString Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON readsPrec :: Int -> ReadS MarkedString # readList :: ReadS [MarkedString] # | |
Show MarkedString Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON showsPrec :: Int -> MarkedString -> ShowS # show :: MarkedString -> String # showList :: [MarkedString] -> ShowS # | |
ToJSON MarkedString Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON toJSON :: MarkedString -> Value # toEncoding :: MarkedString -> Encoding # toJSONList :: [MarkedString] -> Value # toEncodingList :: [MarkedString] -> Encoding # | |
FromJSON MarkedString Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON parseJSON :: Value -> Parser MarkedString # parseJSONList :: Value -> Parser [MarkedString] # |
data HoverContents Source #
Instances
type HoverResponse = ResponseMessage (Maybe Hover) Source #
data ParameterInformation Source #
Instances
data SignatureInformation Source #
SignatureInformation | |
|
Instances
data SignatureHelp Source #
SignatureHelp | |
|
Instances
type SignatureHelpRequest = RequestMessage ClientMethod TextDocumentPositionParams SignatureHelp Source #
data SignatureHelpRegistrationOptions Source #
Instances
data LocationResponseParams Source #
Instances
type DefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams Source #
type TypeDefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams Source #
type ImplementationRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams Source #
data ReferenceContext Source #
Instances
data ReferenceParams Source #
Instances
type ReferencesResponse = ResponseMessage (List Location) Source #
data DocumentHighlightKind Source #
Instances
data DocumentHighlight Source #
Instances
type DocumentHighlightRequest = RequestMessage ClientMethod TextDocumentPositionParams (List DocumentHighlight) Source #
data WorkspaceSymbolParams Source #
Instances
type WorkspaceSymbolRequest = RequestMessage ClientMethod WorkspaceSymbolParams (List SymbolInformation) Source #
data CodeLensParams Source #
Instances
type CodeLensResponse = ResponseMessage (List CodeLens) Source #
data CodeLensRegistrationOptions Source #
Instances
data DocumentLinkParams Source #
Instances
Eq DocumentLinkParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON (==) :: DocumentLinkParams -> DocumentLinkParams -> Bool # (/=) :: DocumentLinkParams -> DocumentLinkParams -> Bool # | |
Read DocumentLinkParams Source # | |
Show DocumentLinkParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON showsPrec :: Int -> DocumentLinkParams -> ShowS # show :: DocumentLinkParams -> String # showList :: [DocumentLinkParams] -> ShowS # | |
ToJSON DocumentLinkParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON toJSON :: DocumentLinkParams -> Value # toEncoding :: DocumentLinkParams -> Encoding # toJSONList :: [DocumentLinkParams] -> Value # toEncodingList :: [DocumentLinkParams] -> Encoding # | |
FromJSON DocumentLinkParams Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON parseJSON :: Value -> Parser DocumentLinkParams # parseJSONList :: Value -> Parser [DocumentLinkParams] # | |
HasTextDocument DocumentLinkParams TextDocumentIdentifier Source # | |
data DocumentLink Source #
Instances
type DocumentLinkRequest = RequestMessage ClientMethod DocumentLinkParams (List DocumentLink) Source #
data FormattingOptions Source #
FormattingOptions | |
|
Instances
data DocumentFormattingParams Source #
Instances
type DocumentFormattingRequest = RequestMessage ClientMethod DocumentFormattingParams (List TextEdit) Source #
data DocumentRangeFormattingParams Source #
Instances
type DocumentRangeFormattingRequest = RequestMessage ClientMethod DocumentRangeFormattingParams (List TextEdit) Source #
data DocumentOnTypeFormattingParams Source #
Instances
type DocumentOnTypeFormattingRequest = RequestMessage ClientMethod DocumentOnTypeFormattingParams (List TextEdit) Source #
data DocumentOnTypeFormattingRegistrationOptions Source #
Instances
data RenameParams Source #
Instances
data ExecuteCommandParams Source #
Instances
data ExecuteCommandRegistrationOptions Source #
Instances
data ApplyWorkspaceEditParams Source #
Instances
data ApplyWorkspaceEditResponseBody Source #
Instances
type ApplyWorkspaceEditRequest = RequestMessage ServerMethod ApplyWorkspaceEditParams ApplyWorkspaceEditResponseBody Source #
Sent from the server to the client
data TraceParams Source #
Instances
data TraceNotification Source #
Instances
Eq TraceNotification Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON (==) :: TraceNotification -> TraceNotification -> Bool # (/=) :: TraceNotification -> TraceNotification -> Bool # | |
Read TraceNotification Source # | |
Show TraceNotification Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON showsPrec :: Int -> TraceNotification -> ShowS # show :: TraceNotification -> String # showList :: [TraceNotification] -> ShowS # | |
ToJSON TraceNotification Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON toJSON :: TraceNotification -> Value # toEncoding :: TraceNotification -> Encoding # toJSONList :: [TraceNotification] -> Value # toEncodingList :: [TraceNotification] -> Encoding # | |
FromJSON TraceNotification Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON parseJSON :: Value -> Parser TraceNotification # parseJSONList :: Value -> Parser [TraceNotification] # | |
HasParams TraceNotification TraceParams Source # | |
Defined in Language.Haskell.LSP.Types.Lens |
data CodeActionKind Source #
CodeActionQuickFix | |
CodeActionRefactor | |
CodeActionRefactorExtract | |
CodeActionRefactorInline | |
CodeActionRefactorRewrite | |
CodeActionSource | |
CodeActionSourceOrganizeImports | |
CodeActionUnknown Text |
Instances
data CodeActionContext Source #
Instances
data CodeActionParams Source #
Instances
data CodeAction Source #
CodeAction | A code action represents a change that can be performed in code, e.g. to fix a problem or to refactor code. A CodeAction must set either |
|
Instances
type CodeActionResponse = ResponseMessage (List CAResult) Source #
Represents a color in RGBA space.
Instances
data ColorInformation Source #
Instances
data DocumentColorParams Source #
DocumentColorParams | |
|
Instances
Eq DocumentColorParams Source # | |
Defined in Language.Haskell.LSP.Types.Color (==) :: DocumentColorParams -> DocumentColorParams -> Bool # (/=) :: DocumentColorParams -> DocumentColorParams -> Bool # | |
Read DocumentColorParams Source # | |
Show DocumentColorParams Source # | |
Defined in Language.Haskell.LSP.Types.Color showsPrec :: Int -> DocumentColorParams -> ShowS # show :: DocumentColorParams -> String # showList :: [DocumentColorParams] -> ShowS # | |
ToJSON DocumentColorParams Source # | |
Defined in Language.Haskell.LSP.Types.Color toJSON :: DocumentColorParams -> Value # toEncoding :: DocumentColorParams -> Encoding # toJSONList :: [DocumentColorParams] -> Value # toEncodingList :: [DocumentColorParams] -> Encoding # | |
FromJSON DocumentColorParams Source # | |
Defined in Language.Haskell.LSP.Types.Color parseJSON :: Value -> Parser DocumentColorParams # parseJSONList :: Value -> Parser [DocumentColorParams] # | |
HasTextDocument DocumentColorParams TextDocumentIdentifier Source # | |
type DocumentColorRequest = RequestMessage ClientMethod DocumentColorParams (List ColorInformation) Source #
data ColorPresentationParams Source #
ColorPresentationParams | |
|
Instances
data ColorPresentation Source #
ColorPresentation | |
|
Instances
type ColorPresentationRequest = RequestMessage ClientMethod ColorPresentationParams (List ColorPresentation) Source #
Instances
data CompletionItemKind Source #
Instances
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 |
Instances
Eq InsertTextFormat Source # | |
Defined in Language.Haskell.LSP.Types.Completion (==) :: InsertTextFormat -> InsertTextFormat -> Bool # (/=) :: InsertTextFormat -> InsertTextFormat -> Bool # | |
Read InsertTextFormat Source # | |
Defined in Language.Haskell.LSP.Types.Completion | |
Show InsertTextFormat Source # | |
Defined in Language.Haskell.LSP.Types.Completion showsPrec :: Int -> InsertTextFormat -> ShowS # show :: InsertTextFormat -> String # showList :: [InsertTextFormat] -> ShowS # | |
ToJSON InsertTextFormat Source # | |
Defined in Language.Haskell.LSP.Types.Completion toJSON :: InsertTextFormat -> Value # toEncoding :: InsertTextFormat -> Encoding # toJSONList :: [InsertTextFormat] -> Value # toEncodingList :: [InsertTextFormat] -> Encoding # | |
FromJSON InsertTextFormat Source # | |
Defined in Language.Haskell.LSP.Types.Completion parseJSON :: Value -> Parser InsertTextFormat # parseJSONList :: Value -> Parser [InsertTextFormat] # | |
HasInsertTextFormat CompletionItem (Maybe InsertTextFormat) Source # | |
data CompletionDoc Source #
Instances
data CompletionItem Source #
CompletionItem | |
|
Instances
data CompletionListType Source #
Instances
data CompletionResponseResult Source #
Instances
data CompletionTriggerKind Source #
How a completion was triggered
CtInvoked | Completion was triggered by typing an identifier (24x7 code complete), manual invocation (e.g Ctrl+Space) or via API. |
CtTriggerCharacter | Completion was triggered by a trigger character specified by
the |
CtTriggerForIncompleteCompletions | Completion was re-triggered as the current completion list is incomplete. |
CtUnknown Scientific | An unknown |
Instances
data CompletionContext Source #
CompletionContext | |
|
Instances
data CompletionParams Source #
CompletionParams | |
|
Instances
type CompletionRequest = RequestMessage ClientMethod CompletionParams CompletionResponseResult Source #
data CompletionRegistrationOptions Source #
Instances
type CompletionItemResolveRequest = RequestMessage ClientMethod CompletionItem CompletionItem Source #
data DiagnosticSeverity Source #
Instances
data DiagnosticRelatedInformation Source #
Instances
type DiagnosticSource = Text Source #
data Diagnostic Source #
Instances
data DocumentFilter Source #
Instances
type DocumentSelector = List DocumentFilter Source #
data FoldingRangeParams Source #
FoldingRangeParams | |
|
Instances
Eq FoldingRangeParams Source # | |
Defined in Language.Haskell.LSP.Types.FoldingRange (==) :: FoldingRangeParams -> FoldingRangeParams -> Bool # (/=) :: FoldingRangeParams -> FoldingRangeParams -> Bool # | |
Read FoldingRangeParams Source # | |
Show FoldingRangeParams Source # | |
Defined in Language.Haskell.LSP.Types.FoldingRange showsPrec :: Int -> FoldingRangeParams -> ShowS # show :: FoldingRangeParams -> String # showList :: [FoldingRangeParams] -> ShowS # | |
ToJSON FoldingRangeParams Source # | |
Defined in Language.Haskell.LSP.Types.FoldingRange toJSON :: FoldingRangeParams -> Value # toEncoding :: FoldingRangeParams -> Encoding # toJSONList :: [FoldingRangeParams] -> Value # toEncodingList :: [FoldingRangeParams] -> Encoding # | |
FromJSON FoldingRangeParams Source # | |
Defined in Language.Haskell.LSP.Types.FoldingRange parseJSON :: Value -> Parser FoldingRangeParams # parseJSONList :: Value -> Parser [FoldingRangeParams] # | |
HasTextDocument FoldingRangeParams TextDocumentIdentifier Source # | |
data FoldingRangeKind Source #
Enum of known range kinds
FoldingRangeComment | Folding range for a comment |
FoldingRangeImports | Folding range for a imports or includes |
FoldingRangeRegion | Folding range for a region (e.g. #region) |
FoldingRangeUnknown Text | Folding range that haskell-lsp-types does not yet support |
Instances
data FoldingRange Source #
Represents a folding range.
FoldingRange | |
|
Instances
type FoldingRangeRequest = RequestMessage ClientMethod FoldingRangeParams (List FoldingRange) Source #
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] |
Instances
Position | |
|
Instances
Instances
Instances
data MarkupKind Source #
Describes the content type that a client supports in various
result literals like Hover
, ParameterInfo
or CompletionItem
.
MkPlainText | Plain text is supported as a content format |
MkMarkdown | Markdown is supported as a content format |
Instances
data MarkupContent Source #
A MarkupContent
literal represents a string value which content is interpreted base on its
| kind flag. Currently the protocol supports plaintext
and markdown
as markup kinds.
|
| If the kind is markdown
then the value can contain fenced code blocks like in GitHub issues.
| See https://help.github.com/articles/creating-and-highlighting-code-blocks/#syntax-highlighting
|
| Here is an example how such a string can be constructed using JavaScript / TypeScript:
| ```ts
| let markdown: MarkdownContent = {
| kind: MarkupKind.Markdown,
| value: [
| '# Header',
| 'Some text',
| '``typescript
,
| 'someCode();',
| '```'
| ].join('\n')
| };
| ```
|
| *Please Note* that clients might sanitize the return markdown. A client could decide to
| remove HTML from the markdown to avoid script execution.
MarkupContent | |
|
Instances
markedUpContent :: Text -> Text -> MarkupContent Source #
Create a MarkupContent
containing a quoted language string only.
unmarkedUpContent :: Text -> MarkupContent Source #
Create a MarkupContent
containing unquoted text
sectionSeparator :: Text Source #
Markdown for a section separator in Markdown, being a horizontal line
Id used for a request, Can be either a String or an Int
Instances
Eq LspId Source # | |
Ord LspId Source # | |
Read LspId Source # | |
Show LspId Source # | |
Hashable LspId Source # | |
Defined in Language.Haskell.LSP.Types.Message | |
ToJSON LspId Source # | |
Defined in Language.Haskell.LSP.Types.Message | |
FromJSON LspId Source # | |
HasId CancelParams LspId Source # | |
Defined in Language.Haskell.LSP.Types.Lens | |
HasId (RequestMessage m req resp) LspId Source # | |
Defined in Language.Haskell.LSP.Types.Lens |
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.
Instances
Eq LspIdRsp Source # | |
Read LspIdRsp Source # | |
Show LspIdRsp Source # | |
Hashable LspIdRsp Source # | |
Defined in Language.Haskell.LSP.Types.Message | |
ToJSON LspIdRsp Source # | |
Defined in Language.Haskell.LSP.Types.Message | |
FromJSON LspIdRsp Source # | |
HasId (ResponseMessage a) LspIdRsp Source # | |
Defined in Language.Haskell.LSP.Types.Lens |
responseId :: LspId -> LspIdRsp Source #
Converts an LspId to its LspIdRsp counterpart.
data ClientMethod Source #
Instances
data ServerMethod Source #
Instances
data RequestMessage m req resp Source #
Instances
ParseError | |
InvalidRequest | |
MethodNotFound | |
InvalidParams | |
InternalError | |
ServerErrorStart | |
ServerErrorEnd | |
ServerNotInitialized | |
UnknownErrorCode | |
RequestCancelled | Note: server error codes are reserved from -32099 to -32000 |
data ResponseError Source #
Instances
data ResponseMessage a Source #
Instances
type ErrorResponse = ResponseMessage () Source #
data NotificationMessage m a Source #
Instances
data CancelParams Source #
Instances
Eq CancelParams Source # | |
Defined in Language.Haskell.LSP.Types.Message (==) :: CancelParams -> CancelParams -> Bool # (/=) :: CancelParams -> CancelParams -> Bool # | |
Read CancelParams Source # | |
Defined in Language.Haskell.LSP.Types.Message readsPrec :: Int -> ReadS CancelParams # readList :: ReadS [CancelParams] # | |
Show CancelParams Source # | |
Defined in Language.Haskell.LSP.Types.Message showsPrec :: Int -> CancelParams -> ShowS # show :: CancelParams -> String # showList :: [CancelParams] -> ShowS # | |
ToJSON CancelParams Source # | |
Defined in Language.Haskell.LSP.Types.Message toJSON :: CancelParams -> Value # toEncoding :: CancelParams -> Encoding # toJSONList :: [CancelParams] -> Value # toEncodingList :: [CancelParams] -> Encoding # | |
FromJSON CancelParams Source # | |
Defined in Language.Haskell.LSP.Types.Message parseJSON :: Value -> Parser CancelParams # parseJSONList :: Value -> Parser [CancelParams] # | |
HasId CancelParams LspId Source # | |
Defined in Language.Haskell.LSP.Types.Lens |
data DocumentSymbolParams Source #
Instances
data SymbolKind Source #
Instances
data DocumentSymbol Source #
Represents programming constructs like variables, classes, interfaces etc. that appear in a document. Document symbols can be hierarchical and they have two ranges: one that encloses its definition and one that points to its most interesting range, e.g. the range of an identifier.
DocumentSymbol | |
|
Instances
data SymbolInformation Source #
Represents information about programming constructs like variables, classes, interfaces etc.
SymbolInformation | |
|
Instances
data TextDocumentIdentifier Source #
Instances
data TextDocumentItem Source #
Instances
data TextDocumentPositionParams Source #
Instances
Instances
Eq Uri Source # | |
Ord Uri Source # | |
Read Uri Source # | |
Show Uri Source # | |
Hashable Uri Source # | |
Defined in Language.Haskell.LSP.Types.Uri | |
ToJSON Uri Source # | |
Defined in Language.Haskell.LSP.Types.Uri | |
ToJSONKey Uri Source # | |
Defined in Language.Haskell.LSP.Types.Uri | |
FromJSON Uri Source # | |
FromJSONKey Uri Source # | |
Defined in Language.Haskell.LSP.Types.Uri | |
HasUri Location Uri Source # | |
HasUri TextDocumentIdentifier Uri Source # | |
Defined in Language.Haskell.LSP.Types.Lens | |
HasUri TextDocumentItem Uri Source # | |
Defined in Language.Haskell.LSP.Types.Lens | |
HasUri VersionedTextDocumentIdentifier Uri Source # | |
Defined in Language.Haskell.LSP.Types.Lens | |
HasUri FileEvent Uri Source # | |
HasUri PublishDiagnosticsParams Uri Source # | |
Defined in Language.Haskell.LSP.Types.Lens | |
HasRootUri InitializeParams (Maybe Uri) Source # | |
Defined in Language.Haskell.LSP.Types.Lens | |
HasChanges WorkspaceEdit (Maybe WorkspaceEditMap) Source # | |
Defined in Language.Haskell.LSP.Types.Lens |
fileScheme :: String Source #
filePathToUri :: FilePath -> Uri Source #
data MessageType Source #
Instances
data ShowMessageParams Source #
Instances
data MessageActionItem Source #
Instances
data ShowMessageRequestParams Source #
ShowMessageRequestParams | |
|
Instances
data LogMessageParams Source #
Instances
data ProgressStartParams Source #
Parameters for ProgressStartNotification
.
Since: 0.10.0.0
ProgressStartParams | |
|
Instances
type ProgressStartNotification = NotificationMessage ServerMethod ProgressStartParams Source #
The windowprogressstart notification is sent from the server to the client to ask the client to start progress.
Since: 0.10.0.0
data ProgressReportParams Source #
Parameters for ProgressReportNotification
Since: 0.10.0.0
ProgressReportParams | |
|
Instances
type ProgressReportNotification = NotificationMessage ServerMethod ProgressReportParams Source #
The windowprogressreport notification is sent from the server to the client to report progress for a previously started progress.
Since: 0.10.0.0
data ProgressDoneParams Source #
Parameters for ProgressDoneNotification
.
Since: 0.10.0.0
Instances
type ProgressDoneNotification = NotificationMessage ServerMethod ProgressDoneParams Source #
The windowprogressdone notification is sent from the server to the client to stop a previously started progress.
Since: 0.10.0.0
data ProgressCancelParams Source #
Parameters for ProgressCancelNotification
.
Since: 0.10.0.0
Instances
type ProgressCancelNotification = NotificationMessage ClientMethod ProgressCancelParams Source #
The windowprogresscancel notification is sent from the client to the server to inform the server that the user has pressed the cancel button on the progress UX. A server receiving a cancel request must still close a progress using the done notification.
Since: 0.10.0.0
Instances
type TextDocumentVersion = Maybe Int Source #
data VersionedTextDocumentIdentifier Source #
Instances
data TextDocumentEdit Source #
Instances
data WorkspaceEdit Source #
Instances
editTextEdit :: TextEdit -> TextEdit -> TextEdit Source #
editTextEdit
outer
inner
applies inner
to the text inside outer
.
data WorkspaceFolder Source #
Instances
type WorkspaceFoldersRequest = RequestMessage ServerMethod () (Maybe (List WorkspaceFolder)) Source #
data WorkspaceFoldersChangeEvent Source #
The workspace folder change event.
WorkspaceFoldersChangeEvent | |
|
Instances
data DidChangeWorkspaceFoldersParams Source #
DidChangeWorkspaceFoldersParams | |
|