{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Language.LSP.Types.CodeAction where
import Data.Aeson.TH
import Data.Aeson.Types
import Data.Default
import Data.Text ( Text )
import Language.LSP.Types.Command
import Language.LSP.Types.Diagnostic
import Language.LSP.Types.Common
import Language.LSP.Types.Location
import Language.LSP.Types.Progress
import Language.LSP.Types.TextDocument
import Language.LSP.Types.Utils
import Language.LSP.Types.WorkspaceEdit
data CodeActionKind
=
CodeActionEmpty
|
CodeActionQuickFix
|
CodeActionRefactor
|
CodeActionRefactorExtract
|
CodeActionRefactorInline
|
CodeActionRefactorRewrite
|
CodeActionSource
|
CodeActionSourceOrganizeImports
| CodeActionUnknown Text
deriving (Read, Show, Eq)
instance ToJSON CodeActionKind where
toJSON CodeActionEmpty = String ""
toJSON CodeActionQuickFix = String "quickfix"
toJSON CodeActionRefactor = String "refactor"
toJSON CodeActionRefactorExtract = String "refactor.extract"
toJSON CodeActionRefactorInline = String "refactor.inline"
toJSON CodeActionRefactorRewrite = String "refactor.rewrite"
toJSON CodeActionSource = String "source"
toJSON CodeActionSourceOrganizeImports = String "source.organizeImports"
toJSON (CodeActionUnknown s) = String s
instance FromJSON CodeActionKind where
parseJSON (String "") = pure CodeActionEmpty
parseJSON (String "quickfix") = pure CodeActionQuickFix
parseJSON (String "refactor") = pure CodeActionRefactor
parseJSON (String "refactor.extract") = pure CodeActionRefactorExtract
parseJSON (String "refactor.inline") = pure CodeActionRefactorInline
parseJSON (String "refactor.rewrite") = pure CodeActionRefactorRewrite
parseJSON (String "source") = pure CodeActionSource
parseJSON (String "source.organizeImports") = pure CodeActionSourceOrganizeImports
parseJSON (String s) = pure (CodeActionUnknown s)
parseJSON _ = mempty
data CodeActionKindClientCapabilities =
CodeActionKindClientCapabilities
{
_valueSet :: List CodeActionKind
} deriving (Show, Read, Eq)
deriveJSON lspOptions ''CodeActionKindClientCapabilities
instance Default CodeActionKindClientCapabilities where
def = CodeActionKindClientCapabilities (List allKinds)
where allKinds = [ CodeActionQuickFix
, CodeActionRefactor
, CodeActionRefactorExtract
, CodeActionRefactorInline
, CodeActionRefactorRewrite
, CodeActionSource
, CodeActionSourceOrganizeImports
]
data CodeActionLiteralSupport =
CodeActionLiteralSupport
{ _codeActionKind :: CodeActionKindClientCapabilities
} deriving (Show, Read, Eq)
deriveJSON lspOptions ''CodeActionLiteralSupport
data CodeActionClientCapabilities = CodeActionClientCapabilities
{
_dynamicRegistration :: Maybe Bool,
_codeActionLiteralSupport :: Maybe CodeActionLiteralSupport,
_isPreferredSupport :: Maybe Bool
}
deriving (Show, Read, Eq)
deriveJSON lspOptions ''CodeActionClientCapabilities
makeExtendingDatatype "CodeActionOptions" [''WorkDoneProgressOptions]
[("_codeActionKinds", [t| Maybe (List CodeActionKind) |])]
deriveJSON lspOptions ''CodeActionOptions
makeExtendingDatatype "CodeActionRegistrationOptions"
[ ''TextDocumentRegistrationOptions
, ''CodeActionOptions
] []
deriveJSON lspOptions ''CodeActionRegistrationOptions
data CodeActionContext = CodeActionContext
{
_diagnostics :: List Diagnostic
, _only :: Maybe (List CodeActionKind)
}
deriving (Read, Show, Eq)
deriveJSON lspOptions ''CodeActionContext
makeExtendingDatatype "CodeActionParams"
[ ''WorkDoneProgressParams
, ''PartialResultParams
]
[ ("_textDocument", [t|TextDocumentIdentifier|]),
("_range", [t|Range|]),
("_context", [t|CodeActionContext|])
]
deriveJSON lspOptions ''CodeActionParams
data CodeAction =
CodeAction
{
_title :: Text,
_kind :: Maybe CodeActionKind,
_diagnostics :: Maybe (List Diagnostic),
_isPreferred :: Maybe Bool,
_edit :: Maybe WorkspaceEdit,
_command :: Maybe Command
}
deriving (Read, Show, Eq)
deriveJSON lspOptions ''CodeAction