@@ -6,7 +6,9 @@ module Language.LSP.Types.CodeAction where
66import Data.Aeson.TH
77import Data.Aeson.Types
88import Data.Default
9+ import Data.String
910import Data.Text ( Text )
11+ import qualified Data.Text as T
1012import Language.LSP.Types.Command
1113import Language.LSP.Types.Diagnostic
1214import Language.LSP.Types.Common
@@ -62,29 +64,57 @@ data CodeActionKind
6264 | CodeActionUnknown Text
6365 deriving (Read , Show , Eq )
6466
67+ fromHierarchicalString :: Text -> CodeActionKind
68+ fromHierarchicalString t = case t of
69+ " " -> CodeActionEmpty
70+ " quickfix" -> CodeActionQuickFix
71+ " refactor" -> CodeActionRefactor
72+ " refactor.extract" -> CodeActionRefactorExtract
73+ " refactor.inline" -> CodeActionRefactorInline
74+ " refactor.rewrite" -> CodeActionRefactorRewrite
75+ " source" -> CodeActionSource
76+ " source.organizeImports" -> CodeActionSourceOrganizeImports
77+ s -> CodeActionUnknown s
78+
79+ toHierarchicalString :: CodeActionKind -> Text
80+ toHierarchicalString k = case k of
81+ CodeActionEmpty -> " "
82+ CodeActionQuickFix -> " quickfix"
83+ CodeActionRefactor -> " refactor"
84+ CodeActionRefactorExtract -> " refactor.extract"
85+ CodeActionRefactorInline -> " refactor.inline"
86+ CodeActionRefactorRewrite -> " refactor.rewrite"
87+ CodeActionSource -> " source"
88+ CodeActionSourceOrganizeImports -> " source.organizeImports"
89+ (CodeActionUnknown s) -> s
90+
91+ instance IsString CodeActionKind where
92+ fromString = fromHierarchicalString . T. pack
93+
6594instance ToJSON CodeActionKind where
66- toJSON CodeActionEmpty = String " "
67- toJSON CodeActionQuickFix = String " quickfix"
68- toJSON CodeActionRefactor = String " refactor"
69- toJSON CodeActionRefactorExtract = String " refactor.extract"
70- toJSON CodeActionRefactorInline = String " refactor.inline"
71- toJSON CodeActionRefactorRewrite = String " refactor.rewrite"
72- toJSON CodeActionSource = String " source"
73- toJSON CodeActionSourceOrganizeImports = String " source.organizeImports"
74- toJSON (CodeActionUnknown s) = String s
95+ toJSON = String . toHierarchicalString
7596
7697instance FromJSON CodeActionKind where
77- parseJSON (String " " ) = pure CodeActionEmpty
78- parseJSON (String " quickfix" ) = pure CodeActionQuickFix
79- parseJSON (String " refactor" ) = pure CodeActionRefactor
80- parseJSON (String " refactor.extract" ) = pure CodeActionRefactorExtract
81- parseJSON (String " refactor.inline" ) = pure CodeActionRefactorInline
82- parseJSON (String " refactor.rewrite" ) = pure CodeActionRefactorRewrite
83- parseJSON (String " source" ) = pure CodeActionSource
84- parseJSON (String " source.organizeImports" ) = pure CodeActionSourceOrganizeImports
85- parseJSON (String s) = pure (CodeActionUnknown s)
86- parseJSON _ = fail " CodeActionKind"
87-
98+ parseJSON (String s) = pure $ fromHierarchicalString s
99+ parseJSON _ = fail " CodeActionKind"
100+
101+ -- | Does the first 'CodeActionKind' subsume the other one, hierarchically. Reflexive.
102+ codeActionKindSubsumes :: CodeActionKind -> CodeActionKind -> Bool
103+ -- Simple but ugly implementation: prefix on the string representation
104+ codeActionKindSubsumes parent child = toHierarchicalString parent `T.isPrefixOf` toHierarchicalString child
105+
106+ -- | The 'CodeActionKind's listed in the LSP spec specifically.
107+ specCodeActionKinds :: [CodeActionKind ]
108+ specCodeActionKinds = [
109+ CodeActionQuickFix
110+ , CodeActionRefactor
111+ , CodeActionRefactorExtract
112+ , CodeActionRefactorInline
113+ , CodeActionRefactorRewrite
114+ , CodeActionSource
115+ , CodeActionSourceOrganizeImports
116+ ]
117+
88118-- -------------------------------------
89119
90120data CodeActionKindClientCapabilities =
@@ -99,15 +129,7 @@ data CodeActionKindClientCapabilities =
99129deriveJSON lspOptions ''CodeActionKindClientCapabilities
100130
101131instance Default CodeActionKindClientCapabilities where
102- def = CodeActionKindClientCapabilities (List allKinds)
103- where allKinds = [ CodeActionQuickFix
104- , CodeActionRefactor
105- , CodeActionRefactorExtract
106- , CodeActionRefactorInline
107- , CodeActionRefactorRewrite
108- , CodeActionSource
109- , CodeActionSourceOrganizeImports
110- ]
132+ def = CodeActionKindClientCapabilities (List specCodeActionKinds)
111133
112134data CodeActionLiteralSupport =
113135 CodeActionLiteralSupport
0 commit comments