{-# 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
  = -- | Empty kind.
    CodeActionEmpty
  | -- | Base kind for quickfix actions: @quickfix@.
    CodeActionQuickFix
  | -- | Base kind for refactoring actions: @refactor@.
    CodeActionRefactor
  | -- | Base kind for refactoring extraction actions: @refactor.extract@.
    -- Example extract actions:
    --
    -- - Extract method
    -- - Extract function
    -- - Extract variable
    -- - Extract interface from class
    -- - ...
    CodeActionRefactorExtract
  | -- | Base kind for refactoring inline actions: @refactor.inline@.
    --
    -- Example inline actions:
    --
    -- - Inline function
    -- - Inline variable
    -- - Inline constant
    -- - ...
    CodeActionRefactorInline
  | -- | Base kind for refactoring rewrite actions: @refactor.rewrite@.
    --
    -- Example rewrite actions:
    --
    -- - Convert JavaScript function to class
    -- - Add or remove parameter
    -- - Encapsulate field
    -- - Make method static
    -- - Move method to base class
    -- - ...
    CodeActionRefactorRewrite
  | -- | Base kind for source actions: @source@.
    --
    -- Source code actions apply to the entire file.
    CodeActionSource
  | -- | Base kind for an organize imports source action: @source.organizeImports@.
    CodeActionSourceOrganizeImports
  | CodeActionUnknown Text
  deriving (ReadPrec [CodeActionKind]
ReadPrec CodeActionKind
Int -> ReadS CodeActionKind
ReadS [CodeActionKind]
(Int -> ReadS CodeActionKind)
-> ReadS [CodeActionKind]
-> ReadPrec CodeActionKind
-> ReadPrec [CodeActionKind]
-> Read CodeActionKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CodeActionKind]
$creadListPrec :: ReadPrec [CodeActionKind]
readPrec :: ReadPrec CodeActionKind
$creadPrec :: ReadPrec CodeActionKind
readList :: ReadS [CodeActionKind]
$creadList :: ReadS [CodeActionKind]
readsPrec :: Int -> ReadS CodeActionKind
$creadsPrec :: Int -> ReadS CodeActionKind
Read, Int -> CodeActionKind -> ShowS
[CodeActionKind] -> ShowS
CodeActionKind -> String
(Int -> CodeActionKind -> ShowS)
-> (CodeActionKind -> String)
-> ([CodeActionKind] -> ShowS)
-> Show CodeActionKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeActionKind] -> ShowS
$cshowList :: [CodeActionKind] -> ShowS
show :: CodeActionKind -> String
$cshow :: CodeActionKind -> String
showsPrec :: Int -> CodeActionKind -> ShowS
$cshowsPrec :: Int -> CodeActionKind -> ShowS
Show, CodeActionKind -> CodeActionKind -> Bool
(CodeActionKind -> CodeActionKind -> Bool)
-> (CodeActionKind -> CodeActionKind -> Bool) -> Eq CodeActionKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeActionKind -> CodeActionKind -> Bool
$c/= :: CodeActionKind -> CodeActionKind -> Bool
== :: CodeActionKind -> CodeActionKind -> Bool
$c== :: CodeActionKind -> CodeActionKind -> Bool
Eq)

instance ToJSON CodeActionKind where
  toJSON :: CodeActionKind -> Value
toJSON CodeActionKind
CodeActionEmpty                      = Text -> Value
String Text
""
  toJSON CodeActionKind
CodeActionQuickFix                   = Text -> Value
String Text
"quickfix"
  toJSON CodeActionKind
CodeActionRefactor                   = Text -> Value
String Text
"refactor"
  toJSON CodeActionKind
CodeActionRefactorExtract            = Text -> Value
String Text
"refactor.extract"
  toJSON CodeActionKind
CodeActionRefactorInline             = Text -> Value
String Text
"refactor.inline"
  toJSON CodeActionKind
CodeActionRefactorRewrite            = Text -> Value
String Text
"refactor.rewrite"
  toJSON CodeActionKind
