{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
module Language.LSP.Types.Method where
import qualified Data.Aeson as A
import Data.Aeson.Types
import Data.Text (Text)
import Language.LSP.Types.Utils
import Data.Function (on)
import Control.Applicative
import Data.GADT.Compare
import Data.Type.Equality
import GHC.Exts (Int(..), dataToTag#)
import Unsafe.Coerce
data From = FromServer | FromClient
data MethodType = Notification | Request
data Method (f :: From) (t :: MethodType) where
Initialize :: Method FromClient Request
Initialized :: Method FromClient Notification
Shutdown :: Method FromClient Request
Exit :: Method FromClient Notification
WorkspaceDidChangeWorkspaceFolders :: Method FromClient Notification
WorkspaceDidChangeConfiguration :: Method FromClient Notification
WorkspaceDidChangeWatchedFiles :: Method FromClient Notification
WorkspaceSymbol :: Method FromClient Request
WorkspaceExecuteCommand :: Method FromClient Request
TextDocumentDidOpen :: Method FromClient Notification
TextDocumentDidChange :: Method FromClient Notification
TextDocumentWillSave :: Method FromClient Notification
TextDocumentWillSaveWaitUntil :: Method FromClient Request
TextDocumentDidSave :: Method FromClient Notification
TextDocumentDidClose :: Method FromClient Notification
TextDocumentCompletion :: Method FromClient Request
CompletionItemResolve :: Method FromClient Request
TextDocumentHover :: Method FromClient Request
TextDocumentSignatureHelp :: Method FromClient Request
TextDocumentDeclaration :: Method FromClient Request
TextDocumentDefinition :: Method FromClient Request
TextDocumentTypeDefinition :: Method FromClient Request
TextDocumentImplementation :: Method FromClient Request
TextDocumentReferences :: Method FromClient Request
TextDocumentDocumentHighlight :: Method FromClient Request
TextDocumentDocumentSymbol :: Method FromClient Request
TextDocumentCodeAction :: Method FromClient Request
TextDocumentCodeLens :: Method FromClient Request
CodeLensResolve :: Method FromClient Request
TextDocumentDocumentLink :: Method FromClient Request
DocumentLinkResolve :: Method FromClient Request
TextDocumentDocumentColor :: Method FromClient Request
TextDocumentColorPresentation :: Method FromClient Request
TextDocumentFormatting :: Method FromClient Request
TextDocumentRangeFormatting :: Method FromClient Request
TextDocumentOnTypeFormatting :: Method FromClient Request
TextDocumentRename :: Method FromClient Request
TextDocumentPrepareRename :: Method FromClient Request
TextDocumentFoldingRange :: Method FromClient Request
TextDocumentSelectionRange :: Method FromClient Request
TextDocumentPrepareCallHierarchy :: Method FromClient Request
CallHierarchyIncomingCalls :: Method FromClient Request
CallHierarchyOutgoingCalls :: Method FromClient Request
TextDocumentSemanticTokens :: Method FromClient Request
TextDocumentSemanticTokensFull :: Method FromClient Request
TextDocumentSemanticTokensFullDelta :: Method FromClient Request
TextDocumentSemanticTokensRange :: Method FromClient Request
WindowShowMessage :: Method FromServer Notification
WindowShowMessageRequest :: Method FromServer Request
WindowShowDocument :: Method FromServer Request
WindowLogMessage :: Method FromServer Notification
WindowWorkDoneProgressCancel :: Method FromClient Notification
WindowWorkDoneProgressCreate :: Method FromServer Request
Progress :: Method FromServer Notification
TelemetryEvent :: Method FromServer Notification
ClientRegisterCapability :: Method FromServer Request
ClientUnregisterCapability :: Method FromServer Request
WorkspaceWorkspaceFolders :: Method FromServer Request
WorkspaceConfiguration :: Method FromServer Request
WorkspaceApplyEdit :: Method FromServer Request
WorkspaceSemanticTokensRefresh :: Method FromServer Request
TextDocumentPublishDiagnostics :: Method FromServer Notification
CancelRequest :: Method f Notification
CustomMethod :: Method f t
data SMethod (m :: Method f t) where
SInitialize :: SMethod Initialize
SInitialized :: SMethod Initialized
SShutdown :: SMethod Shutdown
SExit :: SMethod Exit
SWorkspaceDidChangeWorkspaceFolders :: SMethod WorkspaceDidChangeWorkspaceFolders
SWorkspaceDidChangeConfiguration :: SMethod WorkspaceDidChangeConfiguration
SWorkspaceDidChangeWatchedFiles :: SMethod WorkspaceDidChangeWatchedFiles
SWorkspaceSymbol :: SMethod WorkspaceSymbol
SWorkspaceExecuteCommand :: SMethod WorkspaceExecuteCommand
STextDocumentDidOpen :: SMethod TextDocumentDidOpen
STextDocumentDidChange :: SMethod TextDocumentDidChange
STextDocumentWillSave :: SMethod TextDocumentWillSave
STextDocumentWillSaveWaitUntil :: SMethod TextDocumentWillSaveWaitUntil
STextDocumentDidSave :: SMethod TextDocumentDidSave
STextDocumentDidClose :: SMethod TextDocumentDidClose
STextDocumentCompletion :: SMethod TextDocumentCompletion
SCompletionItemResolve :: SMethod CompletionItemResolve
STextDocumentHover :: SMethod TextDocumentHover
STextDocumentSignatureHelp :: SMethod TextDocumentSignatureHelp
STextDocumentDeclaration :: SMethod TextDocumentDeclaration
STextDocumentDefinition :: SMethod TextDocumentDefinition
STextDocumentTypeDefinition :: SMethod TextDocumentTypeDefinition
STextDocumentImplementation :: SMethod TextDocumentImplementation
STextDocumentReferences :: SMethod TextDocumentReferences
STextDocumentDocumentHighlight :: SMethod TextDocumentDocumentHighlight
STextDocumentDocumentSymbol :: SMethod TextDocumentDocumentSymbol
STextDocumentCodeAction :: SMethod TextDocumentCodeAction
STextDocumentCodeLens :: SMethod TextDocumentCodeLens
SCodeLensResolve :: SMethod CodeLensResolve
STextDocumentDocumentLink :: SMethod TextDocumentDocumentLink
SDocumentLinkResolve :: SMethod DocumentLinkResolve
STextDocumentDocumentColor :: SMethod TextDocumentDocumentColor
STextDocumentColorPresentation :: SMethod TextDocumentColorPresentation
STextDocumentFormatting :: SMethod TextDocumentFormatting
STextDocumentRangeFormatting :: SMethod TextDocumentRangeFormatting
STextDocumentOnTypeFormatting :: SMethod TextDocumentOnTypeFormatting
STextDocumentRename :: SMethod TextDocumentRename
STextDocumentPrepareRename :: SMethod TextDocumentPrepareRename
STextDocumentFoldingRange :: SMethod TextDocumentFoldingRange
STextDocumentSelectionRange :: SMethod TextDocumentSelectionRange
STextDocumentPrepareCallHierarchy :: SMethod TextDocumentPrepareCallHierarchy
SCallHierarchyIncomingCalls :: SMethod CallHierarchyIncomingCalls
SCallHierarchyOutgoingCalls :: SMethod CallHierarchyOutgoingCalls
STextDocumentSemanticTokens :: SMethod TextDocumentSemanticTokens
STextDocumentSemanticTokensFull :: SMethod TextDocumentSemanticTokensFull
STextDocumentSemanticTokensFullDelta :: SMethod TextDocumentSemanticTokensFullDelta
STextDocumentSemanticTokensRange :: SMethod TextDocumentSemanticTokensRange
SWorkspaceSemanticTokensRefresh :: SMethod WorkspaceSemanticTokensRefresh
SWindowShowMessage :: SMethod WindowShowMessage
SWindowShowMessageRequest :: SMethod WindowShowMessageRequest
SWindowShowDocument :: SMethod WindowShowDocument
SWindowLogMessage :: SMethod WindowLogMessage
SWindowWorkDoneProgressCreate :: SMethod WindowWorkDoneProgressCreate
SWindowWorkDoneProgressCancel :: SMethod WindowWorkDoneProgressCancel
SProgress :: SMethod Progress
STelemetryEvent :: SMethod TelemetryEvent
SClientRegisterCapability :: SMethod ClientRegisterCapability
SClientUnregisterCapability :: SMethod ClientUnregisterCapability
SWorkspaceWorkspaceFolders :: SMethod WorkspaceWorkspaceFolders
SWorkspaceConfiguration :: SMethod WorkspaceConfiguration
SWorkspaceApplyEdit :: SMethod WorkspaceApplyEdit
STextDocumentPublishDiagnostics :: SMethod TextDocumentPublishDiagnostics
SCancelRequest :: SMethod CancelRequest
SCustomMethod :: Text -> SMethod CustomMethod
instance GEq SMethod where
geq :: forall (a :: Method f t) (b :: Method f t).
SMethod a -> SMethod b -> Maybe (a :~: b)
geq SMethod a
x SMethod b
y = case forall k (f :: k -> *) (a :: k) (b :: k).
GCompare f =>
f a -> f b -> GOrdering a b
gcompare SMethod a
x SMethod b
y of
GOrdering a b
GLT -> forall a. Maybe a
Nothing
GOrdering a b
GEQ -> forall a. a -> Maybe a
Just forall {k} (a :: k). a :~: a
Refl
GOrdering a b
GGT -> forall a. Maybe a
Nothing
instance GCompare SMethod where
gcompare :: forall (a :: Method f t) (b :: Method f t).
SMethod a -> SMethod b -> GOrdering a b
gcompare (SCustomMethod Text
x) (SCustomMethod Text
y) = case Text
x forall a. Ord a => a -> a -> Ordering
`compare` Text
y of
Ordering
LT -> forall {k} (a :: k) (b :: k). GOrdering a b
GLT
Ordering
EQ -> forall {k} (a :: k). GOrdering a a
GEQ
Ordering
GT -> forall {k} (a :: k) (b :: k). GOrdering a b
GGT
gcompare SMethod a
x SMethod b
y = case Int# -> Int
I# (forall a. a -> Int#
dataToTag# SMethod a
x) forall a. Ord a => a -> a -> Ordering
`compare` Int# -> Int
I# (forall a. a -> Int#
dataToTag# SMethod b
y) of
Ordering
LT -> forall {k} (a :: k) (b :: k). GOrdering a b
GLT
Ordering
EQ -> forall a b. a -> b
unsafeCoerce forall {k} (a :: k). GOrdering a a
GEQ
Ordering
GT -> forall {k} (a :: k) (b :: k). GOrdering a b
GGT
instance Eq (SMethod m) where
== :: SMethod m -> SMethod m -> Bool
(==) = forall {k} (f :: k -> *) (a :: k) (b :: k).
GEq f =>
f a -> f b -> Bool
defaultEq
instance Ord (SMethod m) where
compare :: SMethod m -> SMethod m -> Ordering
compare = forall {k} (f :: k -> *) (a :: k) (b :: k).
GCompare f =>
f a -> f b -> Ordering
defaultCompare
deriving instance Show (SMethod m)
type SClientMethod (m :: Method FromClient t) = SMethod m
type SServerMethod (m :: Method FromServer t) = SMethod m
data SomeClientMethod = forall t (m :: Method FromClient t). SomeClientMethod (SMethod m)
data SomeServerMethod = forall t (m :: Method FromServer t). SomeServerMethod (SMethod m)
data SomeMethod where
SomeMethod :: forall m. SMethod m -> SomeMethod
deriving instance Show SomeMethod
instance Eq SomeMethod where
== :: SomeMethod -> SomeMethod -> Bool
(==) = forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a. ToJSON a => a -> Value
toJSON
instance Ord SomeMethod where
compare :: SomeMethod -> SomeMethod -> Ordering
compare = forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Value -> Text
getString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> Value
toJSON)
where
getString :: Value -> Text
getString (A.String Text
t) = Text
t
getString Value
_ = forall a. HasCallStack => String -> a
error String
"ToJSON instance for some method isn't string"
deriving instance Show SomeClientMethod
instance Eq SomeClientMethod where
== :: SomeClientMethod -> SomeClientMethod -> Bool
(==) = forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a. ToJSON a => a -> Value
toJSON
instance Ord SomeClientMethod where
compare :: SomeClientMethod -> SomeClientMethod -> Ordering
compare = forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Value -> Text
getString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> Value
toJSON)
where
getString :: Value -> Text
getString (A.String Text
t) = Text
t
getString Value
_ = forall a. HasCallStack => String -> a
error String
"ToJSON instance for some method isn't string"
deriving instance Show SomeServerMethod
instance Eq SomeServerMethod where
== :: SomeServerMethod -> SomeServerMethod -> Bool
(==) = forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a. ToJSON a => a -> Value
toJSON
instance Ord SomeServerMethod where
compare :: SomeServerMethod -> SomeServerMethod -> Ordering
compare = forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Value -> Text
getString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> Value
toJSON)
where
getString :: Value -> Text
getString (A.String Text
t) = Text
t
getString Value
_ = forall a. HasCallStack => String -> a
error String
"ToJSON instance for some method isn't string"
instance FromJSON SomeMethod where
parseJSON :: Value -> Parser SomeMethod
parseJSON Value
v = Parser SomeMethod
client forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser SomeMethod
server
where
client :: Parser SomeMethod
client = do
SomeClientMethod
c <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
case SomeClientMethod
c of
SomeClientMethod (SCustomMethod Text
_) -> forall a. Monoid a => a
mempty
SomeClientMethod SMethod m
m -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall {f :: From} {t :: MethodType} (m :: Method f t).
SMethod m -> SomeMethod
SomeMethod SMethod m
m
server :: Parser SomeMethod
server = do
SomeServerMethod
c <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
case SomeServerMethod
c of
SomeServerMethod SMethod m
m -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall {f :: From} {t :: MethodType} (m :: Method f t).
SMethod m -> SomeMethod
SomeMethod SMethod m
m
instance FromJSON SomeClientMethod where
parseJSON :: Value -> Parser SomeClientMethod
parseJSON (A.String Text
"initialize") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'Initialize
SInitialize
parseJSON (A.String Text
"initialized") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'Initialized
SInitialized
parseJSON (A.String Text
"shutdown") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'Shutdown
SShutdown
parseJSON (A.String Text
"exit") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'Exit
SExit
parseJSON (A.String Text
"workspace/didChangeWorkspaceFolders") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'WorkspaceDidChangeWorkspaceFolders
SWorkspaceDidChangeWorkspaceFolders
parseJSON (A.String Text
"workspace/didChangeConfiguration") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'WorkspaceDidChangeConfiguration
SWorkspaceDidChangeConfiguration
parseJSON (A.String Text
"workspace/didChangeWatchedFiles") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'WorkspaceDidChangeWatchedFiles
SWorkspaceDidChangeWatchedFiles
parseJSON (A.String Text
"workspace/symbol") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'WorkspaceSymbol
SWorkspaceSymbol
parseJSON (A.String Text
"workspace/executeCommand") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'WorkspaceExecuteCommand
SWorkspaceExecuteCommand
parseJSON (A.String Text
"textDocument/didOpen") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDidOpen
STextDocumentDidOpen
parseJSON (A.String Text
"textDocument/didChange") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDidChange
STextDocumentDidChange
parseJSON (A.String Text
"textDocument/willSave") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentWillSave
STextDocumentWillSave
parseJSON (A.String Text
"textDocument/willSaveWaitUntil") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentWillSaveWaitUntil
STextDocumentWillSaveWaitUntil
parseJSON (A.String Text
"textDocument/didSave") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDidSave
STextDocumentDidSave
parseJSON (A.String Text
"textDocument/didClose") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDidClose
STextDocumentDidClose
parseJSON (A.String Text
"textDocument/completion") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentCompletion
STextDocumentCompletion
parseJSON (A.String Text
"completionItem/resolve") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'CompletionItemResolve
SCompletionItemResolve
parseJSON (A.String Text
"textDocument/hover") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentHover
STextDocumentHover
parseJSON (A.String Text
"textDocument/signatureHelp") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentSignatureHelp
STextDocumentSignatureHelp
parseJSON (A.String Text
"textDocument/declaration") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDeclaration
STextDocumentDeclaration
parseJSON (A.String Text
"textDocument/definition") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDefinition
STextDocumentDefinition
parseJSON (A.String Text
"textDocument/typeDefinition") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentTypeDefinition
STextDocumentTypeDefinition
parseJSON (A.String Text
"textDocument/implementation") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentImplementation
STextDocumentImplementation
parseJSON (A.String Text
"textDocument/references") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentReferences
STextDocumentReferences
parseJSON (A.String Text
"textDocument/documentHighlight") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDocumentHighlight
STextDocumentDocumentHighlight
parseJSON (A.String Text
"textDocument/documentSymbol") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDocumentSymbol
STextDocumentDocumentSymbol
parseJSON (A.String Text
"textDocument/codeAction") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentCodeAction
STextDocumentCodeAction
parseJSON (A.String Text
"textDocument/codeLens") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentCodeLens
STextDocumentCodeLens
parseJSON (A.String Text
"codeLens/resolve") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'CodeLensResolve
SCodeLensResolve
parseJSON (A.String Text
"textDocument/documentLink") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDocumentLink
STextDocumentDocumentLink
parseJSON (A.String Text
"documentLink/resolve") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'DocumentLinkResolve
SDocumentLinkResolve
parseJSON (A.String Text
"textDocument/documentColor") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentDocumentColor
STextDocumentDocumentColor
parseJSON (A.String Text
"textDocument/colorPresentation") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentColorPresentation
STextDocumentColorPresentation
parseJSON (A.String Text
"textDocument/formatting") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentFormatting
STextDocumentFormatting
parseJSON (A.String Text
"textDocument/rangeFormatting") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentRangeFormatting
STextDocumentRangeFormatting
parseJSON (A.String Text
"textDocument/onTypeFormatting") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentOnTypeFormatting
STextDocumentOnTypeFormatting
parseJSON (A.String Text
"textDocument/rename") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentRename
STextDocumentRename
parseJSON (A.String Text
"textDocument/prepareRename") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentPrepareRename
STextDocumentPrepareRename
parseJSON (A.String Text
"textDocument/foldingRange") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentFoldingRange
STextDocumentFoldingRange
parseJSON (A.String Text
"textDocument/selectionRange") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentSelectionRange
STextDocumentSelectionRange
parseJSON (A.String Text
"textDocument/prepareCallHierarchy") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentPrepareCallHierarchy
STextDocumentPrepareCallHierarchy
parseJSON (A.String Text
"callHierarchy/incomingCalls") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'CallHierarchyIncomingCalls
SCallHierarchyIncomingCalls
parseJSON (A.String Text
"callHierarchy/outgoingCalls") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'CallHierarchyOutgoingCalls
SCallHierarchyOutgoingCalls
parseJSON (A.String Text
"textDocument/semanticTokens") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentSemanticTokens
STextDocumentSemanticTokens
parseJSON (A.String Text
"textDocument/semanticTokens/full") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentSemanticTokensFull
STextDocumentSemanticTokensFull
parseJSON (A.String Text
"textDocument/semanticTokens/full/delta") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentSemanticTokensFullDelta
STextDocumentSemanticTokensFullDelta
parseJSON (A.String Text
"textDocument/semanticTokens/range") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'TextDocumentSemanticTokensRange
STextDocumentSemanticTokensRange
parseJSON (A.String Text
"window/workDoneProgress/cancel") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod SMethod 'WindowWorkDoneProgressCancel
SWindowWorkDoneProgressCancel
parseJSON (A.String Text
"$/cancelRequest") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod forall {f :: From}. SMethod 'CancelRequest
SCancelRequest
parseJSON (A.String Text
m) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromClient t).
SMethod m -> SomeClientMethod
SomeClientMethod (forall {f :: From} {t :: MethodType}. Text -> SMethod 'CustomMethod
SCustomMethod Text
m)
parseJSON Value
_ = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"SomeClientMethod"
instance A.FromJSON SomeServerMethod where
parseJSON :: Value -> Parser SomeServerMethod
parseJSON (A.String Text
"window/showMessage") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WindowShowMessage
SWindowShowMessage
parseJSON (A.String Text
"window/showMessageRequest") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WindowShowMessageRequest
SWindowShowMessageRequest
parseJSON (A.String Text
"window/showDocument") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WindowShowDocument
SWindowShowDocument
parseJSON (A.String Text
"window/logMessage") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WindowLogMessage
SWindowLogMessage
parseJSON (A.String Text
"window/workDoneProgress/create") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WindowWorkDoneProgressCreate
SWindowWorkDoneProgressCreate
parseJSON (A.String Text
"$/progress") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'Progress
SProgress
parseJSON (A.String Text
"telemetry/event") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'TelemetryEvent
STelemetryEvent
parseJSON (A.String Text
"client/registerCapability") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'ClientRegisterCapability
SClientRegisterCapability
parseJSON (A.String Text
"client/unregisterCapability") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'ClientUnregisterCapability
SClientUnregisterCapability
parseJSON (A.String Text
"workspace/workspaceFolders") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WorkspaceWorkspaceFolders
SWorkspaceWorkspaceFolders
parseJSON (A.String Text
"workspace/configuration") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WorkspaceConfiguration
SWorkspaceConfiguration
parseJSON (A.String Text
"workspace/applyEdit") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WorkspaceApplyEdit
SWorkspaceApplyEdit
parseJSON (A.String Text
"workspace/semanticTokens/refresh") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'WorkspaceSemanticTokensRefresh
SWorkspaceSemanticTokensRefresh
parseJSON (A.String Text
"textDocument/publishDiagnostics") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod SMethod 'TextDocumentPublishDiagnostics
STextDocumentPublishDiagnostics
parseJSON (A.String Text
"$/cancelRequest") = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod forall {f :: From}. SMethod 'CancelRequest
SCancelRequest
parseJSON (A.String Text
m) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (t :: MethodType) (m :: Method 'FromServer t).
SMethod m -> SomeServerMethod
SomeServerMethod (forall {f :: From} {t :: MethodType}. Text -> SMethod 'CustomMethod
SCustomMethod Text
m)
parseJSON Value
_ = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"SomeServerMethod"
instance ToJSON SomeMethod where
toJSON :: SomeMethod -> Value
toJSON (SomeMethod SMethod m
m) = forall a. ToJSON a => a -> Value
toJSON SMethod m
m
instance ToJSON SomeClientMethod where
toJSON :: SomeClientMethod -> Value
toJSON (SomeClientMethod SMethod m
m) = forall a. ToJSON a => a -> Value
toJSON SMethod m
m
instance ToJSON SomeServerMethod where
toJSON :: SomeServerMethod -> Value
toJSON (SomeServerMethod SMethod m
m) = forall a. ToJSON a => a -> Value
toJSON SMethod m
m
instance A.ToJSON (SMethod m) where
toJSON :: SMethod m -> Value
toJSON SMethod m
SInitialize = Text -> Value
A.String Text
"initialize"
toJSON SMethod m
SInitialized = Text -> Value
A.String Text
"initialized"
toJSON SMethod m
SShutdown = Text -> Value
A.String Text
"shutdown"
toJSON SMethod m
SExit = Text -> Value
A.String Text
"exit"
toJSON SMethod m
SWorkspaceDidChangeWorkspaceFolders = Text -> Value
A.String Text
"workspace/didChangeWorkspaceFolders"
toJSON SMethod m
SWorkspaceDidChangeConfiguration = Text -> Value
A.String Text
"workspace/didChangeConfiguration"
toJSON SMethod m
SWorkspaceDidChangeWatchedFiles = Text -> Value
A.String Text
"workspace/didChangeWatchedFiles"
toJSON SMethod m
SWorkspaceSymbol = Text -> Value
A.String Text
"workspace/symbol"
toJSON SMethod m
SWorkspaceExecuteCommand = Text -> Value
A.String Text
"workspace/executeCommand"
toJSON SMethod m
STextDocumentDidOpen = Text -> Value
A.String Text
"textDocument/didOpen"
toJSON SMethod m
STextDocumentDidChange = Text -> Value
A.String Text
"textDocument/didChange"
toJSON SMethod m
STextDocumentWillSave = Text -> Value
A.String Text
"textDocument/willSave"
toJSON SMethod m
STextDocumentWillSaveWaitUntil = Text -> Value
A.String Text
"textDocument/willSaveWaitUntil"
toJSON SMethod m
STextDocumentDidSave = Text -> Value
A.String Text
"textDocument/didSave"
toJSON SMethod m
STextDocumentDidClose = Text -> Value
A.String Text
"textDocument/didClose"
toJSON SMethod m
STextDocumentCompletion = Text -> Value
A.String Text
"textDocument/completion"
toJSON SMethod m
SCompletionItemResolve = Text -> Value
A.String Text
"completionItem/resolve"
toJSON SMethod m
STextDocumentHover = Text -> Value
A.String Text
"textDocument/hover"
toJSON SMethod m
STextDocumentSignatureHelp = Text -> Value
A.String Text
"textDocument/signatureHelp"
toJSON SMethod m
STextDocumentReferences = Text -> Value
A.String Text
"textDocument/references"
toJSON SMethod m
STextDocumentDocumentHighlight = Text -> Value
A.String Text
"textDocument/documentHighlight"
toJSON SMethod m
STextDocumentDocumentSymbol = Text -> Value
A.String Text
"textDocument/documentSymbol"
toJSON SMethod m
STextDocumentDeclaration = Text -> Value
A.String Text
"textDocument/declaration"
toJSON SMethod m
STextDocumentDefinition = Text -> Value
A.String Text
"textDocument/definition"
toJSON SMethod m
STextDocumentTypeDefinition = Text -> Value
A.String Text
"textDocument/typeDefinition"
toJSON SMethod m
STextDocumentImplementation = Text -> Value
A.String Text
"textDocument/implementation"
toJSON SMethod m
STextDocumentCodeAction = Text -> Value
A.String Text
"textDocument/codeAction"
toJSON SMethod m
STextDocumentCodeLens = Text -> Value
A.String Text
"textDocument/codeLens"
toJSON SMethod m
SCodeLensResolve = Text -> Value
A.String Text
"codeLens/resolve"
toJSON SMethod m
STextDocumentDocumentColor = Text -> Value
A.String Text
"textDocument/documentColor"
toJSON SMethod m
STextDocumentColorPresentation = Text -> Value
A.String Text
"textDocument/colorPresentation"
toJSON SMethod m
STextDocumentFormatting = Text -> Value
A.String Text
"textDocument/formatting"
toJSON SMethod m
STextDocumentRangeFormatting = Text -> Value
A.String Text
"textDocument/rangeFormatting"
toJSON SMethod m
STextDocumentOnTypeFormatting = Text -> Value
A.String Text
"textDocument/onTypeFormatting"
toJSON SMethod m
STextDocumentRename = Text -> Value
A.String Text
"textDocument/rename"
toJSON SMethod m
STextDocumentPrepareRename = Text -> Value
A.String Text
"textDocument/prepareRename"
toJSON SMethod m
STextDocumentFoldingRange = Text -> Value
A.String Text
"textDocument/foldingRange"
toJSON SMethod m
STextDocumentSelectionRange = Text -> Value
A.String Text
"textDocument/selectionRange"
toJSON SMethod m
STextDocumentPrepareCallHierarchy = Text -> Value
A.String Text
"textDocument/prepareCallHierarchy"
toJSON SMethod m
SCallHierarchyIncomingCalls = Text -> Value
A.String Text
"callHierarchy/incomingCalls"
toJSON SMethod m
SCallHierarchyOutgoingCalls = Text -> Value
A.String Text
"callHierarchy/outgoingCalls"
toJSON SMethod m
STextDocumentSemanticTokens = Text -> Value
A.String Text
"textDocument/semanticTokens"
toJSON SMethod m
STextDocumentSemanticTokensFull = Text -> Value
A.String Text
"textDocument/semanticTokens/full"
toJSON SMethod m
STextDocumentSemanticTokensFullDelta = Text -> Value
A.String Text
"textDocument/semanticTokens/full/delta"
toJSON SMethod m
STextDocumentSemanticTokensRange = Text -> Value
A.String Text
"textDocument/semanticTokens/range"
toJSON SMethod m
STextDocumentDocumentLink = Text -> Value
A.String Text
"textDocument/documentLink"
toJSON SMethod m
SDocumentLinkResolve = Text -> Value
A.String Text
"documentLink/resolve"
toJSON SMethod m
SWindowWorkDoneProgressCancel = Text -> Value
A.String Text
"window/workDoneProgress/cancel"
toJSON SMethod m
SWindowShowMessage = Text -> Value
A.String Text
"window/showMessage"
toJSON SMethod m
SWindowShowMessageRequest = Text -> Value
A.String Text
"window/showMessageRequest"
toJSON SMethod m
SWindowShowDocument = Text -> Value
A.String Text
"window/showDocument"
toJSON SMethod m
SWindowLogMessage = Text -> Value
A.String Text
"window/logMessage"
toJSON SMethod m
SWindowWorkDoneProgressCreate = Text -> Value
A.String Text
"window/workDoneProgress/create"
toJSON SMethod m
SProgress = Text -> Value
A.String Text
"$/progress"
toJSON SMethod m
STelemetryEvent = Text -> Value
A.String Text
"telemetry/event"
toJSON SMethod m
SClientRegisterCapability = Text -> Value
A.String Text
"client/registerCapability"
toJSON SMethod m
SClientUnregisterCapability = Text -> Value
A.String Text
"client/unregisterCapability"
toJSON SMethod m
SWorkspaceWorkspaceFolders = Text -> Value
A.String Text
"workspace/workspaceFolders"
toJSON SMethod m
SWorkspaceConfiguration = Text -> Value
A.String Text
"workspace/configuration"
toJSON SMethod m
SWorkspaceApplyEdit = Text -> Value
A.String Text
"workspace/applyEdit"
toJSON SMethod m
SWorkspaceSemanticTokensRefresh = Text -> Value
A.String Text
"workspace/semanticTokens/refresh"
toJSON SMethod m
STextDocumentPublishDiagnostics = Text -> Value
A.String Text
"textDocument/publishDiagnostics"
toJSON SMethod m
SCancelRequest = Text -> Value
A.String Text
"$/cancelRequest"
toJSON (SCustomMethod Text
m) = Text -> Value
A.String Text
m
makeSingletonFromJSON 'SomeMethod ''SMethod