haskell-lsp-types-0.2.2.0: Haskell library for the Microsoft Language Server Protocol, data types

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.LSP.TH.DataTypesJSON

Synopsis

Documentation

newtype List a 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

Functor List Source # 

Methods

fmap :: (a -> b) -> List a -> List b #

(<$) :: a -> List b -> List a #

Foldable List Source # 

Methods

fold :: Monoid m => List m -> m #

foldMap :: Monoid m => (a -> m) -> List a -> m #

foldr :: (a -> b -> b) -> b -> List a -> b #

foldr' :: (a -> b -> b) -> b -> List a -> b #

foldl :: (b -> a -> b) -> b -> List a -> b #

foldl' :: (b -> a -> b) -> b -> List a -> b #

foldr1 :: (a -> a -> a) -> List a -> a #

foldl1 :: (a -> a -> a) -> List a -> a #

toList :: List a -> [a] #

null :: List a -> Bool #

length :: List a -> Int #

elem :: Eq a => a -> List a -> Bool #

maximum :: Ord a => List a -> a #

minimum :: Ord a => List a -> a #

sum :: Num a => List a -> a #

product :: Num a => List a -> a #

Traversable List Source # 

Methods

traverse :: Applicative f => (a -> f b) -> List a -> f (List b) #

sequenceA :: Applicative f => List (f a) -> f (List a) #

mapM :: Monad m => (a -> m b) -> List a -> m (List b) #

sequence :: Monad m => List (m a) -> m (List a) #

HasRelatedInformation Diagnostic (Maybe (List DiagnosticRelatedInformation)) Source # 
HasArguments ExecuteCommandParams (Maybe (List Value)) Source # 
HasEdits TextDocumentEdit (List TextEdit) Source # 
HasDocumentChanges WorkspaceEdit (Maybe (List TextDocumentEdit)) Source # 
HasChanges WorkspaceEdit (Maybe WorkspaceEditMap) Source # 
HasChanges DidChangeWatchedFilesParams (List FileEvent) Source # 
HasTriggerCharacters CompletionRegistrationOptions (Maybe (List String)) Source # 
HasTriggerCharacters SignatureHelpRegistrationOptions (Maybe (List String)) Source # 
HasCommands ExecuteCommandOptions (List Text) Source # 
HasCommands ExecuteCommandRegistrationOptions (List Text) Source # 
HasRegistrations RegistrationParams (List Registration) Source # 
HasDocumentSelector TextDocumentRegistrationOptions (Maybe DocumentSelector) Source # 
HasDocumentSelector TextDocumentChangeRegistrationOptions (Maybe DocumentSelector) Source # 
HasDocumentSelector CompletionRegistrationOptions (Maybe DocumentSelector) Source # 
HasDocumentSelector SignatureHelpRegistrationOptions (Maybe DocumentSelector) Source # 
HasDocumentSelector CodeLensRegistrationOptions (Maybe DocumentSelector) Source # 
HasUnregistrations UnregistrationParams (List Unregistration) Source # 
HasContentChanges DidChangeTextDocumentParams (List TextDocumentContentChangeEvent) Source # 
HasDiagnostics PublishDiagnosticsParams (List Diagnostic) Source # 
HasDiagnostics CodeActionContext (List Diagnostic) Source # 
HasAdditionalTextEdits CompletionItem (Maybe (List TextEdit)) Source # 
HasItems CompletionListType (List CompletionItem) Source # 
HasContents Hover (List MarkedString) Source # 
HasSignatures SignatureHelp (List SignatureInformation) Source # 
Eq a => Eq (List a) Source # 

Methods

(==) :: List a -> List a -> Bool #

(/=) :: List a -> List a -> Bool #

Ord a => Ord (List a) Source # 

Methods

compare :: List a -> List a -> Ordering #

(<) :: List a -> List a -> Bool #

(<=) :: List a -> List a -> Bool #

(>) :: List a -> List a -> Bool #

(>=) :: List a -> List a -> Bool #

max :: List a -> List a -> List a #

min :: List a -> List a -> List a #

Read a => Read (List a) Source # 
Show a => Show (List a) Source # 

Methods

showsPrec :: Int -> List a -> ShowS #

show :: List a -> String #

showList :: [List a] -> ShowS #

Monoid (List a) Source # 

Methods

mempty :: List a #

mappend :: List a -> List a -> List a #

mconcat :: [List a] -> List a #

ToJSON a => ToJSON (List a) Source # 
FromJSON a => FromJSON (List a) Source # 