CodeActionSource                     = Text -> Value
String Text
"source"
  toJSON CodeActionKind
CodeActionSourceOrganizeImports      = Text -> Value
String Text
"source.organizeImports"
  toJSON (CodeActionUnknown Text
s)                = Text -> Value
String Text
s

instance FromJSON CodeActionKind where
  parseJSON :: Value -> Parser CodeActionKind
parseJSON (String Text
"")                       = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure CodeActionKind
CodeActionEmpty
  parseJSON (String Text
"quickfix")               = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure CodeActionKind
CodeActionQuickFix
  parseJSON (String Text
"refactor")               = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure CodeActionKind
CodeActionRefactor
  parseJSON (String Text
"refactor.extract")       = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure CodeActionKind
CodeActionRefactorExtract
  parseJSON (String Text
"refactor.inline")        = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure CodeActionKind
CodeActionRefactorInline
  parseJSON (String Text
"refactor.rewrite")       = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure CodeActionKind
CodeActionRefactorRewrite
  parseJSON (String Text
"source")                 = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure CodeActionKind
CodeActionSource
  parseJSON (String Text
"source.organizeImports") = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure CodeActionKind
CodeActionSourceOrganizeImports
  parseJSON (String Text
s)                        = CodeActionKind -> Parser CodeActionKind
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> CodeActionKind
CodeActionUnknown Text
s)
  parseJSON Value
_                                 = Parser CodeActionKind
forall a. Monoid a => a
mempty
  
-- -------------------------------------

data CodeActionKindClientCapabilities =
  CodeActionKindClientCapabilities
   { -- | The code action kind values the client supports. When this
     -- property exists the client also guarantees that it will
     -- handle values outside its set gracefully and falls back
     -- to a default value when unknown.
      CodeActionKindClientCapabilities -> List CodeActionKind
_valueSet :: List CodeActionKind
   } deriving (Int -> CodeActionKindClientCapabilities -> ShowS
[CodeActionKindClientCapabilities] -> ShowS
CodeActionKindClientCapabilities -> String
(Int -> CodeActionKindClientCapabilities -> ShowS)
-> (CodeActionKindClientCapabilities -> String)
-> ([CodeActionKindClientCapabilities] -> ShowS)
-> Show CodeActionKindClientCapabilities
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeActionKindClientCapabilities] -> ShowS
$cshowList :: [CodeActionKindClientCapabilities] -> ShowS
show :: CodeActionKindClientCapabilities -> String
$cshow :: CodeActionKindClientCapabilities -> String
showsPrec :: Int -> CodeActionKindClientCapabilities -> ShowS
$cshowsPrec :: Int -> CodeActionKindClientCapabilities -> ShowS
Show, ReadPrec [CodeActionKindClientCapabilities]
ReadPrec CodeActionKindClientCapabilities
Int -> ReadS CodeActionKindClientCapabilities
ReadS [CodeActionKindClientCapabilities]
(Int -> ReadS CodeActionKindClientCapabilities)
-> ReadS [CodeActionKindClientCapabilities]
-> ReadPrec CodeActionKindClientCapabilities
-> ReadPrec [CodeActionKindClientCapabilities]
-> Read CodeActionKindClientCapabilities
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CodeActionKindClientCapabilities]
$creadListPrec :: ReadPrec [CodeActionKindClientCapabilities]
readPrec :: ReadPrec CodeActionKindClientCapabilities
$creadPrec :: ReadPrec CodeActionKindClientCapabilities
readList :: ReadS [CodeActionKindClientCapabilities]
$creadList :: ReadS [CodeActionKindClientCapabilities]
readsPrec :: Int -> ReadS CodeActionKindClientCapabilities
$creadsPrec :: Int -> ReadS CodeActionKindClientCapabilities
Read, CodeActionKindClientCapabilities
-> CodeActionKindClientCapabilities -> Bool
(CodeActionKindClientCapabilities
 -> CodeActionKindClientCapabilities -> Bool)
-> (CodeActionKindClientCapabilities
    -> CodeActionKindClientCapabilities -> Bool)
