Skip to content

Commit 6fce454

Browse files
authored
optimize ambiguity import suggestions (#1669)
1 parent c2c02fb commit 6fce454

File tree

7 files changed

+93
-32
lines changed

7 files changed

+93
-32
lines changed

ghcide/ghcide.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -346,6 +346,7 @@ test-suite ghcide-tests
346346
QuickCheck,
347347
quickcheck-instances,
348348
rope-utf16-splay,
349+
regex-tdfa ^>= 1.3.1,
349350
safe,
350351
safe-exceptions,
351352
shake,

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 31 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -848,31 +848,39 @@ suggestImportDisambiguation df (Just txt) ps@(L _ HsModule {hsmodImports}) diag@
848848
toModuleTarget mName = ExistingImp <$> Map.lookup mName locDic
849849
parensed =
850850
"(" `T.isPrefixOf` T.strip (textInRange _range txt)
851+
-- > removeAllDuplicates [1, 1, 2, 3, 2] = [3]
852+
removeAllDuplicates = map head . filter ((==1) <$> length) . group . sort
853+
hasDuplicate xs = length xs /= length (S.fromList xs)
851854
suggestions symbol mods
852-
| Just targets <- mapM toModuleTarget mods =
853-
sortOn fst
854-
[ ( renderUniquify mode modNameText symbol
855-
, disambiguateSymbol ps diag symbol mode
856-
)
857-
| (modTarget, restImports) <- oneAndOthers targets
858-
, let modName = targetModuleName modTarget
859-
modNameText = T.pack $ moduleNameString modName
860-
, mode <-
861-
HideOthers restImports :
862-
[ ToQualified parensed qual
863-
| ExistingImp imps <- [modTarget]
864-
, L _ qual <- nubOrd $ mapMaybe (ideclAs . unLoc)
865-
$ NE.toList imps
866-
]
867-
++ [ToQualified parensed modName
868-
| any (occursUnqualified symbol . unLoc)
869-
(targetImports modTarget)
870-
|| case modTarget of
871-
ImplicitPrelude{} -> True
872-
_ -> False
873-
]
855+
| hasDuplicate mods = case mapM toModuleTarget (removeAllDuplicates mods) of
856+
Just targets -> suggestionsImpl symbol (map (, []) targets)
857+
Nothing -> []
858+
| otherwise = case mapM toModuleTarget mods of
859+
Just targets -> suggestionsImpl symbol (oneAndOthers targets)
860+
Nothing -> []
861+
suggestionsImpl symbol targetsWithRestImports =
862+
sortOn fst
863+
[ ( renderUniquify mode modNameText symbol
864+
, disambiguateSymbol ps diag symbol mode
865+
)
866+
| (modTarget, restImports) <- targetsWithRestImports
867+
, let modName = targetModuleName modTarget
868+
modNameText = T.pack $ moduleNameString modName
869+
, mode <-
870+
[ ToQualified parensed qual
871+
| ExistingImp imps <- [modTarget]
872+
, L _ qual <- nubOrd $ mapMaybe (ideclAs . unLoc)
873+
$ NE.toList imps
874874
]
875-
| otherwise = []
875+
++ [ToQualified parensed modName
876+
| any (occursUnqualified symbol . unLoc)
877+
(targetImports modTarget)
878+
|| case modTarget of
879+
ImplicitPrelude{} -> True
880+
_ -> False
881+
]
882+
++ [HideOthers restImports | not (null restImports)]
883+
]
876884
renderUniquify HideOthers {} modName symbol =
877885
"Use " <> modName <> " for " <> symbol <> ", hiding other imports"
878886
renderUniquify (ToQualified _ qual) _ symbol =

ghcide/test/data/hiding/FVec.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
{-# LANGUAGE DuplicateRecordFields #-}
2+
3+
module FVec (RecA(..), RecB(..)) where
4+
5+
data Vec a
6+
7+
newtype RecA a = RecA { fromList :: [a] -> Vec a }
8+
9+
newtype RecB a = RecB { fromList :: [a] -> Vec a }
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
module HideQualifyDuplicateRecordFields where
2+
3+
import AVec
4+
import BVec
5+
import CVec
6+
import DVec
7+
import EVec
8+
import FVec
9+
10+
theFun = AVec.fromList
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
module HideQualifyDuplicateRecordFields where
2+
3+
import AVec
4+
import BVec
5+
import CVec
6+
import DVec
7+
import EVec
8+
import FVec
9+
10+
theFun = fromList
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
module HideQualifyDuplicateRecordFieldsSelf where
2+
3+
import FVec
4+
5+
x = fromList

ghcide/test/exe/Main.hs

Lines changed: 27 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -93,14 +93,15 @@ import Test.Tasty.ExpectedFailure
9393
import Test.Tasty.HUnit
9494
import Test.Tasty.Ingredients.Rerun
9595
import Test.Tasty.QuickCheck
96-
import Data.IORef
97-
import Ide.PluginUtils (pluginDescToIdePlugins)
98-
import Control.Concurrent.Async
99-
import Ide.Types
100-
import Data.String (IsString(fromString))
101-
import qualified Language.LSP.Types as LSP
102-
import Data.IORef.Extra (atomicModifyIORef_)
103-
import qualified Development.IDE.Plugin.HLS.GhcIde as Ghcide
96+
import Data.IORef
97+
import Ide.PluginUtils (pluginDescToIdePlugins)
98+
import Control.Concurrent.Async
99+
import Ide.Types
100+
import Data.String (IsString(fromString))
101+
import qualified Language.LSP.Types as LSP
102+
import Data.IORef.Extra (atomicModifyIORef_)
103+
import qualified Development.IDE.Plugin.HLS.GhcIde as Ghcide
104+
import Text.Regex.TDFA ((=~))
104105

105106
waitForProgressBegin :: Session ()
106107
waitForProgressBegin = skipManyTill anyMessage $ satisfyMaybe $ \case
@@ -1673,6 +1674,23 @@ suggestImportDisambiguationTests = testGroup "suggest import disambiguation acti
16731674
compareHideFunctionTo [(8,9),(10,8)]
16741675
"Replace with qualified: E.fromList"
16751676
"HideFunction.expected.qualified.fromList.E.hs"
1677+
, testCase "Hide DuplicateRecordFields" $
1678+
compareTwo
1679+
"HideQualifyDuplicateRecordFields.hs" [(9, 9)]
1680+
"Replace with qualified: AVec.fromList"
1681+
"HideQualifyDuplicateRecordFields.expected.hs"
1682+
, testCase "Duplicate record fields should not be imported" $ do
1683+
withTarget ("HideQualifyDuplicateRecordFields" <.> ".hs") [(9, 9)] $
1684+
\_ actions -> do
1685+
liftIO $
1686+
assertBool "Hidings should not be presented while DuplicateRecordFields exists" $
1687+
all not [ actionTitle =~ T.pack "Use ([A-Za-z][A-Za-z0-9]*) for fromList, hiding other imports"
1688+
| InR CodeAction { _title = actionTitle } <- actions]
1689+
withTarget ("HideQualifyDuplicateRecordFieldsSelf" <.> ".hs") [(4, 4)] $
1690+
\_ actions -> do
1691+
liftIO $
1692+
assertBool "ambiguity from DuplicateRecordFields should not be imported" $
1693+
null actions
16761694
]
16771695
, testGroup "(++)"
16781696
[ testCase "Prelude, parensed" $
@@ -1708,7 +1726,7 @@ suggestImportDisambiguationTests = testGroup "suggest import disambiguation acti
17081726
contentAfterAction <- documentContents doc
17091727
liftIO $ T.replace "\r\n" "\n" expected @=? contentAfterAction
17101728
compareHideFunctionTo = compareTwo "HideFunction.hs"
1711-
auxFiles = ["AVec.hs", "BVec.hs", "CVec.hs", "DVec.hs", "EVec.hs"]
1729+
auxFiles = ["AVec.hs", "BVec.hs", "CVec.hs", "DVec.hs", "EVec.hs", "FVec.hs"]
17121730
withTarget file locs k = withTempDir $ \dir -> runInDir dir $ do
17131731
liftIO $ mapM_ (\fp -> copyFile (hidingDir </> fp) $ dir </> fp)
17141732
$ file : auxFiles

0 commit comments

Comments
 (0)