newtype Uri Source #

Constructors

Uri 

Fields

Instances

Eq Uri Source # 

Methods

(==) :: Uri -> Uri -> Bool #

(/=) :: Uri -> Uri -> Bool #

Ord Uri Source # 

Methods

compare :: Uri -> Uri -> Ordering #

(<) :: Uri -> Uri -> Bool #

(<=) :: Uri -> Uri -> Bool #

(>) :: Uri -> Uri -> Bool #

(>=) :: Uri -> Uri -> Bool #

max :: Uri -> Uri -> Uri #

min :: Uri -> Uri -> Uri #

Read Uri Source # 
Show Uri Source # 

Methods

showsPrec :: Int -> Uri -> ShowS #

show :: Uri -> String #

showList :: [Uri] -> ShowS #

Hashable Uri Source # 

Methods

hashWithSalt :: Int -> Uri -> Int #

hash :: Uri -> Int #

ToJSON Uri Source # 
ToJSONKey Uri Source # 
FromJSON Uri Source # 
FromJSONKey Uri Source # 
HasUri Location Uri Source # 
HasUri VersionedTextDocumentIdentifier Uri Source # 
HasUri TextDocumentIdentifier Uri Source # 
HasUri TextDocumentItem Uri Source # 
HasUri FileEvent Uri Source # 
HasUri PublishDiagnosticsParams Uri Source # 
HasChanges WorkspaceEdit (Maybe WorkspaceEditMap) Source # 
HasRootUri InitializeParams (Maybe Uri) Source # 

data LspIdRsp Source #

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.

data ClientMethod Source #

data RequestMessage m req resp Source #

Constructors

RequestMessage 

Fields

Instances

(Eq req, Eq m) => Eq (RequestMessage m req resp) Source # 

Methods

(==) :: RequestMessage m req resp -> RequestMessage m req resp -> Bool #

(/=) :: RequestMessage m req resp -> RequestMessage m req resp -> Bool #

(Read req, Read m) => Read (RequestMessage m req resp) Source # 

Methods

readsPrec :: Int -> ReadS (RequestMessage m req resp) #

readList :: ReadS [RequestMessage m req resp] #

readPrec :: ReadPrec (RequestMessage m req resp) #

readListPrec :: ReadPrec [RequestMessage m req resp] #

(Show req, Show m) => Show (RequestMessage m req resp) Source # 

Methods

showsPrec :: Int -> RequestMessage m req resp -> ShowS #

show :: RequestMessage m req resp -> String #

showList :: [RequestMessage m req resp] -> ShowS #

(ToJSON m, ToJSON req, ToJSON resp) => ToJSON (RequestMessage m req resp) Source # 

Methods

toJSON :: RequestMessage m req resp -> Value #

toEncoding :: RequestMessage m req resp -> Encoding #

toJSONList :: [RequestMessage m req resp] -> Value #

toEncodingList :: [RequestMessage m req resp] -> Encoding #

(FromJSON m, FromJSON req, FromJSON resp) => FromJSON (RequestMessage m req resp) Source # 

Methods

parseJSON :: Value -> Parser (RequestMessage m req resp) #

parseJSONList :: Value -> Parser [RequestMessage m req resp] #

HasParams (RequestMessage m req resp) req Source # 

Methods

params :: Lens' (RequestMessage m req resp) req Source #

HasMethod (RequestMessage m req resp) m Source # 

Methods

method :: Lens' (RequestMessage m req resp) m Source #

HasJsonrpc (RequestMessage m req resp) Text Source # 

Methods

jsonrpc :: Lens' (RequestMessage m req resp) Text Source #

HasId (RequestMessage m req resp) LspId Source # 

Methods

id :: Lens' (RequestMessage m req resp) LspId Source #

class HasJsonrpc s a | s -> a where Source #

Minimal complete definition

jsonrpc

Methods

jsonrpc :: Lens' s a Source #

class HasParams s a | s -> a where Source #

Minimal complete definition

params

Methods

params :: Lens' s a Source #

class HasCode s a | s -> a where Source #

Minimal complete definition

code

Methods

code :: Lens' s a Source #

data ResponseMessage a Source #

class HasError s a | s -> a where Source #

Minimal complete definition

error

Methods

error :: Lens' s a Source #

class HasResult s a | s -> a where Source #

Minimal complete definition

result

Methods

result :: Lens' s a Source #

data NotificationMessage m a Source #

Constructors

NotificationMessage 

Fields

data Position Source #

Constructors

Position 

Fields

Instances