-> Eq CodeActionKindClientCapabilities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeActionKindClientCapabilities
-> CodeActionKindClientCapabilities -> Bool
$c/= :: CodeActionKindClientCapabilities
-> CodeActionKindClientCapabilities -> Bool
== :: CodeActionKindClientCapabilities
-> CodeActionKindClientCapabilities -> Bool
$c== :: CodeActionKindClientCapabilities
-> CodeActionKindClientCapabilities -> Bool
Eq)

deriveJSON lspOptions ''CodeActionKindClientCapabilities

instance Default CodeActionKindClientCapabilities where
  def :: CodeActionKindClientCapabilities
def = List CodeActionKind -> CodeActionKindClientCapabilities
CodeActionKindClientCapabilities ([CodeActionKind] -> List CodeActionKind
forall a. [a] -> List a
List [CodeActionKind]
allKinds)
    where allKinds :: [CodeActionKind]
allKinds = [ CodeActionKind
CodeActionQuickFix
                     , CodeActionKind
CodeActionRefactor
                     , CodeActionKind
CodeActionRefactorExtract
                     , CodeActionKind
CodeActionRefactorInline
                     , CodeActionKind
CodeActionRefactorRewrite
                     , CodeActionKind
CodeActionSource
                     , CodeActionKind
CodeActionSourceOrganizeImports
                     ]

data CodeActionLiteralSupport =
  CodeActionLiteralSupport
    { CodeActionLiteralSupport -> CodeActionKindClientCapabilities
_codeActionKind :: CodeActionKindClientCapabilities -- ^ The code action kind is support with the following value set.
    } deriving (Int -> CodeActionLiteralSupport -> ShowS
[CodeActionLiteralSupport] -> ShowS
CodeActionLiteralSupport -> String
(Int -> CodeActionLiteralSupport -> ShowS)
-> (CodeActionLiteralSupport -> String)
-> ([CodeActionLiteralSupport] -> ShowS)
-> Show CodeActionLiteralSupport
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeActionLiteralSupport] -> ShowS
$cshowList :: [CodeActionLiteralSupport] -> ShowS
show :: CodeActionLiteralSupport -> String
$cshow :: CodeActionLiteralSupport -> String
showsPrec :: Int -> CodeActionLiteralSupport -> ShowS
$cshowsPrec :: Int -> CodeActionLiteralSupport -> ShowS
Show, ReadPrec [CodeActionLiteralSupport]
ReadPrec CodeActionLiteralSupport
Int -> ReadS CodeActionLiteralSupport
ReadS [CodeActionLiteralSupport]
(Int -> ReadS CodeActionLiteralSupport)
-> ReadS [CodeActionLiteralSupport]
-> ReadPrec CodeActionLiteralSupport
-> ReadPrec [CodeActionLiteralSupport]
-> Read CodeActionLiteralSupport
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CodeActionLiteralSupport]
$creadListPrec :: ReadPrec [CodeActionLiteralSupport]
readPrec :: ReadPrec CodeActionLiteralSupport
$creadPrec :: ReadPrec CodeActionLiteralSupport
readList :: ReadS [CodeActionLiteralSupport]
$creadList :: ReadS [CodeActionLiteralSupport]
readsPrec :: Int -> ReadS CodeActionLiteralSupport
$creadsPrec :: Int -> ReadS CodeActionLiteralSupport
Read, CodeActionLiteralSupport -> CodeActionLiteralSupport -> Bool
(CodeActionLiteralSupport -> CodeActionLiteralSupport -> Bool)
-> (CodeActionLiteralSupport -> CodeActionLiteralSupport -> Bool)
-> Eq CodeActionLiteralSupport
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeActionLiteralSupport -> CodeActionLiteralSupport -> Bool
$c/= :: CodeActionLiteralSupport -> CodeActionLiteralSupport -> Bool
== :: CodeActionLiteralSupport -> CodeActionLiteralSupport -> Bool
$c== :: CodeActionLiteralSupport -> CodeActionLiteralSupport -> Bool
Eq)

