7
7
module Haskell.Ide.Engine.Plugin.HaRe where
8
8
9
9
import Control.Lens.Operators
10
+ import Control.Lens.Setter ((%~) )
11
+ import Control.Lens.Traversal (traverseOf )
10
12
import Control.Monad.State
11
13
import Control.Monad.Trans.Control
12
14
import Data.Aeson
@@ -22,12 +24,14 @@ import qualified Data.Text.IO as T
22
24
import Exception
23
25
import GHC.Generics (Generic )
24
26
import qualified GhcMod.Error as GM
27
+ import qualified GhcMod.Exe.CaseSplit as GM
25
28
import qualified GhcMod.Monad as GM
26
29
import qualified GhcMod.Utils as GM
27
30
import Haskell.Ide.Engine.ArtifactMap
28
31
import Haskell.Ide.Engine.MonadFunctions
29
32
import Haskell.Ide.Engine.MonadTypes
30
33
import Haskell.Ide.Engine.PluginUtils
34
+ import Haskell.Ide.Engine.Plugin.GhcMod (runGhcModCommand )
31
35
import qualified Haskell.Ide.Engine.Plugin.HieExtras as Hie
32
36
import Language.Haskell.GHC.ExactPrint.Print
33
37
import qualified Language.Haskell.LSP.Core as Core
@@ -64,6 +68,9 @@ hareDescriptor plId = PluginDescriptor
64
68
deleteDefCmd
65
69
, PluginCommand " genapplicative" " Generalise a monadic function to use applicative"
66
70
genApplicativeCommand
71
+
72
+ , PluginCommand " casesplit" " Generate a pattern match for a binding under (LINE,COL)"
73
+ splitCaseCmd
67
74
]
68
75
, pluginCodeActionProvider = Just codeActionProvider
69
76
, pluginDiagnosticProvider = Nothing
@@ -213,6 +220,64 @@ genApplicativeCommand' uri pos =
213
220
214
221
-- ---------------------------------------------------------------------
215
222
223
+ splitCaseCmd :: CommandFunc HarePoint WorkspaceEdit
224
+ splitCaseCmd = CmdSync $ \ _ (HP uri pos) -> splitCaseCmd' uri pos
225
+
226
+ splitCaseCmd' :: Uri -> Position -> IdeGhcM (IdeResult WorkspaceEdit )
227
+ splitCaseCmd' uri newPos =
228
+ pluginGetFile " splitCaseCmd: " uri $ \ path -> do
229
+ origText <- GM. withMappedFile path $ liftIO . T. readFile
230
+ ifCachedModule path (IdeResultOk mempty ) $ \ tm info -> runGhcModCommand $
231
+ case newPosToOld info newPos of
232
+ Just oldPos -> do
233
+ let (line, column) = unPos oldPos
234
+ splitResult' <- GM. splits' path tm line column
235
+ case splitResult' of
236
+ Just splitResult -> do
237
+ wEdit <- liftToGhc $ splitResultToWorkspaceEdit origText splitResult
238
+ return $ oldToNewPositions info wEdit
239
+ Nothing -> return mempty
240
+ Nothing -> return mempty
241
+ where
242
+
243
+ -- | Transform all ranges in a WorkspaceEdit from old to new positions.
244
+ oldToNewPositions :: CachedInfo -> WorkspaceEdit -> WorkspaceEdit
245
+ oldToNewPositions info wsEdit =
246
+ wsEdit
247
+ & J. documentChanges %~ (>>= traverseOf (traverse . J. edits . traverse . J. range) (oldRangeToNew info))
248
+ & J. changes %~ (>>= traverseOf (traverse . traverse . J. range) (oldRangeToNew info))
249
+
250
+ -- | Given the range and text to replace, construct a 'WorkspaceEdit'
251
+ -- by diffing the change against the current text.
252
+ splitResultToWorkspaceEdit :: T. Text -> GM. SplitResult -> IdeM WorkspaceEdit
253
+ splitResultToWorkspaceEdit originalText (GM. SplitResult replaceFromLine replaceFromCol replaceToLine replaceToCol replaceWith) =
254
+ diffText (uri, originalText) newText IncludeDeletions
255
+ where
256
+ before = takeUntil (toPos (replaceFromLine, replaceFromCol)) originalText
257
+ after = dropUntil (toPos (replaceToLine, replaceToCol)) originalText
258
+ newText = before <> replaceWith <> after
259
+
260
+ -- | Take the first part of text until the given position.
261
+ -- Returns all characters before the position.
262
+ takeUntil :: Position -> T. Text -> T. Text
263
+ takeUntil (Position l c) txt =
264
+ T. unlines takeLines <> takeCharacters
265
+ where
266
+ textLines = T. lines txt
267
+ takeLines = take l textLines
268
+ takeCharacters = T. take c (textLines !! c)
269
+
270
+ -- | Drop the first part of text until the given position.
271
+ -- Returns all characters after and including the position.
272
+ dropUntil :: Position -> T. Text -> T. Text
273
+ dropUntil (Position l c) txt = dropCharacters
274
+ where
275
+ textLines = T. lines txt
276
+ dropLines = drop l textLines
277
+ dropCharacters = T. drop c (T. unlines dropLines)
278
+
279
+ -- ---------------------------------------------------------------------
280
+
216
281
getRefactorResult :: [ApplyRefacResult ] -> [(FilePath ,T. Text )]
217
282
getRefactorResult = map getNewFile . filter fileModified
218
283
where fileModified ((_,m),_) = m == RefacModified
@@ -294,20 +359,26 @@ hoist f a =
294
359
codeActionProvider :: CodeActionProvider
295
360
codeActionProvider pId docId _ _ (J. Range pos _) _ =
296
361
pluginGetFile " HaRe codeActionProvider: " (docId ^. J. uri) $ \ file ->
297
- ifCachedInfo file (IdeResultOk mempty ) $ \ info -> do
298
- let symbols = getArtifactsAtPos pos (defMap info)
299
- debugm $ show $ map (Hie. showName . snd ) symbols
300
- if not (null symbols)
301
- then
302
- let name = Hie. showName $ snd $ head symbols
303
- in IdeResultOk <$> sequence [
362
+ ifCachedInfo file (IdeResultOk mempty ) $ \ info ->
363
+ case getArtifactsAtPos pos (defMap info) of
364
+ [h] -> do
365
+ let name = Hie. showName $ snd h
366
+ debugm $ show name
367
+ IdeResultOk <$> sequence [
304
368
mkLiftOneAction name
305
369
, mkLiftTopAction name
306
370
, mkDemoteAction name
307
371
, mkDeleteAction name
308
372
, mkDuplicateAction name
309
373
]
310
- else return (IdeResultOk [] )
374
+ _ -> case getArtifactsAtPos pos (locMap info) of
375
+ [h] -> do
376
+ let name = Hie. showName $ snd h
377
+ debugm $ show name
378
+ IdeResultOk <$> sequence [
379
+ mkCaseSplitAction name
380
+ ]
381
+ _ -> return $ IdeResultOk []
311
382
312
383
where
313
384
mkLiftOneAction name = do
@@ -339,3 +410,9 @@ codeActionProvider pId docId _ _ (J.Range pos _) _ =
339
410
title = " Duplicate definition of " <> name
340
411
dupCmd <- mkLspCommand pId " dupdef" title (Just args)
341
412
return $ J. CodeAction title (Just J. CodeActionRefactor ) mempty Nothing (Just dupCmd)
413
+
414
+ mkCaseSplitAction name = do
415
+ let args = [J. toJSON $ HP (docId ^. J. uri) pos]
416
+ title = " Case split on " <> name
417
+ splCmd <- mkLspCommand pId " casesplit" title (Just args)
418
+ return $ J. CodeAction title (Just J. CodeActionRefactorRewrite ) mempty Nothing (Just splCmd)
0 commit comments