Eq Position Source # 
Ord Position Source # 
Read Position Source # 
Show Position Source # 
ToJSON Position Source # 
FromJSON Position Source # 
HasLine Position Int Source # 
HasCharacter Position Int Source # 
HasStart Range Position Source # 
HasEnd Range Position Source # 
HasPosition TextDocumentPositionParams Position Source # 
HasPosition ReferenceParams Position Source # 
HasPosition DocumentOnTypeFormattingParams Position Source # 
HasPosition RenameParams Position Source # 

class HasCharacter s a | s -> a where Source #

Minimal complete definition

character

Methods

character :: Lens' s a Source #

class HasLine s a | s -> a where Source #

Minimal complete definition

line

Methods

line :: Lens' s a Source #

data Range Source #

Constructors

Range 

Fields

Instances

Eq Range Source # 

Methods

(==) :: Range -> Range -> Bool #

(/=) :: Range -> Range -> Bool #

Ord Range Source # 

Methods

compare :: Range -> Range -> Ordering #

(<) :: Range -> Range -> Bool #

(<=) :: Range -> Range -> Bool #

(>) :: Range -> Range -> Bool #

(>=) :: Range -> Range -> Bool #

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Read Range Source # 
Show Range Source # 

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

ToJSON Range Source # 
FromJSON Range Source # 
HasStart Range Position Source # 
HasEnd Range Position Source # 
HasRange Location Range Source # 
HasRange Diagnostic Range Source # 
HasRange TextEdit Range Source # 
HasRange DocumentHighlight Range Source # 
HasRange CodeActionParams Range Source # 
HasRange CodeLens Range Source # 
HasRange DocumentLink Range Source # 
HasRange DocumentRangeFormattingParams Range Source # 
HasRange TextDocumentContentChangeEvent (Maybe Range) Source # 
HasRange Hover (Maybe Range) Source # 

class HasEnd s a | s -> a where Source #

Minimal complete definition

end

Methods

end :: Lens' s a Source #

class HasStart s a | s -> a where Source #

Minimal complete definition

start

Methods

start :: Lens' s a Source #

data DiagnosticSeverity Source #

Constructors

DsError

Error = 1,

DsWarning

Warning = 2,

DsInfo

Info = 3,

DsHint

Hint = 4

Instances

Eq DiagnosticSeverity Source # 
Ord DiagnosticSeverity Source # 
Read DiagnosticSeverity Source # 
Show DiagnosticSeverity Source # 
ToJSON DiagnosticSeverity Source # 
FromJSON DiagnosticSeverity Source # 
HasSeverity Diagnostic (Maybe DiagnosticSeverity) Source # 

data DiagnosticRelatedInformation Source #

Instances

Eq DiagnosticRelatedInformation Source # 
Ord DiagnosticRelatedInformation Source # 
Read DiagnosticRelatedInformation Source # 
Show DiagnosticRelatedInformation Source # 
ToJSON DiagnosticRelatedInformation Source # 
FromJSON DiagnosticRelatedInformation Source # 
HasMessage DiagnosticRelatedInformation Text Source # 
HasLocation DiagnosticRelatedInformation Location Source # 
HasRelatedInformation Diagnostic (Maybe (List DiagnosticRelatedInformation)) Source # 

data Diagnostic Source #

Instances

Eq Diagnostic Source # 
Ord Diagnostic Source # 
Read Diagnostic Source # 
Show Diagnostic Source # 
ToJSON Diagnostic Source # 
FromJSON Diagnostic Source # 
HasMessage Diagnostic Text Source # 
HasRange Diagnostic Range Source # 
HasCode Diagnostic (Maybe Text) Source # 
HasSource Diagnostic (Maybe DiagnosticSource) Source # 
HasSeverity Diagnostic (Maybe DiagnosticSeverity) Source # 
HasRelatedInformation Diagnostic (Maybe (List DiagnosticRelatedInformation)) Source # 
HasDiagnostics PublishDiagnosticsParams (List Diagnostic) Source # 
HasDiagnostics CodeActionContext (List Diagnostic) Source # 

class HasSeverity s a | s -> a where Source #

Minimal complete definition

severity

Methods

severity :: Lens' s a Source #

class HasSource s a | s -> a where Source #

Minimal complete definition

source

Methods

source :: Lens' s a Source #

class HasTitle s a | s -> a where Source #

Minimal complete definition

title

Methods

title :: Lens' s a Source #

class HasNewText s a | s -> a where Source #

Minimal complete definition

newText

Methods

newText :: Lens' s a Source #

