{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Language.Haskell.LSP.Types.Message where
import Control.Monad
import qualified Data.Aeson as A
import Data.Aeson.TH
import Data.Aeson.Types
import Data.Hashable
import Data.Maybe
import Data.Text (Text)
import Language.Haskell.LSP.Types.Constants
data LspId = IdInt Int | IdString Text
deriving (Show,Read,Eq,Ord)
instance A.ToJSON LspId where
toJSON (IdInt i) = toJSON i
toJSON (IdString s) = toJSON s
instance A.FromJSON LspId where
parseJSON v@(A.Number _) = IdInt <$> parseJSON v
parseJSON (A.String s) = return (IdString s)
parseJSON _ = mempty
instance Hashable LspId where
hashWithSalt salt (IdInt i) = hashWithSalt salt i
hashWithSalt salt (IdString s) = hashWithSalt salt s
data LspIdRsp = IdRspInt Int | IdRspString Text | IdRspNull
deriving (Show,Read,Eq)
instance A.ToJSON LspIdRsp where
toJSON (IdRspInt i) = toJSON i
toJSON (IdRspString s) = toJSON s
toJSON IdRspNull = A.Null
instance A.FromJSON LspIdRsp where
parseJSON v@(A.Number _) = IdRspInt <$> parseJSON v
parseJSON (A.String s) = return $ IdRspString s
parseJSON A.Null = return IdRspNull
parseJSON _ = mempty
instance Hashable LspIdRsp where
hashWithSalt salt (IdRspInt i) = hashWithSalt salt i
hashWithSalt salt (IdRspString s) = hashWithSalt salt s
hashWithSalt _ IdRspNull = 0
responseId :: LspId -> LspIdRsp
responseId (IdInt i) = IdRspInt i
responseId (IdString s) = IdRspString s
requestId :: LspIdRsp -> LspId
requestId (IdRspInt i) = IdInt i
requestId (IdRspString s) = IdString s
requestId IdRspNull = error "Null response id"
data ClientMethod =
Initialize
| Initialized
| Shutdown
| Exit
| CancelRequest
| WorkspaceDidChangeWorkspaceFolders
| WorkspaceDidChangeConfiguration
| WorkspaceDidChangeWatchedFiles
| WorkspaceSymbol
| WorkspaceExecuteCommand
| WorkDoneProgressCancel
| TextDocumentDidOpen
| TextDocumentDidChange
| TextDocumentWillSave
| TextDocumentWillSaveWaitUntil
| TextDocumentDidSave
| TextDocumentDidClose
| TextDocumentCompletion
| CompletionItemResolve
| TextDocumentHover
| TextDocumentSignatureHelp
| TextDocumentDefinition
| TextDocumentTypeDefinition
| TextDocumentImplementation
| TextDocumentReferences
| TextDocumentDocumentHighlight
| TextDocumentDocumentSymbol
| TextDocumentCodeAction
| TextDocumentCodeLens
| CodeLensResolve
| TextDocumentDocumentLink
| DocumentLinkResolve
| TextDocumentDocumentColor
| TextDocumentColorPresentation
| TextDocumentFormatting
| TextDocumentRangeFormatting
| TextDocumentOnTypeFormatting
| TextDocumentRename
| TextDocumentPrepareRename
| TextDocumentFoldingRange
| CustomClientMethod Text
deriving (Eq,Ord,Read,Show)
instance A.FromJSON ClientMethod where
parseJSON (A.String "initialize") = return Initialize
parseJSON (A.String "initialized") = return Initialized
parseJSON (A.String "shutdown") = return Shutdown
parseJSON (A.String "exit") = return Exit
parseJSON (A.String "$/cancelRequest") = return CancelRequest
parseJSON (A.String "workspace/didChangeWorkspaceFolders") = return WorkspaceDidChangeWorkspaceFolders
parseJSON (A.String "workspace/didChangeConfiguration") = return WorkspaceDidChangeConfiguration
parseJSON (A.String "workspace/didChangeWatchedFiles") = return WorkspaceDidChangeWatchedFiles
parseJSON (A.String "workspace/symbol") = return WorkspaceSymbol
parseJSON (A.String "workspace/executeCommand") = return WorkspaceExecuteCommand
parseJSON (A.String "textDocument/didOpen") = return TextDocumentDidOpen
parseJSON (A.String "textDocument/didChange") = return TextDocumentDidChange
parseJSON (A.String "textDocument/willSave") = return TextDocumentWillSave
parseJSON (A.String "textDocument/willSaveWaitUntil") = return TextDocumentWillSaveWaitUntil
parseJSON (A.String "textDocument/didSave") = return TextDocumentDidSave
parseJSON (A.String "textDocument/didClose") = return TextDocumentDidClose
parseJSON (A.String "textDocument/completion") = return TextDocumentCompletion
parseJSON (A.String "completionItem/resolve") = return CompletionItemResolve
parseJSON (A.String "textDocument/hover") = return TextDocumentHover
parseJSON (A.String "textDocument/signatureHelp") = return TextDocumentSignatureHelp
parseJSON (A.String "textDocument/definition") = return TextDocumentDefinition
parseJSON (A.String "textDocument/typeDefinition") = return TextDocumentTypeDefinition
parseJSON (A.String "textDocument/implementation") = return TextDocumentImplementation
parseJSON (A.String "textDocument/references") = return TextDocumentReferences
parseJSON (A.String "textDocument/documentHighlight") = return TextDocumentDocumentHighlight
parseJSON (A.String "textDocument/documentSymbol") = return TextDocumentDocumentSymbol
parseJSON (A.String "textDocument/codeAction") = return TextDocumentCodeAction
parseJSON (A.String "textDocument/codeLens") = return TextDocumentCodeLens
parseJSON (A.String "codeLens/resolve") = return CodeLensResolve
parseJSON (A.String "textDocument/documentLink") = return TextDocumentDocumentLink
parseJSON (A.String "documentLink/resolve") = return DocumentLinkResolve
parseJSON (A.String "textDocument/documentColor") = return TextDocumentDocumentColor
parseJSON (A.String "textDocument/colorPresentation") = return TextDocumentColorPresentation
parseJSON (A.String "textDocument/formatting") = return TextDocumentFormatting
parseJSON (A.String "textDocument/rangeFormatting") = return TextDocumentRangeFormatting
parseJSON (A.String "textDocument/onTypeFormatting") = return TextDocumentOnTypeFormatting
parseJSON (A.String "textDocument/rename") = return TextDocumentRename
parseJSON (A.String "textDocument/prepareRename") = return TextDocumentPrepareRename
parseJSON (A.String "textDocument/foldingRange") = return TextDocumentFoldingRange
parseJSON (A.String "window/workDoneProgress/cancel") = return WorkDoneProgressCancel
parseJSON (A.String x) = return (CustomClientMethod x)
parseJSON _ = mempty
instance A.ToJSON ClientMethod where
toJSON Initialize = A.String "initialize"
toJSON Initialized = A.String "initialized"
toJSON Shutdown = A.String "shutdown"
toJSON Exit = A.String "exit"
toJSON CancelRequest = A.String "$/cancelRequest"
toJSON WorkspaceDidChangeWorkspaceFolders = A.String "workspace/didChangeWorkspaceFolders"
toJSON WorkspaceDidChangeConfiguration = A.String "workspace/didChangeConfiguration"
toJSON WorkspaceDidChangeWatchedFiles = A.String "workspace/didChangeWatchedFiles"
toJSON WorkspaceSymbol = A.String "workspace/symbol"
toJSON WorkspaceExecuteCommand = A.String "workspace/executeCommand"
toJSON TextDocumentDidOpen = A.String "textDocument/didOpen"
toJSON TextDocumentDidChange = A.String "textDocument/didChange"
toJSON TextDocumentWillSave = A.String "textDocument/willSave"
toJSON TextDocumentWillSaveWaitUntil = A.String "textDocument/willSaveWaitUntil"
toJSON TextDocumentDidSave = A.String "textDocument/didSave"
toJSON TextDocumentDidClose = A.String "textDocument/didClose"
toJSON TextDocumentCompletion = A.String "textDocument/completion"
toJSON CompletionItemResolve = A.String "completionItem/resolve"
toJSON TextDocumentHover = A.String "textDocument/hover"
toJSON TextDocumentSignatureHelp = A.String "textDocument/signatureHelp"
toJSON TextDocumentReferences = A.String "textDocument/references"
toJSON TextDocumentDocumentHighlight = A.String "textDocument/documentHighlight"
toJSON TextDocumentDocumentSymbol = A.String "textDocument/documentSymbol"
toJSON TextDocumentDefinition = A.String "textDocument/definition"
toJSON TextDocumentTypeDefinition = A.String "textDocument/typeDefinition"
toJSON TextDocumentImplementation = A.String "textDocument/implementation"
toJSON TextDocumentCodeAction = A.String "textDocument/codeAction"
toJSON TextDocumentCodeLens = A.String "textDocument/codeLens"
toJSON CodeLensResolve = A.String "codeLens/resolve"
toJSON TextDocumentDocumentColor = A.String "textDocument/documentColor"
toJSON TextDocumentColorPresentation = A.String "textDocument/colorPresentation"
toJSON TextDocumentFormatting = A.String "textDocument/formatting"
toJSON TextDocumentRangeFormatting = A.String "textDocument/rangeFormatting"
toJSON TextDocumentOnTypeFormatting = A.String "textDocument/onTypeFormatting"
toJSON TextDocumentRename = A.String "textDocument/rename"
toJSON TextDocumentPrepareRename = A.String "textDocument/prepareRename"
toJSON TextDocumentFoldingRange = A.String "textDocument/foldingRange"
toJSON TextDocumentDocumentLink = A.String "textDocument/documentLink"
toJSON DocumentLinkResolve = A.String "documentLink/resolve"
toJSON WorkDoneProgressCancel = A.String "window/workDoneProgress/cancel"
toJSON (CustomClientMethod xs) = A.String xs
data ServerMethod =
WindowShowMessage
| WindowShowMessageRequest
| WindowLogMessage
| WindowWorkDoneProgressCreate
| Progress
| TelemetryEvent
| ClientRegisterCapability
| ClientUnregisterCapability
| WorkspaceWorkspaceFolders
| WorkspaceConfiguration
| WorkspaceApplyEdit
| TextDocumentPublishDiagnostics
| CancelRequestServer
| CustomServerMethod Text
deriving (Eq,Ord,Read,Show)
instance A.FromJSON ServerMethod where
parseJSON (A.String "window/showMessage") = return WindowShowMessage
parseJSON (A.String "window/showMessageRequest") = return WindowShowMessageRequest
parseJSON (A.String "window/logMessage") = return WindowLogMessage
parseJSON (A.String "window/workDoneProgress/create") = return WindowWorkDoneProgressCreate
parseJSON (A.String "$/progress") = return Progress
parseJSON (A.String "telemetry/event") = return TelemetryEvent
parseJSON (A.String "client/registerCapability") = return ClientRegisterCapability
parseJSON (A.String "client/unregisterCapability") = return ClientUnregisterCapability
parseJSON (A.String "workspace/workspaceFolders") = return WorkspaceWorkspaceFolders
parseJSON (A.String "workspace/configuration") = return WorkspaceConfiguration
parseJSON (A.String "workspace/applyEdit") = return WorkspaceApplyEdit
parseJSON (A.String "textDocument/publishDiagnostics") = return TextDocumentPublishDiagnostics
parseJSON (A.String "$/cancelRequest") = return CancelRequestServer
parseJSON (A.String m) = return (CustomServerMethod m)
parseJSON _ = mempty
instance A.ToJSON ServerMethod where
toJSON WindowShowMessage = A.String "window/showMessage"
toJSON WindowShowMessageRequest = A.String "window/showMessageRequest"
toJSON WindowLogMessage = A.String "window/logMessage"
toJSON WindowWorkDoneProgressCreate = A.String "window/workDoneProgress/create"
toJSON Progress = A.String "$/progress"
toJSON TelemetryEvent = A.String "telemetry/event"
toJSON ClientRegisterCapability = A.String "client/registerCapability"
toJSON ClientUnregisterCapability = A.String "client/unregisterCapability"
toJSON WorkspaceWorkspaceFolders = A.String "workspace/workspaceFolders"
toJSON WorkspaceConfiguration = A.String "workspace/configuration"
toJSON WorkspaceApplyEdit = A.String "workspace/applyEdit"
toJSON TextDocumentPublishDiagnostics = A.String "textDocument/publishDiagnostics"
toJSON CancelRequestServer = A.String "$/cancelRequest"
toJSON (CustomServerMethod m) = A.String m
data RequestMessage m req resp =
RequestMessage
{ _jsonrpc :: Text
, _id :: LspId
, _method :: m
, _params :: req
} deriving (Read,Show,Eq)
deriveJSON lspOptions ''RequestMessage
data ErrorCode = ParseError
| InvalidRequest
| MethodNotFound
| InvalidParams
| InternalError
| ServerErrorStart
| ServerErrorEnd
| ServerNotInitialized
| UnknownErrorCode
| RequestCancelled
deriving (Read,Show,Eq)
instance A.ToJSON ErrorCode where
toJSON ParseError = A.Number (-32700)
toJSON InvalidRequest = A.Number (-32600)
toJSON MethodNotFound = A.Number (-32601)
toJSON InvalidParams = A.Number (-32602)
toJSON InternalError = A.Number (-32603)
toJSON ServerErrorStart = A.Number (-32099)
toJSON ServerErrorEnd = A.Number (-32000)
toJSON ServerNotInitialized = A.Number (-32002)
toJSON UnknownErrorCode = A.Number (-32001)
toJSON RequestCancelled = A.Number (-32800)
instance A.FromJSON ErrorCode where
parseJSON (A.Number (-32700)) = pure ParseError
parseJSON (A.Number (-32600)) = pure InvalidRequest
parseJSON (A.Number (-32601)) = pure MethodNotFound
parseJSON (A.Number (-32602)) = pure InvalidParams
parseJSON (A.Number (-32603)) = pure InternalError
parseJSON (A.Number (-32099)) = pure ServerErrorStart
parseJSON (A.Number (-32000)) = pure ServerErrorEnd
parseJSON (A.Number (-32002)) = pure ServerNotInitialized
parseJSON (A.Number (-32001)) = pure UnknownErrorCode
parseJSON (A.Number (-32800)) = pure RequestCancelled
parseJSON _ = mempty
data ResponseError =
ResponseError
{ _code :: ErrorCode
, _message :: Text
, _xdata :: Maybe A.Value
} deriving (Read,Show,Eq)
deriveJSON lspOptions{ fieldLabelModifier = customModifier } ''ResponseError
data ResponseMessage a =
ResponseMessage
{ _jsonrpc :: Text
, _id :: LspIdRsp
, _result :: Maybe a
, _error :: Maybe ResponseError
} deriving (Read,Show,Eq)
deriveToJSON lspOptions ''ResponseMessage
instance FromJSON a => FromJSON (ResponseMessage a) where
parseJSON = withObject "Response" $ \o -> do
rsp <- ResponseMessage
<$> o .: "jsonrpc"
<*> o .: "id"
<*> o .:! "result"
<*> o .:! "error"
unless (isJust (_result rsp) || isJust (_error rsp)) $
fail "ResponseMessage must either have a result or an error"
pure rsp
type ErrorResponse = ResponseMessage ()
type BareResponseMessage = ResponseMessage A.Value
data NotificationMessage m a =
NotificationMessage
{ _jsonrpc :: Text
, _method :: m
, _params :: a
} deriving (Read,Show,Eq)
deriveJSON lspOptions ''NotificationMessage
data CancelParams =
CancelParams
{ _id :: LspId
} deriving (Read,Show,Eq)
deriveJSON lspOptions ''CancelParams
type CancelNotification = NotificationMessage ClientMethod CancelParams
type CancelNotificationServer = NotificationMessage ServerMethod CancelParams