@@ -64,6 +64,7 @@ import Bag (isEmptyBag)
64
64
import qualified Data.HashSet as Set
65
65
import Control.Concurrent.Extra (threadDelay , readVar )
66
66
import Development.IDE.GHC.Util (printRdrName )
67
+ import Ide.PluginUtils (subRange )
67
68
68
69
plugin :: Plugin c
69
70
plugin = codeActionPluginWithRules rules codeAction <> Plugin mempty setHandlersCodeLens
@@ -107,7 +108,8 @@ codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext{_diag
107
108
[ mkCA title [x] edit
108
109
| x <- xs, (title, tedit) <- suggestAction exportsMap ideOptions parsedModule text x
109
110
, let edit = WorkspaceEdit (Just $ Map. singleton uri $ List tedit) Nothing
110
- ] <> caRemoveRedundantImports parsedModule text diag xs uri
111
+ ] <> caRemoveInvalidExports parsedModule text diag xs uri
112
+ <> caRemoveRedundantImports parsedModule text diag xs uri
111
113
112
114
actions' =
113
115
[mkCA title [x] edit
@@ -242,8 +244,8 @@ suggestRemoveRedundantImport ParsedModule{pm_parsed_source = L _ HsModule{hsmod
242
244
| Just [_, bindings] <- matchRegexUnifySpaces _message " The( qualified)? import of ‘([^’]*)’ from module [^ ]* is redundant"
243
245
, Just (L _ impDecl) <- find (\ (L l _) -> srcSpanToRange l == Just _range ) hsmodImports
244
246
, Just c <- contents
245
- , ranges <- map (rangesForBinding impDecl . T. unpack) (T. splitOn " , " bindings)
246
- , ranges' <- extendAllToIncludeCommaIfPossible (indexedByPosition $ T. unpack c) (concat ranges)
247
+ , ranges <- map (rangesForBindingImport impDecl . T. unpack) (T. splitOn " , " bindings)
248
+ , ranges' <- extendAllToIncludeCommaIfPossible False (indexedByPosition $ T. unpack c) (concat ranges)
247
249
, not (null ranges')
248
250
= [( " Remove " <> bindings <> " from import" , [ TextEdit r " " | r <- ranges' ] )]
249
251
@@ -279,6 +281,69 @@ caRemoveRedundantImports m contents digs ctxDigs uri
279
281
_edit = Just WorkspaceEdit {.. }
280
282
_command = Nothing
281
283
284
+ caRemoveInvalidExports :: Maybe ParsedModule -> Maybe T. Text -> [Diagnostic ] -> [Diagnostic ] -> Uri -> [CAResult ]
285
+ caRemoveInvalidExports m contents digs ctxDigs uri
286
+ | Just pm <- m,
287
+ Just txt <- contents,
288
+ txt' <- indexedByPosition $ T. unpack txt,
289
+ r <- mapMaybe (groupDiag pm) digs,
290
+ r' <- map (\ (t,d,rs) -> (t,d,extend txt' rs)) r,
291
+ caRemoveCtx <- mapMaybe removeSingle r',
292
+ allRanges <- nubOrd $ [ range | (_,_,ranges) <- r, range <- ranges],
293
+ allRanges' <- extend txt' allRanges,
294
+ Just caRemoveAll <- removeAll allRanges',
295
+ ctxEdits <- [ x | x@ (_, d, _) <- r, d `elem` ctxDigs],
296
+ not $ null ctxEdits
297
+ = caRemoveCtx ++ [caRemoveAll]
298
+ | otherwise = []
299
+ where
300
+ extend txt ranges = extendAllToIncludeCommaIfPossible True txt ranges
301
+
302
+ groupDiag pm dig
303
+ | Just (title, ranges) <- suggestRemoveRedundantExport pm dig
304
+ = Just (title, dig, ranges)
305
+ | otherwise = Nothing
306
+
307
+ removeSingle (_, _, [] ) = Nothing
308
+ removeSingle (title, diagnostic, ranges) = Just $ CACodeAction CodeAction {.. } where
309
+ tedit = concatMap (\ r -> [TextEdit r " " ]) $ nubOrd ranges
310
+ _changes = Just $ Map. singleton uri $ List tedit
311
+ _title = title
312
+ _kind = Just CodeActionQuickFix
313
+ _diagnostics = Just $ List [diagnostic]
314
+ _documentChanges = Nothing
315
+ _edit = Just WorkspaceEdit {.. }
316
+ _command = Nothing
317
+ removeAll [] = Nothing
318
+ removeAll ranges = Just $ CACodeAction CodeAction {.. } where
319
+ tedit = concatMap (\ r -> [TextEdit r " " ]) ranges
320
+ _changes = Just $ Map. singleton uri $ List tedit
321
+ _title = " Remove all redundant exports"
322
+ _kind = Just CodeActionQuickFix
323
+ _diagnostics = Nothing
324
+ _documentChanges = Nothing
325
+ _edit = Just WorkspaceEdit {.. }
326
+ _command = Nothing
327
+
328
+ suggestRemoveRedundantExport :: ParsedModule -> Diagnostic -> Maybe (T. Text , [Range ])
329
+ suggestRemoveRedundantExport ParsedModule {pm_parsed_source = L _ HsModule {.. }} Diagnostic {.. }
330
+ | msg <- unifySpaces _message
331
+ , Just export <- hsmodExports
332
+ , Just exportRange <- getLocatedRange export
333
+ , exports <- unLoc export
334
+ , Just (removeFromExport, ! ranges) <- fmap (getRanges exports . notInScope) (extractNotInScopeName msg)
335
+ <|> (,[_range]) <$> matchExportItem msg
336
+ <|> (,[_range]) <$> matchDupExport msg
337
+ , subRange _range exportRange
338
+ = Just (" Remove ‘" <> removeFromExport <> " ’ from export" , ranges)
339
+ where
340
+ matchExportItem msg = regexSingleMatch msg " The export item ‘([^’]+)’"
341
+ matchDupExport msg = regexSingleMatch msg " Duplicate ‘([^’]+)’ in export list"
342
+ getRanges exports txt = case smallerRangesForBindingExport exports (T. unpack txt) of
343
+ [] -> (txt, [_range])
344
+ ranges -> (txt, ranges)
345
+ suggestRemoveRedundantExport _ _ = Nothing
346
+
282
347
suggestDeleteUnusedBinding :: ParsedModule -> Maybe T. Text -> Diagnostic -> [(T. Text , [TextEdit ])]
283
348
suggestDeleteUnusedBinding
284
349
ParsedModule {pm_parsed_source = L _ HsModule {hsmodDecls}}
@@ -395,6 +460,9 @@ suggestDeleteUnusedBinding
395
460
data ExportsAs = ExportName | ExportPattern | ExportAll
396
461
deriving (Eq )
397
462
463
+ getLocatedRange :: Located a -> Maybe Range
464
+ getLocatedRange = srcSpanToRange . getLoc
465
+
398
466
suggestExportUnusedTopBinding :: Maybe T. Text -> ParsedModule -> Diagnostic -> [(T. Text , [TextEdit ])]
399
467
suggestExportUnusedTopBinding srcOpt ParsedModule {pm_parsed_source = L _ HsModule {.. }} Diagnostic {.. }
400
468
-- Foo.hs:4:1: warning: [-Wunused-top-binds] Defined but not used: ‘f’
@@ -435,9 +503,6 @@ suggestExportUnusedTopBinding srcOpt ParsedModule{pm_parsed_source = L _ HsModul
435
503
| T. head x `elem` opLetter = (if needsTypeKeyword then " type " else " " ) <> " (" <> x <> " )"
436
504
| otherwise = x
437
505
438
- getLocatedRange :: Located a -> Maybe Range
439
- getLocatedRange = srcSpanToRange . getLoc
440
-
441
506
matchWithDiagnostic :: Range -> Located (IdP GhcPs ) -> Bool
442
507
matchWithDiagnostic Range {_start= l,_end= r} x =
443
508
let loc = fmap _start . getLocatedRange $ x
@@ -1086,17 +1151,30 @@ textInRange (Range (Position startRow startCol) (Position endRow endCol)) text =
1086
1151
linesBeginningWithStartLine = drop startRow (T. splitOn " \n " text)
1087
1152
1088
1153
-- | Returns the ranges for a binding in an import declaration
1089
- rangesForBinding :: ImportDecl GhcPs -> String -> [Range ]
1090
- rangesForBinding ImportDecl {ideclHiding = Just (False , L _ lies)} b =
1154
+ rangesForBindingImport :: ImportDecl GhcPs -> String -> [Range ]
1155
+ rangesForBindingImport ImportDecl {ideclHiding = Just (False , L _ lies)} b =
1091
1156
concatMap (mapMaybe srcSpanToRange . rangesForBinding' b') lies
1092
1157
where
1093
- b' = wrapOperatorInParens (unqualify b)
1158
+ b' = modifyBinding b
1159
+ rangesForBindingImport _ _ = []
1094
1160
1161
+ modifyBinding :: String -> String
1162
+ modifyBinding = wrapOperatorInParens . unqualify
1163
+ where
1095
1164
wrapOperatorInParens x = if isAlpha (head x) then x else " (" <> x <> " )"
1096
-
1097
1165
unqualify x = snd $ breakOnEnd " ." x
1098
1166
1099
- rangesForBinding _ _ = []
1167
+ smallerRangesForBindingExport :: [LIE GhcPs ] -> String -> [Range ]
1168
+ smallerRangesForBindingExport lies b =
1169
+ concatMap (mapMaybe srcSpanToRange . ranges') lies
1170
+ where
1171
+ b' = modifyBinding b
1172
+ ranges' (L _ (IEThingWith _ thing _ inners labels))
1173
+ | showSDocUnsafe (ppr thing) == b' = []
1174
+ | otherwise =
1175
+ [ l' | L l' x <- inners, showSDocUnsafe (ppr x) == b'] ++
1176
+ [ l' | L l' x <- labels, showSDocUnsafe (ppr x) == b']
1177
+ ranges' _ = []
1100
1178
1101
1179
rangesForBinding' :: String -> LIE GhcPs -> [SrcSpan ]
1102
1180
rangesForBinding' b (L l x@ IEVar {}) | showSDocUnsafe (ppr x) == b = [l]
0 commit comments