deriveJSON lspOptions ''CodeActionLiteralSupport

data CodeActionResolveClientCapabilities =
  CodeActionResolveClientCapabilities
    { CodeActionResolveClientCapabilities -> List Text
_properties :: List Text -- ^ The properties that a client can resolve lazily.
    } deriving (Int -> CodeActionResolveClientCapabilities -> ShowS
[CodeActionResolveClientCapabilities] -> ShowS
CodeActionResolveClientCapabilities -> String
(Int -> CodeActionResolveClientCapabilities -> ShowS)
-> (CodeActionResolveClientCapabilities -> String)
-> ([CodeActionResolveClientCapabilities] -> ShowS)
-> Show CodeActionResolveClientCapabilities
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeActionResolveClientCapabilities] -> ShowS
$cshowList :: [CodeActionResolveClientCapabilities] -> ShowS
show :: CodeActionResolveClientCapabilities -> String
$cshow :: CodeActionResolveClientCapabilities -> String
showsPrec :: Int -> CodeActionResolveClientCapabilities -> ShowS
$cshowsPrec :: Int -> CodeActionResolveClientCapabilities -> ShowS
Show, ReadPrec [CodeActionResolveClientCapabilities]
ReadPrec CodeActionResolveClientCapabilities
Int -> ReadS CodeActionResolveClientCapabilities
ReadS [CodeActionResolveClientCapabilities]
(Int -> ReadS CodeActionResolveClientCapabilities)
-> ReadS [CodeActionResolveClientCapabilities]
-> ReadPrec CodeActionResolveClientCapabilities
-> ReadPrec [CodeActionResolveClientCapabilities]
-> Read CodeActionResolveClientCapabilities
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CodeActionResolveClientCapabilities]
$creadListPrec :: ReadPrec [CodeActionResolveClientCapabilities]
readPrec :: ReadPrec CodeActionResolveClientCapabilities
$creadPrec :: ReadPrec CodeActionResolveClientCapabilities
readList :: ReadS [CodeActionResolveClientCapabilities]
$creadList :: ReadS [CodeActionResolveClientCapabilities]
readsPrec :: Int -> ReadS CodeActionResolveClientCapabilities
$creadsPrec :: Int -> ReadS CodeActionResolveClientCapabilities
Read, CodeActionResolveClientCapabilities
-> CodeActionResolveClientCapabilities -> Bool
(CodeActionResolveClientCapabilities
 -> CodeActionResolveClientCapabilities -> Bool)
-> (CodeActionResolveClientCapabilities
    -> CodeActionResolveClientCapabilities -> Bool)
-> Eq CodeActionResolveClientCapabilities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeActionResolveClientCapabilities
-> CodeActionResolveClientCapabilities -> Bool
$c/= :: CodeActionResolveClientCapabilities
-> CodeActionResolveClientCapabilities -> Bool
== :: CodeActionResolveClientCapabilities
-> CodeActionResolveClientCapabilities -> Bool
$c== :: CodeActionResolveClientCapabilities
-> CodeActionResolveClientCapabilities -> Bool
Eq)

deriveJSON lspOptions ''CodeActionResolveClientCapabilities