data VersionedTextDocumentIdentifier Source #

Instances

Eq VersionedTextDocumentIdentifier Source # 
Read VersionedTextDocumentIdentifier Source # 
Show VersionedTextDocumentIdentifier Source # 
ToJSON VersionedTextDocumentIdentifier Source # 
FromJSON VersionedTextDocumentIdentifier Source # 
HasUri VersionedTextDocumentIdentifier Uri Source # 
HasVersion VersionedTextDocumentIdentifier TextDocumentVersion Source # 
HasTextDocument TextDocumentEdit VersionedTextDocumentIdentifier Source # 
HasTextDocument DidChangeTextDocumentParams VersionedTextDocumentIdentifier Source # 

class HasEdits s a | s -> a where Source #

Minimal complete definition

edits

Methods

edits :: Lens' s a Source #

class HasTextDocument s a | s -> a where Source #

Minimal complete definition

textDocument

Methods

textDocument :: Lens' s a Source #

Instances

HasTextDocument TextDocumentEdit VersionedTextDocumentIdentifier Source # 
HasTextDocument TextDocumentPositionParams TextDocumentIdentifier Source # 
HasTextDocument DidOpenTextDocumentParams TextDocumentItem Source # 
HasTextDocument DidChangeTextDocumentParams VersionedTextDocumentIdentifier Source # 
HasTextDocument WillSaveTextDocumentParams TextDocumentIdentifier Source # 
HasTextDocument DidSaveTextDocumentParams TextDocumentIdentifier Source # 
HasTextDocument DidCloseTextDocumentParams TextDocumentIdentifier Source # 
HasTextDocument ReferenceParams TextDocumentIdentifier Source # 
HasTextDocument DocumentSymbolParams TextDocumentIdentifier Source # 
HasTextDocument CodeActionParams TextDocumentIdentifier Source # 
HasTextDocument CodeLensParams TextDocumentIdentifier Source # 
HasTextDocument DocumentLinkParams TextDocumentIdentifier Source # 
HasTextDocument DocumentFormattingParams TextDocumentIdentifier Source # 
HasTextDocument DocumentRangeFormattingParams TextDocumentIdentifier Source # 
HasTextDocument DocumentOnTypeFormattingParams TextDocumentIdentifier Source # 
HasTextDocument RenameParams TextDocumentIdentifier Source # 

data WorkspaceEdit Source #

data TextDocumentIdentifier Source #

Constructors

TextDocumentIdentifier 

Fields

Instances

Eq TextDocumentIdentifier Source # 
Read TextDocumentIdentifier Source # 
Show TextDocumentIdentifier Source # 
ToJSON TextDocumentIdentifier Source # 
FromJSON TextDocumentIdentifier Source # 
HasUri TextDocumentIdentifier Uri Source # 
HasTextDocument TextDocumentPositionParams TextDocumentIdentifier Source # 
HasTextDocument WillSaveTextDocumentParams TextDocumentIdentifier Source # 
HasTextDocument DidSaveTextDocumentParams TextDocumentIdentifier Source # 
HasTextDocument DidCloseTextDocumentParams TextDocumentIdentifier Source # 
HasTextDocument ReferenceParams TextDocumentIdentifier Source # 
HasTextDocument DocumentSymbolParams TextDocumentIdentifier Source # 
HasTextDocument CodeActionParams TextDocumentIdentifier Source # 
HasTextDocument CodeLensParams TextDocumentIdentifier Source # 
HasTextDocument DocumentLinkParams TextDocumentIdentifier Source # 
HasTextDocument DocumentFormattingParams TextDocumentIdentifier Source # 
HasTextDocument DocumentRangeFormattingParams TextDocumentIdentifier Source # 
HasTextDocument DocumentOnTypeFormattingParams TextDocumentIdentifier Source # 
HasTextDocument RenameParams TextDocumentIdentifier Source # 

data TextDocumentItem Source #

Constructors

TextDocumentItem 

Fields

class HasLanguageId s a | s -> a where Source #

Minimal complete definition

languageId

Methods

languageId :: Lens' s a Source #

data TextDocumentPositionParams Source #

data DocumentFilter Source #

Constructors

DocumentFilter 

Instances

