15
15
{-# LANGUAGE ScopedTypeVariables #-}
16
16
{-# LANGUAGE StrictData #-}
17
17
{-# LANGUAGE TupleSections #-}
18
+ {-# LANGUAGE TypeApplications #-}
18
19
{-# LANGUAGE TypeFamilies #-}
19
20
{-# LANGUAGE ViewPatterns #-}
20
-
21
21
{-# OPTIONS_GHC -Wno-orphans #-}
22
22
23
23
-- On 9.4 we get a new redundant constraint warning, but deleting the
@@ -422,7 +422,7 @@ codeActionProvider ideState _pluginId (CodeActionParams _ _ documentId _ context
422
422
423
423
where
424
424
applyAllAction verTxtDocId =
425
- let args = Just $ toJSON (AA verTxtDocId)
425
+ let args = Just $ toJSON (ApplyHint verTxtDocId Nothing )
426
426
in LSP. CodeAction " Apply all hints" (Just LSP. CodeActionKind_QuickFix ) Nothing Nothing Nothing Nothing Nothing args
427
427
428
428
-- | Some hints do not have an associated refactoring
@@ -437,14 +437,10 @@ resolveProvider :: Recorder (WithPriority Log) -> ResolveFunction IdeState Hlint
437
437
resolveProvider recorder ideState _plId ca uri resolveValue = pluginResponse $ do
438
438
file <- getNormalizedFilePath uri
439
439
case resolveValue of
440
- (AA verTxtDocId) -> do
441
- edit <- ExceptT $ liftIO $ applyHint recorder ideState file Nothing verTxtDocId
442
- pure $ ca & LSP. edit ?~ edit
443
- (AO verTxtDocId pos hintTitle) -> do
444
- let oneHint = OneHint pos hintTitle
445
- edit <- ExceptT $ liftIO $ applyHint recorder ideState file (Just oneHint) verTxtDocId
440
+ (ApplyHint verTxtDocId oneHint) -> do
441
+ edit <- ExceptT $ liftIO $ applyHint recorder ideState file oneHint verTxtDocId
446
442
pure $ ca & LSP. edit ?~ edit
447
- (IH verTxtDocId hintTitle ) -> do
443
+ (IgnoreHint verTxtDocId hintTitle ) -> do
448
444
edit <- ExceptT $ liftIO $ ignoreHint recorder ideState file verTxtDocId hintTitle
449
445
pure $ ca & LSP. edit ?~ edit
450
446
@@ -456,13 +452,13 @@ diagnosticToCodeActions verTxtDocId diagnostic
456
452
, let isHintApplicable = " refact:" `T.isPrefixOf` code
457
453
, let hint = T. replace " refact:" " " code
458
454
, let suppressHintTitle = " Ignore hint \" " <> hint <> " \" in this module"
459
- , let suppressHintArguments = IH verTxtDocId hint
455
+ , let suppressHintArguments = IgnoreHint verTxtDocId hint
460
456
= catMaybes
461
457
-- Applying the hint is marked preferred because it addresses the underlying error.
462
458
-- Disabling the rule isn't, because less often used and configuration can be adapted.
463
459
[ if | isHintApplicable
464
460
, let applyHintTitle = " Apply hint \" " <> hint <> " \" "
465
- applyHintArguments = AO verTxtDocId start hint ->
461
+ applyHintArguments = ApplyHint verTxtDocId ( Just $ OneHint start hint) ->
466
462
Just (mkCodeAction applyHintTitle diagnostic (Just (toJSON applyHintArguments)) True )
467
463
| otherwise -> Nothing
468
464
, Just (mkCodeAction suppressHintTitle diagnostic (Just (toJSON suppressHintArguments)) False )
@@ -520,22 +516,25 @@ ignoreHint _recorder ideState nfp verTxtDocId ignoreHintTitle = do
520
516
Nothing -> pure $ Left " Unable to get fileContents"
521
517
522
518
-- ---------------------------------------------------------------------
523
- data HlintResolveCommands = AA { verTxtDocId :: VersionedTextDocumentIdentifier }
524
- | AO { verTxtDocId :: VersionedTextDocumentIdentifier
525
- , start_pos :: Position
526
- -- | There can be more than one hint suggested at the same position, so HintTitle is used to distinguish between them.
527
- , hintTitle :: HintTitle
528
- }
529
- | IH { verTxtDocId :: VersionedTextDocumentIdentifier
530
- , ignoreHintTitle :: HintTitle
531
- } deriving (Generic , ToJSON , FromJSON )
519
+ data HlintResolveCommands =
520
+ ApplyHint
521
+ { verTxtDocId :: VersionedTextDocumentIdentifier
522
+ -- | If Nothing, apply all hints, otherise only apply
523
+ -- the given hint
524
+ , oneHint :: Maybe OneHint
525
+ }
526
+ | IgnoreHint
527
+ { verTxtDocId :: VersionedTextDocumentIdentifier
528
+ , ignoreHintTitle :: HintTitle
529
+ } deriving (Generic , ToJSON , FromJSON )
532
530
533
531
type HintTitle = T. Text
534
532
535
- data OneHint = OneHint
536
- { oneHintPos :: Position
537
- , oneHintTitle :: HintTitle
538
- } deriving (Eq , Show )
533
+ data OneHint =
534
+ OneHint
535
+ { oneHintPos :: Position
536
+ , oneHintTitle :: HintTitle
537
+ } deriving (Generic , Eq , Show , ToJSON , FromJSON )
539
538
540
539
applyHint :: Recorder (WithPriority Log ) -> IdeState -> NormalizedFilePath -> Maybe OneHint -> VersionedTextDocumentIdentifier -> IO (Either String WorkspaceEdit )
541
540
applyHint recorder ide nfp mhint verTxtDocId =
0 commit comments