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 CodeActionOptions
- data DocumentOnTypeFormattingOptions = DocumentOnTypeFormattingOptions {}
- data DocumentLinkOptions = DocumentLinkOptions {}
- data RenameOptions
- 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 CodeActionOptions
- _codeLensProvider :: Maybe CodeLensOptions
- _documentFormattingProvider :: Maybe Bool
- _documentRangeFormattingProvider :: Maybe Bool
- _documentOnTypeFormattingProvider :: Maybe DocumentOnTypeFormattingOptions
- _renameProvider :: Maybe RenameOptions
- _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) (Maybe ())
- type ShutdownResponse = ResponseMessage (Maybe ())
- data ExitParams = ExitParams {
- type ExitNotification = NotificationMessage ClientMethod (Maybe ExitParams)
- type TelemetryNotification = NotificationMessage ServerMethod Value
- type CustomClientNotification = NotificationMessage ClientMethod Value
- type CustomServerNotification = NotificationMessage ServerMethod Value
- type CustomClientRequest = RequestMessage ClientMethod Value Value
- type CustomServerRequest = RequestMessage ServerMethod Value Value
- type CustomResponse = ResponseMessage 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 CodeLens
- type CodeLensResolveResponse = ResponseMessage 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 RangeWithPlaceholder = RangeWithPlaceholder {
- _range :: Range
- _placeholder :: Text
- data RangeOrRangeWithPlaceholder
- type PrepareRenameRequest = RequestMessage ClientMethod TextDocumentPositionParams Range
- type PrepareRenameResponse = ResponseMessage (Maybe RangeOrRangeWithPlaceholder)
- data ExecuteCommandParams = ExecuteCommandParams {
- _command :: Text
- _arguments :: Maybe (List Value)
- _workDoneToken :: Maybe ProgressToken
- 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 {}
- data NumberOrString
- 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
- | WorkDoneProgressCancel
- | 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
- | TextDocumentPrepareRename
- | TextDocumentFoldingRange
- | CustomClientMethod Text
- data ServerMethod
- = WindowShowMessage
- | WindowShowMessageRequest
- | WindowLogMessage
- | WindowWorkDoneProgressCreate
- | Progress
- | TelemetryEvent
- | ClientRegisterCapability
- | ClientUnregisterCapability
- | WorkspaceWorkspaceFolders
- | WorkspaceConfiguration
- | WorkspaceApplyEdit
- | TextDocumentPublishDiagnostics
- | CancelRequestServer
- | CustomServerMethod Text
- 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 ProgressToken
- 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 {}
- newtype NormalizedUri = NormalizedUri Text
- toNormalizedUri :: Uri -> NormalizedUri
- fromNormalizedUri :: NormalizedUri -> Uri
- fileScheme :: String
- windowsOS :: String
- type SystemOS = String
- uriToFilePath :: Uri -> Maybe FilePath
- platformAwareUriToFilePath :: String -> Uri -> Maybe FilePath
- platformAdjustFromUriPath :: SystemOS -> Maybe String -> 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 ProgressParams t = ProgressParams {
- _token :: ProgressToken
- _value :: t
- data WorkDoneProgressBeginParams = WorkDoneProgressBeginParams {}
- type WorkDoneProgressBeginNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressBeginParams)
- data WorkDoneProgressReportParams = WorkDoneProgressReportParams {
- _cancellable :: Maybe Bool
- _message :: Maybe Text
- _percentage :: Maybe Double
- type WorkDoneProgressReportNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressReportParams)
- data WorkDoneProgressEndParams = WorkDoneProgressEndParams {}
- type WorkDoneProgressEndNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressEndParams)
- data WorkDoneProgressCancelParams = WorkDoneProgressCancelParams {}
- type WorkDoneProgressCancelNotification = NotificationMessage ClientMethod WorkDoneProgressCancelParams
- data WorkDoneProgressCreateParams = WorkDoneProgressCreateParams {}
- type WorkDoneProgressCreateRequest = RequestMessage ServerMethod WorkDoneProgressCreateParams ()
- 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 #
CompletionOptions | |
|
Instances
data SignatureHelpOptions Source #
SignatureHelpOptions | |
|
Instances
data CodeLensOptions Source #
Instances
data CodeActionOptions Source #
Instances
Eq CodeActionOptions Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON (==) :: CodeActionOptions -> CodeActionOptions -> Bool # (/=) :: CodeActionOptions -> CodeActionOptions -> Bool # | |
Read CodeActionOptions Source # | |
Show CodeActionOptions Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON showsPrec :: Int -> CodeActionOptions -> ShowS # show :: CodeActionOptions -> String # showList :: [CodeActionOptions] -> ShowS # | |
ToJSON CodeActionOptions Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON toJSON :: CodeActionOptions -> Value # toEncoding :: CodeActionOptions -> Encoding # toJSONList :: [CodeActionOptions] -> Value # toEncodingList :: [CodeActionOptions] -> Encoding # | |
FromJSON CodeActionOptions Source # | |
Defined in Language.Haskell.LSP.Types.DataTypesJSON parseJSON :: Value -> Parser CodeActionOptions # parseJSONList :: Value -> Parser [CodeActionOptions] # | |
HasCodeActionProvider InitializeResponseCapabilitiesInner (Maybe CodeActionOptions) Source # | |
data DocumentOnTypeFormattingOptions Source #
Instances
data DocumentLinkOptions Source #
DocumentLinkOptions | |
|
Instances
data RenameOptions Source #
RenameOptionsStatic Bool | |
RenameOptions | |
|
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) (Maybe ()) Source #
type ShutdownResponse = ResponseMessage (Maybe ()) 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] # |
type CustomResponse = ResponseMessage Value Source #
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 #
ReferenceParams | |
|
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 #
WorkspaceSymbolParams | |
|
Instances
type WorkspaceSymbolRequest = RequestMessage ClientMethod WorkspaceSymbolParams (List SymbolInformation) Source #
data CodeLensParams Source #
CodeLensParams | |
|
Instances
type CodeLensResponse = ResponseMessage (List CodeLens) Source #
data CodeLensRegistrationOptions Source #
Instances
data DocumentLinkParams Source #
DocumentLinkParams | |
|
Instances
data DocumentLink Source #
Instances
type DocumentLinkRequest = RequestMessage ClientMethod DocumentLinkParams (List DocumentLink) Source #
data FormattingOptions Source #
FormattingOptions | |
|
Instances
data DocumentFormattingParams Source #
DocumentFormattingParams | |
|
Instances
type DocumentFormattingRequest = RequestMessage ClientMethod DocumentFormattingParams (List TextEdit) Source #
data DocumentRangeFormattingParams Source #
DocumentRangeFormattingParams | |
|
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 #
RenameParams | |
|
Instances
data RangeWithPlaceholder Source #
Instances
data ExecuteCommandParams Source #
ExecuteCommandParams | |
|
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 #
CodeActionParams | |
|
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
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
data NumberOrString Source #
Instances
type DiagnosticSource = Text Source #
data Diagnostic Source #
Instances
data DocumentFilter Source #
Instances
type DocumentSelector = List DocumentFilter Source #
data FoldingRangeParams Source #
FoldingRangeParams | |
|
Instances
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
Eq Location Source # | |
Ord Location Source # | |
Defined in Language.Haskell.LSP.Types.Location | |
Read Location Source # | |
Show Location Source # | |
Generic Location Source # | |
ToJSON Location Source # | |
Defined in Language.Haskell.LSP.Types.Location | |
FromJSON Location Source # | |
NFData Location Source # | |
Defined in Language.Haskell.LSP.Types.Location | |
HasRange Location Range Source # | |
HasUri Location Uri Source # | |
HasLocation SymbolInformation Location Source # | |
Defined in Language.Haskell.LSP.Types.Lens | |
HasLocation DiagnosticRelatedInformation Location Source # | |
type Rep Location Source # | |
Defined in Language.Haskell.LSP.Types.Location type Rep Location = D1 (MetaData "Location" "Language.Haskell.LSP.Types.Location" "haskell-lsp-types-0.19.0.0-CEbv60D3bPWelIkXQQUwC" False) (C1 (MetaCons "Location" PrefixI True) (S1 (MetaSel (Just "_uri") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Uri) :*: S1 (MetaSel (Just "_range") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Range))) |
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 | |
ContentModified | Note: server error codes are reserved from -32099 to -32000 |
data ResponseError Source #
Instances
data ResponseMessage a Source #
Either result or error must be Just.
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 ProgressToken Source #
A token used to report progress back or return partial results for a specific request. @since 0.17.0.0
Instances
data DocumentSymbolParams Source #
DocumentSymbolParams | |
|
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 #
TextDocumentPositionParams | |
|
Instances
Instances
newtype NormalizedUri Source #
When URIs are supposed to be used as keys, it is important to normalize the percent encoding in the URI since URIs that only differ when it comes to the percent-encoding should be treated as equivalent.
Instances
toNormalizedUri :: Uri -> NormalizedUri Source #
fromNormalizedUri :: NormalizedUri -> Uri Source #
fileScheme :: String Source #
platformAdjustFromUriPath Source #
We pull in the authority because in relative file paths the Uri likes to put everything before the slash into the authority field
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 ProgressParams t Source #
Parameters for a $/progress notification.
ProgressParams | |
|
Instances
data WorkDoneProgressBeginParams Source #
Parameters for WorkDoneProgressBeginNotification
.
Since: 0.10.0.0
WorkDoneProgressBeginParams | |
|
Instances
type WorkDoneProgressBeginNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressBeginParams) Source #
The $/progress begin notification is sent from the server to the client to ask the client to start progress.
Since: 0.10.0.0
data WorkDoneProgressReportParams Source #
Parameters for WorkDoneProgressReportNotification
Since: 0.10.0.0
WorkDoneProgressReportParams | |
|
Instances
type WorkDoneProgressReportNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressReportParams) Source #
The workdone $/progress report notification is sent from the server to the client to report progress for a previously started progress.
Since: 0.10.0.0
data WorkDoneProgressEndParams Source #
Parameters for WorkDoneProgressEndNotification
.
Since: 0.10.0.0
Instances
type WorkDoneProgressEndNotification = NotificationMessage ServerMethod (ProgressParams WorkDoneProgressEndParams) Source #
The $/progress end notification is sent from the server to the client to stop a previously started progress.
Since: 0.10.0.0
data WorkDoneProgressCancelParams Source #
Parameters for WorkDoneProgressCancelNotification
.
Since: 0.10.0.0
WorkDoneProgressCancelParams | |
|
Instances
type WorkDoneProgressCancelNotification = NotificationMessage ClientMethod WorkDoneProgressCancelParams Source #
The windowworkDoneProgresscancel 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
data WorkDoneProgressCreateParams Source #
Instances
type WorkDoneProgressCreateRequest = RequestMessage ServerMethod WorkDoneProgressCreateParams () Source #
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 | |
|