Eq DocumentFilter Source # 
Read DocumentFilter Source # 
Show DocumentFilter Source # 
ToJSON DocumentFilter Source # 
FromJSON DocumentFilter Source # 
HasScheme DocumentFilter Text Source # 
HasLanguage DocumentFilter Text Source # 
HasPattern DocumentFilter (Maybe Text) Source # 
HasDocumentSelector TextDocumentRegistrationOptions (Maybe DocumentSelector) Source # 
HasDocumentSelector TextDocumentChangeRegistrationOptions (Maybe DocumentSelector) Source # 
HasDocumentSelector CompletionRegistrationOptions (Maybe DocumentSelector) Source # 
HasDocumentSelector SignatureHelpRegistrationOptions (Maybe DocumentSelector) Source # 
HasDocumentSelector CodeLensRegistrationOptions (Maybe DocumentSelector) Source # 

class HasPattern s a | s -> a where Source #

Minimal complete definition

pattern

Methods

pattern :: Lens' s a Source #

class HasScheme s a | s -> a where Source #

Minimal complete definition

scheme

Methods

scheme :: Lens' s a Source #

data InitializeParams Source #

Instances

Eq InitializeParams Source # 
Read InitializeParams Source # 
Show InitializeParams Source # 
ToJSON InitializeParams Source # 
FromJSON InitializeParams Source # 
HasCapabilities InitializeParams ClientCapabilities Source # 
HasTrace InitializeParams (Maybe Trace) Source # 
HasRootUri InitializeParams (Maybe Uri) Source # 
HasRootPath InitializeParams (Maybe Text) Source # 
HasProcessId InitializeParams (Maybe Int) Source # 
HasInitializationOptions InitializeParams (Maybe Value) Source # 

class HasProcessId s a | s -> a where Source #

Minimal complete definition

processId

Methods

processId :: Lens' s a Source #

class HasRootPath s a | s -> a where Source #

Minimal complete definition

rootPath

Methods

rootPath :: Lens' s a Source #

class HasRootUri s a | s -> a where Source #

Minimal complete definition

rootUri

Methods

rootUri :: Lens' s a Source #

class HasTrace s a | s -> a where Source #

Minimal complete definition

trace

Methods

trace :: Lens' s a Source #

class HasRetry s a | s -> a where Source #

Minimal complete definition

retry

Methods

retry :: Lens' s a Source #

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.

data CompletionOptions Source #

data DocumentOnTypeFormattingOptions Source #

Instances

Eq DocumentOnTypeFormattingOptions Source # 
Read DocumentOnTypeFormattingOptions Source # 
Show DocumentOnTypeFormattingOptions Source # 
ToJSON DocumentOnTypeFormattingOptions Source # 
FromJSON DocumentOnTypeFormattingOptions Source # 
HasFirstTriggerCharacter DocumentOnTypeFormattingOptions Text Source # 
HasMoreTriggerCharacter DocumentOnTypeFormattingOptions (Maybe [String]) Source # 
HasDocumentOnTypeFormattingProvider InitializeResponseCapabilitiesInner (Maybe DocumentOnTypeFormattingOptions) Source # 

class HasIncludeText s a | s -> a where Source #

Minimal complete definition

includeText

Methods

includeText :: Lens' s a Source #

data TextDocumentSyncOptions Source #

Constructors

TextDocumentSyncOptions 

Fields

Instances

Eq TextDocumentSyncOptions Source # 
Read TextDocumentSyncOptions Source # 
Show TextDocumentSyncOptions Source # 
ToJSON TextDocumentSyncOptions Source # 
FromJSON TextDocumentSyncOptions Source # 
HasWillSaveWaitUntil TextDocumentSyncOptions (Maybe Bool) Source # 
HasWillSave TextDocumentSyncOptions (Maybe Bool) Source # 
HasSave TextDocumentSyncOptions (Maybe SaveOptions) Source # 
HasOpenClose TextDocumentSyncOptions (Maybe Bool) Source # 
HasChange TextDocumentSyncOptions (Maybe TextDocumentSyncKind) Source # 
HasTextDocumentSync InitializeResponseCapabilitiesInner (Maybe TextDocumentSyncOptions) Source # 

class HasOpenClose s a | s -> a where Source #

Minimal complete definition

openClose

Methods

openClose :: Lens' s a Source #

class HasSave s a | s -> a where Source #

Minimal complete definition

save

Methods

save :: Lens' s a Source #

class HasWillSave s a | s -> a where Source #

Minimal complete definition

willSave

Methods

willSave :: Lens' s a Source #

data InitializeResponseCapabilitiesInner Source #

Instances