data CodeActionClientCapabilities = CodeActionClientCapabilities
  { -- | Whether code action supports dynamic registration.
    CodeActionClientCapabilities -> Maybe Bool
_dynamicRegistration :: Maybe Bool,
    -- | The client support code action literals as a valid response
    -- of the `textDocument/codeAction` request.
    -- Since 3.8.0
    CodeActionClientCapabilities -> Maybe CodeActionLiteralSupport
_codeActionLiteralSupport :: Maybe CodeActionLiteralSupport,
    -- | Whether code action supports the `isPreferred` property. Since LSP 3.15.0
    CodeActionClientCapabilities -> Maybe Bool
_isPreferredSupport :: Maybe Bool,
    -- | Whether code action supports the `disabled` property.
    --
    -- @since 3.16.0
    CodeActionClientCapabilities -> Maybe Bool
_disabledSupport :: Maybe Bool,
    -- | Whether code action supports the `data` property which is
    -- preserved between a `textDocument/codeAction` and a
    -- `codeAction/resolve` request.
    --
    -- @since 3.16.0
    CodeActionClientCapabilities -> Maybe Bool
_dataSupport :: Maybe Bool,
    -- | Whether the client supports resolving additional code action
    -- properties via a separate `codeAction/resolve` request.
    --
    -- @since 3.16.0
    CodeActionClientCapabilities
-> Maybe CodeActionResolveClientCapabilities
_resolveSupport :: Maybe CodeActionResolveClientCapabilities,
    -- | Whether the client honors the change annotations in
    -- text edits and resource operations returned via the
    -- `CodeAction#edit` property by for example presenting
    -- the workspace edit in the user interface and asking
    -- for confirmation.
    --
    -- @since 3.16.0
    CodeActionClientCapabilities -> Maybe Bool
_honorsChangeAnnotations :: Maybe Bool
  }
  deriving (Int -> CodeActionClientCapabilities -> ShowS
[CodeActionClientCapabilities] -> ShowS
CodeActionClientCapabilities -> String
(Int -> CodeActionClientCapabilities -> ShowS)
-> (CodeActionClientCapabilities -> String)
-> ([CodeActionClientCapabilities] -> ShowS)
-> Show CodeActionClientCapabilities
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeActionClientCapabilities] -> ShowS
$cshowList :: [CodeActionClientCapabilities] -> ShowS
show :: CodeActionClientCapabilities -> String
$cshow :: CodeActionClientCapabilities -> String
showsPrec :: Int -> CodeActionClientCapabilities -> ShowS
$cshowsPrec :: Int -> CodeActionClientCapabilities -> ShowS
Show, ReadPrec [CodeActionClientCapabilities]
ReadPrec CodeActionClientCapabilities
Int -> ReadS CodeActionClientCapabilities
ReadS [CodeActionClientCapabilities]
(Int -> ReadS CodeActionClientCapabilities)
-> ReadS [CodeActionClientCapabilities]
-> ReadPrec CodeActionClientCapabilities
-> ReadPrec [CodeActionClientCapabilities]
-> Read CodeActionClientCapabilities
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CodeActionClientCapabilities]
$creadListPrec :: ReadPrec [CodeActionClientCapabilities]
readPrec :: ReadPrec CodeActionClientCapabilities
$creadPrec :: ReadPrec CodeActionClientCapabilities
readList :: ReadS [CodeActionClientCapabilities]
$creadList :: ReadS [CodeActionClientCapabilities]
readsPrec :: Int -> ReadS CodeActionClientCapabilities
$creadsPrec :: Int -> ReadS CodeActionClientCapabilities
Read, CodeActionClientCapabilities
-> CodeActionClientCapabilities -> Bool
(CodeActionClientCapabilities
 -> CodeActionClientCapabilities -> Bool)
-> (CodeActionClientCapabilities
    -> CodeActionClientCapabilities -> Bool)
-> Eq CodeActionClientCapabilities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeActionClientCapabilities
-> CodeActionClientCapabilities -> Bool
$c/= :: CodeActionClientCapabilities
-> CodeActionClientCapabilities -> Bool
== :: CodeActionClientCapabilities
-> CodeActionClientCapabilities -> Bool
$c== :: CodeActionClientCapabilities
-> CodeActionClientCapabilities -> Bool
Eq)

deriveJSON lspOptions ''CodeActionClientCapabilities

-- -------------------------------------

makeExtendingDatatype "CodeActionOptions" [''WorkDoneProgressOptions]
  [("_codeActionKinds", [t| Maybe (List CodeActionKind) |]), ("_resolveProvider", [t| Maybe Bool |]) ]
deriveJSON lspOptions ''CodeActionOptions

makeExtendingDatatype "CodeActionRegistrationOptions"
  [ ''TextDocumentRegistrationOptions
  , ''CodeActionOptions
  ] []
deriveJSON lspOptions ''CodeActionRegistrationOptions

