@@ -121,6 +121,7 @@ import Ide.Types hiding
121
121
import Language.Haskell.HLint as Hlint hiding
122
122
(Error )
123
123
import Language.LSP.Server (ProgressCancellable (Cancellable ),
124
+ getVersionedTextDoc ,
124
125
sendRequest ,
125
126
withIndefiniteProgress )
126
127
import Language.LSP.Types hiding
@@ -407,8 +408,11 @@ codeActionProvider :: PluginMethodHandler IdeState TextDocumentCodeAction
407
408
codeActionProvider ideState pluginId (CodeActionParams _ _ documentId _ context)
408
409
| let TextDocumentIdentifier uri = documentId
409
410
, Just docNormalizedFilePath <- uriToNormalizedFilePath (toNormalizedUri uri)
410
- = liftIO $ fmap (Right . LSP. List . map LSP. InR ) $ do
411
+ = do
412
+ verTxtDocId <- getVersionedTextDoc documentId
413
+ liftIO $ fmap (Right . LSP. List . map LSP. InR ) $ do
411
414
allDiagnostics <- atomically $ getDiagnostics ideState
415
+
412
416
let numHintsInDoc = length
413
417
[diagnostic | (diagnosticNormalizedFilePath, _, diagnostic) <- allDiagnostics
414
418
, validCommand diagnostic
@@ -425,19 +429,19 @@ codeActionProvider ideState pluginId (CodeActionParams _ _ documentId _ context)
425
429
pure if | Just modSummaryResult <- modSummaryResult
426
430
, Just source <- source
427
431
, let dynFlags = ms_hspp_opts $ msrModSummary modSummaryResult ->
428
- diags >>= diagnosticToCodeActions dynFlags source pluginId documentId
432
+ diags >>= diagnosticToCodeActions dynFlags source pluginId verTxtDocId
429
433
| otherwise -> []
430
434
| otherwise -> pure []
431
435
if numHintsInDoc > 1 && numHintsInContext > 0 then do
432
- pure $ singleHintCodeActions ++ [applyAllAction]
436
+ pure $ singleHintCodeActions ++ [applyAllAction verTxtDocId ]
433
437
else
434
438
pure singleHintCodeActions
435
439
| otherwise
436
440
= pure $ Right $ LSP. List []
437
441
438
442
where
439
- applyAllAction =
440
- let args = Just [toJSON (documentId ^. LSP. uri) ]
443
+ applyAllAction verTxtDocId =
444
+ let args = Just [toJSON verTxtDocId ]
441
445
cmd = mkLspCommand pluginId " applyAll" " Apply all hints" args
442
446
in LSP. CodeAction " Apply all hints" (Just LSP. CodeActionQuickFix ) Nothing Nothing Nothing Nothing (Just cmd) Nothing
443
447
@@ -451,25 +455,24 @@ codeActionProvider ideState pluginId (CodeActionParams _ _ documentId _ context)
451
455
452
456
-- | Convert a hlint diagnostic into an apply and an ignore code action
453
457
-- if applicable
454
- diagnosticToCodeActions :: DynFlags -> T. Text -> PluginId -> TextDocumentIdentifier -> LSP. Diagnostic -> [LSP. CodeAction ]
455
- diagnosticToCodeActions dynFlags fileContents pluginId documentId diagnostic
458
+ diagnosticToCodeActions :: DynFlags -> T. Text -> PluginId -> VersionedTextDocumentIdentifier -> LSP. Diagnostic -> [LSP. CodeAction ]
459
+ diagnosticToCodeActions dynFlags fileContents pluginId verTxtDocId diagnostic
456
460
| LSP. Diagnostic { _source = Just " hlint" , _code = Just (InR code), _range = LSP. Range start _ } <- diagnostic
457
- , let TextDocumentIdentifier uri = documentId
458
461
, let isHintApplicable = " refact:" `T.isPrefixOf` code
459
462
, let hint = T. replace " refact:" " " code
460
463
, let suppressHintTitle = " Ignore hint \" " <> hint <> " \" in this module"
461
464
, let suppressHintTextEdits = mkSuppressHintTextEdits dynFlags fileContents hint
462
465
, let suppressHintWorkspaceEdit =
463
466
LSP. WorkspaceEdit
464
- (Just (Map. singleton uri (List suppressHintTextEdits)))
467
+ (Just (Map. singleton (verTxtDocId ^. LSP. uri) (List suppressHintTextEdits)))
465
468
Nothing
466
469
Nothing
467
470
= catMaybes
468
471
-- Applying the hint is marked preferred because it addresses the underlying error.
469
472
-- Disabling the rule isn't, because less often used and configuration can be adapted.
470
473
[ if | isHintApplicable
471
474
, let applyHintTitle = " Apply hint \" " <> hint <> " \" "
472
- applyHintArguments = [toJSON (AOP (documentId ^. LSP. uri) start hint)]
475
+ applyHintArguments = [toJSON (AOP verTxtDocId start hint)]
473
476
applyHintCommand = mkLspCommand pluginId " applyOne" applyHintTitle (Just applyHintArguments) ->
474
477
Just (mkCodeAction applyHintTitle diagnostic Nothing (Just applyHintCommand) True )
475
478
| otherwise -> Nothing
@@ -511,13 +514,13 @@ mkSuppressHintTextEdits dynFlags fileContents hint =
511
514
combinedTextEdit : lineSplitTextEditList
512
515
-- ---------------------------------------------------------------------
513
516
514
- applyAllCmd :: Recorder (WithPriority Log ) -> CommandFunction IdeState Uri
515
- applyAllCmd recorder ide uri = do
516
- let file = maybe (error $ show uri ++ " is not a file." )
517
+ applyAllCmd :: Recorder (WithPriority Log ) -> CommandFunction IdeState VersionedTextDocumentIdentifier
518
+ applyAllCmd recorder ide verTxtDocId = do
519
+ let file = maybe (error $ show (verTxtDocId ^. LSP. uri) ++ " is not a file." )
517
520
toNormalizedFilePath'
518
- (uriToFilePath' uri)
521
+ (uriToFilePath' (verTxtDocId ^. LSP. uri) )
519
522
withIndefiniteProgress " Applying all hints" Cancellable $ do
520
- res <- liftIO $ applyHint recorder ide file Nothing
523
+ res <- liftIO $ applyHint recorder ide file Nothing verTxtDocId
521
524
logWith recorder Debug $ LogApplying file res
522
525
case res of
523
526
Left err -> pure $ Left (responseError (T. pack $ " hlint:applyAll: " ++ show err))
@@ -528,10 +531,10 @@ applyAllCmd recorder ide uri = do
528
531
-- ---------------------------------------------------------------------
529
532
530
533
data ApplyOneParams = AOP
531
- { file :: Uri
532
- , start_pos :: Position
534
+ { verTxtDocId :: VersionedTextDocumentIdentifier
535
+ , start_pos :: Position
533
536
-- | There can be more than one hint suggested at the same position, so HintTitle is used to distinguish between them.
534
- , hintTitle :: HintTitle
537
+ , hintTitle :: HintTitle
535
538
} deriving (Eq ,Show ,Generic ,FromJSON ,ToJSON )
536
539
537
540
type HintTitle = T. Text
@@ -542,22 +545,22 @@ data OneHint = OneHint
542
545
} deriving (Eq , Show )
543
546
544
547
applyOneCmd :: Recorder (WithPriority Log ) -> CommandFunction IdeState ApplyOneParams
545
- applyOneCmd recorder ide (AOP uri pos title) = do
548
+ applyOneCmd recorder ide (AOP verTxtDocId pos title) = do
546
549
let oneHint = OneHint pos title
547
- let file = maybe (error $ show uri ++ " is not a file." ) toNormalizedFilePath'
548
- (uriToFilePath' uri)
550
+ let file = maybe (error $ show (verTxtDocId ^. LSP. uri) ++ " is not a file." ) toNormalizedFilePath'
551
+ (uriToFilePath' (verTxtDocId ^. LSP. uri) )
549
552
let progTitle = " Applying hint: " <> title
550
553
withIndefiniteProgress progTitle Cancellable $ do
551
- res <- liftIO $ applyHint recorder ide file (Just oneHint)
554
+ res <- liftIO $ applyHint recorder ide file (Just oneHint) verTxtDocId
552
555
logWith recorder Debug $ LogApplying file res
553
556
case res of
554
557
Left err -> pure $ Left (responseError (T. pack $ " hlint:applyOne: " ++ show err))
555
558
Right fs -> do
556
559
_ <- sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing fs) (\ _ -> pure () )
557
560
pure $ Right Null
558
561
559
- applyHint :: Recorder (WithPriority Log ) -> IdeState -> NormalizedFilePath -> Maybe OneHint -> IO (Either String WorkspaceEdit )
560
- applyHint recorder ide nfp mhint =
562
+ applyHint :: Recorder (WithPriority Log ) -> IdeState -> NormalizedFilePath -> Maybe OneHint -> VersionedTextDocumentIdentifier -> IO (Either String WorkspaceEdit )
563
+ applyHint recorder ide nfp mhint verTxtDocId =
561
564
runExceptT $ do
562
565
let runAction' :: Action a -> IO a
563
566
runAction' = runAction " applyHint" ide
@@ -614,8 +617,7 @@ applyHint recorder ide nfp mhint =
614
617
#endif
615
618
case res of
616
619
Right appliedFile -> do
617
- let uri = fromNormalizedUri (filePathToUri' nfp)
618
- let wsEdit = diffText' True (uri, oldContent) (T. pack appliedFile) IncludeDeletions
620
+ let wsEdit = diffText' True (verTxtDocId, oldContent) (T. pack appliedFile) IncludeDeletions
619
621
ExceptT $ return (Right wsEdit)
620
622
Left err ->
621
623
throwE err
0 commit comments