Eq InitializeResponseCapabilitiesInner Source # 
Read InitializeResponseCapabilitiesInner Source # 
Show InitializeResponseCapabilitiesInner Source # 
ToJSON InitializeResponseCapabilitiesInner Source # 
FromJSON InitializeResponseCapabilitiesInner Source # 
HasCapabilities InitializeResponseCapabilities InitializeResponseCapabilitiesInner Source # 
HasWorkspaceSymbolProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasTextDocumentSync InitializeResponseCapabilitiesInner (Maybe TextDocumentSyncOptions) Source # 
HasSignatureHelpProvider InitializeResponseCapabilitiesInner (Maybe SignatureHelpOptions) Source # 
HasRenameProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasReferencesProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasHoverProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasExperimental InitializeResponseCapabilitiesInner (Maybe Value) Source # 
HasExecuteCommandProvider InitializeResponseCapabilitiesInner (Maybe ExecuteCommandOptions) Source # 
HasDocumentSymbolProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasDocumentRangeFormattingProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasDocumentOnTypeFormattingProvider InitializeResponseCapabilitiesInner (Maybe DocumentOnTypeFormattingOptions) Source # 
HasDocumentLinkProvider InitializeResponseCapabilitiesInner (Maybe DocumentLinkOptions) Source # 
HasDocumentHighlightProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasDocumentFormattingProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasDefinitionProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 
HasCompletionProvider InitializeResponseCapabilitiesInner (Maybe CompletionOptions) Source # 
HasCodeLensProvider InitializeResponseCapabilitiesInner (Maybe CodeLensOptions) Source # 
HasCodeActionProvider InitializeResponseCapabilitiesInner (Maybe Bool) Source # 

data InitializeResponseCapabilities Source #

Information about the capabilities of a language server

data MessageType Source #

Constructors

MtError

Error = 1,

MtWarning

Warning = 2,

MtInfo

Info = 3,

MtLog

Log = 4

Instances

Enum MessageType Source # 
Eq MessageType Source # 
Ord MessageType Source # 
Read MessageType Source # 
Show MessageType Source # 
ToJSON MessageType Source # 
FromJSON MessageType Source # 
HasXtype ShowMessageParams MessageType Source # 
HasXtype ShowMessageRequestParams MessageType Source # 
HasXtype LogMessageParams MessageType Source # 

data ShowMessageRequestParams Source #

data Registration Source #

Constructors

Registration 

Fields

data TextDocumentRegistrationOptions Source #

class HasSettings s a | s -> a where Source #

Minimal complete definition

settings

Methods

settings :: Lens' s a Source #

data TextDocumentContentChangeEvent Source #

Instances

Eq TextDocumentContentChangeEvent Source # 
Read TextDocumentContentChangeEvent Source # 
Show TextDocumentContentChangeEvent Source # 
ToJSON TextDocumentContentChangeEvent Source # 
FromJSON TextDocumentContentChangeEvent Source # 
HasText TextDocumentContentChangeEvent Text Source # 
HasRange TextDocumentContentChangeEvent (Maybe Range) Source # 
HasRangeLength TextDocumentContentChangeEvent (Maybe Int) Source # 
HasContentChanges DidChangeTextDocumentParams (List TextDocumentContentChangeEvent) Source # 

data DidChangeTextDocumentParams Source #

Instances

Eq DidChangeTextDocumentParams Source # 
Read DidChangeTextDocumentParams Source # 
Show DidChangeTextDocumentParams Source # 
ToJSON DidChangeTextDocumentParams Source # 
FromJSON DidChangeTextDocumentParams Source # 
HasTextDocument DidChangeTextDocumentParams VersionedTextDocumentIdentifier Source # 
HasContentChanges DidChangeTextDocumentParams (List TextDocumentContentChangeEvent) Source # 

data TextDocumentChangeRegistrationOptions Source #

Instances

Eq TextDocumentChangeRegistrationOptions Source # 
Read TextDocumentChangeRegistrationOptions Source # 
Show TextDocumentChangeRegistrationOptions Source # 
ToJSON TextDocumentChangeRegistrationOptions Source # 
FromJSON TextDocumentChangeRegistrationOptions Source # 
HasSyncKind TextDocumentChangeRegistrationOptions TextDocumentSyncKind Source # 
HasDocumentSelector TextDocumentChangeRegistrationOptions (Maybe DocumentSelector) Source # 

data WillSaveTextDocumentParams Source #

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

data CompletionItemKind Source #

Instances

Eq CompletionItemKind Source # 
Ord CompletionItemKind Source # 
Read CompletionItemKind Source # 
Show CompletionItemKind Source # 
ToJSON CompletionItemKind Source # 
FromJSON CompletionItemKind Source # 
HasKind CompletionItem (Maybe CompletionItemKind) Source # 

