haskell-lsp-0.2.0.0: Haskell library for the Microsoft Language Server Protocol

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 #

HasParams DidChangeWatchedFilesParams (List FileEvent) Source # 
HasArguments ExecuteCommandParams (Maybe (List Value)) Source # 
HasEdits TextDocumentEdit (List TextEdit) Source # 
HasDocumentChanges WorkspaceEdit (Maybe (List TextDocumentEdit)) Source # 
HasChanges WorkspaceEdit (Maybe WorkspaceEditMap) 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 #

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 #

FromJSON a => FromJSON (List a) Source # 
ToJSON a => ToJSON (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 #

FromJSON Uri Source # 
FromJSONKey Uri Source # 
ToJSON Uri Source # 
ToJSONKey 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 LspId Source #

Id used for a request, Can be either a String or an Int

Constructors

IdInt Int 
IdString Text 

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 #

(FromJSON m0, FromJSON req0, FromJSON resp0) => FromJSON (RequestMessage m0 req0 resp0) Source # 

Methods

parseJSON :: Value -> Parser (RequestMessage m0 req0 resp0) #

parseJSONList :: Value -> Parser [RequestMessage m0 req0 resp0] #

(ToJSON m0, ToJSON req0, ToJSON resp0) => ToJSON (RequestMessage m0 req0 resp0) Source # 

Methods

toJSON :: RequestMessage m0 req0 resp0 -> Value #

toEncoding :: RequestMessage m0 req0 resp0 -> Encoding #

toJSONList :: [RequestMessage m0 req0 resp0] -> Value #

toEncodingList :: [RequestMessage m0 req0 resp0] -> Encoding #

HasParams (RequestMessage m0 req0 resp0) req0 Source # 

Methods

params :: Lens' (RequestMessage m0 req0 resp0) req0 Source #

HasMethod (RequestMessage m0 req0 resp0) m0 Source # 

Methods

method :: Lens' (RequestMessage m0 req0 resp0) m0 Source #

HasJsonrpc (RequestMessage m0 req0 resp0) Text Source # 

Methods

jsonrpc :: Lens' (RequestMessage m0 req0 resp0) Text Source #

HasId (RequestMessage m0 req0 resp0) LspId Source # 

Methods

id :: Lens' (RequestMessage m0 req0 resp0) LspId Source #

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

Minimal complete definition

id

Methods