-- -------------------------------------

-- | Contains additional diagnostic information about the context in which a
-- code action is run.
data CodeActionContext = CodeActionContext
  { -- | An array of diagnostics known on the client side overlapping the range provided to the
    -- @textDocument/codeAction@ request. They are provided so that the server knows which
    -- errors are currently presented to the user for the given range. There is no guarantee
    -- that these accurately reflect the error state of the resource. The primary parameter
    -- to compute code actions is the provided range.
    CodeActionContext -> List Diagnostic
_diagnostics :: List Diagnostic
    -- | Requested kind of actions to return.
    --
    -- Actions not of this kind are filtered out by the client before being shown. So servers
    -- can omit computing them.
  , CodeActionContext -> Maybe (List CodeActionKind)
_only :: Maybe (List CodeActionKind)
  }
  deriving (ReadPrec [CodeActionContext]
ReadPrec CodeActionContext
Int -> ReadS CodeActionContext
ReadS [CodeActionContext]
(Int -> ReadS CodeActionContext)
-> ReadS [CodeActionContext]
-> ReadPrec CodeActionContext
-> ReadPrec [CodeActionContext]
-> Read CodeActionContext
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CodeActionContext]
$creadListPrec :: ReadPrec [CodeActionContext]
readPrec :: ReadPrec CodeActionContext
$creadPrec :: ReadPrec CodeActionContext
readList :: ReadS [CodeActionContext]
$creadList :: ReadS [CodeActionContext]
readsPrec :: Int -> ReadS CodeActionContext
$creadsPrec :: Int -> ReadS CodeActionContext
Read, Int -> CodeActionContext -> ShowS
[CodeActionContext] -> ShowS
CodeActionContext -> String
(Int -> CodeActionContext -> ShowS)
-> (CodeActionContext -> String)
-> ([CodeActionContext] -> ShowS)
-> Show CodeActionContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeActionContext] -> ShowS
$cshowList :: [CodeActionContext] -> ShowS
show :: CodeActionContext -> String
$cshow :: CodeActionContext -> String
showsPrec :: Int -> CodeActionContext -> ShowS
$cshowsPrec :: Int -> CodeActionContext -> ShowS
Show, CodeActionContext -> CodeActionContext -> Bool
(CodeActionContext -> CodeActionContext -> Bool)
-> (CodeActionContext -> CodeActionContext -> Bool)
-> Eq CodeActionContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeActionContext -> CodeActionContext -> Bool
$c/= :: CodeActionContext -> CodeActionContext -> Bool
== :: CodeActionContext -> CodeActionContext -> Bool
$c== :: CodeActionContext -> CodeActionContext -> Bool
Eq)

deriveJSON lspOptions ''CodeActionContext

makeExtendingDatatype "CodeActionParams"
  [ ''WorkDoneProgressParams
  , ''PartialResultParams
  ]
  [ ("_textDocument", [t|TextDocumentIdentifier|]),
    ("_range", [t|Range|]),
    ("_context", [t|CodeActionContext|])
  ]
deriveJSON lspOptions ''CodeActionParams

newtype Reason = Reason {Reason -> Text
_reason :: Text}
  deriving (ReadPrec [Reason]
ReadPrec Reason
Int -> ReadS Reason
ReadS [Reason]
(Int -> ReadS Reason)
-> ReadS [Reason]
-> ReadPrec Reason
-> ReadPrec [Reason]
-> Read Reason
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Reason]
$creadListPrec :: ReadPrec [Reason]
readPrec :: ReadPrec Reason
$creadPrec :: ReadPrec Reason
readList :: ReadS [Reason]
$creadList :: ReadS [Reason]
readsPrec :: Int -> ReadS Reason
$creadsPrec :: Int -> ReadS Reason
Read, Int -> Reason -> ShowS
[Reason] -> ShowS
Reason -> String
(Int -> Reason -> ShowS)
-> (Reason -> String) -> ([Reason] -> ShowS) -> Show Reason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Reason] -> ShowS
$cshowList :: [Reason] -> ShowS
show :: Reason -> String
$cshow :: Reason -> String
showsPrec :: Int -> Reason -> ShowS
$cshowsPrec :: Int -> Reason -> ShowS
Show, Reason -> Reason -> Bool
(Reason -> Reason -> Bool)
-> (Reason -> Reason -> Bool) -> Eq Reason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Reason -> Reason -> Bool
$c/= :: Reason -> Reason -> Bool
== :: Reason -> Reason -> Bool
$c== :: Reason -> Reason -> Bool
Eq)