data CompletionItem Source #

Constructors

CompletionItem 

Fields

  • _label :: Text

    The label of this completion item. By default also the text that is inserted when selecting this completion.

  • _kind :: Maybe CompletionItemKind
     
  • _detail :: Maybe Text

    A human-readable string with additional information about this item, like type or symbol information.

  • _documentation :: Maybe Text

    A human-readable string that represents a doc-comment.

  • _sortText :: Maybe Text

    A string that should be used when filtering a set of completion items. When falsy the label is used.

  • _filterText :: Maybe Text

    A string that should be used when filtering a set of completion items. When falsy the label is used.

  • _insertText :: Maybe Text

    A string that should be inserted a document when selecting this completion. When falsy the label is used.

  • _insertTextFormat :: Maybe InsertTextFormat

    The format of the insert text. The format applies to both the insertText property and the newText property of a provided textEdit.

  • _textEdit :: Maybe TextEdit

    An edit which is applied to a document when selecting this completion. When an edit is provided the value of insertText is ignored.

    • Note:* The range of the edit must be a single line range and it must contain the position at which completion has been requested.
  • _additionalTextEdits :: Maybe (List TextEdit)

    An optional array of additional text edits that are applied when selecting this completion. Edits must not overlap with the main edit nor with themselves.

  • _command :: Maybe Command

    An optional command that is executed *after* inserting this completion. *Note* that additional modifications to the current document should be described with the additionalTextEdits-property.

  • _xdata :: Maybe Value

    An data entry field that is preserved on a completion item between a completion and a completion resolve request.

Instances

Eq CompletionItem Source # 
Read CompletionItem Source # 
Show CompletionItem Source # 
ToJSON CompletionItem Source # 
FromJSON CompletionItem Source # 
HasLabel CompletionItem Text Source # 
HasXdata CompletionItem (Maybe Value) Source # 
HasCommand CompletionItem (Maybe Command) Source # 
HasTextEdit CompletionItem (Maybe TextEdit) Source # 
HasSortText CompletionItem (Maybe Text) Source # 
HasKind CompletionItem (Maybe CompletionItemKind) Source # 
HasInsertTextFormat CompletionItem (Maybe InsertTextFormat) Source # 
HasInsertText CompletionItem (Maybe Text) Source # 
HasFilterText CompletionItem (Maybe Text) Source # 
HasDocumentation CompletionItem (Maybe Text) Source # 
HasDetail CompletionItem (Maybe Text) Source # 
HasAdditionalTextEdits CompletionItem (Maybe (List TextEdit)) Source # 
HasItems CompletionListType (List CompletionItem) Source # 

class HasDetail s a | s -> a where Source #

Minimal complete definition

detail

Methods

detail :: Lens' s a Source #

class HasFilterText s a | s -> a where Source #

Minimal complete definition

filterText

Methods

filterText :: Lens' s a Source #

class HasInsertText s a | s -> a where Source #

Minimal complete definition

insertText

Methods

insertText :: Lens' s a Source #

class HasSortText s a | s -> a where Source #

Minimal complete definition

sortText

Methods

sortText :: Lens' s a Source #

class HasTextEdit s a | s -> a where Source #

Minimal complete definition

textEdit

Methods

textEdit :: Lens' s a Source #

class HasIsIncomplete s a | s -> a where Source #

Minimal complete definition

isIncomplete

Methods

isIncomplete :: Lens' s a Source #

class HasItems s a | s -> a where Source #

Minimal complete definition

items

Methods

items :: Lens' s a Source #

data CompletionRegistrationOptions Source #

Instances

Eq CompletionRegistrationOptions Source # 
Read CompletionRegistrationOptions Source # 
Show CompletionRegistrationOptions Source # 
ToJSON CompletionRegistrationOptions Source # 
FromJSON CompletionRegistrationOptions Source # 
HasTriggerCharacters CompletionRegistrationOptions (Maybe (List String)) Source # 
HasResolveProvider CompletionRegistrationOptions (Maybe Bool) Source # 
HasDocumentSelector CompletionRegistrationOptions (Maybe DocumentSelector) Source # 

class HasValue s a | s -> a where Source #

Minimal complete definition

value

Methods

value :: Lens' s a Source #

class HasContents s a | s -> a where Source #

Minimal complete definition

contents

Methods

contents :: Lens' s a Source #

data SignatureInformation Source #

Instances

