forked from haskell/haskell-language-server
-
Notifications
You must be signed in to change notification settings - Fork 2
/
Copy pathTacticProviders.hs
335 lines (287 loc) · 12 KB
/
TacticProviders.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Wingman.LanguageServer.TacticProviders
( commandProvider
, commandTactic
, tcCommandId
, TacticParams (..)
, TacticProviderData (..)
, useNameFromHypothesis
) where
import Control.Monad
import Data.Aeson
import Data.Bool (bool)
import Data.Coerce
import Data.Maybe
import Data.Monoid
import qualified Data.Text as T
import Data.Traversable
import DataCon (dataConName)
import Development.IDE.Core.UseStale (Tracked, Age(..))
import Development.IDE.GHC.Compat
import GHC.Generics
import GHC.LanguageExtensions.Type (Extension (LambdaCase))
import Ide.PluginUtils
import Ide.Types
import Language.LSP.Types
import OccName
import Prelude hiding (span)
import Wingman.Auto
import Wingman.GHC
import Wingman.Judgements
import Wingman.Machinery (useNameFromHypothesis)
import Wingman.Metaprogramming.Parser (parseMetaprogram)
import Wingman.Tactics
import Wingman.Types
------------------------------------------------------------------------------
-- | A mapping from tactic commands to actual tactics for refinery.
commandTactic :: TacticCommand -> T.Text -> TacticsM ()
commandTactic Auto = const auto
commandTactic Intros = const intros
commandTactic Destruct = useNameFromHypothesis destruct . mkVarOcc . T.unpack
commandTactic DestructPun = useNameFromHypothesis destructPun . mkVarOcc . T.unpack
commandTactic Homomorphism = useNameFromHypothesis homo . mkVarOcc . T.unpack
commandTactic DestructLambdaCase = const destructLambdaCase
commandTactic HomomorphismLambdaCase = const homoLambdaCase
commandTactic DestructAll = const destructAll
commandTactic UseDataCon = userSplit . mkVarOcc . T.unpack
commandTactic Refine = const refine
commandTactic BeginMetaprogram = const metaprogram
commandTactic RunMetaprogram = parseMetaprogram
------------------------------------------------------------------------------
-- | The LSP kind
tacticKind :: TacticCommand -> T.Text
tacticKind Auto = "fillHole"
tacticKind Intros = "introduceLambda"
tacticKind Destruct = "caseSplit"
tacticKind DestructPun = "caseSplitPun"
tacticKind Homomorphism = "homomorphicCaseSplit"
tacticKind DestructLambdaCase = "lambdaCase"
tacticKind HomomorphismLambdaCase = "homomorphicLambdaCase"
tacticKind DestructAll = "splitFuncArgs"
tacticKind UseDataCon = "useConstructor"
tacticKind Refine = "refine"
tacticKind BeginMetaprogram = "beginMetaprogram"
tacticKind RunMetaprogram = "runMetaprogram"
------------------------------------------------------------------------------
-- | Whether or not this code action is preferred -- ostensibly refers to
-- whether or not we can bind it to a key in vs code?
tacticPreferred :: TacticCommand -> Bool
tacticPreferred Auto = True
tacticPreferred Intros = True
tacticPreferred Destruct = True
tacticPreferred DestructPun = False
tacticPreferred Homomorphism = False
tacticPreferred DestructLambdaCase = False
tacticPreferred HomomorphismLambdaCase = False
tacticPreferred DestructAll = True
tacticPreferred UseDataCon = True
tacticPreferred Refine = True
tacticPreferred BeginMetaprogram = False
tacticPreferred RunMetaprogram = True
mkTacticKind :: TacticCommand -> CodeActionKind
mkTacticKind =
CodeActionUnknown . mappend "refactor.wingman." . tacticKind
------------------------------------------------------------------------------
-- | Mapping from tactic commands to their contextual providers. See 'provide',
-- 'filterGoalType' and 'filterBindingType' for the nitty gritty.
commandProvider :: TacticCommand -> TacticProvider
commandProvider Auto =
requireHoleSort (== Hole) $
provide Auto ""
commandProvider Intros =
requireHoleSort (== Hole) $
filterGoalType isFunction $
provide Intros ""
commandProvider Destruct =
requireHoleSort (== Hole) $
filterBindingType destructFilter $ \occ _ ->
provide Destruct $ T.pack $ occNameString occ
commandProvider DestructPun =
requireHoleSort (== Hole) $
filterBindingType destructPunFilter $ \occ _ ->
provide DestructPun $ T.pack $ occNameString occ
commandProvider Homomorphism =
requireHoleSort (== Hole) $
filterBindingType homoFilter $ \occ _ ->
provide Homomorphism $ T.pack $ occNameString occ
commandProvider DestructLambdaCase =
requireHoleSort (== Hole) $
requireExtension LambdaCase $
filterGoalType (isJust . lambdaCaseable) $
provide DestructLambdaCase ""
commandProvider HomomorphismLambdaCase =
requireHoleSort (== Hole) $
requireExtension LambdaCase $
filterGoalType ((== Just True) . lambdaCaseable) $
provide HomomorphismLambdaCase ""
commandProvider DestructAll =
requireHoleSort (== Hole) $
withJudgement $ \jdg ->
case _jIsTopHole jdg && jHasBoundArgs jdg of
True -> provide DestructAll ""
False -> mempty
commandProvider UseDataCon =
requireHoleSort (== Hole) $
withConfig $ \cfg ->
filterTypeProjection
( guardLength (<= cfg_max_use_ctor_actions cfg)
. fromMaybe []
. fmap fst
. tacticsGetDataCons
) $ \dcon ->
provide UseDataCon
. T.pack
. occNameString
. occName
$ dataConName dcon
commandProvider Refine =
requireHoleSort (== Hole) $
provide Refine ""
commandProvider BeginMetaprogram =
requireGHC88OrHigher $
requireHoleSort (== Hole) $
provide BeginMetaprogram ""
commandProvider RunMetaprogram =
requireGHC88OrHigher $
withMetaprogram $ \mp ->
provide RunMetaprogram mp
requireGHC88OrHigher :: TacticProvider -> TacticProvider
requireGHC88OrHigher tp tpd =
#if __GLASGOW_HASKELL__ >= 808
tp tpd
#else
mempty
#endif
------------------------------------------------------------------------------
-- | Return an empty list if the given predicate doesn't hold over the length
guardLength :: (Int -> Bool) -> [a] -> [a]
guardLength f as = bool [] as $ f $ length as
------------------------------------------------------------------------------
-- | A 'TacticProvider' is a way of giving context-sensitive actions to the LS
-- UI.
type TacticProvider
= TacticProviderData
-> IO [Command |? CodeAction]
data TacticProviderData = TacticProviderData
{ tpd_dflags :: DynFlags
, tpd_config :: Config
, tpd_plid :: PluginId
, tpd_uri :: Uri
, tpd_range :: Tracked 'Current Range
, tpd_jdg :: Judgement
, tpd_hole_sort :: HoleSort
}
data TacticParams = TacticParams
{ tp_file :: Uri -- ^ Uri of the file to fill the hole in
, tp_range :: Tracked 'Current Range -- ^ The range of the hole
, tp_var_name :: T.Text
}
deriving stock (Show, Eq, Generic)
deriving anyclass (ToJSON, FromJSON)
requireHoleSort :: (HoleSort -> Bool) -> TacticProvider -> TacticProvider
requireHoleSort p tp tpd =
case p $ tpd_hole_sort tpd of
True -> tp tpd
False -> pure []
withMetaprogram :: (T.Text -> TacticProvider) -> TacticProvider
withMetaprogram tp tpd =
case tpd_hole_sort tpd of
Metaprogram mp -> tp mp tpd
_ -> pure []
------------------------------------------------------------------------------
-- | Restrict a 'TacticProvider', making sure it appears only when the given
-- predicate holds for the goal.
requireExtension :: Extension -> TacticProvider -> TacticProvider
requireExtension ext tp tpd =
case xopt ext $ tpd_dflags tpd of
True -> tp tpd
False -> pure []
------------------------------------------------------------------------------
-- | Restrict a 'TacticProvider', making sure it appears only when the given
-- predicate holds for the goal.
filterGoalType :: (Type -> Bool) -> TacticProvider -> TacticProvider
filterGoalType p tp tpd =
case p $ unCType $ jGoal $ tpd_jdg tpd of
True -> tp tpd
False -> pure []
------------------------------------------------------------------------------
-- | Restrict a 'TacticProvider', making sure it appears only when the given
-- predicate holds for the goal.
withJudgement :: (Judgement -> TacticProvider) -> TacticProvider
withJudgement tp tpd = tp (tpd_jdg tpd) tpd
------------------------------------------------------------------------------
-- | Multiply a 'TacticProvider' for each binding, making sure it appears only
-- when the given predicate holds over the goal and binding types.
filterBindingType
:: (Type -> Type -> Bool) -- ^ Goal and then binding types.
-> (OccName -> Type -> TacticProvider)
-> TacticProvider
filterBindingType p tp tpd =
let jdg = tpd_jdg tpd
hy = jLocalHypothesis jdg
g = jGoal jdg
in fmap join $ for (unHypothesis hy) $ \hi ->
let ty = unCType $ hi_type hi
in case p (unCType g) ty of
True -> tp (hi_name hi) ty tpd
False -> pure []
------------------------------------------------------------------------------
-- | Multiply a 'TacticProvider' by some feature projection out of the goal
-- type. Used e.g. to crete a code action for every data constructor.
filterTypeProjection
:: (Type -> [a]) -- ^ Features of the goal to look into further
-> (a -> TacticProvider)
-> TacticProvider
filterTypeProjection p tp tpd =
fmap join $ for (p $ unCType $ jGoal $ tpd_jdg tpd) $ \a ->
tp a tpd
------------------------------------------------------------------------------
-- | Get access to the 'Config' when building a 'TacticProvider'.
withConfig :: (Config -> TacticProvider) -> TacticProvider
withConfig tp tpd = tp (tpd_config tpd) tpd
------------------------------------------------------------------------------
-- | Terminal constructor for providing context-sensitive tactics. Tactics
-- given by 'provide' are always available.
provide :: TacticCommand -> T.Text -> TacticProvider
provide tc name TacticProviderData{..} = do
let title = tacticTitle tc name
params = TacticParams { tp_file = tpd_uri , tp_range = tpd_range , tp_var_name = name }
cmd = mkLspCommand tpd_plid (tcCommandId tc) title (Just [toJSON params])
pure
$ pure
$ InR
$ CodeAction
{ _title = title
, _kind = Just $ mkTacticKind tc
, _diagnostics = Nothing
, _isPreferred = Just $ tacticPreferred tc
, _disabled = Nothing
, _edit = Nothing
, _command = Just cmd
, _xdata = Nothing
}
------------------------------------------------------------------------------
-- | Construct a 'CommandId'
tcCommandId :: TacticCommand -> CommandId
tcCommandId c = coerce $ T.pack $ "tactics" <> show c <> "Command"
------------------------------------------------------------------------------
-- | We should show homos only when the goal type is the same as the binding
-- type, and that both are usual algebraic types.
homoFilter :: Type -> Type -> Bool
homoFilter (algebraicTyCon -> Just t1) (algebraicTyCon -> Just t2) = t1 == t2
homoFilter _ _ = False
------------------------------------------------------------------------------
-- | We should show destruct for bindings only when those bindings have usual
-- algebraic types.
destructFilter :: Type -> Type -> Bool
destructFilter _ (algebraicTyCon -> Just _) = True
destructFilter _ _ = False
------------------------------------------------------------------------------
-- | We should show destruct punning for bindings only when those bindings have
-- usual algebraic types, and when any of their data constructors are records.
destructPunFilter :: Type -> Type -> Bool
destructPunFilter _ (algebraicTyCon -> Just tc) =
any (not . null . dataConFieldLabels) $ tyConDataCons tc
destructPunFilter _ _ = False