Skip to content

Commit 0d806c3

Browse files
authored
Remove Strict from the language extensions used for code actions (#638)
Since the code action for language extension suggestions uses substring matching, the presence of the literal name of an extension can trigger a false positive. `Strict` is an identifier that occurs frequently in imports, causing the extension to be suggested rather than the removal of a redundant import.
1 parent 71631d8 commit 0d806c3

File tree

2 files changed

+27
-1
lines changed

2 files changed

+27
-1
lines changed

src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -266,7 +266,11 @@ suggestAddExtension Diagnostic{_range=_range,..}
266266

267267
-- | All the GHC extensions
268268
ghcExtensions :: Map.HashMap T.Text Extension
269-
ghcExtensions = Map.fromList . map ( ( T.pack . flagSpecName ) &&& flagSpecFlag ) $ xFlags
269+
ghcExtensions = Map.fromList . filter notStrictFlag . map ( ( T.pack . flagSpecName ) &&& flagSpecFlag ) $ xFlags
270+
where
271+
-- Strict often causes false positives, as in Data.Map.Strict imports.
272+
-- See discussion at https://github.com/digital-asset/ghcide/pull/638
273+
notStrictFlag (name, _) = name /= "Strict"
270274

271275
suggestModuleTypo :: Diagnostic -> [(T.Text, [TextEdit])]
272276
suggestModuleTypo Diagnostic{_range=_range,..}

test/exe/Main.hs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -818,6 +818,28 @@ removeImportTests = testGroup "remove import actions"
818818
, "main = B"
819819
]
820820
liftIO $ expectedContentAfterAction @=? contentAfterAction
821+
, testSession "import containing the identifier Strict" $ do
822+
let contentA = T.unlines
823+
[ "module Strict where"
824+
]
825+
_docA <- createDoc "Strict.hs" "haskell" contentA
826+
let contentB = T.unlines
827+
[ "{-# OPTIONS_GHC -Wunused-imports #-}"
828+
, "module ModuleB where"
829+
, "import Strict"
830+
]
831+
docB <- createDoc "ModuleB.hs" "haskell" contentB
832+
_ <- waitForDiagnostics
833+
[CACodeAction action@CodeAction { _title = actionTitle }]
834+
<- getCodeActions docB (Range (Position 2 0) (Position 2 5))
835+
liftIO $ "Remove import" @=? actionTitle
836+
executeCodeAction action
837+
contentAfterAction <- documentContents docB
838+
let expectedContentAfterAction = T.unlines
839+
[ "{-# OPTIONS_GHC -Wunused-imports #-}"
840+
, "module ModuleB where"
841+
]
842+
liftIO $ expectedContentAfterAction @=? contentAfterAction
821843
]
822844

823845
extendImportTests :: TestTree

0 commit comments

Comments
 (0)