5
5
6
6
module Ide.Plugin.ConfigUtils where
7
7
8
+ import Control.Lens (at , ix , (&) , (?~) )
8
9
import qualified Data.Aeson as A
10
+ import Data.Aeson.Lens (_Object )
9
11
import qualified Data.Aeson.Types as A
10
12
import Data.Default (def )
11
13
import qualified Data.Dependent.Map as DMap
12
14
import qualified Data.Dependent.Sum as DSum
13
- import qualified Data.HashMap.Lazy as HMap
14
15
import Data.List (nub )
16
+ import Data.String (IsString (fromString ))
17
+ import qualified Data.Text as T
15
18
import Ide.Plugin.Config
16
19
import Ide.Plugin.Properties (toDefaultJSON , toVSCodeExtensionSchema )
17
20
import Ide.Types
@@ -25,17 +28,12 @@ import Language.LSP.Types
25
28
-- | Generates a default 'Config', but remains only effective items
26
29
pluginsToDefaultConfig :: IdePlugins a -> A. Value
27
30
pluginsToDefaultConfig IdePlugins {.. } =
28
- A. Object $
29
- HMap. adjust
30
- ( \ (unsafeValueToObject -> o) ->
31
- A. Object $ HMap. insert " plugin" elems o -- inplace the "plugin" section with our 'elems', leaving others unchanged
32
- )
33
- " haskell"
34
- (unsafeValueToObject (A. toJSON defaultConfig))
31
+ -- Use 'ix' to look at all the "haskell" keys in the outer value (since we're not
32
+ -- setting it if missing), then we use '_Object' and 'at' to get at the "plugin" key
33
+ -- and actually set it.
34
+ A. toJSON defaultConfig & ix " haskell" . _Object . at " plugin" ?~ elems
35
35
where
36
36
defaultConfig@ Config {} = def
37
- unsafeValueToObject (A. Object o) = o
38
- unsafeValueToObject _ = error " impossible"
39
37
elems = A. object $ mconcat $ singlePlugin <$> map snd ipMap
40
38
-- Splice genericDefaultConfig and dedicatedDefaultConfig
41
39
-- Example:
@@ -52,7 +50,7 @@ pluginsToDefaultConfig IdePlugins {..} =
52
50
-- }
53
51
singlePlugin PluginDescriptor {pluginConfigDescriptor = ConfigDescriptor {.. }, .. } =
54
52
let x = genericDefaultConfig <> dedicatedDefaultConfig
55
- in [pId A. .= A. object x | not $ null x]
53
+ in [fromString ( T. unpack pId) A. .= A. object x | not $ null x]
56
54
where
57
55
(PluginHandlers (DMap. toList -> handlers)) = pluginHandlers
58
56
customConfigToDedicatedDefaultConfig (CustomConfig p) = toDefaultJSON p
@@ -107,22 +105,22 @@ pluginsToVSCodeExtensionSchema IdePlugins {..} = A.object $ mconcat $ singlePlug
107
105
(PluginId pId) = pluginId
108
106
genericSchema =
109
107
let x =
110
- [withIdPrefix " diagnosticsOn" A. .= schemaEntry " diagnostics" | configHasDiagnostics]
108
+ [toKey' " diagnosticsOn" A. .= schemaEntry " diagnostics" | configHasDiagnostics]
111
109
<> nub (mconcat (handlersToGenericSchema <$> handlers))
112
110
in case x of
113
111
-- If the plugin has only one capability, we produce globalOn instead of the specific one;
114
112
-- otherwise we don't produce globalOn at all
115
- [_] -> [withIdPrefix " globalOn" A. .= schemaEntry " plugin" ]
113
+ [_] -> [toKey' " globalOn" A. .= schemaEntry " plugin" ]
116
114
_ -> x
117
115
dedicatedSchema = customConfigToDedicatedSchema configCustomConfig
118
116
handlersToGenericSchema (IdeMethod m DSum. :=> _) = case m of
119
- STextDocumentCodeAction -> [withIdPrefix " codeActionsOn" A. .= schemaEntry " code actions" ]
120
- STextDocumentCodeLens -> [withIdPrefix " codeLensOn" A. .= schemaEntry " code lenses" ]
121
- STextDocumentRename -> [withIdPrefix " renameOn" A. .= schemaEntry " rename" ]
122
- STextDocumentHover -> [withIdPrefix " hoverOn" A. .= schemaEntry " hover" ]
123
- STextDocumentDocumentSymbol -> [withIdPrefix " symbolsOn" A. .= schemaEntry " symbols" ]
124
- STextDocumentCompletion -> [withIdPrefix " completionOn" A. .= schemaEntry " completions" ]
125
- STextDocumentPrepareCallHierarchy -> [withIdPrefix " callHierarchyOn" A. .= schemaEntry " call hierarchy" ]
117
+ STextDocumentCodeAction -> [toKey' " codeActionsOn" A. .= schemaEntry " code actions" ]
118
+ STextDocumentCodeLens -> [toKey' " codeLensOn" A. .= schemaEntry " code lenses" ]
119
+ STextDocumentRename -> [toKey' " renameOn" A. .= schemaEntry " rename" ]
120
+ STextDocumentHover -> [toKey' " hoverOn" A. .= schemaEntry " hover" ]
121
+ STextDocumentDocumentSymbol -> [toKey' " symbolsOn" A. .= schemaEntry " symbols" ]
122
+ STextDocumentCompletion -> [toKey' " completionOn" A. .= schemaEntry " completions" ]
123
+ STextDocumentPrepareCallHierarchy -> [toKey' " callHierarchyOn" A. .= schemaEntry " call hierarchy" ]
126
124
_ -> []
127
125
schemaEntry desc =
128
126
A. object
@@ -132,3 +130,4 @@ pluginsToVSCodeExtensionSchema IdePlugins {..} = A.object $ mconcat $ singlePlug
132
130
" description" A. .= A. String (" Enables " <> pId <> " " <> desc)
133
131
]
134
132
withIdPrefix x = " haskell.plugin." <> pId <> " ." <> x
133
+ toKey' = fromString . T. unpack . withIdPrefix
0 commit comments