Eq SignatureInformation Source # 
Read SignatureInformation Source # 
Show SignatureInformation Source # 
ToJSON SignatureInformation Source # 
FromJSON SignatureInformation Source # 
HasLabel SignatureInformation Text Source # 
HasDocumentation SignatureInformation (Maybe Text) Source # 
HasParameters SignatureInformation (Maybe [ParameterInformation]) Source # 
HasSignatures SignatureHelp (List SignatureInformation) Source # 

class HasActiveParameter s a | s -> a where Source #

Minimal complete definition

activeParameter

class HasActiveSignature s a | s -> a where Source #

Minimal complete definition

activeSignature

data SignatureHelpRegistrationOptions Source #

Instances

Eq SignatureHelpRegistrationOptions Source # 
Read SignatureHelpRegistrationOptions Source # 
Show SignatureHelpRegistrationOptions Source # 
ToJSON SignatureHelpRegistrationOptions Source # 
FromJSON SignatureHelpRegistrationOptions Source # 
HasTriggerCharacters SignatureHelpRegistrationOptions (Maybe (List String)) Source # 
HasDocumentSelector SignatureHelpRegistrationOptions (Maybe DocumentSelector) Source # 

data SymbolInformation Source #

Constructors

SymbolInformation 

Fields

class HasContainerName s a | s -> a where Source #

Minimal complete definition

containerName

Methods

containerName :: Lens' s a Source #

class HasName s a | s -> a where Source #

Minimal complete definition

name

Methods

name :: Lens' s a Source #

class HasQuery s a | s -> a where Source #

Minimal complete definition

query

Methods

query :: Lens' s a Source #

data CodeLensRegistrationOptions Source #

class HasTarget s a | s -> a where Source #

Minimal complete definition

target

Methods

target :: Lens' s a Source #

data FormattingOptions Source #

Constructors

FormattingOptions 

Fields

Instances

Eq FormattingOptions Source # 
Read FormattingOptions Source # 
Show FormattingOptions Source # 
ToJSON FormattingOptions Source # 
FromJSON FormattingOptions Source # 
HasTabSize FormattingOptions Int Source # 
HasInsertSpaces FormattingOptions Bool Source # 
HasOptions DocumentFormattingParams FormattingOptions Source # 
HasOptions DocumentRangeFormattingParams FormattingOptions Source # 
HasOptions DocumentOnTypeFormattingParams FormattingOptions Source # 

class HasInsertSpaces s a | s -> a where Source #

Minimal complete definition

insertSpaces

Methods

insertSpaces :: Lens' s a Source #

class HasTabSize s a | s -> a where Source #

Minimal complete definition

tabSize

Methods

tabSize :: Lens' s a Source #

data DocumentFormattingParams Source #

data DocumentRangeFormattingParams Source #

Instances

Eq DocumentRangeFormattingParams Source # 
Read DocumentRangeFormattingParams Source # 
Show DocumentRangeFormattingParams Source # 
ToJSON DocumentRangeFormattingParams Source # 
FromJSON DocumentRangeFormattingParams Source # 
HasRange DocumentRangeFormattingParams Range Source # 
HasTextDocument DocumentRangeFormattingParams TextDocumentIdentifier Source # 
HasOptions DocumentRangeFormattingParams FormattingOptions Source # 

data DocumentOnTypeFormattingParams Source #

Instances

Eq DocumentOnTypeFormattingParams Source # 
Read DocumentOnTypeFormattingParams Source # 
Show DocumentOnTypeFormattingParams Source # 
ToJSON DocumentOnTypeFormattingParams Source # 
FromJSON DocumentOnTypeFormattingParams Source # 
HasTextDocument DocumentOnTypeFormattingParams TextDocumentIdentifier Source # 
HasPosition DocumentOnTypeFormattingParams Position Source # 
HasOptions DocumentOnTypeFormattingParams FormattingOptions Source # 
HasCh DocumentOnTypeFormattingParams Text Source # 

class HasCh s a | s -> a where Source #

Minimal complete definition

ch

Methods

ch :: Lens' s a Source #

data DocumentOnTypeFormattingRegistrationOptions Source #

class HasNewName s a | s -> a where Source #

Minimal complete definition

newName

Methods

newName :: Lens' s a Source #

data ExecuteCommandRegistrationOptions Source #

class HasEdit s a | s -> a where Source #

Minimal complete definition

edit

Methods

edit :: Lens' s a Source #

class HasApplied s a | s -> a where Source #

Minimal complete definition

applied

Methods

applied :: Lens' s a Source #