deriveJSON lspOptions ''Reason

-- | A code action represents a change that can be performed in code, e.g. to fix a problem or
-- to refactor code.
--
-- A CodeAction must set either '_edit' and/or a '_command'. If both are supplied,
-- the '_edit' is applied first, then the '_command' is executed.
data CodeAction =
  CodeAction
  { -- | A short, human-readable, title for this code action.
    CodeAction -> Text
_title :: Text,
    -- | The kind of the code action. Used to filter code actions.
    CodeAction -> Maybe CodeActionKind
_kind :: Maybe CodeActionKind,
    -- | The diagnostics that this code action resolves.
    CodeAction -> Maybe (List Diagnostic)
_diagnostics :: Maybe (List Diagnostic),
    -- | Marks this as a preferred action. Preferred actions are used by the `auto fix` command and can be targeted
    -- by keybindings.
    --
    -- A quick fix should be marked preferred if it properly addresses the underlying error.
    -- A refactoring should be marked preferred if it is the most reasonable choice of actions to take.
    --
    -- Since LSP 3.15.0
    CodeAction -> Maybe Bool
_isPreferred :: Maybe Bool,
    CodeAction -> Maybe Reason
_disabled    :: Maybe Reason, -- ^ Marks that the code action cannot currently be applied.
    -- | The workspace edit this code action performs.
    CodeAction -> Maybe WorkspaceEdit
_edit :: Maybe WorkspaceEdit,
    -- | A command this code action executes. If a code action
    -- provides an edit and a command, first the edit is
    -- executed and then the command.
    CodeAction -> Maybe Command
_command :: Maybe Command,
    -- | A data entry field that is preserved on a code action between
    -- a `textDocument/codeAction` and a `codeAction/resolve` request.
    --
    -- @since 3.16.0
    CodeAction -> Maybe Value
_xdata :: Maybe Value
  }
  deriving (ReadPrec [CodeAction]
ReadPrec CodeAction
Int -> ReadS CodeAction
ReadS [CodeAction]
(Int -> ReadS CodeAction)
-> ReadS [CodeAction]
-> ReadPrec CodeAction
-> ReadPrec [CodeAction]
-> Read CodeAction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CodeAction]
$creadListPrec :: ReadPrec [CodeAction]
readPrec :: ReadPrec CodeAction
$creadPrec :: ReadPrec CodeAction
readList :: ReadS [CodeAction]
$creadList :: ReadS [CodeAction]
readsPrec :: Int -> ReadS CodeAction
$creadsPrec :: Int -> ReadS CodeAction
Read, Int -> CodeAction -> ShowS
[CodeAction] -> ShowS
CodeAction -> String
(Int -> CodeAction -> ShowS)
-> (CodeAction -> String)
-> ([CodeAction] -> ShowS)
-> Show CodeAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeAction] -> ShowS
$cshowList :: [CodeAction] -> ShowS
show :: CodeAction -> String
$cshow :: CodeAction -> String
showsPrec :: Int -> CodeAction -> ShowS
$cshowsPrec :: Int -> CodeAction -> ShowS
Show, CodeAction -> CodeAction -> Bool
(CodeAction -> CodeAction -> Bool)
-> (CodeAction -> CodeAction -> Bool) -> Eq CodeAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeAction -> CodeAction -> Bool
$c/= :: CodeAction -> CodeAction -> Bool
== :: CodeAction -> CodeAction -> Bool
$c== :: CodeAction -> CodeAction -> Bool
Eq)
deriveJSON lspOptions ''CodeAction