| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.LSP.TH.DataTypesJSON
Synopsis
- data InitializeParams = InitializeParams {}
- data Trace
- data InitializeError = InitializeError {}
- class HasTrace s a | s -> a where
- class HasRootUri s a | s -> a where
- class HasRootPath s a | s -> a where
- class HasProcessId s a | s -> a where
- class HasInitializationOptions s a | s -> a where
- class HasCapabilities s a | s -> a where
- data CompletionOptions = CompletionOptions {}
- data TextDocumentSyncKind
- class HasRetry s a | s -> a where
- data SignatureHelpOptions = SignatureHelpOptions {}
- class HasTriggerCharacters s a | s -> a where
- class HasResolveProvider s a | s -> a where
- data CodeLensOptions = CodeLensOptions {}
- data DocumentOnTypeFormattingOptions = DocumentOnTypeFormattingOptions {}
- data DocumentLinkOptions = DocumentLinkOptions {}
- class HasMoreTriggerCharacter s a | s -> a where
- class HasFirstTriggerCharacter s a | s -> a where
- data ExecuteCommandOptions = ExecuteCommandOptions {}
- data SaveOptions = SaveOptions {}
- class HasCommands s a | s -> a where
- data TextDocumentSyncOptions = TextDocumentSyncOptions {}
- class HasIncludeText s a | s -> a where
- data InitializeResponseCapabilitiesInner = InitializeResponseCapabilitiesInner {
- _textDocumentSync :: Maybe TDS
- _hoverProvider :: Maybe Bool
- _completionProvider :: Maybe CompletionOptions
- _signatureHelpProvider :: Maybe SignatureHelpOptions
- _definitionProvider :: Maybe Bool
- _referencesProvider :: Maybe Bool
- _documentHighlightProvider :: Maybe Bool
- _documentSymbolProvider :: Maybe Bool
- _workspaceSymbolProvider :: Maybe Bool
- _codeActionProvider :: Maybe Bool
- _codeLensProvider :: Maybe CodeLensOptions
- _documentFormattingProvider :: Maybe Bool
- _documentRangeFormattingProvider :: Maybe Bool
- _documentOnTypeFormattingProvider :: Maybe DocumentOnTypeFormattingOptions
- _renameProvider :: Maybe Bool
- _documentLinkProvider :: Maybe DocumentLinkOptions
- _executeCommandProvider :: Maybe ExecuteCommandOptions
- _experimental :: Maybe Value
- data TDS
- class HasWillSaveWaitUntil s a | s -> a where
- class HasWillSave s a | s -> a where
- class HasSave s a | s -> a where
- class HasOpenClose s a | s -> a where
- class HasChange s a | s -> a where
- data InitializeResponseCapabilities = InitializeResponseCapabilities {}
- class HasWorkspaceSymbolProvider s a | s -> a where
- class HasTextDocumentSync s a | s -> a where
- class HasSignatureHelpProvider s a | s -> a where
- class HasRenameProvider s a | s -> a where
- class HasReferencesProvider s a | s -> a where
- class HasHoverProvider s a | s -> a where
- class HasExperimental s a | s -> a where
- class HasExecuteCommandProvider s a | s -> a where
- class HasDocumentSymbolProvider s a | s -> a where
- class HasDocumentRangeFormattingProvider s a | s -> a where
- class HasDocumentOnTypeFormattingProvider s a | s -> a where
- class HasDocumentLinkProvider s a | s -> a where
- class HasDocumentHighlightProvider s a | s -> a where
- class HasDocumentFormattingProvider s a | s -> a where
- class HasDefinitionProvider s a | s -> a where
- class HasCompletionProvider s a | s -> a where
- class HasCodeLensProvider s a | s -> a where
- class HasCodeActionProvider s a | s -> a where
- data ExitParams = ExitParams {
- type ShutdownResponse = ResponseMessage Text
- type ShutdownRequest = RequestMessage ClientMethod (Maybe Value) Text
- type InitializedNotification = NotificationMessage ClientMethod (Maybe InitializedParams)
- data InitializedParams = InitializedParams {
- type InitializeRequest = RequestMessage ClientMethod InitializeParams InitializeResponseCapabilities
- type InitializeResponse = ResponseMessage InitializeResponseCapabilities
- data ShowMessageParams = ShowMessageParams {
- _xtype :: MessageType
- _message :: Text
- data MessageType
- type ExitNotification = NotificationMessage ClientMethod (Maybe ExitParams)
- data MessageActionItem = MessageActionItem {}
- type ShowMessageNotification = NotificationMessage ServerMethod ShowMessageParams
- class HasXtype s a | s -> a where
- class HasMessage s a | s -> a where
- data ShowMessageRequestParams = ShowMessageRequestParams {
- _xtype :: MessageType
- _message :: Text
- _actions :: Maybe [MessageActionItem]
- class HasTitle s a | s -> a where
- data LogMessageParams = LogMessageParams {
- _xtype :: MessageType
- _message :: Text
- type ShowMessageResponse = ResponseMessage Text
- type ShowMessageRequest = RequestMessage ServerMethod ShowMessageRequestParams Text
- class HasActions s a | s -> a where
- data Registration = Registration {
- _id :: Text
- _method :: ClientMethod
- _registerOptions :: Maybe Value
- type TelemetryNotification = NotificationMessage ServerMethod Value
- type LogMessageNotification = NotificationMessage ServerMethod LogMessageParams
- data RegistrationParams = RegistrationParams {}
- class HasRegisterOptions s a | s -> a where
- class HasMethod s a | s -> a where
- class HasId s a | s -> a where
- data TextDocumentRegistrationOptions = TextDocumentRegistrationOptions {}
- type RegisterCapabilityResponse = ResponseMessage ()
- type RegisterCapabilityRequest = RequestMessage ServerMethod RegistrationParams ()
- class HasRegistrations s a | s -> a where
- data Unregistration = Unregistration {}
- class HasDocumentSelector s a | s -> a where
- data UnregistrationParams = UnregistrationParams {}
- data DidChangeConfigurationParams = DidChangeConfigurationParams {}
- type UnregisterCapabilityResponse = ResponseMessage ()
- type UnregisterCapabilityRequest = RequestMessage ServerMethod UnregistrationParams ()
- class HasUnregistrations s a | s -> a where
- data DidOpenTextDocumentParams = DidOpenTextDocumentParams {}
- type DidChangeConfigurationNotification = NotificationMessage ClientMethod DidChangeConfigurationParams
- class HasSettings s a | s -> a where
- data TextDocumentContentChangeEvent = TextDocumentContentChangeEvent {}
- type DidOpenTextDocumentNotification = NotificationMessage ClientMethod DidOpenTextDocumentParams
- class HasTextDocument s a | s -> a where
- data DidChangeTextDocumentParams = DidChangeTextDocumentParams {}
- class HasText s a | s -> a where
- class HasRangeLength s a | s -> a where
- class HasRange s a | s -> a where
- data TextDocumentChangeRegistrationOptions = TextDocumentChangeRegistrationOptions {}
- type DidChangeTextDocumentNotification = NotificationMessage ClientMethod DidChangeTextDocumentParams
- class HasContentChanges s a | s -> a where
- data WillSaveTextDocumentParams = WillSaveTextDocumentParams {}
- data TextDocumentSaveReason
- class HasSyncKind s a | s -> a where
- data DidSaveTextDocumentParams = DidSaveTextDocumentParams {}
- type WillSaveWaitUntilTextDocumentResponse = ResponseMessage (List TextEdit)
- type WillSaveWaitUntilTextDocumentRequest = RequestMessage ClientMethod WillSaveTextDocumentParams (List TextEdit)
- type WillSaveTextDocumentNotification = NotificationMessage ClientMethod WillSaveTextDocumentParams
- class HasReason s a | s -> a where
- data DidCloseTextDocumentParams = DidCloseTextDocumentParams {}
- type DidSaveTextDocumentNotification = NotificationMessage ClientMethod DidSaveTextDocumentParams
- data FileEvent = FileEvent {
- _uri :: Uri
- _xtype :: FileChangeType
- data FileChangeType
- type DidCloseTextDocumentNotification = NotificationMessage ClientMethod DidCloseTextDocumentParams
- data DidChangeWatchedFilesParams = DidChangeWatchedFilesParams {}
- class HasUri s a | s -> a where
- data PublishDiagnosticsParams = PublishDiagnosticsParams {
- _uri :: Uri
- _diagnostics :: List Diagnostic
- type DidChangeWatchedFilesNotification = NotificationMessage ClientMethod DidChangeWatchedFilesParams
- class HasChanges s a | s -> a where
- data LanguageString = LanguageString {}
- type PublishDiagnosticsNotification = NotificationMessage ServerMethod PublishDiagnosticsParams
- class HasDiagnostics s a | s -> a where
- data Hover = Hover {}
- data MarkedString
- class HasValue s a | s -> a where
- class HasLanguage s a | s -> a where
- data ParameterInformation = ParameterInformation {
- _label :: Text
- _documentation :: Maybe Text
- type HoverResponse = ResponseMessage Hover
- type HoverRequest = RequestMessage ClientMethod TextDocumentPositionParams Hover
- class HasContents s a | s -> a where
- data SignatureInformation = SignatureInformation {}
- class HasLabel s a | s -> a where
- class HasDocumentation s a | s -> a where
- data SignatureHelp = SignatureHelp {}
- class HasParameters s a | s -> a where
- data SignatureHelpRegistrationOptions = SignatureHelpRegistrationOptions {}
- type SignatureHelpResponse = ResponseMessage SignatureHelp
- type SignatureHelpRequest = RequestMessage ClientMethod TextDocumentPositionParams SignatureHelp
- class HasSignatures s a | s -> a where
- class HasActiveSignature s a | s -> a where
- class HasActiveParameter s a | s -> a where
- data ReferenceContext = ReferenceContext {}
- type ImplementationResponse = ResponseMessage LocationResponseParams
- type ImplementationRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams
- type DefinitionResponse = ResponseMessage LocationResponseParams
- type DefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams
- data LocationResponseParams
- data ReferenceParams = ReferenceParams {}
- class HasIncludeDeclaration s a | s -> a where
- data DocumentHighlight = DocumentHighlight {}
- data DocumentHighlightKind
- type ReferencesResponse = ResponseMessage (List Location)
- type ReferencesRequest = RequestMessage ClientMethod ReferenceParams (List Location)
- class HasPosition s a | s -> a where
- class HasContext s a | s -> a where
- data WorkspaceSymbolParams = WorkspaceSymbolParams {}
- type DocumentHighlightsResponse = ResponseMessage (List DocumentHighlight)
- type DocumentHighlightRequest = RequestMessage ClientMethod TextDocumentPositionParams (List DocumentHighlight)
- class HasKind s a | s -> a where
- data CodeLensParams = CodeLensParams {}
- type WorkspaceSymbolsResponse = ResponseMessage (List SymbolInformation)
- type WorkspaceSymbolRequest = RequestMessage ClientMethod WorkspaceSymbolParams (List SymbolInformation)
- class HasQuery s a | s -> a where
- data CodeLens = CodeLens {}
- data CodeLensRegistrationOptions = CodeLensRegistrationOptions {}
- type CodeLensResponse = ResponseMessage (List CodeLens)
- type CodeLensRequest = RequestMessage ClientMethod CodeLensParams (List CodeLens)
- class HasXdata s a | s -> a where
- class HasCommand s a | s -> a where
- data DocumentLinkParams = DocumentLinkParams {}
- type CodeLensResolveResponse = ResponseMessage (List CodeLens)
- type CodeLensResolveRequest = RequestMessage ClientMethod CodeLens (List CodeLens)
- data DocumentLink = DocumentLink {}
- data FormattingOptions = FormattingOptions {
- _tabSize :: Int
- _insertSpaces :: Bool
- type DocumentLinkResolveResponse = ResponseMessage DocumentLink
- type DocumentLinkResolveRequest = RequestMessage ClientMethod DocumentLink DocumentLink
- type DocumentLinkResponse = ResponseMessage (List DocumentLink)
- type DocumentLinkRequest = RequestMessage ClientMethod DocumentLinkParams (List DocumentLink)
- class HasTarget s a | s -> a where
- data DocumentFormattingParams = DocumentFormattingParams {}
- class HasTabSize s a | s -> a where
- class HasInsertSpaces s a | s -> a where
- data DocumentRangeFormattingParams = DocumentRangeFormattingParams {}
- type DocumentFormattingResponse = ResponseMessage (List TextEdit)
- type DocumentFormattingRequest = RequestMessage ClientMethod DocumentFormattingParams (List TextEdit)
- class HasOptions s a | s -> a where
- data DocumentOnTypeFormattingParams = DocumentOnTypeFormattingParams {}
- type DocumentRangeFormattingResponse = ResponseMessage (List TextEdit)
- type DocumentRangeFormattingRequest = RequestMessage ClientMethod DocumentRangeFormattingParams (List TextEdit)
- data DocumentOnTypeFormattingRegistrationOptions = DocumentOnTypeFormattingRegistrationOptions {}
- type DocumentOnTypeFormattingResponse = ResponseMessage (List TextEdit)
- type DocumentOnTypeFormattingRequest = RequestMessage ClientMethod DocumentOnTypeFormattingParams (List TextEdit)
- class HasCh s a | s -> a where
- data RenameParams = RenameParams {}
- data ExecuteCommandParams = ExecuteCommandParams {}
- type RenameResponse = ResponseMessage WorkspaceEdit
- type RenameRequest = RequestMessage ClientMethod RenameParams WorkspaceEdit
- class HasNewName s a | s -> a where
- data ExecuteCommandRegistrationOptions = ExecuteCommandRegistrationOptions {}
- type ExecuteCommandResponse = ResponseMessage Value
- type ExecuteCommandRequest = RequestMessage ClientMethod ExecuteCommandParams Value
- class HasArguments s a | s -> a where
- data ApplyWorkspaceEditParams = ApplyWorkspaceEditParams {}
- data ApplyWorkspaceEditResponseBody = ApplyWorkspaceEditResponseBody {}
- class HasEdit s a | s -> a where
- data TraceParams = TraceParams {}
- type ApplyWorkspaceEditResponse = ResponseMessage ApplyWorkspaceEditResponseBody
- type ApplyWorkspaceEditRequest = RequestMessage ServerMethod ApplyWorkspaceEditParams ApplyWorkspaceEditResponseBody
- class HasApplied s a | s -> a where
- data TraceNotification = TraceNotification {}
- class HasParams s a | s -> a where
- class HasLine s a | s -> a where
- class HasCharacter s a | s -> a where
- class HasStart s a | s -> a where
- class HasEnd s a | s -> a where
- class HasTextEdit s a | s -> a where
- class HasSortText s a | s -> a where
- class HasInsertTextFormat s a | s -> a where
- class HasInsertText s a | s -> a where
- class HasFilterText s a | s -> a where
- class HasDetail s a | s -> a where
- class HasAdditionalTextEdits s a | s -> a where
- class HasItems s a | s -> a where
- class HasIsIncomplete s a | s -> a where
- class HasScheme s a | s -> a where
- class HasPattern s a | s -> a where
- class HasNewText s a | s -> a where
- class HasVersion s a | s -> a where
- class HasEdits s a | s -> a where
- class HasDocumentChanges s a | s -> a where
- class HasJsonrpc s a | s -> a where
- class HasCode s a | s -> a where
- class HasResult s a | s -> a where
- class HasError s a | s -> a where
- class HasLanguageId s a | s -> a where
- class HasSource s a | s -> a where
- class HasSeverity s a | s -> a where
- class HasRelatedInformation s a | s -> a where
- class HasLocation s a | s -> a where
- class HasSelectionRange s a | s -> a where
- class HasName s a | s -> a where
- class HasDeprecated s a | s -> a where
- class HasChildren s a | s -> a where
- class HasContainerName s a | s -> a where
- 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 Command = Command {}
- data CompletionItemKind
- data InsertTextFormat
- data CompletionItem = CompletionItem {
- _label :: Text
- _kind :: Maybe CompletionItemKind
- _detail :: Maybe Text
- _documentation :: Maybe Text
- _sortText :: Maybe Text
- _filterText :: Maybe Text
- _insertText :: Maybe Text
- _insertTextFormat :: Maybe InsertTextFormat
- _textEdit :: Maybe TextEdit
- _additionalTextEdits :: Maybe (List TextEdit)
- _command :: Maybe Command
- _xdata :: Maybe Value
- data CompletionListType = CompletionListType {}
- data CompletionResponseResult
- type CompletionResponse = ResponseMessage CompletionResponseResult
- type CompletionRequest = RequestMessage ClientMethod TextDocumentPositionParams CompletionResponseResult
- data CompletionRegistrationOptions = CompletionRegistrationOptions {}
- type CompletionItemResolveRequest = RequestMessage ClientMethod CompletionItem CompletionItem
- type CompletionItemResolveResponse = ResponseMessage CompletionItem
- data DiagnosticSeverity
- data DiagnosticRelatedInformation = DiagnosticRelatedInformation {}
- type DiagnosticSource = Text
- data Diagnostic = Diagnostic {}
- data DocumentFilter = DocumentFilter {}
- type DocumentSelector = List DocumentFilter
- 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
- data LspId
- data LspIdRsp
- responseId :: LspId -> LspIdRsp
- requestId :: LspIdRsp -> LspId
- data ClientMethod
- = Initialize
- | Initialized
- | Shutdown
- | Exit
- | CancelRequest
- | WorkspaceDidChangeConfiguration
- | WorkspaceDidChangeWatchedFiles
- | WorkspaceSymbol
- | WorkspaceExecuteCommand
- | TextDocumentDidOpen
- | TextDocumentDidChange
- | TextDocumentWillSave
- | TextDocumentWillSaveWaitUntil
- | TextDocumentDidSave
- | TextDocumentDidClose
- | TextDocumentCompletion
- | CompletionItemResolve
- | TextDocumentHover
- | TextDocumentSignatureHelp
- | TextDocumentReferences
- | TextDocumentDocumentHighlight
- | TextDocumentDocumentSymbol
- | TextDocumentFormatting
- | TextDocumentRangeFormatting
- | TextDocumentOnTypeFormatting
- | TextDocumentDefinition
- | TextDocumentImplementation
- | TextDocumentCodeAction
- | TextDocumentCodeLens
- | CodeLensResolve
- | TextDocumentDocumentLink
- | DocumentLinkResolve
- | TextDocumentRename
- | Misc Text
- data ServerMethod
- 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 TextEdit = TextEdit {}
- type TextDocumentVersion = Maybe Int
- data VersionedTextDocumentIdentifier = VersionedTextDocumentIdentifier {}
- data TextDocumentEdit = TextDocumentEdit {}
- type WorkspaceEditMap = HashMap Uri (List TextEdit)
- data WorkspaceEdit = WorkspaceEdit {}
Documentation
data InitializeParams Source #
Constructors
| InitializeParams | |
Fields
| |
Instances
Constructors
| TraceOff | |
| TraceMessages | |
| TraceVerbose |
data InitializeError Source #
Constructors
| InitializeError | |
Instances
class HasTrace s a | s -> a where Source #
Minimal complete definition
Instances
| HasTrace InitializeParams (Maybe Trace) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasRootUri s a | s -> a where Source #
Minimal complete definition
Instances
| HasRootUri InitializeParams (Maybe Uri) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasRootPath s a | s -> a where Source #
Minimal complete definition
Instances
| HasRootPath InitializeParams (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasProcessId s a | s -> a where Source #
Minimal complete definition
Instances
| HasProcessId InitializeParams (Maybe Int) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasInitializationOptions s a | s -> a where Source #
Minimal complete definition
Methods
initializationOptions :: Lens' s a Source #
Instances
| HasInitializationOptions InitializeParams (Maybe Value) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods initializationOptions :: Lens' InitializeParams (Maybe Value) Source # | |
class HasCapabilities s a | s -> a where Source #
Minimal complete definition
Methods
capabilities :: Lens' s a Source #
data CompletionOptions Source #
Constructors
| CompletionOptions | |
Fields | |
Instances
data TextDocumentSyncKind Source #
Constructors
| TdSyncNone | |
| TdSyncFull | |
| TdSyncIncremental |
Instances
class HasRetry s a | s -> a where Source #
Minimal complete definition
Instances
| HasRetry InitializeError Bool Source # | Note: Omitting this parameter from the capabilities is effectively a fourth state, where DidSave events are generated without sending document contents. |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data SignatureHelpOptions Source #
Constructors
| SignatureHelpOptions | |
Fields | |
Instances
class HasTriggerCharacters s a | s -> a where Source #
Minimal complete definition
Methods
triggerCharacters :: Lens' s a Source #
Instances
| HasTriggerCharacters CompletionRegistrationOptions (Maybe (List String)) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods triggerCharacters :: Lens' CompletionRegistrationOptions (Maybe (List String)) Source # | |
| HasTriggerCharacters CompletionOptions (Maybe [String]) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods triggerCharacters :: Lens' CompletionOptions (Maybe [String]) Source # | |
| HasTriggerCharacters SignatureHelpOptions (Maybe [String]) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods triggerCharacters :: Lens' SignatureHelpOptions (Maybe [String]) Source # | |
| HasTriggerCharacters SignatureHelpRegistrationOptions (Maybe (List String)) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods triggerCharacters :: Lens' SignatureHelpRegistrationOptions (Maybe (List String)) Source # | |
class HasResolveProvider s a | s -> a where Source #
Minimal complete definition
Methods
resolveProvider :: Lens' s a Source #
Instances
| HasResolveProvider CompletionRegistrationOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods resolveProvider :: Lens' CompletionRegistrationOptions (Maybe Bool) Source # | |
| HasResolveProvider CompletionOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods resolveProvider :: Lens' CompletionOptions (Maybe Bool) Source # | |
| HasResolveProvider CodeLensOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods resolveProvider :: Lens' CodeLensOptions (Maybe Bool) Source # | |
| HasResolveProvider DocumentLinkOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods resolveProvider :: Lens' DocumentLinkOptions (Maybe Bool) Source # | |
| HasResolveProvider CodeLensRegistrationOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods resolveProvider :: Lens' CodeLensRegistrationOptions (Maybe Bool) Source # | |
data CodeLensOptions Source #
Constructors
| CodeLensOptions | |
Fields | |
Instances
data DocumentOnTypeFormattingOptions Source #
Constructors
| DocumentOnTypeFormattingOptions | |
Fields | |
Instances
data DocumentLinkOptions Source #
Constructors
| DocumentLinkOptions | |
Fields
| |
Instances
class HasMoreTriggerCharacter s a | s -> a where Source #
Minimal complete definition
Methods
moreTriggerCharacter :: Lens' s a Source #
Instances
class HasFirstTriggerCharacter s a | s -> a where Source #
Minimal complete definition
Methods
firstTriggerCharacter :: Lens' s a Source #
data ExecuteCommandOptions Source #
Constructors
| ExecuteCommandOptions | |
Instances
data SaveOptions Source #
Constructors
| SaveOptions | |
Fields
| |
Instances
class HasCommands s a | s -> a where Source #
Minimal complete definition
Instances
data TextDocumentSyncOptions Source #
Constructors
| TextDocumentSyncOptions | |
Fields
| |
Instances
class HasIncludeText s a | s -> a where Source #
Minimal complete definition
Methods
includeText :: Lens' s a Source #
Instances
| HasIncludeText SaveOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods includeText :: Lens' SaveOptions (Maybe Bool) Source # | |
data InitializeResponseCapabilitiesInner Source #
Constructors
Instances
Wrapper for TextDocumentSyncKind fallback.
Constructors
| TDSOptions TextDocumentSyncOptions | |
| TDSKind TextDocumentSyncKind |
Instances
class HasWillSaveWaitUntil s a | s -> a where Source #
Minimal complete definition
Methods
willSaveWaitUntil :: Lens' s a Source #
Instances
| HasWillSaveWaitUntil TextDocumentSyncOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods willSaveWaitUntil :: Lens' TextDocumentSyncOptions (Maybe Bool) Source # | |
class HasWillSave s a | s -> a where Source #
Minimal complete definition
Instances
| HasWillSave TextDocumentSyncOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasSave s a | s -> a where Source #
Minimal complete definition
Instances
| HasSave TextDocumentSyncOptions (Maybe SaveOptions) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods save :: Lens' TextDocumentSyncOptions (Maybe SaveOptions) Source # | |
class HasOpenClose s a | s -> a where Source #
Minimal complete definition
Instances
| HasOpenClose TextDocumentSyncOptions (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasChange s a | s -> a where Source #
Minimal complete definition
Instances
data InitializeResponseCapabilities Source #
Information about the capabilities of a language server
Constructors
| InitializeResponseCapabilities | |
Instances
class HasWorkspaceSymbolProvider s a | s -> a where Source #
Minimal complete definition
Methods
workspaceSymbolProvider :: Lens' s a Source #
class HasTextDocumentSync s a | s -> a where Source #
Minimal complete definition
Methods
textDocumentSync :: Lens' s a Source #
Instances
class HasSignatureHelpProvider s a | s -> a where Source #
Minimal complete definition
Methods
signatureHelpProvider :: Lens' s a Source #
class HasRenameProvider s a | s -> a where Source #
Minimal complete definition
Methods
renameProvider :: Lens' s a Source #
Instances
class HasReferencesProvider s a | s -> a where Source #
Minimal complete definition
Methods
referencesProvider :: Lens' s a Source #
Instances
| HasReferencesProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasHoverProvider s a | s -> a where Source #
Minimal complete definition
Methods
hoverProvider :: Lens' s a Source #
Instances
class HasExperimental s a | s -> a where Source #
Minimal complete definition
Methods
experimental :: Lens' s a Source #
Instances
class HasExecuteCommandProvider s a | s -> a where Source #
Minimal complete definition
Methods
executeCommandProvider :: Lens' s a Source #
class HasDocumentSymbolProvider s a | s -> a where Source #
Minimal complete definition
Methods
documentSymbolProvider :: Lens' s a Source #
Instances
| HasDocumentSymbolProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasDocumentRangeFormattingProvider s a | s -> a where Source #
Minimal complete definition
Methods
class HasDocumentOnTypeFormattingProvider s a | s -> a where Source #
Minimal complete definition
Methods
class HasDocumentLinkProvider s a | s -> a where Source #
Minimal complete definition
Methods
documentLinkProvider :: Lens' s a Source #
class HasDocumentHighlightProvider s a | s -> a where Source #
Minimal complete definition
Methods
documentHighlightProvider :: Lens' s a Source #
class HasDocumentFormattingProvider s a | s -> a where Source #
Minimal complete definition
Methods
documentFormattingProvider :: Lens' s a Source #
class HasDefinitionProvider s a | s -> a where Source #
Minimal complete definition
Methods
definitionProvider :: Lens' s a Source #
Instances
| HasDefinitionProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasCompletionProvider s a | s -> a where Source #
Minimal complete definition
Methods
completionProvider :: Lens' s a Source #
class HasCodeLensProvider s a | s -> a where Source #
Minimal complete definition
Methods
codeLensProvider :: Lens' s a Source #
class HasCodeActionProvider s a | s -> a where Source #
Minimal complete definition
Methods
codeActionProvider :: Lens' s a Source #
Instances
| HasCodeActionProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data ExitParams Source #
Notification from the server to actually exit now, after shutdown acked
Constructors
| ExitParams | |
Instances
| Eq ExitParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| Read ExitParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods readsPrec :: Int -> ReadS ExitParams # readList :: ReadS [ExitParams] # readPrec :: ReadPrec ExitParams # readListPrec :: ReadPrec [ExitParams] # | |
| Show ExitParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods showsPrec :: Int -> ExitParams -> ShowS # show :: ExitParams -> String # showList :: [ExitParams] -> ShowS # | |
| ToJSON ExitParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods toJSON :: ExitParams -> Value # toEncoding :: ExitParams -> Encoding # toJSONList :: [ExitParams] -> Value # toEncodingList :: [ExitParams] -> Encoding # | |
| FromJSON ExitParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
type ShutdownResponse = ResponseMessage Text Source #
type ShutdownRequest = RequestMessage ClientMethod (Maybe Value) Text Source #
data InitializedParams Source #
Constructors
| InitializedParams | |
Instances
type InitializeRequest = RequestMessage ClientMethod InitializeParams InitializeResponseCapabilities Source #
data ShowMessageParams Source #
Constructors
| ShowMessageParams | |
Fields
| |
Instances
data MessageType Source #
Instances
data MessageActionItem Source #
Constructors
| MessageActionItem | |
Instances
class HasXtype s a | s -> a where Source #
Minimal complete definition
Instances
| HasXtype ShowMessageParams MessageType Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasXtype ShowMessageRequestParams MessageType Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods xtype :: Lens' ShowMessageRequestParams MessageType Source # | |
| HasXtype LogMessageParams MessageType Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasXtype FileEvent FileChangeType Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasMessage s a | s -> a where Source #
Minimal complete definition
Instances
data ShowMessageRequestParams Source #
Constructors
| ShowMessageRequestParams | |
Fields
| |
Instances
class HasTitle s a | s -> a where Source #
Minimal complete definition
Instances
data LogMessageParams Source #
Constructors
| LogMessageParams | |
Fields
| |
Instances
class HasActions s a | s -> a where Source #
Minimal complete definition
Instances
| HasActions ShowMessageRequestParams (Maybe [MessageActionItem]) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods actions :: Lens' ShowMessageRequestParams (Maybe [MessageActionItem]) Source # | |
data Registration Source #
Constructors
| Registration | |
Fields
| |
Instances
data RegistrationParams Source #
Constructors
| RegistrationParams | |
Fields | |
Instances
class HasRegisterOptions s a | s -> a where Source #
Minimal complete definition
Methods
registerOptions :: Lens' s a Source #
Instances
| HasRegisterOptions Registration (Maybe Value) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods registerOptions :: Lens' Registration (Maybe Value) Source # | |
class HasMethod s a | s -> a where Source #
Minimal complete definition
Instances
| HasMethod Registration ClientMethod Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasMethod Unregistration Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasMethod (NotificationMessage m a) m Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods method :: Lens' (NotificationMessage m a) m Source # | |
| HasMethod (RequestMessage m req resp) m Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods method :: Lens' (RequestMessage m req resp) m Source # | |
class HasId s a | s -> a where Source #
Minimal complete definition
Instances
| HasId CancelParams LspId Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasId Registration Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasId Unregistration Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasId (ResponseMessage a) LspIdRsp Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasId (RequestMessage m req resp) LspId Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data TextDocumentRegistrationOptions Source #
Constructors
| TextDocumentRegistrationOptions | |
Fields | |
Instances
type RegisterCapabilityResponse = ResponseMessage () Source #
type RegisterCapabilityRequest = RequestMessage ServerMethod RegistrationParams () Source #
Note: originates at the server
class HasRegistrations s a | s -> a where Source #
Minimal complete definition
Methods
registrations :: Lens' s a Source #
Instances
| HasRegistrations RegistrationParams (List Registration) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods registrations :: Lens' RegistrationParams (List Registration) Source # | |
data Unregistration Source #
Constructors
| Unregistration | |
Instances
class HasDocumentSelector s a | s -> a where Source #
Minimal complete definition
Methods
documentSelector :: Lens' s a Source #
Instances
data UnregistrationParams Source #
Constructors
| UnregistrationParams | |
Fields | |
Instances
data DidChangeConfigurationParams Source #
Constructors
| DidChangeConfigurationParams | |
Instances
type UnregisterCapabilityResponse = ResponseMessage () Source #
class HasUnregistrations s a | s -> a where Source #
Minimal complete definition
Methods
unregistrations :: Lens' s a Source #
Instances
data DidOpenTextDocumentParams Source #
Constructors
| DidOpenTextDocumentParams | |
Fields | |
Instances
type DidChangeConfigurationNotification = NotificationMessage ClientMethod DidChangeConfigurationParams Source #
class HasSettings s a | s -> a where Source #
Minimal complete definition
Instances
| HasSettings DidChangeConfigurationParams Value Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data TextDocumentContentChangeEvent Source #
Constructors
| TextDocumentContentChangeEvent | |
Instances
type DidOpenTextDocumentNotification = NotificationMessage ClientMethod DidOpenTextDocumentParams Source #
class HasTextDocument s a | s -> a where Source #
Minimal complete definition
Methods
textDocument :: Lens' s a Source #
Instances
data DidChangeTextDocumentParams Source #
Constructors
| DidChangeTextDocumentParams | |
Instances
class HasText s a | s -> a where Source #
Minimal complete definition
Instances
| HasText TextDocumentItem Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasText TextDocumentContentChangeEvent Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasRangeLength s a | s -> a where Source #
Minimal complete definition
Methods
rangeLength :: Lens' s a Source #
Instances
| HasRangeLength TextDocumentContentChangeEvent (Maybe Int) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods rangeLength :: Lens' TextDocumentContentChangeEvent (Maybe Int) Source # | |
class HasRange s a | s -> a where Source #
Minimal complete definition
Instances
data TextDocumentChangeRegistrationOptions Source #
Constructors
| TextDocumentChangeRegistrationOptions | |
Instances
type DidChangeTextDocumentNotification = NotificationMessage ClientMethod DidChangeTextDocumentParams Source #
class HasContentChanges s a | s -> a where Source #
Minimal complete definition
Methods
contentChanges :: Lens' s a Source #
data WillSaveTextDocumentParams Source #
Constructors
| WillSaveTextDocumentParams | |
Instances
data TextDocumentSaveReason Source #
Constructors
| 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
class HasSyncKind s a | s -> a where Source #
Minimal complete definition
data DidSaveTextDocumentParams Source #
Constructors
| DidSaveTextDocumentParams | |
Fields | |
Instances
type WillSaveWaitUntilTextDocumentRequest = RequestMessage ClientMethod WillSaveTextDocumentParams (List TextEdit) Source #
type WillSaveTextDocumentNotification = NotificationMessage ClientMethod WillSaveTextDocumentParams Source #
class HasReason s a | s -> a where Source #
Minimal complete definition
Instances
| HasReason WillSaveTextDocumentParams TextDocumentSaveReason Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data DidCloseTextDocumentParams Source #
Constructors
| DidCloseTextDocumentParams | |
Fields | |
Instances
type DidSaveTextDocumentNotification = NotificationMessage ClientMethod DidSaveTextDocumentParams Source #
Constructors
| FileEvent | |
Fields
| |
Instances
data FileChangeType Source #
Instances
type DidCloseTextDocumentNotification = NotificationMessage ClientMethod DidCloseTextDocumentParams Source #
data DidChangeWatchedFilesParams Source #
Constructors
| DidChangeWatchedFilesParams | |
Instances
class HasUri s a | s -> a where Source #
Minimal complete definition
Instances
data PublishDiagnosticsParams Source #
Constructors
| PublishDiagnosticsParams | |
Fields
| |
Instances
type DidChangeWatchedFilesNotification = NotificationMessage ClientMethod DidChangeWatchedFilesParams Source #
class HasChanges s a | s -> a where Source #
Minimal complete definition
Instances
data LanguageString Source #
Constructors
| LanguageString | |
Instances
type PublishDiagnosticsNotification = NotificationMessage ServerMethod PublishDiagnosticsParams Source #
class HasDiagnostics s a | s -> a where Source #
Minimal complete definition
Methods
diagnostics :: Lens' s a Source #
Instances
| HasDiagnostics CodeActionContext (List Diagnostic) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods diagnostics :: Lens' CodeActionContext (List Diagnostic) Source # | |
| HasDiagnostics CodeAction (Maybe (List Diagnostic)) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods diagnostics :: Lens' CodeAction (Maybe (List Diagnostic)) Source # | |
| HasDiagnostics PublishDiagnosticsParams (List Diagnostic) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods diagnostics :: Lens' PublishDiagnosticsParams (List Diagnostic) Source # | |
data MarkedString Source #
Constructors
| PlainString Text | |
| CodeString LanguageString |
Instances
| Eq MarkedString Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| Read MarkedString Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods readsPrec :: Int -> ReadS MarkedString # readList :: ReadS [MarkedString] # | |
| Show MarkedString Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods showsPrec :: Int -> MarkedString -> ShowS # show :: MarkedString -> String # showList :: [MarkedString] -> ShowS # | |
| ToJSON MarkedString Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods toJSON :: MarkedString -> Value # toEncoding :: MarkedString -> Encoding # toJSONList :: [MarkedString] -> Value # toEncodingList :: [MarkedString] -> Encoding # | |
| FromJSON MarkedString Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasContents Hover (List MarkedString) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasValue s a | s -> a where Source #
Minimal complete definition
Instances
| HasValue LanguageString Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasValue TraceParams Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasLanguage s a | s -> a where Source #
Minimal complete definition
Instances
| HasLanguage DocumentFilter Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasLanguage LanguageString Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data ParameterInformation Source #
Constructors
| ParameterInformation | |
Fields
| |
Instances
type HoverResponse = ResponseMessage Hover Source #
class HasContents s a | s -> a where Source #
Minimal complete definition
Instances
| HasContents Hover (List MarkedString) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data SignatureInformation Source #
Constructors
| SignatureInformation | |
Fields
| |
Instances
class HasLabel s a | s -> a where Source #
Minimal complete definition
Instances
class HasDocumentation s a | s -> a where Source #
Minimal complete definition
Methods
documentation :: Lens' s a Source #
Instances
| HasDocumentation CompletionItem (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasDocumentation ParameterInformation (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods documentation :: Lens' ParameterInformation (Maybe Text) Source # | |
| HasDocumentation SignatureInformation (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods documentation :: Lens' SignatureInformation (Maybe Text) Source # | |
data SignatureHelp Source #
Constructors
| SignatureHelp | |
Fields
| |
Instances
class HasParameters s a | s -> a where Source #
Minimal complete definition
Methods
parameters :: Lens' s a Source #
Instances
data SignatureHelpRegistrationOptions Source #
Constructors
| SignatureHelpRegistrationOptions | |
Fields | |
Instances
type SignatureHelpRequest = RequestMessage ClientMethod TextDocumentPositionParams SignatureHelp Source #
class HasSignatures s a | s -> a where Source #
Minimal complete definition
Methods
signatures :: Lens' s a Source #
Instances
| HasSignatures SignatureHelp (List SignatureInformation) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods signatures :: Lens' SignatureHelp (List SignatureInformation) Source # | |
class HasActiveSignature s a | s -> a where Source #
Minimal complete definition
Methods
activeSignature :: Lens' s a Source #
Instances
| HasActiveSignature SignatureHelp (Maybe Int) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
class HasActiveParameter s a | s -> a where Source #
Minimal complete definition
Methods
activeParameter :: Lens' s a Source #
Instances
| HasActiveParameter SignatureHelp (Maybe Int) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
data ReferenceContext Source #
Constructors
| ReferenceContext | |
Fields | |
Instances
type ImplementationRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams Source #
type DefinitionRequest = RequestMessage ClientMethod TextDocumentPositionParams LocationResponseParams Source #
data LocationResponseParams Source #
Instances
| Eq LocationResponseParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods (==) :: LocationResponseParams -> LocationResponseParams -> Bool # (/=) :: LocationResponseParams -> LocationResponseParams -> Bool # | |
| Read LocationResponseParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| Show LocationResponseParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods showsPrec :: Int -> LocationResponseParams -> ShowS # show :: LocationResponseParams -> String # showList :: [LocationResponseParams] -> ShowS # | |
| ToJSON LocationResponseParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods toJSON :: LocationResponseParams -> Value # toEncoding :: LocationResponseParams -> Encoding # toJSONList :: [LocationResponseParams] -> Value # | |
| FromJSON LocationResponseParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods parseJSON :: Value -> Parser LocationResponseParams # parseJSONList :: Value -> Parser [LocationResponseParams] # | |
data ReferenceParams Source #
Constructors
| ReferenceParams | |
Fields | |
Instances
class HasIncludeDeclaration s a | s -> a where Source #
Minimal complete definition
Methods
includeDeclaration :: Lens' s a Source #
Instances
| HasIncludeDeclaration ReferenceContext Bool Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
data DocumentHighlight Source #
Constructors
| DocumentHighlight | |
Fields | |
Instances
data DocumentHighlightKind Source #
Instances
type ReferencesResponse = ResponseMessage (List Location) Source #
class HasPosition s a | s -> a where Source #
Minimal complete definition
Instances
class HasContext s a | s -> a where Source #
Minimal complete definition
Instances
| HasContext CodeActionParams CodeActionContext Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods context :: Lens' CodeActionParams CodeActionContext Source # | |
| HasContext ReferenceParams ReferenceContext Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
data WorkspaceSymbolParams Source #
Constructors
| WorkspaceSymbolParams | |
Instances
type DocumentHighlightRequest = RequestMessage ClientMethod TextDocumentPositionParams (List DocumentHighlight) Source #
class HasKind s a | s -> a where Source #
Minimal complete definition
Instances
| HasKind DocumentSymbol SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasKind SymbolInformation SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasKind CompletionItem (Maybe CompletionItemKind) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods kind :: Lens' CompletionItem (Maybe CompletionItemKind) Source # | |
| HasKind CodeAction (Maybe CodeActionKind) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasKind DocumentHighlight (Maybe DocumentHighlightKind) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods kind :: Lens' DocumentHighlight (Maybe DocumentHighlightKind) Source # | |
data CodeLensParams Source #
Constructors
| CodeLensParams | |
Fields | |
Instances
type WorkspaceSymbolRequest = RequestMessage ClientMethod WorkspaceSymbolParams (List SymbolInformation) Source #
class HasQuery s a | s -> a where Source #
Minimal complete definition
Instances
| HasQuery WorkspaceSymbolParams Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data CodeLensRegistrationOptions Source #
Constructors
| CodeLensRegistrationOptions | |
Fields | |
Instances
type CodeLensResponse = ResponseMessage (List CodeLens) Source #
class HasXdata s a | s -> a where Source #
Minimal complete definition
Instances
| HasXdata ResponseError (Maybe Value) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasXdata CompletionItem (Maybe Value) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasXdata CodeLens (Maybe Value) Source # | |
class HasCommand s a | s -> a where Source #
Minimal complete definition
Instances
data DocumentLinkParams Source #
Constructors
| DocumentLinkParams | |
Fields | |
Instances
data DocumentLink Source #
Instances
| Eq DocumentLink Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| Read DocumentLink Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods readsPrec :: Int -> ReadS DocumentLink # readList :: ReadS [DocumentLink] # | |
| Show DocumentLink Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods showsPrec :: Int -> DocumentLink -> ShowS # show :: DocumentLink -> String # showList :: [DocumentLink] -> ShowS # | |
| ToJSON DocumentLink Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods toJSON :: DocumentLink -> Value # toEncoding :: DocumentLink -> Encoding # toJSONList :: [DocumentLink] -> Value # toEncodingList :: [DocumentLink] -> Encoding # | |
| FromJSON DocumentLink Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasRange DocumentLink Range Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasTarget DocumentLink (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data FormattingOptions Source #
Constructors
| FormattingOptions | |
Fields
| |
Instances
type DocumentLinkRequest = RequestMessage ClientMethod DocumentLinkParams (List DocumentLink) Source #
class HasTarget s a | s -> a where Source #
Minimal complete definition
Instances
| HasTarget DocumentLink (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data DocumentFormattingParams Source #
Constructors
| DocumentFormattingParams | |
Fields | |
Instances
class HasTabSize s a | s -> a where Source #
Minimal complete definition
Instances
| HasTabSize FormattingOptions Int Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasInsertSpaces s a | s -> a where Source #
Minimal complete definition
Methods
insertSpaces :: Lens' s a Source #
Instances
| HasInsertSpaces FormattingOptions Bool Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
data DocumentRangeFormattingParams Source #
Constructors
| DocumentRangeFormattingParams | |
Fields | |
Instances
type DocumentFormattingRequest = RequestMessage ClientMethod DocumentFormattingParams (List TextEdit) Source #
class HasOptions s a | s -> a where Source #
Minimal complete definition
Instances
data DocumentOnTypeFormattingParams Source #
Constructors
| DocumentOnTypeFormattingParams | |
Fields | |
Instances
type DocumentRangeFormattingRequest = RequestMessage ClientMethod DocumentRangeFormattingParams (List TextEdit) Source #
data DocumentOnTypeFormattingRegistrationOptions Source #
Constructors
| DocumentOnTypeFormattingRegistrationOptions | |
Fields | |
Instances
type DocumentOnTypeFormattingRequest = RequestMessage ClientMethod DocumentOnTypeFormattingParams (List TextEdit) Source #
class HasCh s a | s -> a where Source #
Minimal complete definition
Instances
| HasCh DocumentOnTypeFormattingParams Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data RenameParams Source #
Constructors
| RenameParams | |
Fields | |
Instances
data ExecuteCommandParams Source #
Constructors
| ExecuteCommandParams | |
Instances
class HasNewName s a | s -> a where Source #
Minimal complete definition
Instances
| HasNewName RenameParams Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data ExecuteCommandRegistrationOptions Source #
Constructors
| ExecuteCommandRegistrationOptions | |
Instances
class HasArguments s a | s -> a where Source #
Minimal complete definition
Instances
| HasArguments Command (Maybe (List Value)) Source # | |
| HasArguments ExecuteCommandParams (Maybe (List Value)) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data ApplyWorkspaceEditParams Source #
Constructors
| ApplyWorkspaceEditParams | |
Fields | |
Instances
data ApplyWorkspaceEditResponseBody Source #
Constructors
| ApplyWorkspaceEditResponseBody | |
Instances
class HasEdit s a | s -> a where Source #
Minimal complete definition
Instances
| HasEdit ApplyWorkspaceEditParams WorkspaceEdit Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods edit :: Lens' ApplyWorkspaceEditParams WorkspaceEdit Source # | |
| HasEdit CodeAction (Maybe WorkspaceEdit) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods edit :: Lens' CodeAction (Maybe WorkspaceEdit) Source # | |
data TraceParams Source #
Constructors
| TraceParams | |
Instances
type ApplyWorkspaceEditRequest = RequestMessage ServerMethod ApplyWorkspaceEditParams ApplyWorkspaceEditResponseBody Source #
Sent from the server to the client
class HasApplied s a | s -> a where Source #
Minimal complete definition
Instances
| HasApplied ApplyWorkspaceEditResponseBody Bool Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data TraceNotification Source #
Constructors
| TraceNotification | |
Fields | |
Instances
class HasParams s a | s -> a where Source #
Minimal complete definition
Instances
| HasParams TraceNotification TraceParams Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasParams (NotificationMessage m a) a Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods params :: Lens' (NotificationMessage m a) a Source # | |
| HasParams (RequestMessage m req resp) req Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods params :: Lens' (RequestMessage m req resp) req Source # | |
class HasCharacter s a | s -> a where Source #
Minimal complete definition
class HasTextEdit s a | s -> a where Source #
Minimal complete definition
Instances
| HasTextEdit CompletionItem (Maybe TextEdit) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasSortText s a | s -> a where Source #
Minimal complete definition
Instances
| HasSortText CompletionItem (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasInsertTextFormat s a | s -> a where Source #
Minimal complete definition
Methods
insertTextFormat :: Lens' s a Source #
Instances
| HasInsertTextFormat CompletionItem (Maybe InsertTextFormat) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods insertTextFormat :: Lens' CompletionItem (Maybe InsertTextFormat) Source # | |
class HasInsertText s a | s -> a where Source #
Minimal complete definition
Methods
insertText :: Lens' s a Source #
Instances
| HasInsertText CompletionItem (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
class HasFilterText s a | s -> a where Source #
Minimal complete definition
Methods
filterText :: Lens' s a Source #
Instances
| HasFilterText CompletionItem (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
class HasDetail s a | s -> a where Source #
Minimal complete definition
Instances
| HasDetail DocumentSymbol (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasDetail CompletionItem (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasAdditionalTextEdits s a | s -> a where Source #
Minimal complete definition
Methods
additionalTextEdits :: Lens' s a Source #
Instances
| HasAdditionalTextEdits CompletionItem (Maybe (List TextEdit)) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods additionalTextEdits :: Lens' CompletionItem (Maybe (List TextEdit)) Source # | |
class HasItems s a | s -> a where Source #
Minimal complete definition
Instances
| HasItems CompletionListType (List CompletionItem) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods items :: Lens' CompletionListType (List CompletionItem) Source # | |
class HasIsIncomplete s a | s -> a where Source #
Minimal complete definition
Methods
isIncomplete :: Lens' s a Source #
Instances
| HasIsIncomplete CompletionListType Bool Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
class HasScheme s a | s -> a where Source #
Minimal complete definition
Instances
| HasScheme DocumentFilter Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasPattern s a | s -> a where Source #
Minimal complete definition
Instances
| HasPattern DocumentFilter (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasNewText s a | s -> a where Source #
Minimal complete definition
class HasVersion s a | s -> a where Source #
Minimal complete definition
class HasEdits s a | s -> a where Source #
Minimal complete definition
Instances
| HasEdits TextDocumentEdit (List TextEdit) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasDocumentChanges s a | s -> a where Source #
Minimal complete definition
Methods
documentChanges :: Lens' s a Source #
Instances
| HasDocumentChanges WorkspaceEdit (Maybe (List TextDocumentEdit)) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods documentChanges :: Lens' WorkspaceEdit (Maybe (List TextDocumentEdit)) Source # | |
class HasJsonrpc s a | s -> a where Source #
Minimal complete definition
Instances
| HasJsonrpc (ResponseMessage a) Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasJsonrpc (NotificationMessage m a) Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasJsonrpc (RequestMessage m req resp) Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasCode s a | s -> a where Source #
Minimal complete definition
Instances
| HasCode ResponseError ErrorCode Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasCode Diagnostic (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasResult s a | s -> a where Source #
Minimal complete definition
Instances
| HasResult (ResponseMessage a) (Maybe a) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasError s a | s -> a where Source #
Minimal complete definition
Instances
| HasError (ResponseMessage a) (Maybe ResponseError) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods error :: Lens' (ResponseMessage a) (Maybe ResponseError) Source # | |
class HasLanguageId s a | s -> a where Source #
Minimal complete definition
Methods
languageId :: Lens' s a Source #
Instances
| HasLanguageId TextDocumentItem Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
class HasSource s a | s -> a where Source #
Minimal complete definition
Instances
| HasSource Diagnostic (Maybe DiagnosticSource) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods source :: Lens' Diagnostic (Maybe DiagnosticSource) Source # | |
class HasSeverity s a | s -> a where Source #
Minimal complete definition
Instances
| HasSeverity Diagnostic (Maybe DiagnosticSeverity) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods severity :: Lens' Diagnostic (Maybe DiagnosticSeverity) Source # | |
class HasRelatedInformation s a | s -> a where Source #
Minimal complete definition
Methods
relatedInformation :: Lens' s a Source #
Instances
class HasLocation s a | s -> a where Source #
Minimal complete definition
Instances
class HasSelectionRange s a | s -> a where Source #
Minimal complete definition
Methods
selectionRange :: Lens' s a Source #
Instances
| HasSelectionRange DocumentSymbol Range Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
class HasName s a | s -> a where Source #
Minimal complete definition
Instances
| HasName DocumentSymbol Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasName SymbolInformation Text Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
class HasDeprecated s a | s -> a where Source #
Minimal complete definition
Methods
deprecated :: Lens' s a Source #
Instances
| HasDeprecated DocumentSymbol (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasDeprecated SymbolInformation (Maybe Bool) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
class HasChildren s a | s -> a where Source #
Minimal complete definition
Instances
| HasChildren DocumentSymbol (Maybe (List DocumentSymbol)) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods children :: Lens' DocumentSymbol (Maybe (List DocumentSymbol)) Source # | |
class HasContainerName s a | s -> a where Source #
Minimal complete definition
Methods
containerName :: Lens' s a Source #
Instances
| HasContainerName SymbolInformation (Maybe Text) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods containerName :: Lens' SymbolInformation (Maybe Text) Source # | |
data CodeActionKind Source #
Constructors
| CodeActionQuickFix | |
| CodeActionRefactor | |
| CodeActionRefactorExtract | |
| CodeActionRefactorInline | |
| CodeActionRefactorRewrite | |
| CodeActionSource | |
| CodeActionSourceOrganizeImports | |
| CodeActionUnknown Text |
Instances
data CodeActionContext Source #
Constructors
| CodeActionContext | |
Fields
| |
Instances
data CodeActionParams Source #
Constructors
| CodeActionParams | |
Fields | |
Instances
data CodeAction Source #
Constructors
| 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 |
Fields
| |
Instances
Constructors
| CACommand Command | |
| CACodeAction CodeAction |
type CodeActionResponse = ResponseMessage (List CAResult) Source #
Instances
data CompletionItemKind Source #
Constructors
Instances
data InsertTextFormat Source #
Constructors
| 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
data CompletionItem Source #
Constructors
| CompletionItem | |
Fields
| |
Instances
data CompletionListType Source #
Constructors
| CompletionListType | |
Fields | |
Instances
data CompletionResponseResult Source #
Constructors
| CompletionList CompletionListType | |
| Completions (List CompletionItem) |
Instances
type CompletionRequest = RequestMessage ClientMethod TextDocumentPositionParams CompletionResponseResult Source #
data CompletionRegistrationOptions Source #
Constructors
| CompletionRegistrationOptions | |
Fields | |
Instances
type CompletionItemResolveRequest = RequestMessage ClientMethod CompletionItem CompletionItem Source #
data DiagnosticSeverity Source #
Instances
data DiagnosticRelatedInformation Source #
Constructors
| DiagnosticRelatedInformation | |
Instances
type DiagnosticSource = Text Source #
data Diagnostic Source #
Constructors
| Diagnostic | |
Fields | |
Instances
data DocumentFilter Source #
Instances
type DocumentSelector = List DocumentFilter 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"
Constructors
| List [a] |
Instances
Constructors
| Position | |
Fields
| |
Instances
Instances
Instances
data MarkupKind Source #
Describes the content type that a client supports in various
result literals like Hover, ParameterInfo or CompletionItem.
Constructors
| MkPlainText | Plain text is supported as a content format |
| MkMarkdown | Markdown is supported as a content format |
Instances
| Eq MarkupKind Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent | |
| Read MarkupKind Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent Methods readsPrec :: Int -> ReadS MarkupKind # readList :: ReadS [MarkupKind] # readPrec :: ReadPrec MarkupKind # readListPrec :: ReadPrec [MarkupKind] # | |
| Show MarkupKind Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent Methods showsPrec :: Int -> MarkupKind -> ShowS # show :: MarkupKind -> String # showList :: [MarkupKind] -> ShowS # | |
| ToJSON MarkupKind Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent Methods toJSON :: MarkupKind -> Value # toEncoding :: MarkupKind -> Encoding # toJSONList :: [MarkupKind] -> Value # toEncodingList :: [MarkupKind] -> Encoding # | |
| FromJSON MarkupKind Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent | |
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.
Constructors
| MarkupContent | |
Fields
| |
Instances
| Eq MarkupContent Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent Methods (==) :: MarkupContent -> MarkupContent -> Bool # (/=) :: MarkupContent -> MarkupContent -> Bool # | |
| Read MarkupContent Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent Methods readsPrec :: Int -> ReadS MarkupContent # readList :: ReadS [MarkupContent] # | |
| Show MarkupContent Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent Methods showsPrec :: Int -> MarkupContent -> ShowS # show :: MarkupContent -> String # showList :: [MarkupContent] -> ShowS # | |
| ToJSON MarkupContent Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent Methods toJSON :: MarkupContent -> Value # toEncoding :: MarkupContent -> Encoding # toJSONList :: [MarkupContent] -> Value # toEncodingList :: [MarkupContent] -> Encoding # | |
| FromJSON MarkupContent Source # | |
Defined in Language.Haskell.LSP.TH.MarkupContent Methods parseJSON :: Value -> Parser MarkupContent # parseJSONList :: Value -> Parser [MarkupContent] # | |
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.TH.Message | |
| ToJSON LspId Source # | |
Defined in Language.Haskell.LSP.TH.Message | |
| FromJSON LspId Source # | |
| HasId CancelParams LspId Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasId (RequestMessage m req resp) LspId Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
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.
Constructors
| IdRspInt Int | |
| IdRspString Text | |
| IdRspNull |
Instances
| Eq LspIdRsp Source # | |
| Read LspIdRsp Source # | |
| Show LspIdRsp Source # | |
| Hashable LspIdRsp Source # | |
Defined in Language.Haskell.LSP.TH.Message | |
| ToJSON LspIdRsp Source # | |
Defined in Language.Haskell.LSP.TH.Message | |
| FromJSON LspIdRsp Source # | |
| HasId (ResponseMessage a) LspIdRsp Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
responseId :: LspId -> LspIdRsp Source #
Converts an LspId to its LspIdRsp counterpart.
data ClientMethod Source #
Constructors
Instances
data ServerMethod Source #
Constructors
| WindowShowMessage | |
| WindowShowMessageRequest | |
| WindowLogMessage | |
| TelemetryEvent | |
| ClientRegisterCapability | |
| ClientUnregisterCapability | |
| WorkspaceApplyEdit | |
| TextDocumentPublishDiagnostics | |
| CancelRequestServer |
Instances
data RequestMessage m req resp Source #
Instances
Constructors
| 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 #
Constructors
| ResponseMessage | |
Instances
type ErrorResponse = ResponseMessage () Source #
data NotificationMessage m a Source #
Constructors
| NotificationMessage | |
Instances
data CancelParams Source #
Constructors
| CancelParams | |
Instances
| Eq CancelParams Source # | |
Defined in Language.Haskell.LSP.TH.Message | |
| Read CancelParams Source # | |
Defined in Language.Haskell.LSP.TH.Message Methods readsPrec :: Int -> ReadS CancelParams # readList :: ReadS [CancelParams] # | |
| Show CancelParams Source # | |
Defined in Language.Haskell.LSP.TH.Message Methods showsPrec :: Int -> CancelParams -> ShowS # show :: CancelParams -> String # showList :: [CancelParams] -> ShowS # | |
| ToJSON CancelParams Source # | |
Defined in Language.Haskell.LSP.TH.Message Methods toJSON :: CancelParams -> Value # toEncoding :: CancelParams -> Encoding # toJSONList :: [CancelParams] -> Value # toEncodingList :: [CancelParams] -> Encoding # | |
| FromJSON CancelParams Source # | |
Defined in Language.Haskell.LSP.TH.Message | |
| HasId CancelParams LspId Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
data DocumentSymbolParams Source #
Constructors
| DocumentSymbolParams | |
Fields | |
Instances
data SymbolKind Source #
Constructors
Instances
| Eq SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.Symbol | |
| Read SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.Symbol Methods readsPrec :: Int -> ReadS SymbolKind # readList :: ReadS [SymbolKind] # readPrec :: ReadPrec SymbolKind # readListPrec :: ReadPrec [SymbolKind] # | |
| Show SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.Symbol Methods showsPrec :: Int -> SymbolKind -> ShowS # show :: SymbolKind -> String # showList :: [SymbolKind] -> ShowS # | |
| ToJSON SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.Symbol Methods toJSON :: SymbolKind -> Value # toEncoding :: SymbolKind -> Encoding # toJSONList :: [SymbolKind] -> Value # toEncodingList :: [SymbolKind] -> Encoding # | |
| FromJSON SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.Symbol | |
| HasKind DocumentSymbol SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
| HasKind SymbolInformation SymbolKind Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods | |
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.
Constructors
| DocumentSymbol | |
Fields
| |
Instances
data SymbolInformation Source #
Represents information about programming constructs like variables, classes, interfaces etc.
Constructors
| SymbolInformation | |
Fields
| |
Instances
Constructors
| DSDocumentSymbols (List DocumentSymbol) | |
| DSSymbolInformation (List SymbolInformation) |
data TextDocumentIdentifier Source #
Constructors
| TextDocumentIdentifier | |
Instances
data TextDocumentItem Source #
Constructors
| TextDocumentItem | |
Instances
data TextDocumentPositionParams Source #
Constructors
| TextDocumentPositionParams | |
Fields | |
Instances
Instances
fileScheme :: String Source #
filePathToUri :: FilePath -> Uri Source #
Instances
| Eq TextEdit Source # | |
| Read TextEdit Source # | |
| Show TextEdit Source # | |
| ToJSON TextEdit Source # | |
Defined in Language.Haskell.LSP.TH.WorkspaceEdit | |
| FromJSON TextEdit Source # | |
| HasRange TextEdit Range Source # | |
| HasNewText TextEdit Text Source # | |
| HasChanges WorkspaceEdit (Maybe WorkspaceEditMap) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods changes :: Lens' WorkspaceEdit (Maybe WorkspaceEditMap) Source # | |
| HasTextEdit CompletionItem (Maybe TextEdit) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
| HasAdditionalTextEdits CompletionItem (Maybe (List TextEdit)) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON Methods additionalTextEdits :: Lens' CompletionItem (Maybe (List TextEdit)) Source # | |
| HasEdits TextDocumentEdit (List TextEdit) Source # | |
Defined in Language.Haskell.LSP.TH.DataTypesJSON | |
type TextDocumentVersion = Maybe Int Source #
data VersionedTextDocumentIdentifier Source #
Constructors
| VersionedTextDocumentIdentifier | |
Fields
| |
Instances
data TextDocumentEdit Source #
Constructors
| TextDocumentEdit | |
Fields | |
Instances
data WorkspaceEdit Source #
Constructors
| WorkspaceEdit | |
Fields | |